Skip to content

Commit c243617

Browse files
committed
Make a test more reliable
For some reason the Cabal cradle is very slow and times out
1 parent eb8240e commit c243617

File tree

2 files changed

+35
-24
lines changed

2 files changed

+35
-24
lines changed

ghcide/test/exe/Main.hs

Lines changed: 25 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
module Main (main) where
1212

1313
import Control.Applicative.Combinators
14-
import Control.Exception (catch)
14+
import Control.Exception (bracket_, catch)
1515
import qualified Control.Lens as Lens
1616
import Control.Monad
1717
import Control.Monad.IO.Class (liftIO)
@@ -41,7 +41,7 @@ import Language.Haskell.LSP.Types.Capabilities
4141
import qualified Language.Haskell.LSP.Types.Lens as Lsp (diagnostics, params, message)
4242
import Language.Haskell.LSP.VFS (applyChange)
4343
import Network.URI
44-
import System.Environment.Blank (getEnv, setEnv)
44+
import System.Environment.Blank (unsetEnv, getEnv, setEnv)
4545
import System.FilePath
4646
import System.IO.Extra hiding (withTempDir)
4747
import qualified System.IO.Extra
@@ -58,8 +58,10 @@ import Test.Tasty.HUnit
5858
import Test.Tasty.QuickCheck
5959
import System.Time.Extra
6060
import Development.IDE.Plugin.CodeAction (typeSignatureCommandId, blockCommandId, matchRegExMultipleImports)
61-
import Development.IDE.Plugin.Test (WaitForIdeRuleResult(..), TestRequest(WaitForIdeRule, BlockSeconds,GetInterfaceFilesDir))
61+
import Development.IDE.Plugin.Test (WaitForIdeRuleResult(..), TestRequest(BlockSeconds,GetInterfaceFilesDir))
6262
import Control.Monad.Extra (whenJust)
63+
import qualified Language.Haskell.LSP.Types.Lens as L
64+
import Control.Lens ((^.))
6365

6466
main :: IO ()
6567
main = do
@@ -630,11 +632,6 @@ cancellationTemplate (edit, undoEdit) mbKey = testCase (maybe "-" fst mbKey) $ r
630632
-- similar to run except it disables kick
631633
runTestNoKick s = withTempDir $ \dir -> runInDir' dir "." "." ["--test-no-kick"] s
632634

633-
waitForAction key TextDocumentIdentifier{_uri} = do
634-
waitId <- sendRequest (CustomClientMethod "test") (WaitForIdeRule key _uri)
635-
ResponseMessage{_result} <- skipManyTill anyMessage $ responseForId waitId
636-
return _result
637-
638635
typeCheck doc = do
639636
Right WaitForIdeRuleResult {..} <- waitForAction "TypeCheck" doc
640637
liftIO $ assertBool "The file should typecheck" ideResultSuccess
@@ -3479,17 +3476,19 @@ simpleSubDirectoryTest =
34793476
expectNoMoreDiagnostics 0.5
34803477

34813478
simpleMultiTest :: TestTree
3482-
simpleMultiTest = testCase "simple-multi-test" $ runWithExtraFiles "multi" $ \dir -> do
3479+
simpleMultiTest = testCase "simple-multi-test" $ withLongTimeout $ runWithExtraFiles "multi" $ \dir -> do
34833480
let aPath = dir </> "a/A.hs"
34843481
bPath = dir </> "b/B.hs"
34853482
aSource <- liftIO $ readFileUtf8 aPath
3486-
(TextDocumentIdentifier adoc) <- createDoc aPath "haskell" aSource
3487-
expectNoMoreDiagnostics 0.5
3483+
adoc <- createDoc aPath "haskell" aSource
3484+
Right WaitForIdeRuleResult {..} <- waitForAction "TypeCheck" adoc
3485+
liftIO $ assertBool "A should typecheck" ideResultSuccess
34883486
bSource <- liftIO $ readFileUtf8 bPath
34893487
bdoc <- createDoc bPath "haskell" bSource
3490-
expectNoMoreDiagnostics 0.5
3488+
Right WaitForIdeRuleResult {..} <- waitForAction "TypeCheck" bdoc
3489+
liftIO $ assertBool "B should typecheck" ideResultSuccess
34913490
locs <- getDefinitions bdoc (Position 2 7)
3492-
let fooL = mkL adoc 2 0 2 3
3491+
let fooL = mkL (adoc ^. L.uri) 2 0 2 3
34933492
checkDefs locs (pure [fooL])
34943493
expectNoMoreDiagnostics 0.5
34953494

