Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit 3835a09

Browse files
committed
Fix tests, add documentation and add newtypes
1 parent 07822b4 commit 3835a09

File tree

2 files changed

+46
-26
lines changed

2 files changed

+46
-26
lines changed

src/Haskell/Ide/Engine/Plugin/HsImport.hs

+37-20
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,12 @@ type ModuleName = T.Text
7878
type SymbolName = T.Text
7979
type DatatypeName = T.Text
8080

81+
-- | Wrapper for a FilePath that is used as an Input file for HsImport
82+
newtype InputFilePath = MkInputFilePath { getInput :: FilePath }
83+
84+
-- | Wrapper for a FilePath that is used as an Output file for HsImport
85+
newtype OutputFilePath = MkOutputFilePath { getOutput :: FilePath }
86+
8187
-- | How to import a module.
8288
-- Can be used to express to import a whole module or only specific symbols
8389
-- from a module.
@@ -128,7 +134,11 @@ importModule uri impStyle modName =
128134
tmpDir <- liftIO getTemporaryDirectory
129135
(output, outputH) <- liftIO $ openTempFile tmpDir "hsimportOutput"
130136
liftIO $ hClose outputH
131-
let args = importStyleToHsImportArgs input output modName impStyle
137+
let args = importStyleToHsImportArgs
138+
(MkInputFilePath input)
139+
(MkOutputFilePath output)
140+
modName
141+
impStyle
132142
-- execute hsimport on the given file and write into a temporary file.
133143
maybeErr <- liftIO $ HsImport.hsimportWithArgs HsImport.defaultConfig args
134144
case maybeErr of
@@ -207,12 +217,12 @@ importModule uri impStyle modName =
207217
-- | Convert the import style arguments into HsImport arguments.
208218
-- Takes an input and an output file as well as a module name.
209219
importStyleToHsImportArgs
210-
:: FilePath -> FilePath -> ModuleName -> ImportStyle -> HsImport.HsImportArgs
220+
:: InputFilePath -> OutputFilePath -> ModuleName -> ImportStyle -> HsImport.HsImportArgs
211221
importStyleToHsImportArgs input output modName style =
212222
let defaultArgs = -- Default args, must be set every time.
213223
HsImport.defaultArgs { HsImport.moduleName = T.unpack modName
214-
, HsImport.inputSrcFile = input
215-
, HsImport.outputSrcFile = output
224+
, HsImport.inputSrcFile = getInput input
225+
, HsImport.outputSrcFile = getOutput output
216226
}
217227

218228
kindToArgs :: SymbolKind -> HsImport.HsImportArgs
@@ -393,6 +403,9 @@ codeActionProvider plId docId _ context = do
393403
--
394404
-- >>> symName "take :: Int -> [a] -> [a]"
395405
-- Just "take"
406+
--
407+
-- >>> symName "take"
408+
-- Just "take"
396409
symName :: T.Text -> Maybe SymbolName
397410
symName = S.headMay . T.words
398411

