Skip to content

Commit 8b7090f

Browse files
mrBlissjneiramergify[bot]
authored
Also suggest importing methods without parent class (#766)
* Make it possible to choose the code action in extendImportTests Let the order of the expected code actions dictate which one to execute, i.e., the first one. This means we no longer test the *order* of the suggested code actions. Through this simple change, we can now test the execution of a code action that doesn't come first in the list of suggested code actions. * 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)`. Co-authored-by: Javier Neira <[email protected]> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 840dd3d commit 8b7090f

File tree

3 files changed

+130
-28
lines changed

3 files changed

+130
-28
lines changed

Diff for: ghcide/src/Development/IDE/Plugin/CodeAction.hs

+63-16
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)
@@ -622,9 +624,13 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
622624
in x{_end = (_end x){_character = succ (_character (_end x))}}
623625
_ -> error "bug in srcspan parser",
624626
importLine <- textInRange range c,
625-
Just ident <- lookupExportMap binding mod,
626-
Just result <- addBindingToImportList ident importLine
627-
= [("Add " <> renderIdentInfo ident <> " to the import list of " <> mod, [TextEdit range result])]
627+
Just ident <- lookupExportMap binding mod
628+
= [ ( "Add " <> rendered <> " to the import list of " <> mod
629+
, [TextEdit range result]
630+
)
631+
| importStyle <- NE.toList $ importStyles ident
632+
, let rendered = renderImportStyle importStyle
633+
, result <- maybeToList $ addBindingToImportList importStyle importLine]
628634
| otherwise = []
629635
lookupExportMap binding mod
630636
| Just match <- Map.lookup binding (getExportsMap exportsMap)
@@ -933,13 +939,15 @@ constructNewImportSuggestions exportsMap (qual, thingMissing) notTheseModules =
933939
, suggestion <- renderNewImport identInfo m
934940
]
935941
where
942+
renderNewImport :: IdentInfo -> T.Text -> [T.Text]
936943
renderNewImport identInfo m
937944
| Just q <- qual
938945
, asQ <- if q == m then "" else " as " <> q
939946
= ["import qualified " <> m <> asQ]
940947
| otherwise
941-
= ["import " <> m <> " (" <> renderIdentInfo identInfo <> ")"
942-
,"import " <> m ]
948+
= ["import " <> m <> " (" <> renderImportStyle importStyle <> ")"
949+
| importStyle <- NE.toList $ importStyles identInfo] ++
950+
["import " <> m ]
943951

944952
canUseIdent :: NotInScope -> IdentInfo -> Bool
945953
canUseIdent NotInScopeDataConstructor{} = isDatacon
@@ -1080,15 +1088,18 @@ rangesForBinding' _ _ = []
10801088
-- import (qualified) A (..) ..
10811089
-- Places the new binding first, preserving whitespace.
10821090
-- Copes with multi-line import lists
1083-
addBindingToImportList :: IdentInfo -> T.Text -> Maybe T.Text
1084-
addBindingToImportList IdentInfo {parent = _parent, ..} importLine =
1091+
addBindingToImportList :: ImportStyle -> T.Text -> Maybe T.Text
1092+
addBindingToImportList importStyle importLine =
10851093
case T.breakOn "(" importLine of
10861094
(pre, T.uncons -> Just (_, rest)) ->
1087-
case _parent of
1088-
-- the binding is not a constructor, add it to the head of import list
1089-
Nothing -> Just $ T.concat [pre, "(", rendered, addCommaIfNeeds rest]
1090-
Just parent -> case T.breakOn parent rest of
1091-
-- the binding is a constructor, and current import list contains its parent
1095+
case importStyle of
1096+
ImportTopLevel rendered ->
1097+
-- the binding has no parent, add it to the head of import list
1098+
Just $ T.concat [pre, "(", rendered, addCommaIfNeeds rest]
1099+
ImportViaParent rendered parent -> case T.breakOn parent rest of
1100+
-- the binding has a parent, and the current import list contains the
1101+
-- parent
1102+
--
10921103
-- `rest'` could be 1. `,...)`
10931104
-- or 2. `(),...)`
10941105
-- or 3. `(ConsA),...)`
@@ -1180,7 +1191,43 @@ matchRegExMultipleImports message = do
11801191
imps <- regExImports imports
11811192
return (binding, imps)
11821193

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

