Skip to content

Commit 25d3dfb

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 f731d92 commit 25d3dfb

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)
@@ -931,13 +937,15 @@ constructNewImportSuggestions exportsMap (qual, thingMissing) notTheseModules =
931937
, suggestion <- renderNewImport identInfo m
932938
]
933939
where
940+
renderNewImport :: IdentInfo -> T.Text -> [T.Text]
934941
renderNewImport identInfo m
935942
| Just q <- qual
936943
, asQ <- if q == m then "" else " as " <> q
937944
= ["import qualified " <> m <> asQ]
938945
| otherwise
939-
= ["import " <> m <> " (" <> renderIdentInfo identInfo <> ")"
940-
,"import " <> m ]
946+
= ["import " <> m <> " (" <> renderImportStyle importStyle <> ")"
947+
| importStyle <- NE.toList $ importStyles identInfo] ++
948+
["import " <> m ]
941949

942950
canUseIdent :: NotInScope -> IdentInfo -> Bool
943951
canUseIdent NotInScopeDataConstructor{} = isDatacon
@@ -1078,15 +1086,18 @@ rangesForBinding' _ _ = []
10781086
-- import (qualified) A (..) ..
10791087
-- Places the new binding first, preserving whitespace.
10801088
-- Copes with multi-line import lists
1081-
addBindingToImportList :: IdentInfo -> T.Text -> Maybe T.Text
1082-
addBindingToImportList IdentInfo {parent = _parent, ..} importLine =
1089+
addBindingToImportList :: ImportStyle -> T.Text -> Maybe T.Text
1090+
addBindingToImportList importStyle importLine =
10831091
case T.breakOn "(" importLine of
10841092
(pre, T.uncons -> Just (_, rest)) ->
1085-
case _parent of
1086-
-- the binding is not a constructor, add it to the head of import list
1087-
Nothing -> Just $ T.concat [pre, "(", rendered, addCommaIfNeeds rest]
1088-
Just parent -> case T.breakOn parent rest of
1089-
-- the binding is a constructor, and current import list contains its parent
1093+
case importStyle of
1094+
ImportTopLevel rendered ->
1095+
-- the binding has no parent, add it to the head of import list
1096+
Just $ T.concat [pre, "(", rendered, addCommaIfNeeds rest]
1097+
ImportViaParent rendered parent -> case T.breakOn parent rest of
1098+
-- the binding has a parent, and the current import list contains the
1099+
-- parent
1100+
--
10901101
-- `rest'` could be 1. `,...)`
10911102
-- or 2. `(),...)`
10921103
-- or 3. `(ConsA),...)`
@@ -1178,7 +1189,43 @@ matchRegExMultipleImports message = do
11781189
imps <- regExImports imports
11791190
return (binding, imps)
11801191

