Track changes to haskell-lsp
[lsp-test.git] / src / Language / Haskell / LSP / Test.hs
index 04fcc21a7f9510a10f4acc0c0eb012a24321db21..151eef7f1687fa0a357058f00f92d425a962d437 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>.
@@ -23,7 +23,7 @@ module Language.Haskell.LSP.Test
   , runSessionWithConfig
   , SessionConfig(..)
   , defaultConfig
-  , module Language.Haskell.LSP.Types.Capabilities
+  , C.fullCaps
   -- ** Exceptions
   , module Language.Haskell.LSP.Test.Exceptions
   , withTimeout
@@ -41,7 +41,9 @@ module Language.Haskell.LSP.Test
   , initializeResponse
   -- ** Documents
   , openDoc
+  , openDoc'
   , closeDoc
+  , changeDoc
   , documentContents
   , getDocumentEdit
   , getDocUri
@@ -52,9 +54,11 @@ module Language.Haskell.LSP.Test
   , waitForDiagnostics
   , waitForDiagnosticsSource
   , noDiagnostics
+  , getCurrentDiagnostics
   -- ** Commands
   , executeCommand
   -- ** Code Actions
+  , getCodeActions
   , getAllCodeActions
   , executeCodeAction
   -- ** Completions
@@ -63,6 +67,7 @@ module Language.Haskell.LSP.Test
   , getReferences
   -- ** Definitions
   , getDefinitions
+  , getTypeDefinitions
   -- ** Renaming
   , rename
   -- ** Hover
@@ -74,6 +79,8 @@ module Language.Haskell.LSP.Test
   , formatRange
   -- ** Edits
   , applyEdit
+  -- ** Code lenses
+  , getCodeLenses
   ) where
 
 import Control.Applicative.Combinators
@@ -89,9 +96,11 @@ import Data.Default
 import qualified Data.HashMap.Strict as HashMap
 import qualified Data.Map as Map
 import Data.Maybe
-import Language.Haskell.LSP.Types hiding (id, capabilities, message)
-import qualified Language.Haskell.LSP.Types as LSP
-import Language.Haskell.LSP.Types.Capabilities
+import Language.Haskell.LSP.Types
+import Language.Haskell.LSP.Types.Lens hiding
+  (id, capabilities, message, executeCommand, applyEdit, rename)
+import qualified Language.Haskell.LSP.Types.Lens as LSP
+import qualified Language.Haskell.LSP.Types.Capabilities as C
 import Language.Haskell.LSP.Messages
 import Language.Haskell.LSP.VFS
 import Language.Haskell.LSP.Test.Compat
@@ -103,7 +112,7 @@ import Language.Haskell.LSP.Test.Server
 import System.IO
 import System.Directory
 import System.FilePath
-import qualified Yi.Rope as Rope
+import qualified Data.Rope.UTF16 as Rope
 
 -- | Starts a new session.
 --
@@ -114,7 +123,7 @@ import qualified Yi.Rope as Rope
 -- >       params = TextDocumentPositionParams doc
 -- >   hover <- request TextDocumentHover params
 runSession :: String -- ^ The command to run the server.
-           -> ClientCapabilities -- ^ The capabilities that the client should declare.
+           -> C.ClientCapabilities -- ^ The capabilities that the client should declare.
            -> FilePath -- ^ The filepath to the root directory for the session.
            -> Session a -- ^ The session to run.
            -> IO a
@@ -123,7 +132,7 @@ runSession = runSessionWithConfig def
 -- | Starts a new sesion with a custom configuration.
 runSessionWithConfig :: SessionConfig -- ^ Configuration options for the session.
                      -> String -- ^ The command to run the server.
-                     -> ClientCapabilities -- ^ The capabilities that the client should declare.
+                     -> C.ClientCapabilities -- ^ The capabilities that the client should declare.
                      -> FilePath -- ^ The filepath to the root directory for the session.
                      -> Session a -- ^ The session to run.
                      -> IO a
@@ -137,9 +146,9 @@ runSessionWithConfig config serverExe caps rootDir session = do
                                           Nothing
                                           caps
                                           (Just TraceOff)
-  withServer serverExe (logStdErr config) $ \serverIn serverOut _ ->
-    runSessionWithHandles serverIn serverOut listenServer config caps rootDir $ do
-
+                                          Nothing
+  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
 
