Skip to content

Commit a00f7f7

Browse files
committed
Suggest imports without the parent class
When suggesting to import a method `m` of class `C` from module `M`, in addition to the suggestions `import M` and `import M (C(m))`, also suggest importing the method without mentioning the enclosing class: `import M (m)`.
1 parent 25cf2bb commit a00f7f7

File tree

3 files changed

+110
-19
lines changed

3 files changed

+110
-19
lines changed

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

Lines changed: 63 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,8 @@ import Data.Aeson.Types (toJSON, fromJSON, Value(..), Result(..))
4848
import Data.Char
4949
import Data.Maybe
5050
import Data.List.Extra
51+
import Data.List.NonEmpty (NonEmpty((:|)))
52+
import qualified Data.List.NonEmpty as NE
5153
import qualified Data.Text as T
5254
import Text.Regex.TDFA (mrAfter, (=~), (=~~))
5355
import Outputable (ppr, showSDocUnsafe)
@@ -620,9 +622,13 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
620622
in x{_end = (_end x){_character = succ (_character (_end x))}}
621623
_ -> error "bug in srcspan parser",
622624
importLine <- textInRange range c,
623-
Just ident <- lookupExportMap binding mod,
624-
Just result <- addBindingToImportList ident importLine
625-
= [("Add " <> renderIdentInfo ident <> " to the import list of " <> mod, [TextEdit range result])]
625+
Just ident <- lookupExportMap binding mod
626+
= [ ( "Add " <> rendered <> " to the import list of " <> mod
627+
, [TextEdit range result]
628+
)
629+
| importStyle <- NE.toList $ importStyles ident
630+
, let rendered = renderImportStyle importStyle
631+
, result <- maybeToList $ addBindingToImportList importStyle importLine]
626632
| otherwise = []
627633
lookupExportMap binding mod
628634
| Just match <- Map.lookup binding (getExportsMap exportsMap)
@@ -924,13 +930,15 @@ constructNewImportSuggestions exportsMap (qual, thingMissing) notTheseModules =
924930
, suggestion <- renderNewImport identInfo m
925931
]
926932
where
933+
renderNewImport :: IdentInfo -> T.Text -> [T.Text]
927934
renderNewImport identInfo m
928935
| Just q <- qual
929936
, asQ <- if q == m then "" else " as " <> q
930937
= ["import qualified " <> m <> asQ]
931938
| otherwise
932-
= ["import " <> m <> " (" <> renderIdentInfo identInfo <> ")"
933-
,"import " <> m ]
939+
= ["import " <> m <> " (" <> renderImportStyle importStyle <> ")"
940+
| importStyle <- NE.toList $ importStyles identInfo] ++
941+
["import " <> m ]
934942

935943
canUseIdent :: NotInScope -> IdentInfo -> Bool
936944
canUseIdent NotInScopeDataConstructor{} = isDatacon
@@ -1071,15 +1079,18 @@ rangesForBinding' _ _ = []
10711079
-- import (qualified) A (..) ..
10721080
-- Places the new binding first, preserving whitespace.
10731081
-- Copes with multi-line import lists
1074-
addBindingToImportList :: IdentInfo -> T.Text -> Maybe T.Text
1075-
addBindingToImportList IdentInfo {parent = _parent, ..} importLine =
1082+
addBindingToImportList :: ImportStyle -> T.Text -> Maybe T.Text
1083+
addBindingToImportList importStyle importLine =
10761084
case T.breakOn "(" importLine of
10771085
(pre, T.uncons -> Just (_, rest)) ->
1078-
case _parent of
1079-
-- the binding is not a constructor, add it to the head of import list
1080-
Nothing -> Just $ T.concat [pre, "(", rendered, addCommaIfNeeds rest]
1081-
Just parent -> case T.breakOn parent rest of
1082-
-- the binding is a constructor, and current import list contains its parent
1086+
case importStyle of
1087+
ImportTopLevel rendered ->
1088+
-- the binding has no parent, add it to the head of import list
1089+
Just $ T.concat [pre, "(", rendered, addCommaIfNeeds rest]
1090+
ImportViaParent rendered parent -> case T.breakOn parent rest of
1091+
-- the binding has a parent, and the current import list contains the
1092+
-- parent
1093+
--
10831094
-- `rest'` could be 1. `,...)`
10841095
-- or 2. `(),...)`
10851096
-- or 3. `(ConsA),...)`
@@ -1171,7 +1182,43 @@ matchRegExMultipleImports message = do
11711182
imps <- regExImports imports
11721183
return (binding, imps)
11731184