1181-
renderIdentInfo :: IdentInfo -> T.Text
1182-
renderIdentInfo IdentInfo {parent, rendered}
1183-
| Just p <- parent = p <> "(" <> rendered <> ")"
1184-
| otherwise = rendered
1192+
-- | Possible import styles for an 'IdentInfo'.
1193+
--
1194+
-- The first 'Text' parameter corresponds to the 'rendered' field of the
1195+
-- 'IdentInfo'.
1196+
data ImportStyle
1197+
= ImportTopLevel T.Text
1198+
-- ^ Import a top-level export from a module, e.g., a function, a type, a
1199+
-- class.
1200+
--
1201+
-- > import M (?)
1202+
--
1203+
-- Some exports that have a parent, like a type-class method or an
1204+
-- associated type/data family, can still be imported as a top-level
1205+
-- import.
1206+
--
1207+
-- Note that this is not the case for constructors, they must always be
1208+
-- imported as part of their parent data type.
1209+
1210+
| ImportViaParent T.Text T.Text
1211+
-- ^ Import an export (first parameter) through its parent (second
1212+
-- parameter).
1213+
--
1214+
-- import M (P(?))
1215+
--
1216+
-- @P@ and @?@ can be a data type and a constructor, a class and a method,
1217+
-- a class and an associated type/data family, etc.
1218+
1219+
importStyles :: IdentInfo -> NonEmpty ImportStyle
1220+
importStyles IdentInfo {parent, rendered, isDatacon}
1221+
| Just p <- parent
1222+
-- Constructors always have to be imported via their parent data type, but
1223+
-- methods and associated type/data families can also be imported as
1224+
-- top-level exports.
1225+
= ImportViaParent rendered p :| [ImportTopLevel rendered | not isDatacon]
1226+
| otherwise
1227+
= ImportTopLevel rendered :| []
1228+
1229+
renderImportStyle :: ImportStyle -> T.Text
1230+
renderImportStyle (ImportTopLevel x) = x
1231+
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
@@ -1207,6 +1207,46 @@ extendImportTests = testGroup "extend import actions"
12071207
, " )"
12081208
, "main = print (stuffA, stuffB)"
12091209
])
1210+
, testSession "extend single line import with method within class" $ template
1211+
[("ModuleA.hs", T.unlines
1212+
[ "module ModuleA where"
1213+
, "class C a where"
1214+
, " m1 :: a -> a"
1215+
, " m2 :: a -> a"
1216+
])]
1217+
("ModuleB.hs", T.unlines
1218+
[ "module ModuleB where"
1219+
, "import ModuleA (C(m1))"
1220+
, "b = m2"
1221+
])
1222+
(Range (Position 2 5) (Position 2 5))
1223+
["Add C(m2) to the import list of ModuleA",
1224+
"Add m2 to the import list of ModuleA"]
1225+
(T.unlines
1226+
[ "module ModuleB where"
1227+
, "import ModuleA (C(m2, m1))"
1228+
, "b = m2"
1229+
])
1230+
, testSession "extend single line import with method without class" $ template
1231+
[("ModuleA.hs", T.unlines
1232+
[ "module ModuleA where"
1233+
, "class C a where"
1234+
, " m1 :: a -> a"
1235+
, " m2 :: a -> a"
1236+
])]
1237+
("ModuleB.hs", T.unlines
1238+
[ "module ModuleB where"
1239+
, "import ModuleA (C(m1))"
1240+
, "b = m2"
1241+
])
1242+
(Range (Position 2 5) (Position 2 5))
1243+
["Add m2 to the import list of ModuleA",
1244+
"Add C(m2) to the import list of ModuleA"]
1245+
(T.unlines
1246+
[ "module ModuleB where"
1247+
, "import ModuleA (m2, C(m1))"
1248+
, "b = m2"
1249+
])
12101250
, testSession "extend import list with multiple choices" $ template
12111251
[("ModuleA.hs", T.unlines
12121252
-- this is just a dummy module to help the arguments needed for this test
@@ -1296,6 +1336,8 @@ suggestImportTests = testGroup "suggest import actions"
12961336
, test False [] "f :: Typeable a => a" ["f = undefined"] "import Data.Typeable.Internal (Typeable)"
12971337
-- package not in scope
12981338
, test False [] "f = quickCheck" [] "import Test.QuickCheck (quickCheck)"
1339+
-- don't omit the parent data type of a constructor
1340+
, test False [] "f ExitSuccess = ()" [] "import System.Exit (ExitSuccess)"
12991341
]
13001342
, testGroup "want suggestion"
13011343
[ wantWait [] "f = foo" [] "import Foo (foo)"
@@ -1316,6 +1358,7 @@ suggestImportTests = testGroup "suggest import actions"
13161358
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative (Alternative)"
13171359
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative"
13181360
, test True [] "f = empty" [] "import Control.Applicative (Alternative(empty))"
1361+
, test True [] "f = empty" [] "import Control.Applicative (empty)"
13191362
, test True [] "f = empty" [] "import Control.Applicative"
13201363
, test True [] "f = (&)" [] "import Data.Function ((&))"
13211364
, test True [] "f = NE.nonEmpty" [] "import qualified Data.List.NonEmpty as NE"
@@ -1326,6 +1369,7 @@ suggestImportTests = testGroup "suggest import actions"
13261369
, test True [] "f = [] & id" [] "import Data.Function ((&))"
13271370
, test True [] "f = (&) [] id" [] "import Data.Function ((&))"
13281371
, test True [] "f = (.|.)" [] "import Data.Bits (Bits((.|.)))"
1372+
, test True [] "f = (.|.)" [] "import Data.Bits ((.|.))"
13291373
]
13301374
]
13311375
where

0 commit comments

Comments
 (0)