@@ -147,18 +156,21 @@ runSessionWithConfig config serverExe caps rootDir session = do
 
       initRspVar <- initRsp <$> ask
       liftIO $ putMVar initRspVar initRspMsg
-
       sendNotification Initialized InitializedParams
 
-      -- Run the actual test
-      result <- session
+      case lspConfig config of
+        Just cfg -> sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams cfg)
+        Nothing -> return ()
 
-      sendNotification Exit ExitParams
-
-      return result
+      -- Run the actual test
+      session
   where
-  -- | Listens to the server output, makes sure it matches the record and
-  -- signals any semaphores
+  -- | 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
@@ -168,13 +180,15 @@ 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
 
 -- | The current text contents of a document.
 documentContents :: TextDocumentIdentifier -> Session T.Text
 documentContents doc = do
   vfs <- vfs <$> get
-  let file = vfs Map.! (doc ^. uri)
+  let file = vfsMap vfs Map.! toNormalizedUri (doc ^. uri)
   return $ Rope.toText $ Language.Haskell.LSP.VFS._text file
 
 -- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -259,7 +273,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
 
@@ -269,7 +283,16 @@ 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
+
+sendNotification TextDocumentDidChange params = do
+    let params' = fromJust $ decode $ encode params
+        n :: DidChangeTextDocumentNotification
+        n = NotificationMessage "2.0" TextDocumentDidChange params'
+    oldVFS <- vfs <$> get
+    let (newVFS,_) = changeFromClientVFS oldVFS n
     modify (\s -> s { vfs = newVFS })
     sendMessage n
 
@@ -288,19 +311,20 @@ initializeResponse = initRsp <$> ask >>= (liftIO . readMVar)
 -- | Opens a text document and sends a notification to the client.
 openDoc :: FilePath -> String -> Session TextDocumentIdentifier
 openDoc file languageId = do
-  item <- getDocItem file languageId
-  sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams item)
-  TextDocumentIdentifier <$> getDocUri file
-  where
-  -- | Reads in a text document as the first version.
-  getDocItem :: FilePath -- ^ The path to the text document to read in.
-            -> String -- ^ The language ID, e.g "haskell" for .hs files.
-            -> Session TextDocumentItem
-  getDocItem file languageId = do
   context <- ask
   let fp = rootDir context </> file
   contents <- liftIO $ T.readFile fp
-    return $ TextDocumentItem (filePathToUri fp) (T.pack languageId) 0 contents
+  openDoc' file languageId contents
+
+-- | This is a variant of `openDoc` that takes the file content as an argument.
+openDoc' :: FilePath -> String -> T.Text -> Session TextDocumentIdentifier
+openDoc' file languageId contents = do
+  context <- ask
+  let fp = rootDir context </> file
+      uri = filePathToUri fp
+      item = TextDocumentItem uri (T.pack languageId) 0 contents
+  sendNotification TextDocumentDidOpen (DidOpenTextDocumentParams item)
+  pure $ TextDocumentIdentifier uri
 
 -- | Closes a text document and sends a notification to the client.
 closeDoc :: TextDocumentIdentifier -> Session ()
@@ -308,10 +332,12 @@ closeDoc docId = do
   let params = DidCloseTextDocumentParams (TextDocumentIdentifier (docId ^. uri))
   sendNotification TextDocumentDidClose params
 
-  oldVfs <- vfs <$> get
-  let notif = NotificationMessage "" TextDocumentDidClose params
-  newVfs <- liftIO $ closeVFS oldVfs notif
-  modify $ \s -> s { vfs = newVfs }
+-- | Changes a text document and sends a notification to the client
+changeDoc :: TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> Session ()
+changeDoc docId changes = do
+  verDoc <- getVersionedDoc docId
+  let params = DidChangeTextDocumentParams (verDoc & version . non 0 +~ 1) (List changes)
+  sendNotification TextDocumentDidChange params
 
 -- | Gets the Uri for the file corrected to the session directory.
 getDocUri :: FilePath -> Session Uri
@@ -341,7 +367,7 @@ waitForDiagnosticsSource src = do
     matches d = d ^. source == Just (T.pack src)
 
 -- | Expects a 'PublishDiagnosticsNotification' and throws an
--- 'UnexpectedDiagnosticsException' if there are any diagnostics
+-- 'UnexpectedDiagnostics' exception if there are any diagnostics
 -- returned.
 noDiagnostics :: Session ()
 noDiagnostics = do
@@ -351,27 +377,36 @@ 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
+  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"
 
