hls-tactics-plugin-1.4.0.0: Wingman plugin for Haskell Language Server
Safe HaskellNone
LanguageHaskell2010

Wingman.AbstractLSP.Types

Synopsis

Documentation

data Interaction where Source #

An Interaction is an existential Continuation, which handles both sides of the request/response interaction for LSP.

Constructors

Interaction :: (IsTarget target, IsContinuationSort sort, ToJSON b, FromJSON b) => Continuation sort target b -> Interaction 

data Metadata Source #

Metadata for a command. Used by both code actions and lenses, though for lenses, only md_title is currently used.

Constructors

Metadata 

Instances

Instances details
Eq Metadata Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Show Metadata Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

data SynthesizeCommand a b Source #

Whether we're defining a CodeAction or CodeLens.

class IsContinuationSort a where Source #

Transform a "continuation sort" into a CommandId.

Methods

toCommandId :: a -> CommandId Source #

data ContinuationResult Source #

Ways a Continuation can resolve.

Constructors

ErrorMessages [UserFacingMessage]

Produce some error messages.

RawEdit WorkspaceEdit

Produce an explicit WorkspaceEdit.

GraftEdit (Graft (Either String) ParsedSource)

Produce a Graft, corresponding to a transformation of the current AST.

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.

Constructors

Continuation 

Fields

data FileContext Source #

What file are we looking at, and what bit of it?

Constructors

FileContext 

Fields

Instances

Instances details
Eq FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Ord FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Show FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Generic FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Associated Types

type Rep FileContext :: Type -> Type #

ToJSON FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

FromJSON FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

type Rep FileContext Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

type Rep FileContext = D1 ('MetaData "FileContext" "Wingman.AbstractLSP.Types" "hls-tactics-plugin-1.4.0.0-CDY1FtnQAdCF6qnNiOOrMd" 'False) (C1 ('MetaCons "FileContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "fc_uri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Uri) :*: (S1 ('MetaSel ('Just "fc_nfp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NormalizedFilePath) :*: S1 ('MetaSel ('Just "fc_range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Tracked 'Current Range))))))

data LspEnv Source #

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.

Associated Types

type TargetArgs t Source #

Instances

Instances details
IsTarget HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Associated Types

type TargetArgs HoleTarget Source #

IsTarget EmptyCaseT Source # 
Instance details

Defined in Wingman.EmptyCase

Associated Types

type 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.

Constructors

HoleTarget 

Instances

Instances details
Bounded HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Enum HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Eq HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Ord HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Show HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

IsTarget HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Associated Types

type TargetArgs HoleTarget Source #

type TargetArgs HoleTarget Source # 
Instance details

Defined in Wingman.AbstractLSP.Types

Orphan instances