36349dae864f4fbd63aa82c6016d87da1bd52084
[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 import System.Console.ANSI
23
24 satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
25 satisfy pred = do
26   
27   skipTimeout <- overridingTimeout <$> get
28   timeoutId <- curTimeoutId <$> get
29   unless skipTimeout $ do
30     chan <- asks messageChan
31     timeout <- asks (messageTimeout . config)
32     void $ liftIO $ forkIO $ do
33       threadDelay (timeout * 1000000)
34       writeChan chan (TimeoutMessage timeoutId)
35
36   x <- await
37
38   unless skipTimeout $
39     modify $ \s -> s { curTimeoutId = timeoutId + 1 }
40
41   modify $ \s -> s { lastReceivedMessage = Just x }
42
43   if pred x
44     then do
45       liftIO $ do
46         setSGR [SetColor Foreground Vivid Magenta]
47         putStrLn $ "<-- " ++ B.unpack (encodeMsg x)
48         setSGR [Reset]
49       return x
50     else empty
51
52 -- | Matches a message of type 'a'.
53 message :: forall a. (Typeable a, FromJSON a) => Session a
54 message =
55   let parser = decode . encodeMsg :: FromServerMessage -> Maybe a
56   in named (T.pack $ show $ head $ snd $ splitTyConApp $ last $ typeRepArgs $ typeOf parser) $
57     castMsg <$> satisfy (isJust . parser)
58
59 -- | Matches if the message is a notification.
60 anyNotification :: Session FromServerMessage
61 anyNotification = named "Any notification" $ satisfy isServerNotification
62
63 -- | Matches if the message is a request.
64 anyRequest :: Session FromServerMessage
65 anyRequest = named "Any request" $ satisfy isServerRequest
66
67 -- | Matches if the message is a response.
68 anyResponse :: Session FromServerMessage
69 anyResponse = named "Any response" $ satisfy isServerResponse
70
71 responseForId :: forall a. FromJSON a => LspId -> Session (ResponseMessage a)
72 responseForId lid = named (T.pack $ "Response for id: " ++ show lid) $ do
73   let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
74   x <- satisfy (maybe False (\z -> z ^. LSP.id == responseId lid) . parser)
75   return $ castMsg x
76
77 anyMessage :: Session FromServerMessage
78 anyMessage = satisfy (const True)
79
80 -- | A stupid method for getting out the inner message.
81 castMsg :: FromJSON a => FromServerMessage -> a
82 castMsg = fromMaybe (error "Failed casting a message") . decode . encodeMsg
83
84 -- | A version of encode that encodes FromServerMessages as if they
85 -- weren't wrapped.
86 encodeMsg :: FromServerMessage -> B.ByteString
87 encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
88
89 -- | Matches if the message is a log message notification or a show message notification/request.
90 loggingNotification :: Session FromServerMessage
91 loggingNotification = named "Logging notification" $ satisfy shouldSkip
92   where
93     shouldSkip (NotLogMessage _) = True
94     shouldSkip (NotShowMessage _) = True
95     shouldSkip (ReqShowMessage _) = True
96     shouldSkip _ = False
97
98 publishDiagnosticsNotification :: Session PublishDiagnosticsNotification
99 publishDiagnosticsNotification = named "Publish diagnostics notification" $ do
100   NotPublishDiagnostics diags <- satisfy test
101   return diags
102   where test (NotPublishDiagnostics _) = True
103         test _ = False