Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Interaction where
- Interaction :: (IsTarget target, IsContinuationSort sort, ToJSON b, FromJSON b) => Continuation sort target b -> Interaction
- data Metadata = Metadata {}
- data SynthesizeCommand a b
- = SynthesizeCodeAction (LspEnv -> TargetArgs a -> MaybeT (LspM Config) [(Metadata, b)])
- | SynthesizeCodeLens (LspEnv -> TargetArgs a -> MaybeT (LspM Config) [(Range, Metadata, b)])
- class IsContinuationSort a where
- toCommandId :: a -> CommandId
- data ContinuationResult
- data Continuation sort target payload = Continuation {
- c_sort :: sort
- c_makeCommand :: SynthesizeCommand target payload
- c_runCommand :: LspEnv -> TargetArgs target -> FileContext -> payload -> MaybeT (LspM Config) [ContinuationResult]
- data FileContext = FileContext {}
- data LspEnv = LspEnv {}
- class IsTarget t where
- type TargetArgs t
- fetchTargetArgs :: LspEnv -> MaybeT (LspM Config) (TargetArgs t)
- data HoleTarget = HoleTarget
- getNfp :: Applicative m => Uri -> MaybeT m NormalizedFilePath
Documentation
data Interaction where Source #
An Interaction
is an existential Continuation
, which handles both
sides of the request/response interaction for LSP.
Interaction :: (IsTarget target, IsContinuationSort sort, ToJSON b, FromJSON b) => Continuation sort target b -> Interaction |
Metadata for a command. Used by both code actions and lenses, though for
lenses, only md_title
is currently used.
Metadata | |
|
Instances
data SynthesizeCommand a b Source #
Whether we're defining a CodeAction or CodeLens.
SynthesizeCodeAction (LspEnv -> TargetArgs a -> MaybeT (LspM Config) [(Metadata, b)]) | |
SynthesizeCodeLens (LspEnv -> TargetArgs a -> MaybeT (LspM Config) [(Range, Metadata, b)]) |
class IsContinuationSort a where Source #
Transform a "continuation sort" into a CommandId
.
toCommandId :: a -> CommandId Source #
Instances
IsContinuationSort Text Source # | |
Defined in Wingman.AbstractLSP.Types toCommandId :: Text -> CommandId Source # | |
IsContinuationSort CommandId Source # | |
Defined in Wingman.AbstractLSP.Types toCommandId :: CommandId -> CommandId Source # | |
IsContinuationSort TacticCommand Source # | |
Defined in Wingman.LanguageServer.TacticProviders toCommandId :: TacticCommand -> CommandId Source # | |
IsContinuationSort EmptyCaseT Source # | |
Defined in Wingman.EmptyCase toCommandId :: EmptyCaseT -> CommandId Source # |
data ContinuationResult Source #
Ways a Continuation
can resolve.
ErrorMessages [UserFacingMessage] | Produce some error messages. |
RawEdit WorkspaceEdit | Produce an explicit |
GraftEdit (Graft (Either String) ParsedSource) | Produce a |
data Continuation sort target payload Source #
A Continuation
is a single object corresponding to an action that users
can take via LSP. It generalizes codeactions and codelenses, allowing for
a significant amount of code reuse.
Given Continuation sort target payload
:
the sort
corresponds to a CommandId
, allowing you to namespace actions
rather than working directly with text. This functionality is driven via
IsContinuationSort
.
the target
is used to fetch data from LSP on both sides of the
request/response barrier. For example, you can use it to resolve what node
in the AST the incoming range refers to. This functionality is driven via
IsTarget
.
the payload
is used for data you'd explicitly like to send from the
request to the response. It's like target
, but only gets computed once.
This is beneficial if you can do it, but requires that your data is
serializable via JSON.
Continuation | |
|
data FileContext Source #
What file are we looking at, and what bit of it?
Instances
Everything we need to resolve continuations.
class IsTarget t where Source #
Extract some information from LSP, so it can be passed to the requests and
responses of a Continuation
.
type TargetArgs t Source #
fetchTargetArgs :: LspEnv -> MaybeT (LspM Config) (TargetArgs t) Source #
Instances
IsTarget HoleTarget Source # | |
Defined in Wingman.AbstractLSP.Types type TargetArgs HoleTarget Source # fetchTargetArgs :: LspEnv -> MaybeT (LspM Config) (TargetArgs HoleTarget) Source # | |
IsTarget EmptyCaseT Source # | |
Defined in Wingman.EmptyCase type TargetArgs EmptyCaseT Source # fetchTargetArgs :: LspEnv -> MaybeT (LspM Config) (TargetArgs EmptyCaseT) Source # |
data HoleTarget Source #
A HoleTarget
is a target (see IsTarget
) which succeeds if the given
range is an HsExpr hole. It gives continuations access to the resulting
tactic judgement.
Instances
getNfp :: Applicative m => Uri -> MaybeT m NormalizedFilePath Source #