@@ -108,13 +108,13 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
108
108
| x <- xs, (title, tedit) <- suggestAction exportsMap ideOptions parsedModule text x
109
109
, let edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
110
110
] <> caRemoveRedundantImports parsedModule text diag xs uri
111
-
111
+
112
112
actions' =
113
113
[mkCA title [x] edit
114
114
| x <- xs
115
115
, Just ps <- [annotatedPS]
116
116
, Just dynflags <- [df]
117
- , (title, graft) <- suggestExactAction dynflags ps x
117
+ , (title, graft) <- suggestExactAction exportsMap dynflags ps x
118
118
, let edit = either error id $
119
119
rewriteToEdit dynflags uri (annsA ps) graft
120
120
]
@@ -171,14 +171,16 @@ commandHandler lsp _ideState ExecuteCommandParams{..}
171
171
= return (Right Null , Nothing )
172
172
173
173
suggestExactAction ::
174
+ ExportsMap ->
174
175
DynFlags ->
175
176
Annotated ParsedSource ->
176
177
Diagnostic ->
177
178
[(T. Text , Rewrite )]
178
- suggestExactAction df ps x =
179
+ suggestExactAction exportsMap df ps x =
179
180
concat
180
181
[ suggestConstraint df (astA ps) x
181
182
, suggestImplicitParameter (astA ps) x
183
+ , suggestExtendImport exportsMap (astA ps) x
182
184
]
183
185
184
186
suggestAction
@@ -191,7 +193,6 @@ suggestAction
191
193
suggestAction packageExports ideOptions parsedModule text diag = concat
192
194
-- Order these suggestions by priority
193
195
[ suggestSignature True diag
194
- , suggestExtendImport packageExports text diag
195
196
, suggestFillTypeWildcard diag
196
197
, suggestFixConstructorImport text diag
197
198
, suggestModuleTypo diag
@@ -660,32 +661,31 @@ getIndentedGroupsBy pred inp = case dropWhile (not.pred) inp of
660
661
indentation :: T. Text -> Int
661
662
indentation = T. length . T. takeWhile isSpace
662
663
663
- suggestExtendImport :: ExportsMap -> Maybe T. Text -> Diagnostic -> [(T. Text , [ TextEdit ] )]
664
- suggestExtendImport exportsMap contents Diagnostic {_range= _range,.. }
664
+ suggestExtendImport :: ExportsMap -> ParsedSource -> Diagnostic -> [(T. Text , Rewrite )]
665
+ suggestExtendImport exportsMap ( L _ HsModule {hsmodImports}) Diagnostic {_range= _range,.. }
665
666
| Just [binding, mod , srcspan] <-
666
667
matchRegexUnifySpaces _message
667
668
" Perhaps you want to add ‘([^’]*)’ to the import list in the import of ‘([^’]*)’ *\\ ((.*)\\ ).$"
668
- , Just c <- contents
669
- = suggestions c binding mod srcspan
669
+ = suggestions hsmodImports binding mod srcspan
670
670
| Just (binding, mod_srcspan) <-
671
671
matchRegExMultipleImports _message
672
- , Just c <- contents
673
- = mod_srcspan >>= (\ (x, y) -> suggestions c binding x y)
672
+ = mod_srcspan >>= uncurry (suggestions hsmodImports binding)
674
673
| otherwise = []
675
674
where
676
- suggestions c binding mod srcspan
675
+ unImportStyle (ImportTopLevel x) = (Nothing , T. unpack x)
676
+ unImportStyle (ImportViaParent x y) = (Just $ T. unpack y, T. unpack x)
677
+ suggestions decls binding mod srcspan
677
678
| range <- case [ x | (x," " ) <- readSrcSpan (T. unpack srcspan)] of
678
679
[s] -> let x = realSrcSpanToRange s
679
680
in x{_end = (_end x){_character = succ (_character (_end x))}}
680
681
_ -> error " bug in srcspan parser" ,
681
- importLine <- textInRange range c ,
682
+ Just decl <- findImportDeclByRange decls range ,
682
683
Just ident <- lookupExportMap binding mod
683
- = [ ( " Add " <> rendered <> " to the import list of " <> mod
684
- , [ TextEdit range result]
684
+ = [ ( " Add " <> renderImportStyle importStyle <> " to the import list of " <> mod
685
+ , uncurry extendImport (unImportStyle importStyle) decl
685
686
)
686
687
| importStyle <- NE. toList $ importStyles ident
687
- , let rendered = renderImportStyle importStyle
688
- , result <- maybeToList $ addBindingToImportList importStyle importLine]
688
+ ]
689
689
| otherwise = []
690
690
lookupExportMap binding mod
691
691
| Just match <- Map. lookup binding (getExportsMap exportsMap)
@@ -700,6 +700,9 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
700
700
, parent = Nothing
701
701
, isDatacon = False }
702
702
703
+ findImportDeclByRange :: [LImportDecl GhcPs ] -> Range -> Maybe (LImportDecl GhcPs )
704
+ findImportDeclByRange xs range = find (\ (L l _)-> srcSpanToRange l == Just range) xs
705
+
703
706
suggestFixConstructorImport :: Maybe T. Text -> Diagnostic -> [(T. Text , [TextEdit ])]
704
707
suggestFixConstructorImport _ Diagnostic {_range= _range,.. }
705
708
-- ‘Success’ is a data constructor of ‘Result’
@@ -1109,49 +1112,6 @@ rangesForBinding' b (L l (IEThingWith _ thing _ inners labels))
1109
1112
[ l' | L l' x <- labels, showSDocUnsafe (ppr x) == b]
1110
1113
rangesForBinding' _ _ = []
1111
1114
1112
- -- | Extends an import list with a new binding.
1113
- -- Assumes an import statement of the form:
1114
- -- import (qualified) A (..) ..
1115
- -- Places the new binding first, preserving whitespace.
1116
- -- Copes with multi-line import lists
1117
- addBindingToImportList :: ImportStyle -> T. Text -> Maybe T. Text
1118
- addBindingToImportList importStyle importLine =
1119
- case T. breakOn " (" importLine of
1120
- (pre, T. uncons -> Just (_, rest)) ->
1121
- case importStyle of
1122
- ImportTopLevel rendered ->
1123
- -- the binding has no parent, add it to the head of import list
1124
- Just $ T. concat [pre, " (" , rendered, addCommaIfNeeds rest]
1125
- ImportViaParent rendered parent -> case T. breakOn parent rest of
1126
- -- the binding has a parent, and the current import list contains the
1127
- -- parent
1128
- --
1129
- -- `rest'` could be 1. `,...)`
1130
- -- or 2. `(),...)`
1131
- -- or 3. `(ConsA),...)`
1132
- -- or 4. `)`
1133
- (leading, T. stripPrefix parent -> Just rest') -> case T. uncons (T. stripStart rest') of
1134
- -- case 1: no children and parentheses, e.g. `import A(Foo,...)` --> `import A(Foo(Cons), ...)`
1135
- Just (' ,' , rest'') -> Just $ T. concat [pre, " (" , leading, parent, " (" , rendered, " )" , addCommaIfNeeds rest'']
1136
- -- case 2: no children but parentheses, e.g. `import A(Foo(),...)` --> `import A(Foo(Cons), ...)`
1137
- Just (' (' , T. uncons -> Just (' )' , rest'')) -> Just $ T. concat [pre, " (" , leading, parent, " (" , rendered, " )" , rest'']
1138
- -- case 3: children with parentheses, e.g. `import A(Foo(ConsA),...)` --> `import A(Foo(Cons, ConsA), ...)`
1139
- Just (' (' , T. breakOn " )" -> (children, rest''))
1140
- | not (T. null children),
1141
- -- ignore A(Foo({-...-}), ...)
1142
- not $ " {-" `T.isPrefixOf` T. stripStart children
1143
- -> Just $ T. concat [pre, " (" , leading, parent, " (" , rendered, " , " , children, rest'']
1144
- -- case 4: no trailing, e.g. `import A(..., Foo)` --> `import A(..., Foo(Cons))`
1145
- Just (' )' , _) -> Just $ T. concat [pre, " (" , leading, parent, " (" , rendered, " )" , rest']
1146
- _ -> Nothing
1147
- -- current import list does not contain the parent, e.g. `import A(...)` --> `import A(Foo(Cons), ...)`
1148
- _ -> Just $ T. concat [pre, " (" , parent, " (" , rendered, " )" , addCommaIfNeeds rest]
1149
- _ -> Nothing
1150
- where
1151
- addCommaIfNeeds r = case T. uncons (T. stripStart r) of
1152
- Just (' )' , _) -> r
1153
- _ -> " , " <> r
1154
-
1155
1115
-- | 'matchRegex' combined with 'unifySpaces'
1156
1116
matchRegexUnifySpaces :: T. Text -> T. Text -> Maybe [T. Text ]
1157
1117
matchRegexUnifySpaces message = matchRegex (unifySpaces message)
@@ -1243,6 +1203,7 @@ data ImportStyle
1243
1203
--
1244
1204
-- @P@ and @?@ can be a data type and a constructor, a class and a method,
1245
1205
-- a class and an associated type/data family, etc.
1206
+ deriving Show
1246
1207
1247
1208
importStyles :: IdentInfo -> NonEmpty ImportStyle
1248
1209
importStyles IdentInfo {parent, rendered, isDatacon}
0 commit comments