Make URL absolute in workspace/didChangeWatchedFile
[lsp-test.git] / src / Language / Haskell / LSP / Test.hs
index c4b90fb944489828f718d173db11bb902bc1e822..81bdc8a8b465087baa960fbc6b1303e8497fcff7 100644 (file)
@@ -8,7 +8,7 @@ Module      : Language.Haskell.LSP.Test
 Description : A functional testing framework for LSP servers.
 Maintainer  : luke_lau@icloud.com
 Stability   : experimental
-Portability : POSIX
+Portability : non-portable
 
 Provides the framework to start functionally testing
 <https://github.com/Microsoft/language-server-protocol Language Server Protocol servers>.
@@ -37,11 +37,12 @@ module Language.Haskell.LSP.Test
   , module Language.Haskell.LSP.Test.Parsing
   -- * Utilities
   -- | Quick helper functions for common tasks.
+
   -- ** Initialization
   , initializeResponse
   -- ** Documents
+  , createDoc
   , openDoc
-  , openDoc'
   , closeDoc
   , changeDoc
   , documentContents
@@ -81,6 +82,8 @@ module Language.Haskell.LSP.Test
   , applyEdit
   -- ** Code lenses
   , getCodeLenses
+  -- ** Capabilities
+  , getRegisteredCapabilities
   ) where
 
 import Control.Applicative.Combinators
@@ -89,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
@@ -109,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.
 --
@@ -136,11 +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)
@@ -148,31 +154,43 @@ runSessionWithConfig config serverExe caps rootDir session = do
                                           caps
                                           (Just TraceOff)
                                           Nothing
-  withServer serverExe (logStdErr config) $ \serverIn serverOut _ ->
-    runSessionWithHandles serverIn serverOut (\h c -> listenServer h c) config caps rootDir $ 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
-
       sendNotification Initialized InitializedParams
 
       case lspConfig config of
         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
-      result <- session
-      return result
+      session
   where
-  -- | Listens to the server output, makes sure it matches the record and
-  -- signals any semaphores
-  -- Note that on Windows, we cannot kill a thread stuck in getNextMessage.
-  -- So we have to wait for the exit notification to kill the process first
-  -- and then getNextMessage will fail.
+  -- | Asks the server to shutdown and exit politely
+  exitServer :: Session ()
+  exitServer = request_ Shutdown (Nothing :: Maybe Value) >> sendNotification Exit ExitParams
+
+  -- | Listens to the server output until the shutdown ack,
+  -- makes sure it matches the record and signals any semaphores
   listenServer :: Handle -> SessionContext -> IO ()
   listenServer serverOut context = do
     msgBytes <- getNextMessage serverOut
@@ -182,14 +200,37 @@ runSessionWithConfig config serverExe caps rootDir session = do
     let msg = decodeFromServerMsg reqMap msgBytes
     writeChan (messageChan context) (ServerMessage msg)
 
-    listenServer serverOut context
+    case msg of
+      (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 = vfs Map.! toNormalizedUri (doc ^. uri)
-  return $ Rope.toText $ Language.Haskell.LSP.VFS._text file
+  let file = vfsMap vfs Map.! toNormalizedUri (doc ^. uri)
+  return (virtualFileText file)
 
 -- | Parses an ApplyEditRequest, checks that it is for the passed document
 -- and returns the new content
@@ -273,7 +314,7 @@ sendNotification TextDocumentDidOpen params = do
       n :: DidOpenTextDocumentNotification
       n = NotificationMessage "2.0" TextDocumentDidOpen params'
   oldVFS <- vfs <$> get
-  newVFS <- liftIO $ openVFS oldVFS n
+  let (newVFS,_) = openVFS oldVFS n
   modify (\s -> s { vfs = newVFS })
   sendMessage n
 
@@ -283,7 +324,7 @@ sendNotification TextDocumentDidClose params = do
       n :: DidCloseTextDocumentNotification
       n = NotificationMessage "2.0" TextDocumentDidClose params'
   oldVFS <- vfs <$> get
-  newVFS <- liftIO $ closeVFS oldVFS n
+  let (newVFS,_) = closeVFS oldVFS n
   modify (\s -> s { vfs = newVFS })
   sendMessage n
 
@@ -292,7 +333,7 @@ sendNotification TextDocumentDidChange params = do
         n :: DidChangeTextDocumentNotification
         n = NotificationMessage "2.0" TextDocumentDidChange params'
     oldVFS <- vfs <$> get
-    newVFS <- liftIO $ changeFromClientVFS oldVFS n
+    let (newVFS,_) = changeFromClientVFS oldVFS n
     modify (\s -> s { vfs = newVFS })
     sendMessage n
 
@@ -308,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
@@ -317,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
@@ -326,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
@@ -377,22 +473,21 @@ 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) :: 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]
 getCodeActions doc range = do
   ctx <- getCodeActionContext doc
