b6830357db5b32144f9629d900d5f42b91f64196
[lsp-test.git] / src / Language / Haskell / LSP / Test / Parsing.hs
1 {-# LANGUAGE MultiParamTypeClasses #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
3 {-# LANGUAGE RankNTypes #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 module Language.Haskell.LSP.Test.Parsing where
6
7 import Control.Applicative
8 import Control.Concurrent
9 import Control.Lens
10 import Control.Monad.IO.Class
11 import Control.Monad
12 import Data.Aeson
13 import qualified Data.ByteString.Lazy.Char8 as B
14 import Data.Conduit.Parser
15 import Data.Maybe
16 import qualified Data.Text as T
17 import Data.Typeable
18 import Language.Haskell.LSP.Messages
19 import Language.Haskell.LSP.Types as LSP hiding (error)
20 import Language.Haskell.LSP.Test.Messages
21 import Language.Haskell.LSP.Test.Session
22
23 satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
24 satisfy pred = do
25   
26   skipTimeout <- overridingTimeout <$> get
27   timeoutId <- curTimeoutId <$> get
28   unless skipTimeout $ do
29     chan <- asks messageChan
30     timeout <- asks (messageTimeout . config)
31     void $ liftIO $ forkIO $ do
32       threadDelay (timeout * 1000000)
33       writeChan chan (TimeoutMessage timeoutId)
34
35   x <- await
36
37   unless skipTimeout $
38     modify $ \s -> s { curTimeoutId = timeoutId + 1 }
39
40   modify $ \s -> s { lastReceivedMessage = Just x }
41
42   if pred x
43     then do
44       logMsg LogServer x
45       return x
46     else empty
47
48 -- | Matches a message of type 'a'.
49 message :: forall a. (Typeable a, FromJSON a) => Session a
50 message =
51   let parser = decode . encodeMsg :: FromServerMessage -> Maybe a
52   in named (T.pack $ show $ head $ snd $ splitTyConApp $ last $ typeRepArgs $ typeOf parser) $
53     castMsg <$> satisfy (isJust . parser)
54
55 -- | Matches if the message is a notification.
56 anyNotification :: Session FromServerMessage
57 anyNotification = named "Any notification" $ satisfy isServerNotification
58
59 -- | Matches if the message is a request.
60 anyRequest :: Session FromServerMessage
61 anyRequest = named "Any request" $ satisfy isServerRequest
62
63 -- | Matches if the message is a response.
64 anyResponse :: Session FromServerMessage
65 anyResponse = named "Any response" $ satisfy isServerResponse
66
67 responseForId :: forall a. FromJSON a => LspId -> Session (ResponseMessage a)
68 responseForId lid = named (T.pack $ "Response for id: " ++ show lid) $ do
69   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
70   x <- satisfy (maybe False (\z -> z ^. LSP.id == responseId lid) . parser)
71   return $ castMsg x
72
73 anyMessage :: Session FromServerMessage
74 anyMessage = satisfy (const True)
75
76 -- | A stupid method for getting out the inner message.
77 castMsg :: FromJSON a => FromServerMessage -> a
78 castMsg = fromMaybe (error "Failed casting a message") . decode . encodeMsg
79
80 -- | A version of encode that encodes FromServerMessages as if they
81 -- weren't wrapped.
82 encodeMsg :: FromServerMessage -> B.ByteString
83 encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
84
85 -- | Matches if the message is a log message notification or a show message notification/request.
86 loggingNotification :: Session FromServerMessage
87 loggingNotification = named "Logging notification" $ satisfy shouldSkip
88   where
89     shouldSkip (NotLogMessage _) = True
90     shouldSkip (NotShowMessage _) = True
91     shouldSkip (ReqShowMessage _) = True
92     shouldSkip _ = False
93
94 publishDiagnosticsNotification :: Session PublishDiagnosticsNotification
95 publishDiagnosticsNotification = named "Publish diagnostics notification" $ do
96   NotPublishDiagnostics diags <- satisfy test
97   return diags
98   where test (NotPublishDiagnostics _) = True
99         test _ = False