Skip to content

Commit 8ab6604

Browse files
authored
Merge pull request #504 from joyfulmantis/resolve-helper
Adds resolve helper functions to lsp-test
2 parents 7ad866f + 5fc619c commit 8ab6604

File tree

2 files changed

+68
-0
lines changed

2 files changed

+68
-0
lines changed

lsp-test/ChangeLog.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
# Revision history for lsp-test
22

3+
## 0.15.0.1
4+
5+
* Adds helper functions to resolve code lens, code actions, and completion items.
6+
37
## 0.15.0.0
48

59
* Support `lsp-types-2.0.0.0` and `lsp-2.0.0.0`.

lsp-test/src/Language/LSP/Test.hs

Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
{-# LANGUAGE ScopedTypeVariables #-}
88
{-# LANGUAGE ExistentialQuantification #-}
99
{-# LANGUAGE DuplicateRecordFields #-}
10+
{-# LANGUAGE LambdaCase #-}
1011

1112
{-|
1213
Module : Language.LSP.Test
@@ -69,10 +70,14 @@ module Language.LSP.Test
6970
, executeCommand
7071
-- ** Code Actions
7172
, getCodeActions
73+
, getAndResolveCodeActions
7274
, getAllCodeActions
7375
, executeCodeAction
76+
, resolveCodeAction
77+
, resolveAndExecuteCodeAction
7478
-- ** Completions
7579
, getCompletions
80+
, getAndResolveCompletions
7681
-- ** References
7782
, getReferences
7883
-- ** Definitions
@@ -93,6 +98,8 @@ module Language.LSP.Test
9398
, applyEdit
9499
-- ** Code lenses
95100
, getCodeLenses
101+
, getAndResolveCodeLenses
102+
, resolveCodeLens
96103
-- ** Call hierarchy
97104
, prepareCallHierarchy
98105
, incomingCalls
@@ -135,6 +142,7 @@ import System.FilePath
135142
import System.Process (ProcessHandle, CreateProcess)
136143
import qualified System.FilePath.Glob as Glob
137144
import Control.Monad.State (execState)
145+
import Data.Traversable (for)
138146

139147
-- | Starts a new session.
140148
--
@@ -530,6 +538,16 @@ getCodeActions doc range = do
530538
Right (InR _) -> return []
531539
Left error -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. L.id) error)
532540

541+
-- | Returns the code actions in the specified range, resolving any with
542+
-- a non empty _data_ field.
543+
getAndResolveCodeActions :: TextDocumentIdentifier -> Range -> Session [Command |? CodeAction]
544+
getAndResolveCodeActions doc range = do
545+
items <- getCodeActions doc range
546+
for items $ \case
547+
l@(InL _) -> pure l
548+
(InR r) | isJust (r ^. L.data_) -> InR <$> resolveCodeAction r
549+
r@(InR _) -> pure r
550+
533551
-- | Returns all the code actions in a document by
534552
-- querying the code actions at each of the current
535553
-- diagnostics' positions.
@@ -605,6 +623,22 @@ executeCodeAction action = do
605623
let req = TRequestMessage "" (IdInt 0) SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing e)
606624
in updateState (FromServerMess SMethod_WorkspaceApplyEdit req)
607625

626+
-- |Resolves the provided code action.
627+
resolveCodeAction :: CodeAction -> Session CodeAction
628+
resolveCodeAction ca = do
629+
rsp <- request SMethod_CodeActionResolve ca
630+
case rsp ^. L.result of
631+
Right ca -> return ca
632+
Left er -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. L.id) er)
633+
634+
-- |If a code action contains a _data_ field: resolves the code action, then
635+
-- executes it. Otherwise, just executes it.
636+
resolveAndExecuteCodeAction :: CodeAction -> Session ()
637+
resolveAndExecuteCodeAction ca@CodeAction{_data_=Just _} = do
638+
caRsp <- resolveCodeAction ca
639+
executeCodeAction caRsp
640+
resolveAndExecuteCodeAction ca = executeCodeAction ca
641+
608642
-- | Adds the current version to the document, as tracked by the session.
609643
getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
610644
getVersionedDoc (TextDocumentIdentifier uri) = do
@@ -648,6 +682,21 @@ getCompletions doc pos = do
648682
InR (InL c) -> return $ c ^. L.items
649683
InR (InR _) -> return []
650684

685+
-- | Returns the completions for the position in the document, resolving any with
686+
-- a non empty _data_ field.
687+
getAndResolveCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem]
688+
getAndResolveCompletions doc pos = do
689+
items <- getCompletions doc pos
690+
for items $ \item -> if isJust (item ^. L.data_) then resolveCompletion item else pure item
691+
692+
-- |Resolves the provided completion item.
693+
resolveCompletion :: CompletionItem -> Session CompletionItem
694+
resolveCompletion ci = do
695+
rsp <- request SMethod_CompletionItemResolve ci
696+
case rsp ^. L.result of
697+
Right ci -> return ci
698+
Left error -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. L.id) error)
699+
651700
-- | Returns the references for the position in the document.
652701
getReferences :: TextDocumentIdentifier -- ^ The document to lookup in.
653702
-> Position -- ^ The position to lookup.
@@ -749,6 +798,21 @@ getCodeLenses tId = do
749798
rsp <- request SMethod_TextDocumentCodeLens (CodeLensParams Nothing Nothing tId)
750799
pure $ absorbNull $ getResponseResult rsp
751800

801+
-- | Returns the code lenses for the specified document, resolving any with
802+
-- a non empty _data_ field.
803+
getAndResolveCodeLenses :: TextDocumentIdentifier -> Session [CodeLens]
804+
getAndResolveCodeLenses tId = do
805+
codeLenses <- getCodeLenses tId
806+
for codeLenses $ \codeLens -> if isJust (codeLens ^. L.data_) then resolveCodeLens codeLens else pure codeLens
807+
808+
-- |Resolves the provided code lens.
809+
resolveCodeLens :: CodeLens -> Session CodeLens
810+
resolveCodeLens cl = do
811+
rsp <- request SMethod_CodeLensResolve cl
812+
case rsp ^. L.result of
813+
Right cl -> return cl
814+
Left error -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. L.id) error)
815+
752816
-- | Pass a param and return the response from `prepareCallHierarchy`
753817
prepareCallHierarchy :: CallHierarchyPrepareParams -> Session [CallHierarchyItem]
754818
prepareCallHierarchy = resolveRequestWithListResp SMethod_TextDocumentPrepareCallHierarchy

0 commit comments

Comments
 (0)