Add unexpected message exception
[opengl.git] / src / Language / Haskell / LSP / Test / Parsing.hs
1 {-# LANGUAGE MultiParamTypeClasses #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
3 {-# LANGUAGE RankNTypes #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 module Language.Haskell.LSP.Test.Parsing where
6
7 import Control.Applicative
8 import Control.Concurrent
9 import Control.Monad.IO.Class
10 import Control.Monad.Trans.Class
11 import Data.Aeson
12 import qualified Data.ByteString.Lazy.Char8 as B
13 import Data.Conduit.Parser
14 import Data.Maybe
15 import Language.Haskell.LSP.Messages
16 import Language.Haskell.LSP.Types hiding (error)
17 import Language.Haskell.LSP.Test.Exceptions
18 import Language.Haskell.LSP.Test.Messages
19 import Language.Haskell.LSP.Test.Session
20
21 satisfy :: (MonadIO m, MonadSessionConfig m) => (a -> Bool) -> ConduitParser a m a
22 satisfy pred = do
23   timeout <- timeout <$> lift sessionConfig
24   tId <- liftIO myThreadId
25   timeoutThread <- liftIO $ forkIO $ do
26     threadDelay (timeout * 1000000)
27     throwTo tId TimeoutException
28   x <- await
29   liftIO $ killThread timeoutThread
30   if pred x
31     then return x
32     else empty
33
34 -- | Matches if the message is a notification.
35 anyNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
36 anyNotification = named "Any notification" $ satisfy isServerNotification
37
38 notification :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => ConduitParser FromServerMessage m (NotificationMessage ServerMethod a)
39 notification = named "Notification" $ do
40   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (NotificationMessage ServerMethod a)
41   x <- satisfy (isJust . parser)
42   return $ castMsg x
43
44 -- | Matches if the message is a request.
45 anyRequest :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
46 anyRequest = named "Any request" $ satisfy isServerRequest
47
48 request :: forall m a b. (MonadIO m, MonadSessionConfig m, FromJSON a, FromJSON b) => ConduitParser FromServerMessage m (RequestMessage ServerMethod a b)
49 request = named "Request" $ do
50   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (RequestMessage ServerMethod a b)
51   x <- satisfy (isJust . parser)
52   return $ castMsg x
53
54 -- | Matches if the message is a response.
55 anyResponse :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
56 anyResponse = named "Any response" $ satisfy isServerResponse
57
58 response :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => ConduitParser FromServerMessage m (ResponseMessage a)
59 response = named "Response" $ do
60   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
61   x <- satisfy (isJust . parser)
62   return $ castMsg x
63
64 -- | A stupid method for getting out the inner message.
65 castMsg :: FromJSON a => FromServerMessage -> a
66 castMsg = fromMaybe (error "Failed casting a message") . decode . encodeMsg
67
68 -- | A version of encode that encodes FromServerMessages as if they
69 -- weren't wrapped.
70 encodeMsg :: FromServerMessage -> B.ByteString
71 encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
72
73 -- | Matches if the message is a log message notification or a show message notification/request.
74 loggingNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
75 loggingNotification = named "Logging notification" $ satisfy shouldSkip
76   where
77     shouldSkip (NotLogMessage _) = True
78     shouldSkip (NotShowMessage _) = True
79     shouldSkip (ReqShowMessage _) = True
80     shouldSkip _ = False
81
82 publishDiagnosticsNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m PublishDiagnosticsNotification
83 publishDiagnosticsNotification = named "Publish diagnostics notification" $ do
84   NotPublishDiagnostics diags <- satisfy test
85   return diags
86   where test (NotPublishDiagnostics _) = True
87         test _ = False