X-Git-Url: https://git.lukelau.me/?a=blobdiff_plain;f=src%2FLanguage%2FLSP%2FTest%2FParsing.hs;h=e55909f4c59fc9076c665d9b8f66811ae9981bb9;hb=7cef3a40e4774016c464d43b2a79c2bd6ef084d3;hp=26625b555111bbf554643baf3ad18690a632f17b;hpb=cf9e06e2eb79b113ff861866690f14166d1fa4e7;p=lsp-test.git diff --git a/src/Language/LSP/Test/Parsing.hs b/src/Language/LSP/Test/Parsing.hs index 26625b5..e55909f 100644 --- a/src/Language/LSP/Test/Parsing.hs +++ b/src/Language/LSP/Test/Parsing.hs @@ -2,9 +2,9 @@ {-# LANGUAGE EmptyCase #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeInType #-} {-# LANGUAGE KindSignatures #-} -{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeInType #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE RankNTypes #-} @@ -110,7 +110,7 @@ named s (Session x) = Session (Data.Conduit.Parser.named s x) -- | Matches a request or a notification coming from the server. message :: SServerMethod m -> Session (ServerMessage m) -message m1 = named (T.pack $ show m1) $ satisfyMaybe $ \case +message m1 = named (T.pack $ "Request for: " <> show m1) $ satisfyMaybe $ \case FromServerMess m2 msg -> do HRefl <- mEqServer m1 m2 pure msg @@ -161,7 +161,7 @@ anyResponse = named "Any response" $ satisfy $ \case -- | Matches a response coming from the server. response :: SMethod (m :: Method FromClient Request) -> Session (ResponseMessage m) -response m1 = named (T.pack $ show m1) $ satisfyMaybe $ \case +response m1 = named (T.pack $ "Response for: " <> show m1) $ satisfyMaybe $ \case FromServerRsp m2 msg -> do HRefl <- mEqClient m1 m2 pure msg @@ -198,9 +198,9 @@ loggingNotification = named "Logging notification" $ satisfy shouldSkip shouldSkip (FromServerMess SWindowShowMessageRequest _) = True shouldSkip _ = False --- | Matches a 'Language.LSP.Test.PublishDiagnosticsNotification' +-- | Matches a 'Language.LSP.Types.TextDocumentPublishDiagnostics' -- (textDocument/publishDiagnostics) notification. -publishDiagnosticsNotification :: Session PublishDiagnosticsNotification +publishDiagnosticsNotification :: Session (Message TextDocumentPublishDiagnostics) publishDiagnosticsNotification = named "Publish diagnostics notification" $ satisfyMaybe $ \msg -> case msg of FromServerMess STextDocumentPublishDiagnostics diags -> Just diags