Add back parser namers
[lsp-test.git] / src / Language / Haskell / LSP / Test / Parsing.hs
1 {-# LANGUAGE MultiParamTypeClasses #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
3 {-# LANGUAGE RankNTypes #-}
4 {-# LANGUAGE OverloadedStrings #-}
5
6 module Language.Haskell.LSP.Test.Parsing
7   ( -- $receiving
8     satisfy
9   , message
10   , anyRequest
11   , anyResponse
12   , anyNotification
13   , anyMessage
14   , loggingNotification
15   , publishDiagnosticsNotification
16   , responseForId
17   ) where
18
19 import Control.Applicative
20 import Control.Concurrent
21 import Control.Lens
22 import Control.Monad.IO.Class
23 import Control.Monad
24 import Data.Aeson
25 import qualified Data.ByteString.Lazy.Char8 as B
26 import Data.Conduit.Parser hiding (named)
27 import qualified Data.Conduit.Parser (named)
28 import qualified Data.Text as T
29 import Data.Typeable
30 import Language.Haskell.LSP.Messages
31 import Language.Haskell.LSP.Types
32 import qualified Language.Haskell.LSP.Types.Lens as LSP
33 import Language.Haskell.LSP.Test.Messages
34 import Language.Haskell.LSP.Test.Session
35
36 -- $receiving
37 -- To receive a message, just specify the type that expect:
38 --
39 -- @
40 -- msg1 <- message :: Session ApplyWorkspaceEditRequest
41 -- msg2 <- message :: Session HoverResponse
42 -- @
43 --
44 -- 'Language.Haskell.LSP.Test.Session' is actually just a parser
45 -- that operates on messages under the hood. This means that you
46 -- can create and combine parsers to match speicifc sequences of
47 -- messages that you expect.
48 --
49 -- For example, if you wanted to match either a definition or
50 -- references request:
51 --
52 -- > defOrImpl = (message :: Session DefinitionRequest)
53 -- >          <|> (message :: Session ReferencesRequest)
54 --
55 -- If you wanted to match any number of telemetry
56 -- notifications immediately followed by a response:
57 --
58 -- @
59 -- logThenDiags =
60 --  skipManyTill (message :: Session TelemetryNotification)
61 --               anyResponse
62 -- @
63
64 -- | Consumes and returns the next message, if it satisfies the specified predicate.
65 --
66 -- @since 0.5.2.0
67 satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
68 satisfy pred = satisfyMaybe (\msg -> if pred msg then Just msg else Nothing)
69
70 -- | Consumes and returns the result of the specified predicate if it returns `Just`.
71 --
72 -- @since 0.6.1.0
73 satisfyMaybe :: (FromServerMessage -> Maybe a) -> Session a
74 satisfyMaybe pred = do
75
76   skipTimeout <- overridingTimeout <$> get
77   timeoutId <- curTimeoutId <$> get
78   unless skipTimeout $ do
79     chan <- asks messageChan
80     timeout <- asks (messageTimeout . config)
81     void $ liftIO $ forkIO $ do
82       threadDelay (timeout * 1000000)
83       writeChan chan (TimeoutMessage timeoutId)
84
85   x <- Session await
86
87   unless skipTimeout $
88     modify $ \s -> s { curTimeoutId = timeoutId + 1 }
89
90   modify $ \s -> s { lastReceivedMessage = Just x }
91
92   case pred x of
93     Just a -> do
94       logMsg LogServer x
95       return a
96     Nothing -> empty
97
98 named :: T.Text -> Session a -> Session a
99 named s (Session x) = Session (Data.Conduit.Parser.named s x)
100
101 -- | Matches a message of type @a@.
102 message :: forall a. (Typeable a, FromJSON a) => Session a
103 message =
104   let parser = decode . encodeMsg :: FromServerMessage -> Maybe a
105   in named (T.pack $ show $ head $ snd $ splitTyConApp $ last $ typeRepArgs $ typeOf parser) $
106      satisfyMaybe parser
107
108 -- | Matches if the message is a notification.
109 anyNotification :: Session FromServerMessage
110 anyNotification = named "Any notification" $ satisfy isServerNotification
111
112 -- | Matches if the message is a request.
113 anyRequest :: Session FromServerMessage
114 anyRequest = named "Any request" $ satisfy isServerRequest
115
116 -- | Matches if the message is a response.
117 anyResponse :: Session FromServerMessage
118 anyResponse = named "Any response" $ satisfy isServerResponse
119
120 -- | Matches a response for a specific id.
121 responseForId :: forall a. FromJSON a => LspId -> Session (ResponseMessage a)
122 responseForId lid = named (T.pack $ "Response for id: " ++ show lid) $ do
123   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
124   satisfyMaybe $ \msg -> do
125     z <- parser msg
126     guard (z ^. LSP.id == responseId lid)
127     pure z
128
129 -- | Matches any type of message.
130 anyMessage :: Session FromServerMessage
131 anyMessage = satisfy (const True)
132
133 -- | A version of encode that encodes FromServerMessages as if they
134 -- weren't wrapped.
135 encodeMsg :: FromServerMessage -> B.ByteString
136 encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
137
138 -- | Matches if the message is a log message notification or a show message notification/request.
139 loggingNotification :: Session FromServerMessage
140 loggingNotification = named "Logging notification" $ satisfy shouldSkip
141   where
142     shouldSkip (NotLogMessage _) = True
143     shouldSkip (NotShowMessage _) = True
144     shouldSkip (ReqShowMessage _) = True
145     shouldSkip _ = False
146
147 -- | Matches a 'Language.Haskell.LSP.Test.PublishDiagnosticsNotification'
148 -- (textDocument/publishDiagnostics) notification.
149 publishDiagnosticsNotification :: Session PublishDiagnosticsNotification
150 publishDiagnosticsNotification = named "Publish diagnostics notification" $
151   satisfyMaybe $ \msg -> case msg of
152     NotPublishDiagnostics diags -> Just diags
153     _ -> Nothing