Diff for: ghcide/src/Development/IDE/Types/Exports.hs

+3-3
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

Diff for: ghcide/test/exe/Main.hs

+64-9
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
@@ -1235,7 +1275,9 @@ extendImportTests = testGroup "extend import actions"
12351275
])
12361276
]
12371277
where
1238-
template setUpModules moduleUnderTest range expectedActions expectedContentB = do
1278+
codeActionTitle CodeAction{_title=x} = x
1279+
1280+
template setUpModules moduleUnderTest range expectedTitles expectedContentB = do
12391281
sendNotification WorkspaceDidChangeConfiguration
12401282
(DidChangeConfigurationParams $ toJSON
12411283
def{checkProject = overrideCheckProject})
@@ -1245,14 +1287,23 @@ extendImportTests = testGroup "extend import actions"
12451287
docB <- createDoc (fst moduleUnderTest) "haskell" (snd moduleUnderTest)
12461288
_ <- waitForDiagnostics
12471289
void (skipManyTill anyMessage message :: Session WorkDoneProgressEndNotification)
1248-
codeActions <- filter (\(CACodeAction CodeAction{_title=x}) -> T.isPrefixOf "Add" x)
1249-
<$> getCodeActions docB range
1250-
let expectedTitles = (\(CACodeAction CodeAction{_title=x}) ->x) <$> codeActions
1251-
liftIO $ expectedActions @=? expectedTitles
1252-
1253-
-- Get the first action and execute the first action
1254-
let CACodeAction action : _
1255-
= sortOn (\(CACodeAction CodeAction{_title=x}) -> x) codeActions
1290+
actionsOrCommands <- getCodeActions docB range
1291+
let codeActions =
1292+
filter
1293+
(T.isPrefixOf "Add" . codeActionTitle)
1294+
[ca | CACodeAction ca <- actionsOrCommands]
1295+
actualTitles = codeActionTitle <$> codeActions
1296+
-- Note that we are not testing the order of the actions, as the
1297+
-- order of the expected actions indicates which one we'll execute
1298+
-- in this test, i.e., the first one.
1299+
liftIO $ sort expectedTitles @=? sort actualTitles
1300+
1301+
-- Execute the action with the same title as the first expected one.
1302+
-- Since we tested that both lists have the same elements (possibly
1303+
-- in a different order), this search cannot fail.
1304+
let firstTitle:_ = expectedTitles
1305+
action = fromJust $
1306+
find ((firstTitle ==) . codeActionTitle) codeActions
12561307
executeCodeAction action
12571308
contentAfterAction <- documentContents docB
12581309
liftIO $ expectedContentB @=? contentAfterAction
@@ -1285,6 +1336,8 @@ suggestImportTests = testGroup "suggest import actions"
12851336
, test False [] "f :: Typeable a => a" ["f = undefined"] "import Data.Typeable.Internal (Typeable)"
12861337
-- package not in scope
12871338
, 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)"
12881341
]
12891342
, testGroup "want suggestion"
12901343
[ wantWait [] "f = foo" [] "import Foo (foo)"
@@ -1305,6 +1358,7 @@ suggestImportTests = testGroup "suggest import actions"
13051358
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative (Alternative)"
13061359
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative"
13071360
, test True [] "f = empty" [] "import Control.Applicative (Alternative(empty))"
1361+
, test True [] "f = empty" [] "import Control.Applicative (empty)"
13081362
, test True [] "f = empty" [] "import Control.Applicative"
13091363
, test True [] "f = (&)" [] "import Data.Function ((&))"
13101364
, test True [] "f = NE.nonEmpty" [] "import qualified Data.List.NonEmpty as NE"
@@ -1315,6 +1369,7 @@ suggestImportTests = testGroup "suggest import actions"
13151369
, test True [] "f = [] & id" [] "import Data.Function ((&))"
13161370
, test True [] "f = (&) [] id" [] "import Data.Function ((&))"
13171371
, test True [] "f = (.|.)" [] "import Data.Bits (Bits((.|.)))"
1372+
, test True [] "f = (.|.)" [] "import Data.Bits ((.|.))"
13181373
]
13191374
]
13201375
where

0 commit comments

Comments
 (0)