e55909f4c59fc9076c665d9b8f66811ae9981bb9
[lsp-test.git] / src / Language / LSP / Test / Parsing.hs
1 {-# LANGUAGE MultiParamTypeClasses #-}
2 {-# LANGUAGE EmptyCase #-}
3 {-# LANGUAGE TypeOperators #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeInType #-}
6 {-# LANGUAGE KindSignatures #-}
7 {-# LANGUAGE TypeInType #-}
8 {-# LANGUAGE GADTs #-}
9 {-# LANGUAGE LambdaCase #-}
10 {-# LANGUAGE RankNTypes #-}
11 {-# LANGUAGE OverloadedStrings #-}
12
13 module Language.LSP.Test.Parsing
14   ( -- $receiving
15     satisfy
16   , satisfyMaybe
17   , message
18   , response
19   , responseForId
20   , customRequest
21   , customNotification
22   , anyRequest
23   , anyResponse
24   , anyNotification
25   , anyMessage
26   , loggingNotification
27   , publishDiagnosticsNotification
28   ) where
29
30 import Control.Applicative
31 import Control.Concurrent
32 import Control.Monad.IO.Class
33 import Control.Monad
34 import Data.Conduit.Parser hiding (named)
35 import qualified Data.Conduit.Parser (named)
36 import qualified Data.Text as T
37 import Data.Typeable
38 import Language.LSP.Types
39 import Language.LSP.Test.Session
40
41 -- $receiving
42 -- To receive a message, specify the method of the message to expect:
43 --
44 -- @
45 -- msg1 <- message SWorkspaceApplyEdit
46 -- msg2 <- message STextDocumentHover
47 -- @
48 --
49 -- 'Language.LSP.Test.Session' is actually just a parser
50 -- that operates on messages under the hood. This means that you
51 -- can create and combine parsers to match speicifc sequences of
52 -- messages that you expect.
53 --
54 -- For example, if you wanted to match either a definition or
55 -- references request:
56 --
57 -- > defOrImpl = message STextDocumentDefinition
58 -- >          <|> message STextDocumentReferences
59 --
60 -- If you wanted to match any number of telemetry
61 -- notifications immediately followed by a response:
62 --
63 -- @
64 -- logThenDiags =
65 --  skipManyTill (message STelemetryEvent)
66 --               anyResponse
67 -- @
68
69 -- | Consumes and returns the next message, if it satisfies the specified predicate.
70 --
71 -- @since 0.5.2.0
72 satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
73 satisfy pred = satisfyMaybe (\msg -> if pred msg then Just msg else Nothing)
74
75 -- | Consumes and returns the result of the specified predicate if it returns `Just`.
76 --
77 -- @since 0.6.1.0
78 satisfyMaybe :: (FromServerMessage -> Maybe a) -> Session a
79 satisfyMaybe pred = satisfyMaybeM (pure . pred)
80
81 satisfyMaybeM :: (FromServerMessage -> Session (Maybe a)) -> Session a
82 satisfyMaybeM pred = do 
83   
84   skipTimeout <- overridingTimeout <$> get
85   timeoutId <- getCurTimeoutId
86   unless skipTimeout $ do
87     chan <- asks messageChan
88     timeout <- asks (messageTimeout . config)
89     void $ liftIO $ forkIO $ do
90       threadDelay (timeout * 1000000)
91       writeChan chan (TimeoutMessage timeoutId)
92
93   x <- Session await
94
95   unless skipTimeout (bumpTimeoutId timeoutId)
96
97   modify $ \s -> s { lastReceivedMessage = Just x }
98
99   res <- pred x
100
101   case res of
102     Just a -> do
103       logMsg LogServer x
104       return a
105     Nothing -> empty
106
107 named :: T.Text -> Session a -> Session a
108 named s (Session x) = Session (Data.Conduit.Parser.named s x)
109
110
111 -- | Matches a request or a notification coming from the server.
112 message :: SServerMethod m -> Session (ServerMessage m)
113 message m1 = named (T.pack $ "Request for: " <> show m1) $ satisfyMaybe $ \case
114   FromServerMess m2 msg -> do
115     HRefl <- mEqServer m1 m2
116     pure msg
117   _ -> Nothing
118
119 customRequest :: T.Text -> Session (ServerMessage (CustomMethod :: Method FromServer Request))
120 customRequest m = named m $ satisfyMaybe $ \case
121   FromServerMess m1 msg -> case splitServerMethod m1 of
122     IsServerEither -> case msg of
123       ReqMess _ | m1 == SCustomMethod m -> Just msg
124       _ -> Nothing
125     _ -> Nothing
126   _ -> Nothing
127
128 customNotification :: T.Text -> Session (ServerMessage (CustomMethod :: Method FromServer Notification))
129 customNotification m = named m $ satisfyMaybe $ \case
130   FromServerMess m1 msg -> case splitServerMethod m1 of
131     IsServerEither -> case msg of
132       NotMess _ | m1 == SCustomMethod m -> Just msg
133       _ -> Nothing
134     _ -> Nothing
135   _ -> Nothing
136
137 -- | Matches if the message is a notification.
138 anyNotification :: Session FromServerMessage
139 anyNotification = named "Any notification" $ satisfy $ \case
140   FromServerMess m msg -> case splitServerMethod m of
141     IsServerNot -> True
142     IsServerEither -> case msg of
143       NotMess _ -> True
144       _ -> False
145     _ -> False
146   FromServerRsp _ _ -> False
147
148 -- | Matches if the message is a request.
149 anyRequest :: Session FromServerMessage
150 anyRequest = named "Any request" $ satisfy $ \case
151   FromServerMess m _ -> case splitServerMethod m of
152     IsServerReq -> True
153     _ -> False
154   FromServerRsp _ _ -> False
155
156 -- | Matches if the message is a response.
157 anyResponse :: Session FromServerMessage
158 anyResponse = named "Any response" $ satisfy $ \case
159   FromServerMess _ _ -> False
160   FromServerRsp _ _ -> True
161
162 -- | Matches a response coming from the server.
163 response :: SMethod (m :: Method FromClient Request) -> Session (ResponseMessage m)
164 response m1 = named (T.pack $ "Response for: " <> show m1) $ satisfyMaybe $ \case
165   FromServerRsp m2 msg -> do
166     HRefl <- mEqClient m1 m2
167     pure msg
168   _ -> Nothing
169
170 -- | Like 'response', but matches a response for a specific id.
171 responseForId :: SMethod (m :: Method FromClient Request) -> LspId m -> Session (ResponseMessage m)
172 responseForId m lid = named (T.pack $ "Response for id: " ++ show lid) $ do
173   satisfyMaybe $ \msg -> do
174     case msg of
175       FromServerMess _ _ -> Nothing
176       FromServerRsp m' rspMsg@(ResponseMessage _ lid' _) ->
177         case mEqClient m m' of
178           Just HRefl -> do
179             guard (lid' == Just lid)
180             pure rspMsg
181           Nothing
182             | SCustomMethod tm <- m
183             , SCustomMethod tm' <- m'
184             , tm == tm'
185             , lid' == Just lid -> pure rspMsg
186           _ -> empty
187
188 -- | Matches any type of message.
189 anyMessage :: Session FromServerMessage
190 anyMessage = satisfy (const True)
191
192 -- | Matches if the message is a log message notification or a show message notification/request.
193 loggingNotification :: Session FromServerMessage
194 loggingNotification = named "Logging notification" $ satisfy shouldSkip
195   where
196     shouldSkip (FromServerMess SWindowLogMessage _) = True
197     shouldSkip (FromServerMess SWindowShowMessage _) = True
198     shouldSkip (FromServerMess SWindowShowMessageRequest _) = True
199     shouldSkip _ = False
200
201 -- | Matches a 'Language.LSP.Types.TextDocumentPublishDiagnostics'
202 -- (textDocument/publishDiagnostics) notification.
203 publishDiagnosticsNotification :: Session (Message TextDocumentPublishDiagnostics)
204 publishDiagnosticsNotification = named "Publish diagnostics notification" $
205   satisfyMaybe $ \msg -> case msg of
206     FromServerMess STextDocumentPublishDiagnostics diags -> Just diags
207     _ -> Nothing