Add publishDiagnosticsNotification
authorLuke Lau <luke_lau@icloud.com>
Fri, 8 Jun 2018 23:46:25 +0000 (19:46 -0400)
committerLuke Lau <luke_lau@icloud.com>
Fri, 8 Jun 2018 23:46:25 +0000 (19:46 -0400)
src/Language/Haskell/LSP/Test.hs
src/Language/Haskell/LSP/Test/Parsing.hs

index 068fc2dd0a3cbc17e9da1b98b0f92c5238263f5b..c16ae84f2a6a9864033246767f984ec2ae40fb37 100644 (file)
@@ -28,6 +28,7 @@ module Language.Haskell.LSP.Test
   , response
   , notification
   , loggingNotification
+  , publishDiagnosticsNotification
   -- * Combinators
   , choice
   , option
index 53485f19c832ed0cdaab269fbc758aec16cbb1c8..81e5cbed3d64b5ece0f330ea686c7f2b92cce110 100644 (file)
@@ -1,4 +1,3 @@
-{-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}
 module Language.Haskell.LSP.Test.Parsing where
@@ -9,7 +8,7 @@ import Control.Monad.IO.Class
 import Control.Monad.Trans.Reader
 import Control.Monad.Trans.State
 import Language.Haskell.LSP.Messages
-import Language.Haskell.LSP.Types
+import Language.Haskell.LSP.Types hiding (error)
 import Language.Haskell.LSP.Test.Messages
 import Language.Haskell.LSP.Test.Decoding
 import System.IO
@@ -18,8 +17,6 @@ import Control.Concurrent.MVar
 import Data.Conduit hiding (await)
 import Data.Conduit.Parser
 
-data MessageParserState = MessageParserState
-
 data SessionContext = SessionContext
   {
     serverIn :: Handle,
@@ -68,6 +65,13 @@ loggingNotification = satisfy shouldSkip
     shouldSkip (ReqShowMessage _) = True
     shouldSkip _ = False
 
+publishDiagnosticsNotification :: Session PublishDiagnosticsNotification
+publishDiagnosticsNotification = do
+  (NotPublishDiagnostics diags) <- satisfy test
+  return diags
+  where test (NotPublishDiagnostics _) = False
+        test _ = False
+
 satisfy :: Monad m => (a -> Bool) -> ConduitParser a m a
 satisfy pred = do
   x <- await