update equality function
[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     res <- mEqServer m1 m2
116     case res of
117       Right HRefl -> pure msg
118       Left f -> Nothing
119   _ -> Nothing
120
121 customRequest :: T.Text -> Session (ServerMessage (CustomMethod :: Method FromServer Request))
122 customRequest m = named m $ satisfyMaybe $ \case
123   FromServerMess m1 msg -> case splitServerMethod m1 of
124     IsServerEither -> case msg of
125       ReqMess _ | m1 == SCustomMethod m -> Just msg
126       _ -> Nothing
127     _ -> Nothing
128   _ -> Nothing
129
130 customNotification :: T.Text -> Session (ServerMessage (CustomMethod :: Method FromServer Notification))
131 customNotification m = named m $ satisfyMaybe $ \case
132   FromServerMess m1 msg -> case splitServerMethod m1 of
133     IsServerEither -> case msg of
134       NotMess _ | m1 == SCustomMethod m -> Just msg
135       _ -> Nothing
136     _ -> Nothing
137   _ -> Nothing
138
139 -- | Matches if the message is a notification.
140 anyNotification :: Session FromServerMessage
141 anyNotification = named "Any notification" $ satisfy $ \case
142   FromServerMess m msg -> case splitServerMethod m of
143     IsServerNot -> True
144     IsServerEither -> case msg of
145       NotMess _ -> True
146       _ -> False
147     _ -> False
148   FromServerRsp _ _ -> False
149
150 -- | Matches if the message is a request.
151 anyRequest :: Session FromServerMessage
152 anyRequest = named "Any request" $ satisfy $ \case
153   FromServerMess m _ -> case splitServerMethod m of
154     IsServerReq -> True
155     _ -> False
156   FromServerRsp _ _ -> False
157
158 -- | Matches if the message is a response.
159 anyResponse :: Session FromServerMessage
160 anyResponse = named "Any response" $ satisfy $ \case
161   FromServerMess _ _ -> False
162   FromServerRsp _ _ -> True
163
164 -- | Matches a response coming from the server.
165 response :: SMethod (m :: Method FromClient Request) -> Session (ResponseMessage m)
166 response m1 = named (T.pack $ "Response for: " <> show m1) $ satisfyMaybe $ \case
167   FromServerRsp m2 msg -> do
168     HRefl <- runEq mEqClient m1 m2
169     pure msg
170   _ -> Nothing
171
172 -- | Like 'response', but matches a response for a specific id.
173 responseForId :: SMethod (m :: Method FromClient Request) -> LspId m -> Session (ResponseMessage m)
174 responseForId m lid = named (T.pack $ "Response for id: " ++ show lid) $ do
175   satisfyMaybe $ \msg -> do
176     case msg of
177       FromServerMess _ _ -> Nothing
178       FromServerRsp m' rspMsg@(ResponseMessage _ lid' _) -> do
179         HRefl <- runEq mEqClient m m'
180         guard (Just lid == lid')
181         pure rspMsg
182
183 -- | Matches any type of message.
184 anyMessage :: Session FromServerMessage
185 anyMessage = satisfy (const True)
186
187 -- | Matches if the message is a log message notification or a show message notification/request.
188 loggingNotification :: Session FromServerMessage
189 loggingNotification = named "Logging notification" $ satisfy shouldSkip
190   where
191     shouldSkip (FromServerMess SWindowLogMessage _) = True
192     shouldSkip (FromServerMess SWindowShowMessage _) = True
193     shouldSkip (FromServerMess SWindowShowMessageRequest _) = True
194     shouldSkip _ = False
195
196 -- | Matches a 'Language.LSP.Types.TextDocumentPublishDiagnostics'
197 -- (textDocument/publishDiagnostics) notification.
198 publishDiagnosticsNotification :: Session (Message TextDocumentPublishDiagnostics)
199 publishDiagnosticsNotification = named "Publish diagnostics notification" $
200   satisfyMaybe $ \msg -> case msg of
201     FromServerMess STextDocumentPublishDiagnostics diags -> Just diags
202     _ -> Nothing