@@ -1817,7 +1817,7 @@ extendImportTests = testGroup "extend import actions"
1817
1817
, " f = Foo 1"
1818
1818
])
1819
1819
(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 " ]
1821
1821
(T. unlines
1822
1822
[ " module ModuleB where"
1823
1823
, " import ModuleA(Foo (Foo))"
@@ -1997,11 +1997,14 @@ suggestImportTests = testGroup "suggest import actions"
1997
1997
, test False [] " f ExitSuccess = ()" [] " import System.Exit (ExitSuccess)"
1998
1998
-- don't suggest data constructor when we only need the type
1999
1999
, 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(..))"
2000
2002
]
2001
2003
, testGroup " want suggestion"
2002
2004
[ wantWait [] " f = foo" [] " import Foo (foo)"
2003
2005
, wantWait [] " f = Bar" [] " import Bar (Bar(Bar))"
2004
2006
, wantWait [] " f :: Bar" [] " import Bar (Bar)"
2007
+ , wantWait [] " f = Bar" [] " import Bar (Bar(..))"
2005
2008
, test True [] " f = nonEmpty" [] " import Data.List.NonEmpty (nonEmpty)"
2006
2009
, test True [] " f = (:|)" [] " import Data.List.NonEmpty (NonEmpty((:|)))"
2007
2010
, test True [] " f :: Natural" [" f = undefined" ] " import Numeric.Natural (Natural)"
@@ -2045,29 +2048,11 @@ suggestImportTests = testGroup "suggest import actions"
2045
2048
] " f = T.putStrLn" [] " import qualified Data.Text.IO as T"
2046
2049
]
2047
2050
, 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
- ]
2058
2051
]
2059
2052
where
2060
2053
test = test' False
2061
2054
wantWait = test' True True
2062
2055
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
-
2071
2056
test' waitForCheckProject wanted imps def other newImp = testSessionWithExtraFiles " hover" (T. unpack def) $ \ dir -> do
2072
2057
configureCheckProject waitForCheckProject
2073
2058
let before = T. unlines $ " module A where" : [" import " <> x | x <- imps] ++ def : other
@@ -2076,7 +2061,13 @@ suggestImportTests = testGroup "suggest import actions"
2076
2061
liftIO $ writeFileUTF8 (dir </> " hie.yaml" ) cradle
2077
2062
liftIO $ writeFileUTF8 (dir </> " B.hs" ) $ unlines [" {-# LANGUAGE PatternSynonyms #-}" , " module B where" , " pattern Some x = Just x" ]
2078
2063
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
2080
2071
if wanted
2081
2072
then do
2082
2073
action <- liftIO $ pickActionWithTitle newImp actions
@@ -2086,16 +2077,6 @@ suggestImportTests = testGroup "suggest import actions"
2086
2077
else
2087
2078
liftIO $ [_title | InR CodeAction {_title} <- actions, _title == newImp ] @?= []
2088
2079
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
-
2099
2080
suggestImportDisambiguationTests :: TestTree
2100
2081
suggestImportDisambiguationTests = testGroup " suggest import disambiguation actions"
2101
2082
[ testGroup " Hiding strategy works"
0 commit comments