Add SessionConfig
[opengl.git] / src / Language / Haskell / LSP / Test / Parsing.hs
1 {-# LANGUAGE MultiParamTypeClasses #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
4 {-# LANGUAGE RankNTypes #-}
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   liftIO $ forkIO $ do
26     threadDelay (timeout * 1000000)
27     throwTo tId TimeoutException
28   x <- await
29   if pred x
30     then return x
31     else empty
32
33 -- | Matches if the message is a notification.
34 anyNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
35 anyNotification = satisfy isServerNotification
36
37 notification :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => ConduitParser FromServerMessage m (NotificationMessage ServerMethod a)
38 notification = do
39   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (NotificationMessage ServerMethod a)
40   x <- satisfy (isJust . parser)
41   return $ decodeMsg $ encodeMsg x
42
43 -- | Matches if the message is a request.
44 anyRequest :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
45 anyRequest = satisfy isServerRequest
46
47 request :: forall m a b. (MonadIO m, MonadSessionConfig m, FromJSON a, FromJSON b) => ConduitParser FromServerMessage m (RequestMessage ServerMethod a b)
48 request = do
49   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (RequestMessage ServerMethod a b)
50   x <- satisfy (isJust . parser)
51   return $ decodeMsg $ encodeMsg x
52
53 -- | Matches if the message is a response.
54 anyResponse :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
55 anyResponse = satisfy isServerResponse
56
57 response :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => ConduitParser FromServerMessage m (ResponseMessage a)
58 response = do
59   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
60   x <- satisfy (isJust . parser)
61   return $ decodeMsg $ encodeMsg x
62
63 -- | A version of encode that encodes FromServerMessages as if they
64 -- weren't wrapped.
65 encodeMsg :: FromServerMessage -> B.ByteString
66 encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
67
68 decodeMsg :: FromJSON a => B.ByteString -> a
69 decodeMsg x = fromMaybe (error $ "Unexpected message type\nGot:\n " ++ show x)
70                   (decode x)
71
72 -- | Matches if the message is a log message notification or a show message notification/request.
73 loggingNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage
74 loggingNotification = satisfy shouldSkip
75   where
76     shouldSkip (NotLogMessage _) = True
77     shouldSkip (NotShowMessage _) = True
78     shouldSkip (ReqShowMessage _) = True
79     shouldSkip _ = False
80
81 publishDiagnosticsNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m PublishDiagnosticsNotification
82 publishDiagnosticsNotification = do
83   NotPublishDiagnostics diags <- satisfy test
84   return diags
85   where test (NotPublishDiagnostics _) = True
86         test _ = False