Add getHighlights
[opengl.git] / src / Language / Haskell / LSP / Test.hs
index 427b6172674e0dce35ede6689e1c0b25b992aac5..e47109e03da0f1e83c84466423ad2fd2cd2262aa 100644 (file)
@@ -9,7 +9,9 @@
 -- Maintainer  : luke_lau@icloud.com
 -- Stability   : experimental
 --
--- A framework for testing <https://github.com/Microsoft/language-server-protocol Language Server Protocol servers> at the JSON level.
+-- A framework for testing
+-- <https://github.com/Microsoft/language-server-protocol Language Server Protocol servers>
+-- functionally.
 
 module Language.Haskell.LSP.Test
   (
@@ -39,25 +41,6 @@ module Language.Haskell.LSP.Test
   , loggingNotification
   , publishDiagnosticsNotification
   -- * Combinators
-  , choice
-  , option
-  , optional
-  , between
-  , some
-  , many
-  , sepBy
-  , sepBy1
-  , sepEndBy1
-  , sepEndBy
-  , endBy1
-  , endBy
-  , count
-  , manyTill
-  , skipMany
-  , skipSome
-  , skipManyTill
-  , skipSomeTill
-  , (<|>)
   , satisfy
   -- * Utilities
   , initializeResponse
@@ -71,6 +54,7 @@ module Language.Haskell.LSP.Test
   , getDocumentSymbols
   -- ** Diagnostics
   , waitForDiagnostics
+  , waitForDiagnosticsSource
   , noDiagnostics
   -- ** Commands
   , executeCommand
@@ -79,11 +63,20 @@ module Language.Haskell.LSP.Test
   , executeCodeAction
   -- ** Completions
   , getCompletions
+  -- ** References
+  , getReferences
+  -- ** Definitions
+  , getDefinitions
+  -- ** Renaming
+  , rename
+  -- ** Hover
+  , getHover
+  -- ** Highlights
+  , getHighlights
   -- ** Edits
   , applyEdit
   ) where
 
-import Control.Applicative
 import Control.Applicative.Combinators
 import Control.Concurrent
 import Control.Monad
@@ -326,6 +319,17 @@ waitForDiagnostics = do
   let (List diags) = diagsNot ^. params . LSP.diagnostics
   return diags
 
+waitForDiagnosticsSource :: String -> Session [Diagnostic]
+waitForDiagnosticsSource src = do
+  diags <- waitForDiagnostics
+  let res = filter matches diags
+  if null res
+    then waitForDiagnosticsSource src
+    else return res
+  where
+    matches :: Diagnostic -> Bool
+    matches d = d ^. source == Just (T.pack src)
+
 -- | Expects a 'PublishDiagnosticsNotification' and throws an
 -- 'UnexpectedDiagnosticsException' if there are any diagnostics
 -- returned.
@@ -428,9 +432,52 @@ getCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem]
 getCompletions doc pos = do
   rsp <- sendRequest TextDocumentCompletion (TextDocumentPositionParams doc pos)
 
-  let exc = throw $ UnexpectedResponseError (rsp ^. LSP.id)
-                                            (fromJust $ rsp ^. LSP.error)
-      res = fromMaybe exc (rsp ^. result)
-  case res of
+  case getResponseResult rsp of
     Completions (List items) -> return items
     CompletionList (CompletionListType _ (List items)) -> return items
+
+-- | Returns the references for the position in the document.
+getReferences :: TextDocumentIdentifier -- ^ The document to lookup in.
+              -> Position -- ^ The position to lookup. 
+              -> Bool -- ^ Whether to include declarations as references.
+              -> Session [Location] -- ^ The locations of the references.
+getReferences doc pos inclDecl =
+  let ctx = ReferenceContext inclDecl
+      params = ReferenceParams doc pos ctx
+  in getResponseResult <$> sendRequest 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 <$> sendRequest TextDocumentDefinition 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)
+  rsp <- sendRequest TextDocumentRename params :: Session RenameResponse
+  let wEdit = getResponseResult rsp
+      req = RequestMessage "" (IdInt 0) WorkspaceApplyEdit (ApplyWorkspaceEditParams wEdit)
+  updateState (ReqApplyWorkspaceEdit req)
+
+-- ^ Returns the hover information at the specified position.
+getHover :: TextDocumentIdentifier -> Position -> Session (Maybe Hover)
+getHover doc pos =
+  let params = TextDocumentPositionParams doc pos
+  in getResponseResult <$> sendRequest TextDocumentHover params
+
+getHighlights :: TextDocumentIdentifier -> Position -> Session [DocumentHighlight]
+getHighlights doc pos =
+  let params = TextDocumentPositionParams doc pos
+  in getResponseResult <$> sendRequest 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)
+