Add unexpected message exception
[opengl.git] / test / ParsingTests.hs
index 7824ef3b4f7ff930388b7f3ebcd53274c21f901d..fe8d36671d7fca4192498a12a3445c67a1d3a397 100644 (file)
@@ -1,4 +1,5 @@
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE FlexibleInstances #-}
 module ParsingTests where
 
 import Control.Lens hiding (List)
@@ -7,8 +8,14 @@ import Language.Haskell.LSP.Test
 import Language.Haskell.LSP.Types
 import Data.Conduit
 import Data.Conduit.Parser
+import Data.Default
 import Test.Hspec
 
+type TestSession = ConduitParser FromServerMessage IO
+
+instance MonadSessionConfig IO where
+  sessionConfig = return def
+
 parsingSpec :: Spec
 parsingSpec =
   describe "diagnostics" $ do
@@ -18,10 +25,9 @@ parsingSpec =
                                        (PublishDiagnosticsParams (Uri "foo")
                                                                  (List [])))
     it "get picked up" $ do
-      let 
-          source = yield testDiag
+      let source = yield testDiag
           session = do
-            diags <- publishDiagnosticsNotification
+            diags <- publishDiagnosticsNotification :: TestSession PublishDiagnosticsNotification
             return $ diags ^. params . uri
       runConduit (source .| runConduitParser session) `shouldReturn` Uri "foo"
     it "get picked up after skipping others before" $ do
@@ -33,6 +39,6 @@ parsingSpec =
           notTestDiag = NotLogMessage (NotificationMessage "2.0" WindowLogMessage (LogMessageParams MtLog "foo"))
           source = yield notTestDiag >> yield testDiag
           session = do
-            diags <- skipManyTill notification publishDiagnosticsNotification
+            diags <- skipManyTill anyNotification notification :: TestSession PublishDiagnosticsNotification
             return $ diags ^. params . uri
       runConduit (source .| runConduitParser session) `shouldReturn` Uri "foo"
\ No newline at end of file