{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
module Language.Haskell.LSP.Test.Parsing
(
satisfy
, satisfyMaybe
, message
, anyRequest
, anyResponse
, anyNotification
, anyMessage
, loggingNotification
, publishDiagnosticsNotification
, responseForId
) where
import Control.Applicative
import Control.Concurrent
import Control.Lens
import Control.Monad.IO.Class
import Control.Monad
import Data.Aeson
import qualified Data.ByteString.Lazy.Char8 as B
import Data.Conduit.Parser hiding (named)
import qualified Data.Conduit.Parser (named)
import qualified Data.Text as T
import Data.Typeable
import Language.Haskell.LSP.Messages
import Language.Haskell.LSP.Types
import qualified Language.Haskell.LSP.Types.Lens as LSP
import Language.Haskell.LSP.Test.Messages
import Language.Haskell.LSP.Test.Session
satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
satisfy pred = satisfyMaybe (\msg -> if pred msg then Just msg else Nothing)
satisfyMaybe :: (FromServerMessage -> Maybe a) -> Session a
satisfyMaybe pred = do
skipTimeout <- overridingTimeout <$> get
timeoutId <- curTimeoutId <$> get
unless skipTimeout $ do
chan <- asks messageChan
timeout <- asks (messageTimeout . config)
void $ liftIO $ forkIO $ do
threadDelay (timeout * 1000000)
writeChan chan (TimeoutMessage timeoutId)
x <- Session await
unless skipTimeout $
modify $ \s -> s { curTimeoutId = timeoutId + 1 }
modify $ \s -> s { lastReceivedMessage = Just x }
case pred x of
Just a -> do
logMsg LogServer x
return a
Nothing -> empty
named :: T.Text -> Session a -> Session a
named s (Session x) = Session (Data.Conduit.Parser.named s x)
message :: forall a. (Typeable a, FromJSON a) => Session a
message =
let parser = decode . encodeMsg :: FromServerMessage -> Maybe a
in named (T.pack $ show $ head $ snd $ splitTyConApp $ last $ typeRepArgs $ typeOf parser) $
satisfyMaybe parser
anyNotification :: Session FromServerMessage
anyNotification = named "Any notification" $ satisfy isServerNotification
anyRequest :: Session FromServerMessage
anyRequest = named "Any request" $ satisfy isServerRequest
anyResponse :: Session FromServerMessage
anyResponse = named "Any response" $ satisfy isServerResponse
responseForId :: forall a. FromJSON a => LspId -> Session (ResponseMessage a)
responseForId lid = named (T.pack $ "Response for id: " ++ show lid) $ do
let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a)
satisfyMaybe $ \msg -> do
z <- parser msg
guard (z ^. LSP.id == responseId lid)
pure z
anyMessage :: Session FromServerMessage
anyMessage = satisfy (const True)
encodeMsg :: FromServerMessage -> B.ByteString
encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue })
loggingNotification :: Session FromServerMessage
loggingNotification = named "Logging notification" $ satisfy shouldSkip
where
shouldSkip (NotLogMessage _) = True
shouldSkip (NotShowMessage _) = True
shouldSkip (ReqShowMessage _) = True
shouldSkip _ = False
publishDiagnosticsNotification :: Session PublishDiagnosticsNotification
publishDiagnosticsNotification = named "Publish diagnostics notification" $
satisfyMaybe $ \msg -> case msg of
NotPublishDiagnostics diags -> Just diags
_ -> Nothing