1174-
renderIdentInfo :: IdentInfo -> T.Text
1175-
renderIdentInfo IdentInfo {parent, rendered}
1176-
| Just p <- parent = p <> "(" <> rendered <> ")"
1177-
| otherwise = rendered
1185+
-- | Possible import styles for an 'IdentInfo'.
1186+
--
1187+
-- The first 'Text' parameter corresponds to the 'rendered' field of the
1188+
-- 'IdentInfo'.
1189+
data ImportStyle
1190+
= ImportTopLevel T.Text
1191+
-- ^ Import a top-level export from a module, e.g., a function, a type, a
1192+
-- class.
1193+
--
1194+
-- > import M (?)
1195+
--
1196+
-- Some exports that have a parent, like a type-class method or an
1197+
-- associated type/data family, can still be imported as a top-level
1198+
-- import.
1199+
--
1200+
-- Note that this is not the case for constructors, they must always be
1201+
-- imported as part of their parent data type.
1202+
1203+
| ImportViaParent T.Text T.Text
1204+
-- ^ Import an export (first parameter) through its parent (second
1205+
-- parameter).
1206+
--
1207+
-- import M (P(?))
1208+
--
1209+
-- @P@ and @?@ can be a data type and a constructor, a class and a method,
1210+
-- a class and an associated type/data family, etc.
1211+
1212+
importStyles :: IdentInfo -> NonEmpty ImportStyle
1213+
importStyles IdentInfo {parent, rendered, isDatacon}
1214+
| Just p <- parent
1215+
-- Constructors always have to be imported via their parent data type, but
1216+
-- methods and associated type/data families can also be imported as
1217+
-- top-level exports.
1218+
= ImportViaParent rendered p :| [ImportTopLevel rendered | not isDatacon]
1219+
| otherwise
1220+
= ImportTopLevel rendered :| []
1221+
1222+
renderImportStyle :: ImportStyle -> T.Text
1223+
renderImportStyle (ImportTopLevel x) = x
1224+
renderImportStyle (ImportViaParent x p) = p <> "(" <> x <> ")"

