Skip to content

Commit 0a83296

Browse files
committed
Rewrite the test
1 parent 3bc50c6 commit 0a83296

File tree

1 file changed

+11
-30
lines changed

1 file changed

+11
-30
lines changed

ghcide/test/exe/Main.hs

Lines changed: 11 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -1817,7 +1817,7 @@ extendImportTests = testGroup "extend import actions"
18171817
, "f = Foo 1"
18181818
])
18191819
(Range (Position 3 4) (Position 3 6))
1820-
["Add Foo(Foo) to the import list of ModuleA"]
1820+
["Add Foo(Foo) to the import list of ModuleA", "Add Foo(..) to the import list of ModuleA"]
18211821
(T.unlines
18221822
[ "module ModuleB where"
18231823
, "import ModuleA(Foo (Foo))"
@@ -1997,11 +1997,14 @@ suggestImportTests = testGroup "suggest import actions"
19971997
, test False [] "f ExitSuccess = ()" [] "import System.Exit (ExitSuccess)"
19981998
-- don't suggest data constructor when we only need the type
19991999
, test False [] "f :: Bar" [] "import Bar (Bar(Bar))"
2000+
-- don't suggest all data constructors for the data type
2001+
, test False [] "f :: Bar" [] "import Bar (Bar(..))"
20002002
]
20012003
, testGroup "want suggestion"
20022004
[ wantWait [] "f = foo" [] "import Foo (foo)"
20032005
, wantWait [] "f = Bar" [] "import Bar (Bar(Bar))"
20042006
, wantWait [] "f :: Bar" [] "import Bar (Bar)"
2007+
, wantWait [] "f = Bar" [] "import Bar (Bar(..))"
20052008
, test True [] "f = nonEmpty" [] "import Data.List.NonEmpty (nonEmpty)"
20062009
, test True [] "f = (:|)" [] "import Data.List.NonEmpty (NonEmpty((:|)))"
20072010
, test True [] "f :: Natural" ["f = undefined"] "import Numeric.Natural (Natural)"
@@ -2045,29 +2048,11 @@ suggestImportTests = testGroup "suggest import actions"
20452048
] "f = T.putStrLn" [] "import qualified Data.Text.IO as T"
20462049
]
20472050
, expectFailBecause "importing pattern synonyms is unsupported" $ test True [] "k (Some x) = x" [] "import B (pattern Some)"
2048-
, testGroup "Import with all constructors"
2049-
[ testCase "new import" $
2050-
testAllCons
2051-
[]
2052-
["import A", "import A (Foo(Foo))", "import A (Foo(..))"]
2053-
, testCase "extened import" $
2054-
testAllCons
2055-
["import A()"]
2056-
["Add Foo(Foo) to the import list of A", "Add Foo(..) to the import list of A"]
2057-
]
20582051
]
20592052
where
20602053
test = test' False
20612054
wantWait = test' True True
20622055

2063-
getActions doc defLine waitForCheckProject = do
2064-
waitForProgressDone
2065-
_ <- waitForDiagnostics
2066-
-- there isn't a good way to wait until the whole project is checked atm
2067-
when waitForCheckProject $ liftIO $ sleep 0.5
2068-
let range = Range (Position defLine 0) (Position defLine maxBound)
2069-
getCodeActions doc range
2070-
20712056
test' waitForCheckProject wanted imps def other newImp = testSessionWithExtraFiles "hover" (T.unpack def) $ \dir -> do
20722057
configureCheckProject waitForCheckProject
20732058
let before = T.unlines $ "module A where" : ["import " <> x | x <- imps] ++ def : other
@@ -2076,7 +2061,13 @@ suggestImportTests = testGroup "suggest import actions"
20762061
liftIO $ writeFileUTF8 (dir </> "hie.yaml") cradle
20772062
liftIO $ writeFileUTF8 (dir </> "B.hs") $ unlines ["{-# LANGUAGE PatternSynonyms #-}", "module B where", "pattern Some x = Just x"]
20782063
doc <- createDoc "Test.hs" "haskell" before
2079-
actions <- getActions doc (fromIntegral $ length imps + 1) waitForCheckProject
2064+
waitForProgressDone
2065+
_ <- waitForDiagnostics
2066+
-- there isn't a good way to wait until the whole project is checked atm
2067+
when waitForCheckProject $ liftIO $ sleep 0.5
2068+
let defLine = fromIntegral $ length imps + 1
2069+
range = Range (Position defLine 0) (Position defLine maxBound)
2070+
actions <- getCodeActions doc range
20802071
if wanted
20812072
then do
20822073
action <- liftIO $ pickActionWithTitle newImp actions
@@ -2086,16 +2077,6 @@ suggestImportTests = testGroup "suggest import actions"
20862077
else
20872078
liftIO $ [_title | InR CodeAction{_title} <- actions, _title == newImp ] @?= []
20882079

2089-
testAllCons imported expected = run' $ \dir -> do
2090-
configureCheckProject True
2091-
void $ createDoc (dir </> "A.hs")
2092-
"haskell"
2093-
(T.unlines ["module A where", "data Foo = Foo | Bar"])
2094-
doc <- createDoc (dir </> "Test.hs") "haskell" $ T.unlines (imported ++ ["f = Foo"])
2095-
actions <- getActions doc (fromIntegral $ length imported) True
2096-
let titles = [_title | InR CodeAction{_title} <- actions, _title `elem` expected]
2097-
liftIO $ sort expected @=? sort titles
2098-
20992080
suggestImportDisambiguationTests :: TestTree
21002081
suggestImportDisambiguationTests = testGroup "suggest import disambiguation actions"
21012082
[ testGroup "Hiding strategy works"

0 commit comments

Comments
 (0)