Rename recorded to replay
[lsp-test.git] / test / Test.hs
1 {-# LANGUAGE DuplicateRecordFields #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 import           Test.Hspec
4 import           Data.Proxy
5 import           Control.Monad.IO.Class
6 import           Control.Lens hiding (List)
7 import           Language.Haskell.LSP.Test
8 import           Language.Haskell.LSP.Test.Replay
9 import           Language.Haskell.LSP.TH.DataTypesJSON
10
11 main = hspec $ do
12   describe "manual session validation" $ 
13     it "passes a test" $
14       runSession "test/recordings/renamePass" $ do
15         docItem <- getDocItem "Desktop/simple.hs" "haskell"
16         docId   <- TextDocumentIdentifier <$> getDocUri "Desktop/simple.hs"
17
18         sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
19
20         (NotificationMessage _ TextDocumentPublishDiagnostics (PublishDiagnosticsParams _ (List diags))) <-
21           getMessage :: Session PublishDiagnosticsNotification
22
23         liftIO $ diags `shouldBe` []
24         
25         sendRequest (Proxy :: Proxy DocumentSymbolRequest)
26                     TextDocumentDocumentSymbol
27                     (DocumentSymbolParams docId)
28
29         (ResponseMessage _ _ (Just (List symbols)) Nothing) <- getMessage :: Session DocumentSymbolsResponse
30         liftIO $ do
31           let mainSymbol = head symbols
32           mainSymbol ^. name `shouldBe` "main"
33           mainSymbol ^. kind `shouldBe` SkFunction
34           mainSymbol ^. location . range `shouldBe` Range (Position 3 0) (Position 3 4)
35           mainSymbol ^. containerName `shouldBe` Nothing
36   
37   describe "replay session" $
38     it "passes a test" $
39       replaySession "test/recordings/renamePass" `shouldReturn` True