2e829f372284373fa6d5673f9509e140c250387e
[lsp-test.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.Chan
9 import Control.Concurrent.MVar
10 import Control.Monad.Trans.Class
11 import Control.Monad.IO.Class
12 import Control.Monad.Trans.Reader
13 import Control.Monad.Trans.State
14 import Data.Aeson
15 import qualified Data.ByteString.Lazy.Char8 as B
16 import Data.Conduit hiding (await)
17 import Data.Conduit.Parser
18 import Data.Maybe
19 import Language.Haskell.LSP.Messages
20 import Language.Haskell.LSP.Types 
21 import Language.Haskell.LSP.Test.Decoding
22 import Language.Haskell.LSP.Test.Messages
23 import System.IO
24
25 data SessionContext = SessionContext
26   {
27     serverIn :: Handle,
28     rootDir :: FilePath,
29     messageChan :: Chan FromServerMessage,
30     requestMap :: MVar RequestMap
31   }
32
33 newtype SessionState = SessionState
34   {
35     curReqId :: LspId
36   }
37
38 type ParserStateReader a s r m = ConduitParser a (StateT s (ReaderT r m))
39
40 -- | A session representing one instance of launching and connecting to a server.
41 -- 
42 -- You can send and receive messages to the server within 'Session' via 'getMessage',
43 -- 'sendRequest' and 'sendNotification'.
44 --
45 -- @
46 -- runSession \"path\/to\/root\/dir\" $ do
47 --   docItem <- getDocItem "Desktop/simple.hs" "haskell"
48 --   sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams docItem)
49 --   diagnostics <- getMessage :: Session PublishDiagnosticsNotification
50 -- @
51 type Session = ParserStateReader FromServerMessage SessionState SessionContext IO
52
53 -- | Matches if the message is a notification.
54 anyNotification :: Monad m => ConduitParser FromServerMessage m FromServerMessage
55 anyNotification = satisfy isServerNotification
56
57 notification :: forall m a. (Monad m, FromJSON a) => ConduitParser FromServerMessage m (NotificationMessage ServerMethod a)
58 notification = do
59   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (NotificationMessage ServerMethod a)
60   x <- satisfy (isJust . parser)
61   return $ fromJust $ decode $ encodeMsg x
62
63 -- | Matches if the message is a request.
64 anyRequest :: Monad m => ConduitParser FromServerMessage m FromServerMessage
65 anyRequest = satisfy isServerRequest
66
67 request :: forall m a b. (Monad m, FromJSON a, FromJSON b) => ConduitParser FromServerMessage m (RequestMessage ServerMethod a b)
68 request = do
69   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (RequestMessage ServerMethod a b)
70   x <- satisfy (isJust . parser)
71   return $ fromJust $ decode $ encodeMsg x
72
73 -- | Matches if the message is a response.
74 anyResponse :: Monad m => ConduitParser FromServerMessage m FromServerMessage
75 anyResponse = satisfy isServerResponse
76
77 response :: forall m a. (Monad m, FromJSON a) => ConduitParser FromServerMessage m (ResponseMessage a)
78 response = do
79   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
80   x <- satisfy (isJust . parser)
81   return $ fromJust $ decode $ encodeMsg x
82
83 -- | A version of encode that encodes FromServerMessages as if they
84 -- weren't wrapped.
85 encodeMsg :: FromServerMessage -> B.ByteString
86 encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
87
88 -- | Matches if the message is a log message notification or a show message notification/request.
89 loggingNotification :: Monad m => ConduitParser FromServerMessage m FromServerMessage
90 loggingNotification = satisfy shouldSkip
91   where
92     shouldSkip (NotLogMessage _) = True
93     shouldSkip (NotShowMessage _) = True
94     shouldSkip (ReqShowMessage _) = True
95     shouldSkip _ = False
96
97 publishDiagnosticsNotification :: Monad m => ConduitParser FromServerMessage m PublishDiagnosticsNotification
98 publishDiagnosticsNotification = do
99   NotPublishDiagnostics diags <- satisfy test
100   return diags
101   where test (NotPublishDiagnostics _) = True
102         test _ = False
103
104 satisfy :: Monad m => (a -> Bool) -> ConduitParser a m a
105 satisfy pred = do
106   x <- await
107   if pred x
108     then return x
109     else empty
110
111 chanSource :: MonadIO m => Chan o -> ConduitT i o m b
112 chanSource c = do
113   x <- liftIO $ readChan c
114   yield x
115   chanSource c
116
117 runSession' :: Chan FromServerMessage -> SessionContext -> SessionState -> Session a -> IO (a, SessionState)
118 runSession' chan context state session = runReaderT (runStateT conduit state) context
119   where conduit = runConduit $ chanSource chan .| runConduitParser session
120
121 get :: Monad m => ParserStateReader a s r m s
122 get = lift Control.Monad.Trans.State.get
123
124 put :: Monad m => s -> ParserStateReader a s r m ()
125 put = lift . Control.Monad.Trans.State.put
126
127 modify :: Monad m => (s -> s) -> ParserStateReader a s r m ()
128 modify = lift . Control.Monad.Trans.State.modify
129
130 ask :: Monad m => ParserStateReader a s r m r
131 ask = lift $ lift Control.Monad.Trans.Reader.ask