@@ -132,7 +132,7 @@ suggestAction packageExports ideOptions parsedModule text df annSource diag =
132132 [ suggestSignature True diag
133133 , rewrite df annSource $ \ _ ps -> suggestExtendImport packageExports ps diag
134134 , rewrite df annSource $ \ df ps ->
135- suggestImportDisambiguation df ps diag
135+ suggestImportDisambiguation df text ps diag
136136 , suggestFillTypeWildcard diag
137137 , suggestFixConstructorImport text diag
138138 , suggestModuleTypo diag
@@ -705,8 +705,12 @@ suggestExtendImport exportsMap (L _ HsModule {hsmodImports}) Diagnostic{_range=_
705705 , parent = Nothing
706706 , isDatacon = False }
707707
708- data HidingMode = HideOthers [ModuleTarget ]
709- | ToQualified ModuleName
708+ data HidingMode
709+ = HideOthers [ModuleTarget ]
710+ | ToQualified
711+ Bool
712+ -- ^ Parenthesised?
713+ ModuleName
710714 deriving (Show )
711715
712716data ModuleTarget
@@ -730,10 +734,11 @@ isPreludeImplicit = xopt Lang.ImplicitPrelude
730734-- | Suggests disambiguation for ambiguous symbols.
731735suggestImportDisambiguation ::
732736 DynFlags ->
737+ Maybe T. Text ->
733738 ParsedSource ->
734739 Diagnostic ->
735740 [(T. Text , [Rewrite ])]
736- suggestImportDisambiguation df ps@ (L _ HsModule {hsmodImports}) diag@ Diagnostic {.. }
741+ suggestImportDisambiguation df ( Just txt) ps@ (L _ HsModule {hsmodImports}) diag@ Diagnostic {.. }
737742 | Just [ambiguous] <-
738743 matchRegexUnifySpaces
739744 _message
@@ -759,7 +764,8 @@ suggestImportDisambiguation df ps@(L _ HsModule {hsmodImports}) diag@Diagnostic
759764 = Just $ ImplicitPrelude $
760765 maybe [] NE. toList (Map. lookup " Prelude" locDic)
761766 toModuleTarget mName = ExistingImp <$> Map. lookup mName locDic
762-
767+ parensed =
768+ " (" `T.isPrefixOf` T. strip (textInRange _range txt)
763769 suggestions symbol mods
764770 | Just targets <- mapM toModuleTarget mods =
765771 sortOn fst
@@ -771,12 +777,12 @@ suggestImportDisambiguation df ps@(L _ HsModule {hsmodImports}) diag@Diagnostic
771777 modNameText = T. pack $ moduleNameString modName
772778 , mode <-
773779 HideOthers restImports :
774- [ ToQualified qual
780+ [ ToQualified parensed qual
775781 | ExistingImp imps <- [modTarget]
776782 , L _ qual <- nubOrd $ mapMaybe (ideclAs . unLoc)
777783 $ NE. toList imps
778784 ]
779- ++ [ToQualified modName
785+ ++ [ToQualified parensed modName
780786 | any (occursUnqualified symbol . unLoc)
781787 (targetImports modTarget)
782788 || case modTarget of
@@ -787,11 +793,12 @@ suggestImportDisambiguation df ps@(L _ HsModule {hsmodImports}) diag@Diagnostic
787793 | otherwise = []
788794 renderUniquify HideOthers {} modName symbol =
789795 " Use " <> modName <> " for " <> symbol <> " , hiding other imports"
790- renderUniquify (ToQualified qual) _ symbol =
796+ renderUniquify (ToQualified _ qual) _ symbol =
791797 " Replace with qualified: "
792798 <> T. pack (moduleNameString qual)
793799 <> " ."
794800 <> symbol
801+ suggestImportDisambiguation _ _ _ _ = []
795802
796803occursUnqualified :: T. Text -> ImportDecl GhcPs -> Bool
797804occursUnqualified symbol ImportDecl {.. }
@@ -832,14 +839,18 @@ disambiguateSymbol pm Diagnostic {..} (T.unpack -> symbol) = \case
832839 else hideSymbol symbol <$> imps
833840 | ImplicitPrelude imps <- hiddens0
834841 ]
835- (ToQualified qualMod) ->
842+ (ToQualified parensed qualMod) ->
836843 let occSym = mkVarOcc symbol
837844 rdr = Qual qualMod occSym
838- in [ Rewrite (rangeToSrcSpan " <dummy>" _range) $ \ df -> do
839- liftParseAST @ (HsExpr GhcPs ) df $
845+ in [ if parensed
846+ then Rewrite (rangeToSrcSpan " <dummy>" _range) $ \ df ->
847+ liftParseAST @ (HsExpr GhcPs ) df $
840848 prettyPrint $
841849 HsVar @ GhcPs noExtField $
842850 L (UnhelpfulSpan " " ) rdr
851+ else Rewrite (rangeToSrcSpan " <dummy>" _range) $ \ df ->
852+ liftParseAST @ RdrName df $
853+ prettyPrint $ L (UnhelpfulSpan " " ) rdr
843854 ]
844855
845856findImportDeclByRange :: [LImportDecl GhcPs ] -> Range -> Maybe (LImportDecl GhcPs )
0 commit comments