@@ -85,7 +85,8 @@ import Outputable (Outputable,
8585 showSDocUnsafe )
8686import RdrName (GlobalRdrElt (.. ),
8787 lookupGlobalRdrEnv )
88- import SrcLoc (realSrcSpanEnd ,
88+ import SrcLoc (HasSrcSpan (.. ),
89+ realSrcSpanEnd ,
8990 realSrcSpanStart )
9091import TcRnTypes (ImportAvails (.. ),
9192 TcGblEnv (.. ))
@@ -234,8 +235,8 @@ findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l)
234235-- imported from ‘Data.ByteString’ at B.hs:6:1-22
235236-- imported from ‘Data.ByteString.Lazy’ at B.hs:8:1-27
236237-- imported from ‘Data.Text’ at B.hs:7:1-16
237- suggestHideShadow :: ParsedSource -> Maybe TcModuleResult -> Maybe HieAstResult -> Diagnostic -> [(T. Text , [Either TextEdit Rewrite ])]
238- suggestHideShadow ps@ (L _ HsModule {hsmodImports}) mTcM mHar Diagnostic {_message, _range}
238+ suggestHideShadow :: ParsedSource -> T. Text -> Maybe TcModuleResult -> Maybe HieAstResult -> Diagnostic -> [(T. Text , [Either TextEdit Rewrite ])]
239+ suggestHideShadow ps@ (L _ HsModule {hsmodImports}) fileContents mTcM mHar Diagnostic {_message, _range}
239240 | Just [identifier, modName, s] <-
240241 matchRegexUnifySpaces
241242 _message
@@ -260,7 +261,7 @@ suggestHideShadow ps@(L _ HsModule {hsmodImports}) mTcM mHar Diagnostic {_messag
260261 mDecl <- findImportDeclByModuleName hsmodImports $ T. unpack modName,
261262 title <- " Hide " <> identifier <> " from " <> modName =
262263 if modName == " Prelude" && null mDecl
263- then maybeToList $ (\ (_, te) -> (title, [Left te])) <$> newImportToEdit (hideImplicitPreludeSymbol identifier) ps
264+ then maybeToList $ (\ (_, te) -> (title, [Left te])) <$> newImportToEdit (hideImplicitPreludeSymbol identifier) ps fileContents
264265 else maybeToList $ (title,) . pure . pure . hideSymbol (T. unpack identifier) <$> mDecl
265266 | otherwise = []
266267
@@ -887,9 +888,10 @@ suggestImportDisambiguation ::
887888 DynFlags ->
888889 Maybe T. Text ->
889890 ParsedSource ->
891+ T. Text ->
890892 Diagnostic ->
891893 [(T. Text , [Either TextEdit Rewrite ])]
892- suggestImportDisambiguation df (Just txt) ps@ (L _ HsModule {hsmodImports}) diag@ Diagnostic {.. }
894+ suggestImportDisambiguation df (Just txt) ps@ (L _ HsModule {hsmodImports}) fileContents diag@ Diagnostic {.. }
893895 | Just [ambiguous] <-
894896 matchRegexUnifySpaces
895897 _message
@@ -930,7 +932,7 @@ suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) diag@
930932 suggestionsImpl symbol targetsWithRestImports =
931933 sortOn fst
932934 [ ( renderUniquify mode modNameText symbol
933- , disambiguateSymbol ps diag symbol mode
935+ , disambiguateSymbol ps fileContents diag symbol mode
934936 )
935937 | (modTarget, restImports) <- targetsWithRestImports
936938 , let modName = targetModuleName modTarget
@@ -964,7 +966,7 @@ suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) diag@
964966 <> T. pack (moduleNameString qual)
965967 <> " ."
966968 <> symbol
967- suggestImportDisambiguation _ _ _ _ = []
969+ suggestImportDisambiguation _ _ _ _ _ = []
968970
969971occursUnqualified :: T. Text -> ImportDecl GhcPs -> Bool
970972occursUnqualified symbol ImportDecl {.. }
@@ -989,19 +991,20 @@ targetModuleName (ExistingImp _) =
989991
990992disambiguateSymbol ::
991993 ParsedSource ->
994+ T. Text ->
992995 Diagnostic ->
993996 T. Text ->
994997 HidingMode ->
995998 [Either TextEdit Rewrite ]
996- disambiguateSymbol pm Diagnostic {.. } (T. unpack -> symbol) = \ case
999+ disambiguateSymbol pm fileContents Diagnostic {.. } (T. unpack -> symbol) = \ case
9971000 (HideOthers hiddens0) ->
9981001 [ Right $ hideSymbol symbol idecl
9991002 | ExistingImp idecls <- hiddens0
10001003 , idecl <- NE. toList idecls
10011004 ]
10021005 ++ mconcat
10031006 [ if null imps
1004- then maybeToList $ Left . snd <$> newImportToEdit (hideImplicitPreludeSymbol $ T. pack symbol) pm
1007+ then maybeToList $ Left . snd <$> newImportToEdit (hideImplicitPreludeSymbol $ T. pack symbol) pm fileContents
10051008 else Right . hideSymbol symbol <$> imps
10061009 | ImplicitPrelude imps <- hiddens0
10071010 ]
@@ -1203,8 +1206,8 @@ removeRedundantConstraints df (L _ HsModule {hsmodDecls}) Diagnostic{..}
12031206
12041207-------------------------------------------------------------------------------------------------
12051208
1206- suggestNewOrExtendImportForClassMethod :: ExportsMap -> ParsedSource -> Diagnostic -> [(T. Text , CodeActionKind , [Either TextEdit Rewrite ])]
1207- suggestNewOrExtendImportForClassMethod packageExportsMap ps Diagnostic {_message}
1209+ suggestNewOrExtendImportForClassMethod :: ExportsMap -> ParsedSource -> T. Text -> Diagnostic -> [(T. Text , CodeActionKind , [Either TextEdit Rewrite ])]
1210+ suggestNewOrExtendImportForClassMethod packageExportsMap ps fileContents Diagnostic {_message}
12081211 | Just [methodName, className] <-
12091212 matchRegexUnifySpaces
12101213 _message
@@ -1229,7 +1232,7 @@ suggestNewOrExtendImportForClassMethod packageExportsMap ps Diagnostic {_message
12291232 ]
12301233 -- new
12311234 _
1232- | Just (range, indent) <- newImportInsertRange ps
1235+ | Just (range, indent) <- newImportInsertRange ps fileContents
12331236 ->
12341237 (\ (kind, unNewImport -> x) -> (x, kind, [Left $ TextEdit range (x <> " \n " <> T. replicate indent " " )])) <$>
12351238 [ (quickFixImportKind' " new" style, newUnqualImport moduleNameText rendered False )
@@ -1239,8 +1242,8 @@ suggestNewOrExtendImportForClassMethod packageExportsMap ps Diagnostic {_message
12391242 <> [(quickFixImportKind " new.all" , newImportAll moduleNameText)]
12401243 | otherwise -> []
12411244
1242- suggestNewImport :: ExportsMap -> ParsedSource -> Diagnostic -> [(T. Text , CodeActionKind , TextEdit )]
1243- suggestNewImport packageExportsMap ps@ (L _ HsModule {.. }) Diagnostic {_message}
1245+ suggestNewImport :: ExportsMap -> ParsedSource -> T. Text -> Diagnostic -> [(T. Text , CodeActionKind , TextEdit )]
1246+ suggestNewImport packageExportsMap ps@ (L _ HsModule {.. }) fileContents Diagnostic {_message}
12441247 | msg <- unifySpaces _message
12451248 , Just thingMissing <- extractNotInScopeName msg
12461249 , qual <- extractQualifiedModuleName msg
@@ -1249,13 +1252,13 @@ suggestNewImport packageExportsMap ps@(L _ HsModule {..}) Diagnostic{_message}
12491252 >>= (findImportDeclByModuleName hsmodImports . T. unpack)
12501253 >>= ideclAs . unLoc
12511254 <&> T. pack . moduleNameString . unLoc
1252- , Just (range, indent) <- newImportInsertRange ps
1255+ , Just (range, indent) <- newImportInsertRange ps fileContents
12531256 , extendImportSuggestions <- matchRegexUnifySpaces msg
12541257 " Perhaps you want to add ‘[^’]*’ to the import list in the import of ‘([^’]*)’"
12551258 = sortOn fst3 [(imp, kind, TextEdit range (imp <> " \n " <> T. replicate indent " " ))
12561259 | (kind, unNewImport -> imp) <- constructNewImportSuggestions packageExportsMap (qual <|> qual', thingMissing) extendImportSuggestions
12571260 ]
1258- suggestNewImport _ _ _ = []
1261+ suggestNewImport _ _ _ _ = []
12591262
12601263constructNewImportSuggestions
12611264 :: ExportsMap -> (Maybe T. Text , NotInScope ) -> Maybe [T. Text ] -> [(CodeActionKind , NewImport )]
@@ -1282,26 +1285,70 @@ constructNewImportSuggestions exportsMap (qual, thingMissing) notTheseModules =
12821285newtype NewImport = NewImport { unNewImport :: T. Text}
12831286 deriving (Show , Eq , Ord )
12841287
1285- newImportToEdit :: NewImport -> ParsedSource -> Maybe (T. Text , TextEdit )
1286- newImportToEdit (unNewImport -> imp) ps
1287- | Just (range, indent) <- newImportInsertRange ps
1288+ newImportToEdit :: NewImport -> ParsedSource -> T. Text -> Maybe (T. Text , TextEdit )
1289+ newImportToEdit (unNewImport -> imp) ps fileContents
1290+ | Just (range, indent) <- newImportInsertRange ps fileContents
12881291 = Just (imp, TextEdit range (imp <> " \n " <> T. replicate indent " " ))
12891292 | otherwise = Nothing
12901293
1291- newImportInsertRange :: ParsedSource -> Maybe (Range , Int )
1292- newImportInsertRange (L _ HsModule {.. })
1294+ -- | Finds the next valid position for inserting a new import declaration
1295+ -- If the file already has existing imports it will be inserted under the last of these,
1296+ -- it is assumed that the existing last import declaration is in a valid position
1297+ -- If the file does not have existing imports, but has a (module ... where) declaration,
1298+ -- the new import will be inserted directly under this declaration (accounting for explicit exports)
1299+ -- If the file has neither existing imports nor a module declaration,
1300+ -- the import will be inserted at line zero if there are no pragmas,
1301+ -- otherwise inserted one line after the last file-header pragma
1302+ newImportInsertRange :: ParsedSource -> T. Text -> Maybe (Range , Int )
1303+ newImportInsertRange (L _ HsModule {.. }) fileContents
12931304 | Just (uncurry Position -> insertPos, col) <- case hsmodImports of
1294- [] -> case getLoc (head hsmodDecls) of
1295- OldRealSrcSpan s -> let col = srcLocCol (realSrcSpanStart s) - 1
1296- in Just ((srcLocLine (realSrcSpanStart s) - 1 , col), col)
1297- _ -> Nothing
1298- _ -> case getLoc (last hsmodImports) of
1299- OldRealSrcSpan s -> let col = srcLocCol (realSrcSpanStart s) - 1
1300- in Just ((srcLocLine $ realSrcSpanEnd s,col), col)
1301- _ -> Nothing
1305+ [] -> findPositionNoImports hsmodName hsmodExports fileContents
1306+ _ -> findPositionFromImportsOrModuleDecl hsmodImports last True
13021307 = Just (Range insertPos insertPos, col)
13031308 | otherwise = Nothing
13041309
1310+ -- | Insert the import under the Module declaration exports if they exist, otherwise just under the module declaration
1311+ -- If no module declaration exists, then no exports will exist either, in that case
1312+ -- insert the import after any file-header pragmas or at position zero if there are no pragmas
1313+ findPositionNoImports :: Maybe (Located ModuleName ) -> Maybe (Located [LIE name ]) -> T. Text -> Maybe ((Int , Int ), Int )
1314+ findPositionNoImports Nothing _ fileContents = findNextPragmaPosition fileContents
1315+ findPositionNoImports _ (Just hsmodExports) _ = findPositionFromImportsOrModuleDecl hsmodExports id False
1316+ findPositionNoImports (Just hsmodName) _ _ = findPositionFromImportsOrModuleDecl hsmodName id False
1317+
1318+ findPositionFromImportsOrModuleDecl :: SrcLoc. HasSrcSpan a => t -> (t -> a ) -> Bool -> Maybe ((Int , Int ), Int )
1319+ findPositionFromImportsOrModuleDecl hsField f hasImports = case getLoc (f hsField) of
1320+ OldRealSrcSpan s ->
1321+ let col = calcCol s
1322+ in Just ((srcLocLine (realSrcSpanEnd s), col), col)
1323+ _ -> Nothing
1324+ where calcCol s = if hasImports then srcLocCol (realSrcSpanStart s) - 1 else 0
1325+
1326+ -- | Find the position one after the last file-header pragma
1327+ -- Defaults to zero if there are no pragmas in file
1328+ findNextPragmaPosition :: T. Text -> Maybe ((Int , Int ), Int )
1329+ findNextPragmaPosition contents = Just ((lineNumber, 0 ), 0 )
1330+ where
1331+ lineNumber = afterLangPragma . afterOptsGhc $ afterShebang
1332+ afterLangPragma = afterPragma " LANGUAGE" contents'
1333+ afterOptsGhc = afterPragma " OPTIONS_GHC" contents'
1334+ afterShebang = lastLineWithPrefix (T. isPrefixOf " #!" ) contents' 0
1335+ contents' = T. lines contents
1336+
1337+ afterPragma :: T. Text -> [T. Text ] -> Int -> Int
1338+ afterPragma name contents lineNum = lastLineWithPrefix (checkPragma name) contents lineNum
1339+
1340+ lastLineWithPrefix :: (T. Text -> Bool ) -> [T. Text ] -> Int -> Int
1341+ lastLineWithPrefix p contents lineNum = max lineNum next
1342+ where
1343+ next = maybe lineNum succ $ listToMaybe . reverse $ findIndices p contents
1344+
1345+ checkPragma :: T. Text -> T. Text -> Bool
1346+ checkPragma name = check
1347+ where
1348+ check l = isPragma l && getName l == name
1349+ getName l = T. take (T. length name) $ T. dropWhile isSpace $ T. drop 3 l
1350+ isPragma = T. isPrefixOf " {-#"
1351+
13051352-- | Construct an import declaration with at most one symbol
13061353newImport
13071354 :: T. Text -- ^ module name
0 commit comments