+-- | 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 Nothing)
+
+  case rsp ^. result of
+    Just (List xs) -> return xs
+    _ -> throw (UnexpectedResponseError (rsp ^. LSP.id) (fromJust $ rsp ^. LSP.error))
+
 -- | Returns all the code actions in a document by
 -- querying the code actions at each of the current
 -- diagnostics' positions.
 getAllCodeActions :: TextDocumentIdentifier -> Session [CAResult]
 getAllCodeActions doc = do
-  curDiags <- fromMaybe [] . Map.lookup (doc ^. uri) . curDiagnostics <$> get
-  let ctx = CodeActionContext (List curDiags) Nothing
+  ctx <- getCodeActionContext doc
 
-  foldM (go ctx) [] curDiags
+  foldM (go ctx) [] =<< getCurrentDiagnostics doc
 
   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 mRes mErr <- request TextDocumentCodeAction (CodeActionParams doc (diag ^. range) ctx Nothing)
 
       case mErr of
         Just e -> throw (UnexpectedResponseError rspLid e)
@@ -379,11 +414,21 @@ getAllCodeActions doc = do
           let Just (List cmdOrCAs) = mRes
             in return (acc ++ cmdOrCAs)
 
+getCodeActionContext :: TextDocumentIdentifier -> Session CodeActionContext
+getCodeActionContext doc = do
+  curDiags <- getCurrentDiagnostics doc
+  return $ CodeActionContext (List curDiags) Nothing
+
+-- | Returns the current diagnostics that have been sent to the client.
+-- Note that this does not wait for more to come in.
+getCurrentDiagnostics :: TextDocumentIdentifier -> Session [Diagnostic]
+getCurrentDiagnostics doc = fromMaybe [] . Map.lookup (toNormalizedUri $ doc ^. uri) . curDiagnostics <$> get
+
 -- | Executes a command.
 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.
@@ -404,10 +449,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.!? uri of
-          Just (VirtualFile v _) -> Just v
+        case fs Map.!? toNormalizedUri uri of
+          Just vf -> Just (virtualFileVersion vf)
           _ -> Nothing
   return (VersionedTextDocumentIdentifier uri ver)
 
@@ -420,9 +465,9 @@ applyEdit doc edit = do
   caps <- asks sessionCapabilities
 
   let supportsDocChanges = fromMaybe False $ do
-        let ClientCapabilities mWorkspace _ _ = caps
-        WorkspaceClientCapabilities _ mEdit _ _ _ _ _ _ <- mWorkspace
-        WorkspaceEditClientCapabilities mDocChanges <- mEdit
+        let mWorkspace = C._workspace caps
+        C.WorkspaceClientCapabilities _ mEdit _ _ _ _ _ _ <- mWorkspace
+        C.WorkspaceEditClientCapabilities mDocChanges <- mEdit
         mDocChanges
 
   let wEdit = if supportsDocChanges
@@ -442,7 +487,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
@@ -455,21 +500,32 @@ 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.
 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 =
-  let params = TextDocumentPositionParams doc pos
-  in getResponseResult <$> request TextDocumentDefinition params
+getDefinitions doc pos = do
+  let params = TextDocumentPositionParams doc pos Nothing
+  rsp <- request TextDocumentDefinition params :: Session DefinitionResponse
+  case getResponseResult rsp of
+      SingleLoc loc -> pure [loc]
+      MultiLoc locs -> pure locs
+
+-- | Returns the type definition(s) for the term at the specified position.
+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 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)
@@ -478,13 +534,13 @@ 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.
@@ -497,14 +553,14 @@ getResponseResult rsp = fromMaybe exc (rsp ^. result)
 -- | 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
 
@@ -513,3 +569,10 @@ applyTextEdits doc edits =
   let wEdit = WorkspaceEdit (Just (HashMap.singleton (doc ^. uri) edits)) Nothing
       req = RequestMessage "" (IdInt 0) WorkspaceApplyEdit (ApplyWorkspaceEditParams wEdit)
   in updateState (ReqApplyWorkspaceEdit req)
+
+-- | Returns the code lenses for the specified document.
+getCodeLenses :: TextDocumentIdentifier -> Session [CodeLens]
+getCodeLenses tId = do
+    rsp <- request TextDocumentCodeLens (CodeLensParams tId Nothing) :: Session CodeLensResponse
+    case getResponseResult rsp of
+        List res -> pure res