@@ -403,7 +416,7 @@ codeActionProvider plId docId _ context = do
403416
mkImportAction modName importDiagnostic symbolType = do
404417
cmd <- mkLspCommand plId "import" title (Just cmdParams)
405418
return (Just (codeAction cmd))
406-
where
419+
where
407420
codeAction cmd = J.CodeAction title
408421
(Just J.CodeActionQuickFix)
409422
(Just (J.List [diagnostic importDiagnostic]))
@@ -413,6 +426,8 @@ codeActionProvider plId docId _ context = do
413426
<> modName
414427
<> case termType importDiagnostic of
415428
Hiding _ -> "hiding "
429+
-- ^ Note, that it must never happen
430+
-- in combination with `symbolType == Nothing`
416431
Import _ -> ""
417432
<> case symbolType of
418433
Just s -> case s of
@@ -442,25 +457,27 @@ codeActionProvider plId docId _ context = do
442457
-- This looks at the error message and tries to extract the expected
443458
-- signature of an unknown function.
444459
-- If this is not possible, Nothing is returned.
445-
extractImportableTerm :: T.Text -> Maybe (T.Text, (SymbolImport SymbolType) )
460+
extractImportableTerm :: T.Text -> Maybe (T.Text, SymbolImport SymbolType)
446461
extractImportableTerm dirtyMsg =
447-
let extractedTerm =
448-
asum
449-
[ (\name -> (name, Import Symbol)) <$> T.stripPrefix "Variable not in scope: " importMsg
450-
, (\name -> (T.init name, Import Type)) <$> T.stripPrefix "Not in scope: type constructor or class ‘" importMsg
451-
, (\name -> (name, Import Constructor)) <$> T.stripPrefix "Data constructor not in scope: " importMsg
452-
]
462+
let extractedTerm = asum
463+
[ (\name -> (name, Import Symbol))
464+
<$> T.stripPrefix "Variable not in scope: " importMsg
465+
, (\name -> (T.init name, Import Type))
466+
<$> T.stripPrefix
467+
"Not in scope: type constructor or class ‘"
468+
importMsg
469+
, (\name -> (name, Import Constructor))
470+
<$> T.stripPrefix "Data constructor not in scope: " importMsg]
453471
in do
454-
(n, s) <- extractedTerm
455-
let n' = T.strip n
456-
return (n', s)
457-
where
458-
importMsg =
459-
head
460-
-- Get rid of the rename suggestion parts
472+
(n, s) <- extractedTerm
473+
let n' = T.strip n
474+
return (n', s)
475+
where
476+
importMsg = head
477+
-- Get rid of the rename suggestion parts
461478
$ T.splitOn "Perhaps you meant "
462479
$ T.replace "\n" " "
463-
-- Get rid of trailing/leading whitespace on each individual line
480+
-- Get rid of trailing/leading whitespace on each individual line
464481
$ T.unlines
465482
$ map T.strip
466483
$ T.lines

test/unit/CodeActionsSpec.hs

+9-6
Original file line numberDiff line numberDiff line change
@@ -15,19 +15,22 @@ spec = do
1515
describe "import code actions" $ do
1616
it "pick up variable not in scope" $
1717
let msg = "Variable not in scope: fromJust :: Maybe Integer -> t"
18-
in extractImportableTerm msg `shouldBe` Just "fromJust :: Maybe Integer -> t"
18+
in extractImportableTerm msg `shouldBe` Just ("fromJust :: Maybe Integer -> t", Import Symbol)
1919
it "pick up variable not in scope with 'perhaps you meant'" $
2020
let msg = "• Variable not in scope: msgs :: T.Text\n• Perhaps you meant ‘msg’ (line 90)"
21-
in extractImportableTerm msg `shouldBe` Just "msgs :: T.Text"
21+
in extractImportableTerm msg `shouldBe` Just ("msgs :: T.Text", Import Symbol)
2222
it "pick up multi-line variable not in scope" $
2323
let msg = "Variable not in scope:\nliftIO\n:: IO [FilePath]\n-> GhcMod.Monad.Newtypes.GmT\n (GhcMod.Monad.Newtypes.GmOutT IdeM) [[t0]]"
24-
in extractImportableTerm msg `shouldBe` Just "liftIO :: IO [FilePath] -> GhcMod.Monad.Newtypes.GmT (GhcMod.Monad.Newtypes.GmOutT IdeM) [[t0]]"
24+
in extractImportableTerm msg `shouldBe` Just ("liftIO :: IO [FilePath] -> GhcMod.Monad.Newtypes.GmT (GhcMod.Monad.Newtypes.GmOutT IdeM) [[t0]]", Import Symbol)
2525
it "pick up when" $
2626
let msg = "Variable not in scope: when :: Bool -> IO () -> t"
27-
in extractImportableTerm msg `shouldBe` Just "when :: Bool -> IO () -> t"
27+
in extractImportableTerm msg `shouldBe` Just ("when :: Bool -> IO () -> t", Import Symbol)
2828
it "pick up data constructors" $
2929
let msg = "Data constructor not in scope: ExitFailure :: Integer -> t"
30-
in extractImportableTerm msg `shouldBe` Just "ExitFailure :: Integer -> t"
30+
in extractImportableTerm msg `shouldBe` Just ("ExitFailure :: Integer -> t", Import Constructor)
31+
it "pick up type" $
32+
let msg = "Not in scope: type constructor or class ‘Text"
33+
in extractImportableTerm msg `shouldBe` Just ("Text", Import Type)
3134

3235
describe "rename code actions" $ do
3336
it "pick up variable not in scope perhaps you meant" $
@@ -146,7 +149,7 @@ spec = do
146149
\ Text.Megaparsec.Error.ShowErrorComponent e, Ord t) =>\n\
147150
\ OutputFormat -> Format.Result t e -> IO b"
148151
in extractMissingSignature msg `shouldBe` Just expected
149-
152+
150153
describe "unused term code actions" $ do
151154
it "pick up unused term" $
152155
let msg = " Defined but not used: ‘imUnused’"

0 commit comments

Comments
 (0)