X-Git-Url: https://git.lukelau.me/?p=lsp-test.git;a=blobdiff_plain;f=src%2FLanguage%2FHaskell%2FLSP%2FTest.hs;h=81bdc8a8b465087baa960fbc6b1303e8497fcff7;hp=1a3b2e2ad7098511fc9a27ce67480ac6f2adcd95;hb=a7fd35b1582f9816d8caa90a7b2e3aa765fb0446;hpb=a7b6c9f03f4878ded66c71ff30529b77110efcb4 diff --git a/src/Language/Haskell/LSP/Test.hs b/src/Language/Haskell/LSP/Test.hs index 1a3b2e2..81bdc8a 100644 --- a/src/Language/Haskell/LSP/Test.hs +++ b/src/Language/Haskell/LSP/Test.hs @@ -41,8 +41,8 @@ module Language.Haskell.LSP.Test -- ** Initialization , initializeResponse -- ** Documents + , createDoc , openDoc - , openDoc' , closeDoc , changeDoc , documentContents @@ -82,6 +82,8 @@ module Language.Haskell.LSP.Test , applyEdit -- ** Code lenses , getCodeLenses + -- ** Capabilities + , getRegisteredCapabilities ) where import Control.Applicative.Combinators @@ -90,12 +92,13 @@ import Control.Monad import Control.Monad.IO.Class import Control.Exception import Control.Lens hiding ((.=), List) +import qualified Data.Map.Strict as Map import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Aeson import Data.Default import qualified Data.HashMap.Strict as HashMap -import qualified Data.Map as Map +import Data.List import Data.Maybe import Language.Haskell.LSP.Types import Language.Haskell.LSP.Types.Lens hiding @@ -110,10 +113,11 @@ import Language.Haskell.LSP.Test.Exceptions import Language.Haskell.LSP.Test.Parsing import Language.Haskell.LSP.Test.Session import Language.Haskell.LSP.Test.Server +import System.Environment import System.IO import System.Directory import System.FilePath -import qualified Data.Rope.UTF16 as Rope +import qualified System.FilePath.Glob as Glob -- | Starts a new session. -- @@ -137,10 +141,12 @@ runSessionWithConfig :: SessionConfig -- ^ Configuration options for the session -> FilePath -- ^ The filepath to the root directory for the session. -> Session a -- ^ The session to run. -> IO a -runSessionWithConfig config serverExe caps rootDir session = do +runSessionWithConfig config' serverExe caps rootDir session = do pid <- getCurrentProcessID absRootDir <- canonicalizePath rootDir + config <- envOverrideConfig config' + let initializeParams = InitializeParams (Just pid) (Just $ T.pack absRootDir) (Just $ filePathToUri absRootDir) @@ -151,9 +157,16 @@ runSessionWithConfig config serverExe caps rootDir session = do withServer serverExe (logStdErr config) $ \serverIn serverOut serverProc -> runSessionWithHandles serverIn serverOut serverProc listenServer config caps rootDir exitServer $ do -- Wrap the session around initialize and shutdown calls - initRspMsg <- request Initialize initializeParams :: Session InitializeResponse + -- initRspMsg <- sendRequest Initialize initializeParams :: Session InitializeResponse + initReqId <- sendRequest Initialize initializeParams + + -- Because messages can be sent in between the request and response, + -- collect them and then... + (inBetween, initRspMsg) <- manyTill_ anyMessage (responseForId initReqId) - liftIO $ maybe (return ()) (putStrLn . ("Error while initializing: " ++) . show ) (initRspMsg ^. LSP.error) + case initRspMsg ^. LSP.result of + Left error -> liftIO $ putStrLn ("Error while initializing: " ++ show error) + Right _ -> pure () initRspVar <- initRsp <$> ask liftIO $ putMVar initRspVar initRspMsg @@ -163,6 +176,12 @@ runSessionWithConfig config serverExe caps rootDir session = do Just cfg -> sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams cfg) Nothing -> return () + -- ... relay them back to the user Session so they can match on them! + -- As long as they are allowed. + forM_ inBetween checkLegalBetweenMessage + msgChan <- asks messageChan + liftIO $ writeList2Chan msgChan (ServerMessage <$> inBetween) + -- Run the actual test session where @@ -185,12 +204,33 @@ runSessionWithConfig config serverExe caps rootDir session = do (RspShutdown _) -> return () _ -> listenServer serverOut context + -- | Is this message allowed to be sent by the server between the intialize + -- request and response? + -- https://microsoft.github.io/language-server-protocol/specifications/specification-3-15/#initialize + checkLegalBetweenMessage :: FromServerMessage -> Session () + checkLegalBetweenMessage (NotShowMessage _) = pure () + checkLegalBetweenMessage (NotLogMessage _) = pure () + checkLegalBetweenMessage (NotTelemetry _) = pure () + checkLegalBetweenMessage (ReqShowMessage _) = pure () + checkLegalBetweenMessage msg = throw (IllegalInitSequenceMessage msg) + + -- | Check environment variables to override the config + envOverrideConfig :: SessionConfig -> IO SessionConfig + envOverrideConfig cfg = do + logMessages' <- fromMaybe (logMessages cfg) <$> checkEnv "LSP_TEST_LOG_MESSAGES" + logStdErr' <- fromMaybe (logStdErr cfg) <$> checkEnv "LSP_TEST_LOG_STDERR" + return $ cfg { logMessages = logMessages', logStdErr = logStdErr' } + where checkEnv :: String -> IO (Maybe Bool) + checkEnv s = fmap convertVal <$> lookupEnv s + convertVal "0" = False + convertVal _ = True + -- | The current text contents of a document. documentContents :: TextDocumentIdentifier -> Session T.Text documentContents doc = do vfs <- vfs <$> get let file = vfsMap vfs Map.! toNormalizedUri (doc ^. uri) - return $ Rope.toText $ Language.Haskell.LSP.VFS._text file + return (virtualFileText file) -- | Parses an ApplyEditRequest, checks that it is for the passed document -- and returns the new content @@ -309,7 +349,61 @@ sendResponse = sendMessage initializeResponse :: Session InitializeResponse initializeResponse = initRsp <$> ask >>= (liftIO . readMVar) --- | Opens a text document and sends a notification to the client. +-- | /Creates/ a new text document. This is different from 'openDoc' +-- as it sends a workspace/didChangeWatchedFiles notification letting the server +-- know that a file was created within the workspace, __provided that the server +-- has registered for it__, and the file matches any patterns the server +-- registered for. +-- It /does not/ actually create a file on disk, but is useful for convincing +-- the server that one does exist. +-- +-- @since 11.0.0.0 +createDoc :: FilePath -- ^ The path to the document to open, __relative to the root directory__. + -> String -- ^ The text document's language identifier, e.g. @"haskell"@. + -> T.Text -- ^ The content of the text document to create. + -> Session TextDocumentIdentifier -- ^ The identifier of the document just created. +createDoc file languageId contents = do + dynCaps <- curDynCaps <$> get + rootDir <- asks rootDir + caps <- asks sessionCapabilities + absFile <- liftIO $ canonicalizePath (rootDir file) + let regs = filter (\r -> r ^. method == WorkspaceDidChangeWatchedFiles) $ + Map.elems dynCaps + watchHits :: FileSystemWatcher -> Bool + watchHits (FileSystemWatcher pattern kind) = + -- If WatchKind is exlcuded, defaults to all true as per spec + fileMatches pattern && createHits (fromMaybe (WatchKind True True True) kind) + + fileMatches pattern = Glob.match (Glob.compile pattern) relOrAbs + -- If the pattern is absolute then match against the absolute fp + where relOrAbs + | isAbsolute pattern = absFile + | otherwise = file + + createHits (WatchKind create _ _) = create + + regHits :: Registration -> Bool + regHits reg = isJust $ do + opts <- reg ^. registerOptions + fileWatchOpts <- case fromJSON opts :: Result DidChangeWatchedFilesRegistrationOptions of + Success x -> Just x + Error _ -> Nothing + if foldl' (\acc w -> acc || watchHits w) False (fileWatchOpts ^. watchers) + then Just () + else Nothing + + clientCapsSupports = + caps ^? workspace . _Just . didChangeWatchedFiles . _Just . dynamicRegistration . _Just + == Just True + shouldSend = clientCapsSupports && foldl' (\acc r -> acc || regHits r) False regs + + when shouldSend $ + sendNotification WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $ + List [ FileEvent (filePathToUri (rootDir file)) FcCreated ] + openDoc' file languageId contents + +-- | Opens a text document that /exists on disk/, and sends a +-- textDocument/didOpen notification to the server. openDoc :: FilePath -> String -> Session TextDocumentIdentifier openDoc file languageId = do context <- ask @@ -318,6 +412,7 @@ openDoc file languageId = do openDoc' file languageId contents -- | This is a variant of `openDoc` that takes the file content as an argument. +-- Use this is the file exists /outside/ of the current workspace. openDoc' :: FilePath -> String -> T.Text -> Session TextDocumentIdentifier openDoc' file languageId contents = do context <- ask @@ -327,13 +422,13 @@ openDoc' file languageId contents = do sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams item) pure $ TextDocumentIdentifier uri --- | Closes a text document and sends a notification to the client. +-- | Closes a text document and sends a textDocument/didOpen notification to the server. closeDoc :: TextDocumentIdentifier -> Session () closeDoc docId = do let params = DidCloseTextDocumentParams (TextDocumentIdentifier (docId ^. uri)) sendNotification TextDocumentDidClose params --- | Changes a text document and sends a notification to the client +-- | Changes a text document and sends a textDocument/didOpen notification to the server. changeDoc :: TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> Session () changeDoc docId changes = do verDoc <- getVersionedDoc docId @@ -378,12 +473,11 @@ noDiagnostics = do -- | Returns the symbols in a document. getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [DocumentSymbol] [SymbolInformation]) getDocumentSymbols doc = do - ResponseMessage _ rspLid mRes mErr <- request TextDocumentDocumentSymbol (DocumentSymbolParams doc Nothing) :: Session DocumentSymbolsResponse - maybe (return ()) (throw . UnexpectedResponseError rspLid) mErr - case mRes of - Just (DSDocumentSymbols (List xs)) -> return (Left xs) - Just (DSSymbolInformation (List xs)) -> return (Right xs) - Nothing -> Prelude.error "No result and no error in DocumentSymbolsResponse" + ResponseMessage _ rspLid res <- request TextDocumentDocumentSymbol (DocumentSymbolParams doc Nothing) :: Session DocumentSymbolsResponse + case res of + Right (DSDocumentSymbols (List xs)) -> return (Left xs) + Right (DSSymbolInformation (List xs)) -> return (Right xs) + Left err -> throw (UnexpectedResponseError rspLid err) -- | Returns the code actions in the specified range. getCodeActions :: TextDocumentIdentifier -> Range -> Session [CAResult] @@ -392,8 +486,8 @@ getCodeActions doc range = do rsp <- request TextDocumentCodeAction (CodeActionParams doc range ctx Nothing) case rsp ^. result of - Just (List xs) -> return xs - _ -> throw (UnexpectedResponseError (rsp ^. LSP.id) (fromJust $ rsp ^. LSP.error)) + Right (List xs) -> return xs + Left error -> throw (UnexpectedResponseError (rsp ^. LSP.id) error) -- | Returns all the code actions in a document by -- querying the code actions at each of the current @@ -407,13 +501,11 @@ getAllCodeActions doc = do where go :: CodeActionContext -> [CAResult] -> Diagnostic -> Session [CAResult] go ctx acc diag = do - ResponseMessage _ rspLid mRes mErr <- request TextDocumentCodeAction (CodeActionParams doc (diag ^. range) ctx Nothing) + ResponseMessage _ rspLid res <- request TextDocumentCodeAction (CodeActionParams doc (diag ^. range) ctx Nothing) - case mErr of - Just e -> throw (UnexpectedResponseError rspLid e) - Nothing -> - let Just (List cmdOrCAs) = mRes - in return (acc ++ cmdOrCAs) + case res of + Left e -> throw (UnexpectedResponseError rspLid e) + Right (List cmdOrCAs) -> pure (acc ++ cmdOrCAs) getCodeActionContext :: TextDocumentIdentifier -> Session CodeActionContext getCodeActionContext doc = do @@ -547,9 +639,10 @@ getHighlights doc pos = -- | Checks the response for errors and throws an exception if needed. -- Returns the result if successful. getResponseResult :: ResponseMessage a -> a -getResponseResult rsp = fromMaybe exc (rsp ^. result) - where exc = throw $ UnexpectedResponseError (rsp ^. LSP.id) - (fromJust $ rsp ^. LSP.error) +getResponseResult rsp = + case rsp ^. result of + Right x -> x + Left err -> throw $ UnexpectedResponseError (rsp ^. LSP.id) err -- | Applies formatting to the specified document. formatDoc :: TextDocumentIdentifier -> FormattingOptions -> Session () @@ -577,3 +670,10 @@ getCodeLenses tId = do rsp <- request TextDocumentCodeLens (CodeLensParams tId Nothing) :: Session CodeLensResponse case getResponseResult rsp of List res -> pure res + +-- | Returns a list of capabilities that the server has requested to /dynamically/ +-- register during the 'Session'. +-- +-- @since 0.11.0.0 +getRegisteredCapabilities :: Session [Registration] +getRegisteredCapabilities = (Map.elems . curDynCaps) <$> get \ No newline at end of file