Skip to content
This repository has been archived by the owner on Jan 2, 2021. It is now read-only.

Commit

Permalink
Fix flaky tests
Browse files Browse the repository at this point in the history
  • Loading branch information
pepeiborra committed Sep 5, 2020
1 parent 4edf523 commit bff6195
Showing 1 changed file with 9 additions and 4 deletions.
13 changes: 9 additions & 4 deletions test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ import Test.Tasty.ExpectedFailure
import Test.Tasty.Ingredients.Rerun
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import System.Time.Extra

main :: IO ()
main = do
Expand Down Expand Up @@ -1036,9 +1037,9 @@ suggestImportTests = testGroup "suggest import actions"
, test False [] "f = quickCheck" [] "import Test.QuickCheck (quickCheck)"
]
, testGroup "want suggestion"
[ test True [] "f = foo" [] "import Foo (foo)"
, test True [] "f = Bar" [] "import Bar (Bar(Bar))"
, test True [] "f :: Bar" [] "import Bar (Bar)"
[ wantWait [] "f = foo" [] "import Foo (foo)"
, wantWait [] "f = Bar" [] "import Bar (Bar(Bar))"
, wantWait [] "f :: Bar" [] "import Bar (Bar)"
, test True [] "f = nonEmpty" [] "import Data.List.NonEmpty (nonEmpty)"
, test True [] "f = (:|)" [] "import Data.List.NonEmpty (NonEmpty((:|)))"
, test True [] "f :: Natural" ["f = undefined"] "import Numeric.Natural (Natural)"
Expand Down Expand Up @@ -1066,13 +1067,17 @@ suggestImportTests = testGroup "suggest import actions"
]
]
where
test wanted imps def other newImp = testSessionWithExtraFiles "hover" (T.unpack def) $ \dir -> do
test = test' False
wantWait = test' True True
test' waitForCheckProject wanted imps def other newImp = testSessionWithExtraFiles "hover" (T.unpack def) $ \dir -> do
let before = T.unlines $ "module A where" : ["import " <> x | x <- imps] ++ def : other
after = T.unlines $ "module A where" : ["import " <> x | x <- imps] ++ [newImp] ++ def : other
cradle = "cradle: {direct: {arguments: [-hide-all-packages, -package, base, -package, text, -package-env, -, A, Bar, Foo, GotoHover]}}"
liftIO $ writeFileUTF8 (dir </> "hie.yaml") cradle
doc <- createDoc "Test.hs" "haskell" before
void (skipManyTill anyMessage message :: Session WorkDoneProgressEndNotification)
-- there isn't a good way to wait until the whole project is checked atm
when waitForCheckProject $ liftIO $ sleep 0.1
_diags <- waitForDiagnostics
let defLine = length imps + 1
range = Range (Position defLine 0) (Position defLine maxBound)
Expand Down

0 comments on commit bff6195

Please sign in to comment.