Add argument for server executable
[lsp-test.git] / test / Test.hs
1 {-# LANGUAGE DuplicateRecordFields #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 import           Test.Hspec
4 import           Data.Maybe
5 import           Data.Proxy
6 import           Control.Monad.IO.Class
7 import           Control.Lens hiding (List)
8 import           Language.Haskell.LSP.Test
9 import           Language.Haskell.LSP.Test.Replay
10 import           Language.Haskell.LSP.Types
11 import           Language.Haskell.LSP.Messages
12 import           ParsingTests
13
14 main = hspec $ do
15   describe "manual session validation" $ do
16     it "passes a test" $
17       runSession "hie" "test/recordings/renamePass" $ do
18         doc <- openDoc "Desktop/simple.hs" "haskell"
19
20         skipMany loggingNotification
21
22         NotPublishDiagnostics diagsNot <- notification
23
24         liftIO $ diagsNot ^. params . diagnostics `shouldBe` List []
25         
26         sendRequest (Proxy :: Proxy DocumentSymbolRequest)
27                     TextDocumentDocumentSymbol
28                     (DocumentSymbolParams doc)
29
30         RspDocumentSymbols rspSymbols <- response
31         
32         liftIO $ do
33           let (List symbols) = fromJust (rspSymbols ^. result)
34               mainSymbol = head symbols
35           mainSymbol ^. name `shouldBe` "main"
36           mainSymbol ^. kind `shouldBe` SkFunction
37           mainSymbol ^. location . range `shouldBe` Range (Position 3 0) (Position 3 4)
38           mainSymbol ^. containerName `shouldBe` Nothing
39     
40     it "fails a test" $
41       -- TODO: Catch the exception in haskell-lsp-test and provide nicer output
42       let session = runSession "hie" "test/recordings/renamePass" $ do
43                     openDoc "Desktop/simple.hs" "haskell"
44                     skipMany loggingNotification
45                     request
46         in session `shouldThrow` anyException
47   
48   describe "replay session" $ do
49     it "passes a test" $
50       replaySession "hie" "test/recordings/renamePass" `shouldReturn` True
51     it "fails a test" $
52       replaySession "hie" "test/recordings/renameFail" `shouldReturn` False
53   
54   parsingSpec