Allow message types to be infered
[lsp-test.git] / test / ParsingTests.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module ParsingTests where
3
4 import Control.Lens hiding (List)
5 import Language.Haskell.LSP.Messages
6 import Language.Haskell.LSP.Test
7 import Language.Haskell.LSP.Types
8 import Data.Conduit
9 import Data.Conduit.Parser
10 import Test.Hspec
11
12 parsingSpec :: Spec
13 parsingSpec =
14   describe "diagnostics" $ do
15     let testDiag = NotPublishDiagnostics
16                    (NotificationMessage "2.0"
17                                        TextDocumentPublishDiagnostics
18                                        (PublishDiagnosticsParams (Uri "foo")
19                                                                  (List [])))
20     it "get picked up" $ do
21       let source = yield testDiag
22           session = do
23             diags <- publishDiagnosticsNotification :: ConduitParser FromServerMessage IO PublishDiagnosticsNotification
24             return $ diags ^. params . uri
25       runConduit (source .| runConduitParser session) `shouldReturn` Uri "foo"
26     it "get picked up after skipping others before" $ do
27       let testDiag = NotPublishDiagnostics
28                     (NotificationMessage "2.0"
29                                           TextDocumentPublishDiagnostics
30                                           (PublishDiagnosticsParams (Uri "foo")
31                                                                     (List [])))
32           notTestDiag = NotLogMessage (NotificationMessage "2.0" WindowLogMessage (LogMessageParams MtLog "foo"))
33           source = yield notTestDiag >> yield testDiag
34           session = do
35             diags <- skipManyTill anyNotification notification :: ConduitParser FromServerMessage IO PublishDiagnosticsNotification
36             return $ diags ^. params . uri
37       runConduit (source .| runConduitParser session) `shouldReturn` Uri "foo"