X-Git-Url: http://git.lukelau.me/?a=blobdiff_plain;f=src%2FLanguage%2FHaskell%2FLSP%2FTest%2FParsing.hs;h=614495b27e68c051249fa10beb0bef0e5a11b788;hb=d8e460543b7cbc32550bed20d20ef4b13d6705a5;hp=693c62e9aab0670e83001003803d72798cb2ec1f;hpb=5170a20560a68b8fcaed83ecaf6146d84a147992;p=lsp-test.git diff --git a/src/Language/Haskell/LSP/Test/Parsing.hs b/src/Language/Haskell/LSP/Test/Parsing.hs index 693c62e..614495b 100644 --- a/src/Language/Haskell/LSP/Test/Parsing.hs +++ b/src/Language/Haskell/LSP/Test/Parsing.hs @@ -1,77 +1,104 @@ {-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} +{-# LANGUAGE OverloadedStrings #-} module Language.Haskell.LSP.Test.Parsing where import Control.Applicative +import Control.Concurrent +import Control.Lens +import Control.Monad.IO.Class +import Control.Monad.Trans.Class import Data.Aeson import qualified Data.ByteString.Lazy.Char8 as B import Data.Conduit.Parser import Data.Maybe import Language.Haskell.LSP.Messages -import Language.Haskell.LSP.Types hiding (error) +import Language.Haskell.LSP.Types as LSP hiding (error) +import Language.Haskell.LSP.Test.Exceptions import Language.Haskell.LSP.Test.Messages +import Language.Haskell.LSP.Test.Session +import System.Console.ANSI + +satisfy :: (MonadIO m, MonadSessionConfig m) => (FromServerMessage -> Bool) -> ConduitParser FromServerMessage m FromServerMessage +satisfy pred = do + timeout <- timeout <$> lift sessionConfig + tId <- liftIO myThreadId + timeoutThread <- liftIO $ forkIO $ do + threadDelay (timeout * 1000000) + throwTo tId TimeoutException + x <- await + liftIO $ killThread timeoutThread + + if pred x + then do + liftIO $ do + setSGR [SetColor Foreground Vivid Magenta] + putStrLn $ "<-- " ++ B.unpack (encodeMsg x) + setSGR [Reset] + return x + else empty -- | Matches if the message is a notification. -anyNotification :: Monad m => ConduitParser FromServerMessage m FromServerMessage -anyNotification = satisfy isServerNotification +anyNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage +anyNotification = named "Any notification" $ satisfy isServerNotification -notification :: forall m a. (Monad m, FromJSON a) => ConduitParser FromServerMessage m (NotificationMessage ServerMethod a) -notification = do +notification :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => ConduitParser FromServerMessage m (NotificationMessage ServerMethod a) +notification = named "Notification" $ do let parser = decode . encodeMsg :: FromServerMessage -> Maybe (NotificationMessage ServerMethod a) x <- satisfy (isJust . parser) - return $ decodeMsg $ encodeMsg x + return $ castMsg x -- | Matches if the message is a request. -anyRequest :: Monad m => ConduitParser FromServerMessage m FromServerMessage -anyRequest = satisfy isServerRequest +anyRequest :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage +anyRequest = named "Any request" $ satisfy isServerRequest -request :: forall m a b. (Monad m, FromJSON a, FromJSON b) => ConduitParser FromServerMessage m (RequestMessage ServerMethod a b) -request = do +request :: forall m a b. (MonadIO m, MonadSessionConfig m, FromJSON a, FromJSON b) => ConduitParser FromServerMessage m (RequestMessage ServerMethod a b) +request = named "Request" $ do let parser = decode . encodeMsg :: FromServerMessage -> Maybe (RequestMessage ServerMethod a b) x <- satisfy (isJust . parser) - return $ decodeMsg $ encodeMsg x + return $ castMsg x -- | Matches if the message is a response. -anyResponse :: Monad m => ConduitParser FromServerMessage m FromServerMessage -anyResponse = satisfy isServerResponse +anyResponse :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage +anyResponse = named "Any response" $ satisfy isServerResponse -response :: forall m a. (Monad m, FromJSON a) => ConduitParser FromServerMessage m (ResponseMessage a) -response = do +response :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => ConduitParser FromServerMessage m (ResponseMessage a) +response = named "Response" $ do let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a) x <- satisfy (isJust . parser) - return $ decodeMsg $ encodeMsg x + return $ castMsg x + +responseForId :: forall m a. (MonadIO m, MonadSessionConfig m, FromJSON a) => LspId -> ConduitParser FromServerMessage m (ResponseMessage a) +responseForId lid = named "Response for id" $ do + let parser = decode . encodeMsg :: FromServerMessage -> Maybe (ResponseMessage a) + x <- satisfy (maybe False (\z -> z ^. LSP.id == responseId lid) . parser) + return $ castMsg x + +anyMessage :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage +anyMessage = satisfy (const True) + +-- | A stupid method for getting out the inner message. +castMsg :: FromJSON a => FromServerMessage -> a +castMsg = fromMaybe (error "Failed casting a message") . decode . encodeMsg -- | A version of encode that encodes FromServerMessages as if they -- weren't wrapped. encodeMsg :: FromServerMessage -> B.ByteString encodeMsg = encode . genericToJSON (defaultOptions { sumEncoding = UntaggedValue }) -decodeMsg :: FromJSON a => B.ByteString -> a -decodeMsg x = fromMaybe (error $ "Unexpected message type\nGot:\n " ++ show x) - (decode x) - -- | Matches if the message is a log message notification or a show message notification/request. -loggingNotification :: Monad m => ConduitParser FromServerMessage m FromServerMessage -loggingNotification = satisfy shouldSkip +loggingNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m FromServerMessage +loggingNotification = named "Logging notification" $ satisfy shouldSkip where shouldSkip (NotLogMessage _) = True shouldSkip (NotShowMessage _) = True shouldSkip (ReqShowMessage _) = True shouldSkip _ = False -publishDiagnosticsNotification :: Monad m => ConduitParser FromServerMessage m PublishDiagnosticsNotification -publishDiagnosticsNotification = do +publishDiagnosticsNotification :: (MonadIO m, MonadSessionConfig m) => ConduitParser FromServerMessage m PublishDiagnosticsNotification +publishDiagnosticsNotification = named "Publish diagnostics notification" $ do NotPublishDiagnostics diags <- satisfy test return diags where test (NotPublishDiagnostics _) = True test _ = False \ No newline at end of file - -satisfy :: Monad m => (a -> Bool) -> ConduitParser a m a -satisfy pred = do - x <- await - if pred x - then return x - else empty -