11
11
module Main (main ) where
12
12
13
13
import Control.Applicative.Combinators
14
- import Control.Exception (catch )
14
+ import Control.Exception (bracket_ , catch )
15
15
import qualified Control.Lens as Lens
16
16
import Control.Monad
17
17
import Control.Monad.IO.Class (liftIO )
@@ -41,7 +41,7 @@ import Language.Haskell.LSP.Types.Capabilities
41
41
import qualified Language.Haskell.LSP.Types.Lens as Lsp (diagnostics , params , message )
42
42
import Language.Haskell.LSP.VFS (applyChange )
43
43
import Network.URI
44
- import System.Environment.Blank (getEnv , setEnv )
44
+ import System.Environment.Blank (unsetEnv , getEnv , setEnv )
45
45
import System.FilePath
46
46
import System.IO.Extra hiding (withTempDir )
47
47
import qualified System.IO.Extra
@@ -58,8 +58,10 @@ import Test.Tasty.HUnit
58
58
import Test.Tasty.QuickCheck
59
59
import System.Time.Extra
60
60
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 ))
62
62
import Control.Monad.Extra (whenJust )
63
+ import qualified Language.Haskell.LSP.Types.Lens as L
64
+ import Control.Lens ((^.) )
63
65
64
66
main :: IO ()
65
67
main = do
@@ -630,11 +632,6 @@ cancellationTemplate (edit, undoEdit) mbKey = testCase (maybe "-" fst mbKey) $ r
630
632
-- similar to run except it disables kick
631
633
runTestNoKick s = withTempDir $ \ dir -> runInDir' dir " ." " ." [" --test-no-kick" ] s
632
634
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
-
638
635
typeCheck doc = do
639
636
Right WaitForIdeRuleResult {.. } <- waitForAction " TypeCheck" doc
640
637
liftIO $ assertBool " The file should typecheck" ideResultSuccess
@@ -3479,17 +3476,19 @@ simpleSubDirectoryTest =
3479
3476
expectNoMoreDiagnostics 0.5
3480
3477
3481
3478
simpleMultiTest :: TestTree
3482
- simpleMultiTest = testCase " simple-multi-test" $ runWithExtraFiles " multi" $ \ dir -> do
3479
+ simpleMultiTest = testCase " simple-multi-test" $ withLongTimeout $ runWithExtraFiles " multi" $ \ dir -> do
3483
3480
let aPath = dir </> " a/A.hs"
3484
3481
bPath = dir </> " b/B.hs"
3485
3482
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
3488
3486
bSource <- liftIO $ readFileUtf8 bPath
3489
3487
bdoc <- createDoc bPath " haskell" bSource
3490
- expectNoMoreDiagnostics 0.5
3488
+ Right WaitForIdeRuleResult {.. } <- waitForAction " TypeCheck" bdoc
3489
+ liftIO $ assertBool " B should typecheck" ideResultSuccess
3491
3490
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
3493
3492
checkDefs locs (pure [fooL])
3494
3493
expectNoMoreDiagnostics 0.5
3495
3494
@@ -3502,11 +3501,11 @@ simpleMultiTest2 = testCase "simple-multi-test2" $ runWithExtraFiles "multi" $ \
3502
3501
bdoc <- createDoc bPath " haskell" bSource
3503
3502
expectNoMoreDiagnostics 10
3504
3503
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
3508
3507
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
3510
3509
checkDefs locs (pure [fooL])
3511
3510
expectNoMoreDiagnostics 0.5
3512
3511
@@ -3855,6 +3854,9 @@ run' s = withTempDir $ \dir -> runInDir dir (s dir)
3855
3854
runInDir :: FilePath -> Session a -> IO a
3856
3855
runInDir dir = runInDir' dir " ." " ." []
3857
3856
3857
+ withLongTimeout :: IO a -> IO a
3858
+ withLongTimeout = bracket_ (setEnv " LSP_TIMEOUT" " 120" True ) (unsetEnv " LSP_TIMEOUT" )
3859
+
3858
3860
-- | Takes a directory as well as relative paths to where we should launch the executable as well as the session root.
3859
3861
runInDir' :: FilePath -> FilePath -> FilePath -> [String ] -> Session a -> IO a
3860
3862
runInDir' dir startExeIn startSessionIn extraOptions s = do
@@ -3875,19 +3877,19 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
3875
3877
setEnv " HOME" " /homeless-shelter" False
3876
3878
let lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities $ Just True }
3877
3879
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 }
3878
3886
runSessionWithConfig conf{logColor} cmd lspTestCaps projDir s
3879
3887
where
3880
3888
checkEnv :: String -> IO (Maybe Bool )
3881
3889
checkEnv s = fmap convertVal <$> getEnv s
3882
3890
convertVal " 0" = False
3883
3891
convertVal _ = True
3884
3892
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
-
3891
3893
openTestDataDoc :: FilePath -> Session TextDocumentIdentifier
3892
3894
openTestDataDoc path = do
3893
3895
source <- liftIO $ readFileUtf8 $ " test/data" </> path
0 commit comments