X-Git-Url: http://git.lukelau.me/?a=blobdiff_plain;f=test%2FTest.hs;h=401fd9815fd09e81db4f3af8dafeff13ebc2f2ad;hb=f1238f8db54eafbf0e3352140818875ad4cfd997;hp=986b4c5202e16da4b8e187b77a2db2db38b541ee;hpb=93bbb70d531238c46a28eb356a68c3648b88082f;p=lsp-test.git diff --git a/test/Test.hs b/test/Test.hs index 986b4c5..401fd98 100644 --- a/test/Test.hs +++ b/test/Test.hs @@ -1,13 +1,42 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE OverloadedStrings #-} import Test.Hspec -import Language.Haskell.LSP.Test.Recorded +import Data.Proxy +import Control.Monad.IO.Class +import Control.Lens hiding (List) +import Language.Haskell.LSP.Test +import Language.Haskell.LSP.Test.Replay +import Language.Haskell.LSP.Types +import Language.Haskell.LSP.Messages main = hspec $ do - describe "Replay" $ do - it "passes a test" $ do - replay "test/recordings/renamePass/client.log" - "test/recordings/renamePass/server.log" - `shouldReturn` True - -- it "fails a test" $ - -- replay "test/recordings/documentSymbolFail/client.log" - -- "test/recordings/documentSymbolFail/server.log" - -- `shouldReturn` False + describe "manual session validation" $ + it "passes a test" $ + runSession "test/recordings/renamePass" $ do + docItem <- getDocItem "Desktop/simple.hs" "haskell" + docId <- TextDocumentIdentifier <$> getDocUri "Desktop/simple.hs" + + sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem) + + skipMany loggingNotification + + (NotPublishDiagnostics (NotificationMessage _ TextDocumentPublishDiagnostics (PublishDiagnosticsParams _ (List diags)))) <- notification + + liftIO $ diags `shouldBe` [] + + sendRequest (Proxy :: Proxy DocumentSymbolRequest) + TextDocumentDocumentSymbol + (DocumentSymbolParams docId) + + (RspDocumentSymbols (ResponseMessage _ _ (Just (List symbols)) Nothing)) <- response + + liftIO $ do + let mainSymbol = head symbols + mainSymbol ^. name `shouldBe` "main" + mainSymbol ^. kind `shouldBe` SkFunction + mainSymbol ^. location . range `shouldBe` Range (Position 3 0) (Position 3 4) + mainSymbol ^. containerName `shouldBe` Nothing + + describe "replay session" $ + it "passes a test" $ + replaySession "test/recordings/renamePass" `shouldReturn` True \ No newline at end of file