@@ -3502,11 +3501,11 @@ simpleMultiTest2 = testCase "simple-multi-test2" $ runWithExtraFiles "multi" $ \
35023501
bdoc <- createDoc bPath "haskell" bSource
35033502
expectNoMoreDiagnostics 10
35043503
aSource <- liftIO $ readFileUtf8 aPath
3505-
(TextDocumentIdentifier adoc) <- createDoc aPath "haskell" aSource
3506-
-- Need to have some delay here or the test fails
3507-
expectNoMoreDiagnostics 10
3504+
adoc <- createDoc aPath "haskell" aSource
3505+
Right WaitForIdeRuleResult {..} <- waitForAction "TypeCheck" adoc
3506+
liftIO $ assertBool "A should typecheck" ideResultSuccess
35083507
locs <- getDefinitions bdoc (Position 2 7)
3509-
let fooL = mkL adoc 2 0 2 3
3508+
let fooL = mkL (adoc ^. L.uri) 2 0 2 3
35103509
checkDefs locs (pure [fooL])
35113510
expectNoMoreDiagnostics 0.5
35123511

@@ -3855,6 +3854,9 @@ run' s = withTempDir $ \dir -> runInDir dir (s dir)
38553854
runInDir :: FilePath -> Session a -> IO a
38563855
runInDir dir = runInDir' dir "." "." []
38573856

3857+
withLongTimeout :: IO a -> IO a
3858+
withLongTimeout = bracket_ (setEnv "LSP_TIMEOUT" "120" True) (unsetEnv "LSP_TIMEOUT")
3859+
38583860
-- | Takes a directory as well as relative paths to where we should launch the executable as well as the session root.
38593861
runInDir' :: FilePath -> FilePath -> FilePath -> [String] -> Session a -> IO a
38603862
runInDir' dir startExeIn startSessionIn extraOptions s = do
@@ -3875,19 +3877,19 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
38753877
setEnv "HOME" "/homeless-shelter" False
38763878
let lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities $ Just True }
38773879
logColor <- fromMaybe True <$> checkEnv "LSP_TEST_LOG_COLOR"
3880+
timeoutOverride <- fmap read <$> getEnv "LSP_TIMEOUT"
3881+
let conf = defaultConfig{messageTimeout = fromMaybe (messageTimeout defaultConfig) timeoutOverride}
3882+
-- uncomment this or set LSP_TEST_LOG_STDERR=1 to see all logging
3883+
-- { logStdErr = True }
3884+
-- uncomment this or set LSP_TEST_LOG_MESSAGES=1 to see all messages
3885+
-- { logMessages = True }
38783886
runSessionWithConfig conf{logColor} cmd lspTestCaps projDir s
38793887
where
38803888
checkEnv :: String -> IO (Maybe Bool)
38813889
checkEnv s = fmap convertVal <$> getEnv s
38823890
convertVal "0" = False
38833891
convertVal _ = True
38843892

3885-
conf = defaultConfig
3886-
-- uncomment this or set LSP_TEST_LOG_STDERR=1 to see all logging
3887-
-- { logStdErr = True }
3888-
-- uncomment this or set LSP_TEST_LOG_MESSAGES=1 to see all messages
3889-
-- { logMessages = True }
3890-
38913893
openTestDataDoc :: FilePath -> Session TextDocumentIdentifier
38923894
openTestDataDoc path = do
38933895
source <- liftIO $ readFileUtf8 $ "test/data" </> path

ghcide/test/src/Development/IDE/Test.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,9 @@ module Development.IDE.Test
1515
, checkDiagnosticsForDoc
1616
, canonicalizeUri
1717
, standardizeQuotes
18-
,flushMessages) where
18+
, flushMessages
19+
, waitForAction
20+
) where
1921

2022
import Control.Applicative.Combinators
2123
import Control.Lens hiding (List)
@@ -32,6 +34,7 @@ import System.Time.Extra
3234
import Test.Tasty.HUnit
3335
import System.Directory (canonicalizePath)
3436
import Data.Maybe (fromJust)
37+
import Development.IDE.Plugin.Test (WaitForIdeRuleResult, TestRequest(WaitForIdeRule))
3538

3639

3740
-- | (0-based line number, 0-based column number)
@@ -180,3 +183,9 @@ standardizeQuotes msg = let
180183
repl '`' = '\''
181184
repl c = c
182185
in T.map repl msg
186+
187+
waitForAction :: String -> TextDocumentIdentifier -> Session (Either ResponseError WaitForIdeRuleResult)
188+
waitForAction key TextDocumentIdentifier{_uri} = do
189+
waitId <- sendRequest (CustomClientMethod "test") (WaitForIdeRule key _uri)
190+
ResponseMessage{_result} <- skipManyTill anyMessage $ responseForId waitId
191+
return _result

0 commit comments

Comments
 (0)