Skip to content

Commit c7cd09e

Browse files
konnpepeiborraberberman
authored
ghcide: Implements a CodeAction to disambiguate ambiguous symbols (#1264)
* wip * Draft completed * Removes Unuseds * Redundant extension * linting * Makes HLint happy * tweak for transfer annotation logic (not working) * Initial implementation done * Import list reorder * Remove redundant fmt * lint * Missing import * Excludes false-positive qualified imports * A first test (not enough though) * fmt.sh * Some more test cases * More test cases * Ah! CRLF have bitten me! * Tentative workaround for #1274 * Wait much to ensure rewrite suggestion to be collected * Tests for type suggestion * Slightly more wait * A little smarter waiting strartegy for actions * Import list slim up * Adjusted to the master * Update ghcide/src/Development/IDE/Plugin/CodeAction.hs Co-authored-by: Pepe Iborra <[email protected]> * Rewrote using `expectDiagnostics` * Case for Prelude.++ * Corrects test name * Renames `rawIEWrapName` to `unqualIEWrapName`, and moved to the appropriate module * Rewrote qualifying strategy with `Rewrite` * Use exactprint also for hideImplicitPreludeSymbol * Unify exact actions and `suggestImportDisambiguation` * Moves a comment to the right place * Won't panic on errornous input, let HLS keep going * No, each errornous rewrite must not be dropped seprately, but discarded as a whole * Update ghcide/src/Development/IDE/Spans/Common.hs Co-authored-by: Potato Hatsue <[email protected]> * ieNames * Makes Splice plugin compiles * Stop using nfp * Since there is global `setEntryDPT dp00`, we don't add offset here * Removes redundant (why warned here?) * Made `hideImplicitPreludeSymbol` total Co-authored-by: Pepe Iborra <[email protected]> Co-authored-by: Potato Hatsue <[email protected]>
1 parent 6b6c405 commit c7cd09e

25 files changed

+659
-58
lines changed

ghcide/src/Development/IDE/GHC/Error.hs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,9 @@ module Development.IDE.GHC.Error
1717
, realSrcLocToPosition
1818
, realSrcSpanToLocation
1919
, srcSpanToFilename
20+
, rangeToSrcSpan
21+
, rangeToRealSrcSpan
22+
, positionToRealSrcLoc
2023
, zeroSpan
2124
, realSpan
2225
, isInsideSrcSpan
@@ -39,6 +42,7 @@ import Panic
3942
import ErrUtils
4043
import SrcLoc
4144
import qualified Outputable as Out
45+
import Data.String (fromString)
4246

4347

4448

@@ -102,6 +106,20 @@ srcSpanToLocation src = do
102106
-- important that the URI's we produce have been properly normalized, otherwise they point at weird places in VS Code
103107
pure $ Location (fromNormalizedUri $ filePathToUri' $ toNormalizedFilePath' fs) rng
104108

109+
rangeToSrcSpan :: NormalizedFilePath -> Range -> SrcSpan
110+
rangeToSrcSpan = fmap RealSrcSpan . rangeToRealSrcSpan
111+
112+
rangeToRealSrcSpan
113+
:: NormalizedFilePath -> Range -> RealSrcSpan
114+
rangeToRealSrcSpan nfp =
115+
mkRealSrcSpan
116+
<$> positionToRealSrcLoc nfp . _start
117+
<*> positionToRealSrcLoc nfp . _end
118+
119+
positionToRealSrcLoc :: NormalizedFilePath -> Position -> RealSrcLoc
120+
positionToRealSrcLoc nfp (Position l c)=
121+
mkRealSrcLoc (fromString $ fromNormalizedFilePath nfp) (l + 1) (c + 1)
122+
105123
isInsideSrcSpan :: Position -> SrcSpan -> Bool
106124
p `isInsideSrcSpan` r = case srcSpanToRange r of
107125
Just (Range sp ep) -> sp <= p && p <= ep

ghcide/src/Development/IDE/GHC/Orphans.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ import qualified StringBuffer as SB
2222
import Data.Text (Text)
2323
import Data.String (IsString(fromString))
2424
import Retrie.ExactPrint (Annotated)
25-
import Data.List (foldl')
2625

2726

2827
-- Orphan instances for types from the GHC API.

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 173 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -43,16 +43,22 @@ import qualified Data.Text as T
4343
import Text.Regex.TDFA (mrAfter, (=~), (=~~))
4444
import Outputable (Outputable, ppr, showSDoc, showSDocUnsafe)
4545
import Data.Function
46-
import Control.Arrow ((>>>))
46+
import Control.Arrow ((>>>), second)
4747
import Data.Functor
4848
import Control.Applicative ((<|>))
4949
import Safe (atMay)
5050
import Bag (isEmptyBag)
5151
import qualified Data.HashSet as Set
5252
import Control.Concurrent.Extra (readVar)
53-
import Development.IDE.GHC.Util (printRdrName)
53+
import Development.IDE.GHC.Util (printRdrName, prettyPrint)
5454
import Ide.PluginUtils (subRange)
5555
import Ide.Types
56+
import qualified Data.DList as DL
57+
import Development.IDE.Spans.Common
58+
import OccName
59+
import qualified GHC.LanguageExtensions as Lang
60+
import Control.Lens (alaf)
61+
import Data.Monoid (Ap(..))
5662

5763
descriptor :: PluginId -> PluginDescriptor IdeState
5864
descriptor plId =
@@ -103,10 +109,12 @@ mkCA title diags edit =
103109
rewrite ::
104110
Maybe DynFlags ->
105111
Maybe (Annotated ParsedSource) ->
106-
(DynFlags -> ParsedSource -> [(T.Text, Rewrite)]) ->
112+
(DynFlags -> ParsedSource -> [(T.Text, [Rewrite])]) ->
107113
[(T.Text, [TextEdit])]
108114
rewrite (Just df) (Just ps) f
109-
| Right edit <- (traverse . traverse) (rewriteToEdit df (annsA ps)) (f df $ astA ps) = edit
115+
| Right edit <- (traverse . traverse)
116+
(alaf Ap foldMap (rewriteToEdit df (annsA ps)))
117+
(f df $ astA ps) = edit
110118
rewrite _ _ _ = []
111119

112120
suggestAction
@@ -118,10 +126,13 @@ suggestAction
118126
-> Maybe (Annotated ParsedSource)
119127
-> Diagnostic
120128
-> [(T.Text, [TextEdit])]
121-
suggestAction packageExports ideOptions parsedModule text df annSource diag = concat
129+
suggestAction packageExports ideOptions parsedModule text df annSource diag =
130+
concat
122131
-- Order these suggestions by priority
123132
[ suggestSignature True diag
124133
, rewrite df annSource $ \_ ps -> suggestExtendImport packageExports ps diag
134+
, rewrite df annSource $ \df ps ->
135+
suggestImportDisambiguation df ps diag
125136
, suggestFillTypeWildcard diag
126137
, suggestFixConstructorImport text diag
127138
, suggestModuleTypo diag
@@ -301,8 +312,8 @@ suggestDeleteUnusedBinding
301312
let findSig (L (RealSrcSpan l) (SigD _ sig)) = findRelatedSigSpan indexedContent name l sig
302313
findSig _ = []
303314
in
304-
[extendForSpaces indexedContent $ toRange l]
305-
++ concatMap findSig hsmodDecls
315+
extendForSpaces indexedContent (toRange l) :
316+
concatMap findSig hsmodDecls
306317
_ -> concatMap (findRelatedSpanForMatch indexedContent name) matches
307318
findRelatedSpans _ _ _ = []
308319

@@ -377,7 +388,7 @@ suggestDeleteUnusedBinding
377388
then
378389
let findSig (L (RealSrcSpan l) sig) = findRelatedSigSpan indexedContent name l sig
379390
findSig _ = []
380-
in [extendForSpaces indexedContent $ toRange l] ++ concatMap findSig lsigs
391+
in extendForSpaces indexedContent (toRange l) : concatMap findSig lsigs
381392
else concatMap (findRelatedSpanForMatch indexedContent name) matches
382393
findRelatedSpanForHsBind _ _ _ _ = []
383394

@@ -655,7 +666,7 @@ getIndentedGroupsBy pred inp = case dropWhile (not.pred) inp of
655666
indentation :: T.Text -> Int
656667
indentation = T.length . T.takeWhile isSpace
657668

658-
suggestExtendImport :: ExportsMap -> ParsedSource -> Diagnostic -> [(T.Text, Rewrite)]
669+
suggestExtendImport :: ExportsMap -> ParsedSource -> Diagnostic -> [(T.Text, [Rewrite])]
659670
suggestExtendImport exportsMap (L _ HsModule {hsmodImports}) Diagnostic{_range=_range,..}
660671
| Just [binding, mod, srcspan] <-
661672
matchRegexUnifySpaces _message
@@ -676,7 +687,7 @@ suggestExtendImport exportsMap (L _ HsModule {hsmodImports}) Diagnostic{_range=_
676687
Just decl <- findImportDeclByRange decls range,
677688
Just ident <- lookupExportMap binding mod
678689
= [ ( "Add " <> renderImportStyle importStyle <> " to the import list of " <> mod
679-
, uncurry extendImport (unImportStyle importStyle) decl
690+
, [uncurry extendImport (unImportStyle importStyle) decl]
680691
)
681692
| importStyle <- NE.toList $ importStyles ident
682693
]
@@ -694,6 +705,143 @@ suggestExtendImport exportsMap (L _ HsModule {hsmodImports}) Diagnostic{_range=_
694705
, parent = Nothing
695706
, isDatacon = False}
696707

708+
data HidingMode = HideOthers [ModuleTarget]
709+
| ToQualified ModuleName
710+
deriving (Show)
711+
712+
data ModuleTarget
713+
= ExistingImp (NonEmpty (LImportDecl GhcPs))
714+
| ImplicitPrelude [LImportDecl GhcPs]
715+
deriving (Show)
716+
717+
targetImports :: ModuleTarget -> [LImportDecl GhcPs]
718+
targetImports (ExistingImp ne) = NE.toList ne
719+
targetImports (ImplicitPrelude xs) = xs
720+
721+
oneAndOthers :: [a] -> [(a, [a])]
722+
oneAndOthers = go
723+
where
724+
go [] = []
725+
go (x : xs) = (x, xs) : map (second (x :)) (go xs)
726+
727+
isPreludeImplicit :: DynFlags -> Bool
728+
isPreludeImplicit = xopt Lang.ImplicitPrelude
729+
730+
-- | Suggests disambiguation for ambiguous symbols.
731+
suggestImportDisambiguation ::
732+
DynFlags ->
733+
ParsedSource ->
734+
Diagnostic ->
735+
[(T.Text, [Rewrite])]
736+
suggestImportDisambiguation df ps@(L _ HsModule {hsmodImports}) diag@Diagnostic {..}
737+
| Just [ambiguous] <-
738+
matchRegexUnifySpaces
739+
_message
740+
"Ambiguous occurrence ‘([^’]+)’"
741+
, Just modules <-
742+
map last
743+
<$> allMatchRegexUnifySpaces _message "imported from ‘([^’]+)’" =
744+
suggestions ambiguous modules
745+
| otherwise = []
746+
where
747+
locDic =
748+
fmap (NE.fromList . DL.toList) $
749+
Map.fromListWith (<>) $
750+
map
751+
( \i@(L _ idecl) ->
752+
( T.pack $ moduleNameString $ unLoc $ ideclName idecl
753+
, DL.singleton i
754+
)
755+
)
756+
hsmodImports
757+
toModuleTarget "Prelude"
758+
| isPreludeImplicit df
759+
= Just $ ImplicitPrelude $
760+
maybe [] NE.toList (Map.lookup "Prelude" locDic)
761+
toModuleTarget mName = ExistingImp <$> Map.lookup mName locDic
762+
763+
suggestions symbol mods
764+
| Just targets <- mapM toModuleTarget mods =
765+
sortOn fst
766+
[ ( renderUniquify mode modNameText symbol
767+
, disambiguateSymbol ps diag symbol mode
768+
)
769+
| (modTarget, restImports) <- oneAndOthers targets
770+
, let modName = targetModuleName modTarget
771+
modNameText = T.pack $ moduleNameString modName
772+
, mode <-
773+
HideOthers restImports :
774+
[ ToQualified qual
775+
| ExistingImp imps <- [modTarget]
776+
, L _ qual <- nubOrd $ mapMaybe (ideclAs . unLoc)
777+
$ NE.toList imps
778+
]
779+
++ [ToQualified modName
780+
| any (occursUnqualified symbol . unLoc)
781+
(targetImports modTarget)
782+
|| case modTarget of
783+
ImplicitPrelude{} -> True
784+
_ -> False
785+
]
786+
]
787+
| otherwise = []
788+
renderUniquify HideOthers {} modName symbol =
789+
"Use " <> modName <> " for " <> symbol <> ", hiding other imports"
790+
renderUniquify (ToQualified qual) _ symbol =
791+
"Replace with qualified: "
792+
<> T.pack (moduleNameString qual)
793+
<> "."
794+
<> symbol
795+
796+
occursUnqualified :: T.Text -> ImportDecl GhcPs -> Bool
797+
occursUnqualified symbol ImportDecl{..}
798+
| isNothing ideclAs = Just False /=
799+
-- I don't find this particularly comprehensible,
800+
-- but HLint suggested me to do so...
801+
(ideclHiding <&> \(isHiding, L _ ents) ->
802+
let occurs = any ((symbol `symbolOccursIn`) . unLoc) ents
803+
in isHiding && not occurs || not isHiding && occurs
804+
)
805+
occursUnqualified _ _ = False
806+
807+
symbolOccursIn :: T.Text -> IE GhcPs -> Bool
808+
symbolOccursIn symb = any ((== symb). showNameWithoutUniques) . ieNames
809+
810+
targetModuleName :: ModuleTarget -> ModuleName
811+
targetModuleName ImplicitPrelude{} = mkModuleName "Prelude"
812+
targetModuleName (ExistingImp (L _ ImportDecl{..} :| _)) =
813+
unLoc ideclName
814+
targetModuleName (ExistingImp _) =
815+
error "Cannot happen!"
816+
817+
disambiguateSymbol ::
818+
ParsedSource ->
819+
Diagnostic ->
820+
T.Text ->
821+
HidingMode ->
822+
[Rewrite]
823+
disambiguateSymbol pm Diagnostic {..} (T.unpack -> symbol) = \case
824+
(HideOthers hiddens0) ->
825+
[ hideSymbol symbol idecl
826+
| ExistingImp idecls <- hiddens0
827+
, idecl <- NE.toList idecls
828+
]
829+
++ mconcat
830+
[ if null imps
831+
then maybeToList $ hideImplicitPreludeSymbol symbol pm
832+
else hideSymbol symbol <$> imps
833+
| ImplicitPrelude imps <- hiddens0
834+
]
835+
(ToQualified qualMod) ->
836+
let occSym = mkVarOcc symbol
837+
rdr = Qual qualMod occSym
838+
in [ Rewrite (rangeToSrcSpan "<dummy>" _range) $ \df -> do
839+
liftParseAST @(HsExpr GhcPs) df $
840+
prettyPrint $
841+
HsVar @GhcPs noExtField $
842+
L (UnhelpfulSpan "") rdr
843+
]
844+
697845
findImportDeclByRange :: [LImportDecl GhcPs] -> Range -> Maybe (LImportDecl GhcPs)
698846
findImportDeclByRange xs range = find (\(L l _)-> srcSpanToRange l == Just range) xs
699847

@@ -711,13 +859,13 @@ suggestFixConstructorImport _ Diagnostic{_range=_range,..}
711859
in [("Fix import of " <> fixedImport, [TextEdit _range fixedImport])]
712860
| otherwise = []
713861
-- | Suggests a constraint for a declaration for which a constraint is missing.
714-
suggestConstraint :: DynFlags -> ParsedSource -> Diagnostic -> [(T.Text, Rewrite)]
862+
suggestConstraint :: DynFlags -> ParsedSource -> Diagnostic -> [(T.Text, [Rewrite])]
715863
suggestConstraint df parsedModule diag@Diagnostic {..}
716864
| Just missingConstraint <- findMissingConstraint _message
717865
= let codeAction = if _message =~ ("the type signature for:" :: String)
718866
then suggestFunctionConstraint df parsedModule
719867
else suggestInstanceConstraint df parsedModule
720-
in codeAction diag missingConstraint
868+
in map (second (:[])) $ codeAction diag missingConstraint
721869
| otherwise = []
722870
where
723871
findMissingConstraint :: T.Text -> Maybe T.Text
@@ -773,14 +921,14 @@ suggestInstanceConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missing
773921
suggestImplicitParameter ::
774922
ParsedSource ->
775923
Diagnostic ->
776-
[(T.Text, Rewrite)]
924+
[(T.Text, [Rewrite])]
777925
suggestImplicitParameter (L _ HsModule {hsmodDecls}) Diagnostic {_message, _range}
778926
| Just [implicitT] <- matchRegexUnifySpaces _message "Unbound implicit parameter \\(([^:]+::.+)\\) arising",
779927
Just (L _ (ValD _ FunBind {fun_id = L _ funId})) <- findDeclContainingLoc (_start _range) hsmodDecls,
780928
Just (TypeSig _ _ HsWC {hswc_body = HsIB {hsib_body}}) <- findSigOfDecl (== funId) hsmodDecls
781929
=
782930
[( "Add " <> implicitT <> " to the context of " <> T.pack (printRdrName funId)
783-
, appendConstraint (T.unpack implicitT) hsib_body)]
931+
, [appendConstraint (T.unpack implicitT) hsib_body])]
784932
| otherwise = []
785933

786934
findTypeSignatureName :: T.Text -> Maybe T.Text
@@ -1098,11 +1246,22 @@ rangesForBinding' _ _ = []
10981246
matchRegexUnifySpaces :: T.Text -> T.Text -> Maybe [T.Text]
10991247
matchRegexUnifySpaces message = matchRegex (unifySpaces message)
11001248

1249+
-- | 'allMatchRegex' combined with 'unifySpaces'
1250+
allMatchRegexUnifySpaces :: T.Text -> T.Text -> Maybe [[T.Text]]
1251+
allMatchRegexUnifySpaces message =
1252+
allMatchRegex (unifySpaces message)
1253+
11011254
-- | Returns Just (the submatches) for the first capture, or Nothing.
11021255
matchRegex :: T.Text -> T.Text -> Maybe [T.Text]
11031256
matchRegex message regex = case message =~~ regex of
11041257
Just (_ :: T.Text, _ :: T.Text, _ :: T.Text, bindings) -> Just bindings
11051258
Nothing -> Nothing
1259+
1260+
-- | Returns Just (all matches) for the first capture, or Nothing.
1261+
allMatchRegex :: T.Text -> T.Text -> Maybe [[T.Text]]
1262+
allMatchRegex message regex = message =~~ regex
1263+
1264+
11061265
unifySpaces :: T.Text -> T.Text
11071266
unifySpaces = T.unwords . T.words
11081267

0 commit comments

Comments
 (0)