ghcide/src/Development/IDE/Types/Exports.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -53,15 +53,15 @@ mkIdentInfos (Avail n) =
5353
mkIdentInfos (AvailTC parent (n:nn) flds)
5454
-- Following the GHC convention that parent == n if parent is exported
5555
| n == parent
56-
= [ IdentInfo (pack (prettyPrint n)) (pack (printName n)) (Just $! parentP) True
56+
= [ IdentInfo (pack (prettyPrint n)) (pack (printName n)) (Just $! parentP) (isDataConName n)
5757
| n <- nn ++ map flSelector flds
5858
] ++
59-
[ IdentInfo (pack (prettyPrint n)) (pack (printName n)) Nothing False]
59+
[ IdentInfo (pack (prettyPrint n)) (pack (printName n)) Nothing (isDataConName n)]
6060
where
6161
parentP = pack $ prettyPrint parent
6262

6363
mkIdentInfos (AvailTC _ nn flds)
64-
= [ IdentInfo (pack (prettyPrint n)) (pack (printName n)) Nothing True
64+
= [ IdentInfo (pack (prettyPrint n)) (pack (printName n)) Nothing (isDataConName n)
6565
| n <- nn ++ map flSelector flds
6666
]
6767

ghcide/test/exe/Main.hs

Lines changed: 44 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1203,6 +1203,46 @@ extendImportTests = testGroup "extend import actions"
12031203
, " )"
12041204
, "main = print (stuffA, stuffB)"
12051205
])
1206+
, testSession "extend single line import with method within class" $ template
1207+
[("ModuleA.hs", T.unlines
1208+
[ "module ModuleA where"
1209+
, "class C a where"
1210+
, " m1 :: a -> a"
1211+
, " m2 :: a -> a"
1212+
])]
1213+
("ModuleB.hs", T.unlines
1214+
[ "module ModuleB where"
1215+
, "import ModuleA (C(m1))"
1216+
, "b = m2"
1217+
])
1218+
(Range (Position 2 5) (Position 2 5))
1219+
["Add C(m2) to the import list of ModuleA",
1220+
"Add m2 to the import list of ModuleA"]
1221+
(T.unlines
1222+
[ "module ModuleB where"
1223+
, "import ModuleA (C(m2, m1))"
1224+
, "b = m2"
1225+
])
1226+
, testSession "extend single line import with method without class" $ template
1227+
[("ModuleA.hs", T.unlines
1228+
[ "module ModuleA where"
1229+
, "class C a where"
1230+
, " m1 :: a -> a"
1231+
, " m2 :: a -> a"
1232+
])]
1233+
("ModuleB.hs", T.unlines
1234+
[ "module ModuleB where"
1235+
, "import ModuleA (C(m1))"
1236+
, "b = m2"
1237+
])
1238+
(Range (Position 2 5) (Position 2 5))
1239+
["Add m2 to the import list of ModuleA",
1240+
"Add C(m2) to the import list of ModuleA"]
1241+
(T.unlines
1242+
[ "module ModuleB where"
1243+
, "import ModuleA (m2, C(m1))"
1244+
, "b = m2"
1245+
])
12061246
, testSession "extend import list with multiple choices" $ template
12071247
[("ModuleA.hs", T.unlines
12081248
-- this is just a dummy module to help the arguments needed for this test
@@ -1286,6 +1326,8 @@ suggestImportTests = testGroup "suggest import actions"
12861326
, test False [] "f :: Typeable a => a" ["f = undefined"] "import Data.Typeable.Internal (Typeable)"
12871327
-- package not in scope
12881328
, test False [] "f = quickCheck" [] "import Test.QuickCheck (quickCheck)"
1329+
-- don't omit the parent data type of a constructor
1330+
, test False [] "f ExitSuccess = ()" [] "import System.Exit (ExitSuccess)"
12891331
]
12901332
, testGroup "want suggestion"
12911333
[ wantWait [] "f = foo" [] "import Foo (foo)"
@@ -1306,6 +1348,7 @@ suggestImportTests = testGroup "suggest import actions"
13061348
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative (Alternative)"
13071349
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative"
13081350
, test True [] "f = empty" [] "import Control.Applicative (Alternative(empty))"
1351+
, test True [] "f = empty" [] "import Control.Applicative (empty)"
13091352
, test True [] "f = empty" [] "import Control.Applicative"
13101353
, test True [] "f = (&)" [] "import Data.Function ((&))"
13111354
, test True [] "f = NE.nonEmpty" [] "import qualified Data.List.NonEmpty as NE"
@@ -1316,6 +1359,7 @@ suggestImportTests = testGroup "suggest import actions"
13161359
, test True [] "f = [] & id" [] "import Data.Function ((&))"
13171360
, test True [] "f = (&) [] id" [] "import Data.Function ((&))"
13181361
, test True [] "f = (.|.)" [] "import Data.Bits (Bits((.|.)))"
1362+
, test True [] "f = (.|.)" [] "import Data.Bits ((.|.))"
13191363
]
13201364
]
13211365
where

0 commit comments

Comments
 (0)