-  rsp <- request TextDocumentCodeAction (CodeActionParams doc range ctx)
+  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
@@ -406,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)
+      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
@@ -428,7 +521,7 @@ getCurrentDiagnostics doc = fromMaybe [] . Map.lookup (toNormalizedUri $ doc ^.
 executeCommand :: Command -> Session ()
 executeCommand cmd = do
   let args = decode $ encode $ fromJust $ cmd ^. arguments
-      execParams = ExecuteCommandParams (cmd ^. command) args
+      execParams = ExecuteCommandParams (cmd ^. command) args Nothing
   request_ WorkspaceExecuteCommand execParams
 
 -- | Executes a code action.
@@ -449,10 +542,10 @@ executeCodeAction action = do
 -- | Adds the current version to the document, as tracked by the session.
 getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
 getVersionedDoc (TextDocumentIdentifier uri) = do
-  fs <- vfs <$> get
+  fs <- vfsMap . vfs <$> get
   let ver =
         case fs Map.!? toNormalizedUri uri of
-          Just (VirtualFile v _ _) -> Just v
+          Just vf -> Just (virtualFileVersion vf)
           _ -> Nothing
   return (VersionedTextDocumentIdentifier uri ver)
 
@@ -487,7 +580,7 @@ applyEdit doc edit = do
 -- | Returns the completions for the position in the document.
 getCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem]
 getCompletions doc pos = do
-  rsp <- request TextDocumentCompletion (TextDocumentPositionParams doc pos)
+  rsp <- request TextDocumentCompletion (TextDocumentPositionParams doc pos Nothing)
 
   case getResponseResult rsp of
     Completions (List items) -> return items
@@ -500,7 +593,7 @@ getReferences :: TextDocumentIdentifier -- ^ The document to lookup in.
               -> Session [Location] -- ^ The locations of the references.
 getReferences doc pos inclDecl =
   let ctx = ReferenceContext inclDecl
-      params = ReferenceParams doc pos ctx
+      params = ReferenceParams doc pos ctx Nothing
   in getResponseResult <$> request TextDocumentReferences params
 
 -- | Returns the definition(s) for the term at the specified position.
@@ -508,7 +601,7 @@ getDefinitions :: TextDocumentIdentifier -- ^ The document the term is in.
                -> Position -- ^ The position the term is at.
                -> Session [Location] -- ^ The location(s) of the definitions
 getDefinitions doc pos = do
-  let params = TextDocumentPositionParams doc pos
+  let params = TextDocumentPositionParams doc pos Nothing
   rsp <- request TextDocumentDefinition params :: Session DefinitionResponse
   case getResponseResult rsp of
       SingleLoc loc -> pure [loc]
@@ -519,13 +612,13 @@ getTypeDefinitions :: TextDocumentIdentifier -- ^ The document the term is in.
                -> Position -- ^ The position the term is at.
                -> Session [Location] -- ^ The location(s) of the definitions
 getTypeDefinitions doc pos =
-  let params = TextDocumentPositionParams doc pos
+  let params = TextDocumentPositionParams doc pos Nothing
   in getResponseResult <$> request TextDocumentTypeDefinition params
 
 -- | Renames the term at the specified position.
 rename :: TextDocumentIdentifier -> Position -> String -> Session ()
 rename doc pos newName = do
-  let params = RenameParams doc pos (T.pack newName)
+  let params = RenameParams doc pos (T.pack newName) Nothing
   rsp <- request TextDocumentRename params :: Session RenameResponse
   let wEdit = getResponseResult rsp
       req = RequestMessage "" (IdInt 0) WorkspaceApplyEdit (ApplyWorkspaceEditParams wEdit)
@@ -534,33 +627,34 @@ rename doc pos newName = do
 -- | Returns the hover information at the specified position.
 getHover :: TextDocumentIdentifier -> Position -> Session (Maybe Hover)
 getHover doc pos =
-  let params = TextDocumentPositionParams doc pos
+  let params = TextDocumentPositionParams doc pos Nothing
   in getResponseResult <$> request TextDocumentHover params
 
 -- | Returns the highlighted occurences of the term at the specified position
 getHighlights :: TextDocumentIdentifier -> Position -> Session [DocumentHighlight]
 getHighlights doc pos =
-  let params = TextDocumentPositionParams doc pos
+  let params = TextDocumentPositionParams doc pos Nothing
   in getResponseResult <$> request TextDocumentDocumentHighlight params
 
 -- | 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 ()
 formatDoc doc opts = do
-  let params = DocumentFormattingParams doc opts
+  let params = DocumentFormattingParams doc opts Nothing
   edits <- getResponseResult <$> request TextDocumentFormatting params
   applyTextEdits doc edits
 
 -- | Applies formatting to the specified range in a document.
 formatRange :: TextDocumentIdentifier -> FormattingOptions -> Range -> Session ()
 formatRange doc opts range = do
-  let params = DocumentRangeFormattingParams doc range opts
+  let params = DocumentRangeFormattingParams doc range opts Nothing
   edits <- getResponseResult <$> request TextDocumentRangeFormatting params
   applyTextEdits doc edits
 
@@ -573,6 +667,13 @@ applyTextEdits doc edits =
 -- | Returns the code lenses for the specified document.
 getCodeLenses :: TextDocumentIdentifier -> Session [CodeLens]
 getCodeLenses tId = do
-    rsp <- request TextDocumentCodeLens (CodeLensParams tId) :: Session CodeLensResponse
+    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