Add manual session testing
[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.TH.DataTypesJSON
9
10 main = hspec $
11   describe "manual session validation" $ 
12     it "passes a test" $
13       runSession "test/recordings/renamePass" $ do
14         docItem <- getDocItem "Desktop/simple.hs" "haskell"
15         docId   <- TextDocumentIdentifier <$> getDocUri "Desktop/simple.hs"
16
17         sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
18
19         (NotificationMessage _ TextDocumentPublishDiagnostics (PublishDiagnosticsParams _ (List diags))) <-
20           getMessage :: Session PublishDiagnosticsNotification
21
22         liftIO $ diags `shouldBe` []
23         
24         sendRequest (Proxy :: Proxy DocumentSymbolRequest)
25                     TextDocumentDocumentSymbol
26                     (DocumentSymbolParams docId)
27
28         (ResponseMessage _ _ (Just (List symbols)) Nothing) <- getMessage :: Session DocumentSymbolsResponse
29         liftIO $ do
30           let mainSymbol = head symbols
31           mainSymbol ^. name `shouldBe` "main"
32           mainSymbol ^. kind `shouldBe` SkFunction
33           mainSymbol ^. location . range `shouldBe` Range (Position 3 0) (Position 3 4)
34           mainSymbol ^. containerName `shouldBe` Nothing