ghcide-2.0.0.0: The core of an IDE
Safe HaskellSafe-Inferred
LanguageHaskell2010

Development.IDE.Plugin.Completions.Types

Synopsis

Documentation

data CompletionResolveData Source #

The data that is acutally sent for resolve support We need the URI to be able to reconstruct the GHC environment in the file the completion was triggered in.

Constructors

CompletionResolveData 

Fields

Instances

Instances details
FromJSON CompletionResolveData Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

ToJSON CompletionResolveData Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Generic CompletionResolveData Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Associated Types

type Rep CompletionResolveData :: Type -> Type #

type Rep CompletionResolveData Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep CompletionResolveData = D1 ('MetaData "CompletionResolveData" "Development.IDE.Plugin.Completions.Types" "ghcide-2.0.0.0-CkqMLm1apMuG7gZqD0vay" 'False) (C1 ('MetaCons "CompletionResolveData" 'PrefixI 'True) (S1 ('MetaSel ('Just "itemFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Uri) :*: (S1 ('MetaSel ('Just "itemNeedsType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "itemName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameDetails))))

data NameDetails Source #

This is a JSON serialisable representation of a GHC Name that we include in completion responses so that we can recover the original name corresponding to the completion item. This is used to resolve additional details on demand about the item like its type and documentation.

Constructors

NameDetails Module OccName 

data PosPrefixInfo Source #

Describes the line at the current cursor position

Constructors

PosPrefixInfo 

Fields

  • fullLine :: !Text

    The full contents of the line the cursor is at

  • prefixScope :: !Text

    If any, the module name that was typed right before the cursor position. For example, if the user has typed "Data.Maybe.from", then this property will be Data.Maybe If OverloadedRecordDot is enabled, "Shape.rect.width" will be "Shape.rect"

  • prefixText :: !Text

    The word right before the cursor position, after removing the module part. For example if the user has typed "Data.Maybe.from", then this property will be "from"

  • cursorPos :: !Position

    The cursor position

data CachedCompletions Source #

End result of the completions

Constructors

CC 

Fields

data CompItem Source #

Constructors

CI 

Fields

Instances

Instances details
Show CompItem Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Eq CompItem Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

data ExtendImport Source #

Constructors

ExtendImport 

Instances

Instances details
FromJSON ExtendImport Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

ToJSON ExtendImport Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Generic ExtendImport Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Associated Types

type Rep ExtendImport :: Type -> Type #

Show ExtendImport Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Eq ExtendImport Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep ExtendImport Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep ExtendImport = D1 ('MetaData "ExtendImport" "Development.IDE.Plugin.Completions.Types" "ghcide-2.0.0.0-CkqMLm1apMuG7gZqD0vay" 'False) (C1 ('MetaCons "ExtendImport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "doc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Uri) :*: S1 ('MetaSel ('Just "newThing") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "thingParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "importName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "importQual") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))

data NonLocalCompletions Source #

Constructors

NonLocalCompletions 

Instances

Instances details
Generic NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Associated Types

type Rep NonLocalCompletions :: Type -> Type #

Show NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

NFData NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Methods

rnf :: NonLocalCompletions -> () #

Eq NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Hashable NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep NonLocalCompletions = D1 ('MetaData "NonLocalCompletions" "Development.IDE.Plugin.Completions.Types" "ghcide-2.0.0.0-CkqMLm1apMuG7gZqD0vay" 'False) (C1 ('MetaCons "NonLocalCompletions" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult NonLocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

data LocalCompletions Source #

Constructors

LocalCompletions 

Instances

Instances details
Generic LocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Associated Types

type Rep LocalCompletions :: Type -> Type #

Show LocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

NFData LocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Methods

rnf :: LocalCompletions -> () #

Eq LocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

Hashable LocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep LocalCompletions Source # 
Instance details

Defined in Development.IDE.Plugin.Completions.Types

type Rep LocalCompletions = D1 ('MetaData "LocalCompletions" "Development.IDE.Plugin.Completions.Types" "ghcide-2.0.0.0-CkqMLm1apMuG7gZqD0vay" 'False) (C1 ('MetaCons "LocalCompletions" 'PrefixI 'False) (U1 :: Type -> Type))
type RuleResult LocalCompletions Source #

Produce completions info for a file

Instance details

Defined in Development.IDE.Plugin.Completions.Types

properties :: Properties '['PropertyKey "autoExtendOn" 'TBoolean, 'PropertyKey "snippetsOn" 'TBoolean] Source #