| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Development.IDE.Plugin.Completions.Types
Synopsis
- data CompItem = CI {
- compKind :: CompletionItemKind
- insertText :: Snippet
- provenance :: Provenance
- label :: Text
- typeText :: Maybe Text
- isInfix :: Maybe Backtick
- isTypeCompl :: Bool
- additionalTextEdits :: Maybe ExtendImport
- nameDetails :: Maybe NameDetails
- isLocalCompletion :: Bool
- data CompletionsConfig = CompletionsConfig {}
- data SnippetAny
- data CachedCompletions = CC {
- allModNamesAsNS :: [Text]
- unqualCompls :: [CompItem]
- qualCompls :: QualCompls
- anyQualCompls :: [Maybe Text -> CompItem]
- importableModules :: [Text]
- data ExtendImport = ExtendImport {
- doc :: !Uri
- newThing :: !Text
- thingParent :: !(Maybe Text)
- importName :: !Text
- importQual :: !(Maybe Text)
- properties :: Properties '['PropertyKey "autoExtendOn" 'TBoolean, 'PropertyKey "snippetsOn" 'TBoolean]
- data LocalCompletions = LocalCompletions
- data NonLocalCompletions = NonLocalCompletions
- data Backtick
- extendImportCommandId :: Text
- data Provenance
- newtype Snippet = Snippet [SnippetAny]
- snippetText :: Text -> Snippet
- snippetVariable :: Text -> Snippet
- snippetVariableDefault :: Text -> SnippetAny -> Snippet
- snippetToText :: Snippet -> Text
- snippetLexOrd :: Snippet -> Snippet -> Ordering
- data NameDetails = NameDetails Module OccName
- newtype QualCompls = QualCompls {
- getQualCompls :: Map Text [CompItem]
- data PosPrefixInfo = PosPrefixInfo {
- fullLine :: !Text
- prefixScope :: !Text
- prefixText :: !Text
- cursorPos :: !Position
- nsJSON :: NameSpace -> Value
- parseNs :: Value -> Parser NameSpace
- data CompletionResolveData = CompletionResolveData {
- itemFile :: Uri
- itemNeedsType :: Bool
- itemName :: NameDetails
Documentation
Constructors
| CI | |
Fields
| |
data CompletionsConfig Source #
Constructors
| CompletionsConfig | |
Fields
| |
data SnippetAny Source #
SnippetAny can be used to construct sanitized snippets. See the LSP
spec for more details.
Constructors
| SText Text | Literal text |
| STabStop Int (Maybe SnippetAny) | Creates a tab stop, i.e. parts of the snippet that are meant to be filled in by the user and that can be jumped between using the tab key. The optional field can be used to provide a placeholder value. |
| SChoice Int (NonEmpty Text) | Presents a choice between the provided values to the user |
| SVariable Text (Maybe SnippetAny) | Snippet variable. See the spec for possible values. The optional field can be used to provide a default value for when the variable is not set. |
Instances
| Show SnippetAny Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> SnippetAny -> ShowS # show :: SnippetAny -> String # showList :: [SnippetAny] -> ShowS # | |
| Eq SnippetAny Source # | |
Defined in Development.IDE.Plugin.Completions.Types | |
data CachedCompletions Source #
End result of the completions
Constructors
| CC | |
Fields
| |
Instances
| Monoid CachedCompletions Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods mappend :: CachedCompletions -> CachedCompletions -> CachedCompletions # mconcat :: [CachedCompletions] -> CachedCompletions # | |
| Semigroup CachedCompletions Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods (<>) :: CachedCompletions -> CachedCompletions -> CachedCompletions # sconcat :: NonEmpty CachedCompletions -> CachedCompletions # stimes :: Integral b => b -> CachedCompletions -> CachedCompletions # | |
| Show CachedCompletions Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> CachedCompletions -> ShowS # show :: CachedCompletions -> String # showList :: [CachedCompletions] -> ShowS # | |
| NFData CachedCompletions Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods rnf :: CachedCompletions -> () # | |
data ExtendImport Source #
Constructors
| ExtendImport | |
Fields
| |
Instances
properties :: Properties '['PropertyKey "autoExtendOn" 'TBoolean, 'PropertyKey "snippetsOn" 'TBoolean] Source #
data LocalCompletions Source #
Constructors
| LocalCompletions |
Instances
| Generic LocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Associated Types
Methods from :: LocalCompletions -> Rep LocalCompletions x # to :: Rep LocalCompletions x -> LocalCompletions # | |||||
| Show LocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> LocalCompletions -> ShowS # show :: LocalCompletions -> String # showList :: [LocalCompletions] -> ShowS # | |||||
| NFData LocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods rnf :: LocalCompletions -> () # | |||||
| Eq LocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods (==) :: LocalCompletions -> LocalCompletions -> Bool # (/=) :: LocalCompletions -> LocalCompletions -> Bool # | |||||
| Hashable LocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types | |||||
| type Rep LocalCompletions Source # | |||||
| type RuleResult LocalCompletions Source # | Produce completions info for a file | ||||
Defined in Development.IDE.Plugin.Completions.Types | |||||
data NonLocalCompletions Source #
Constructors
| NonLocalCompletions |
Instances
| Generic NonLocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Associated Types
Methods from :: NonLocalCompletions -> Rep NonLocalCompletions x # to :: Rep NonLocalCompletions x -> NonLocalCompletions # | |||||
| Show NonLocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> NonLocalCompletions -> ShowS # show :: NonLocalCompletions -> String # showList :: [NonLocalCompletions] -> ShowS # | |||||
| NFData NonLocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods rnf :: NonLocalCompletions -> () # | |||||
| Eq NonLocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods (==) :: NonLocalCompletions -> NonLocalCompletions -> Bool # (/=) :: NonLocalCompletions -> NonLocalCompletions -> Bool # | |||||
| Hashable NonLocalCompletions Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types | |||||
| type Rep NonLocalCompletions Source # | |||||
| type RuleResult NonLocalCompletions Source # | |||||
Constructors
| Surrounded | |
| LeftSide |
data Provenance Source #
Instances
| Show Provenance Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> Provenance -> ShowS # show :: Provenance -> String # showList :: [Provenance] -> ShowS # | |
| Eq Provenance Source # | |
Defined in Development.IDE.Plugin.Completions.Types | |
| Ord Provenance Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods compare :: Provenance -> Provenance -> Ordering # (<) :: Provenance -> Provenance -> Bool # (<=) :: Provenance -> Provenance -> Bool # (>) :: Provenance -> Provenance -> Bool # (>=) :: Provenance -> Provenance -> Bool # max :: Provenance -> Provenance -> Provenance # min :: Provenance -> Provenance -> Provenance # | |
Constructors
| Snippet [SnippetAny] |
snippetText :: Text -> Snippet Source #
snippetVariable :: Text -> Snippet Source #
snippetVariableDefault :: Text -> SnippetAny -> Snippet Source #
snippetToText :: Snippet -> Text Source #
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 |
Instances
| FromJSON NameDetails Source # | |
Defined in Development.IDE.Plugin.Completions.Types | |
| ToJSON NameDetails Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods toJSON :: NameDetails -> Value # toEncoding :: NameDetails -> Encoding # toJSONList :: [NameDetails] -> Value # toEncodingList :: [NameDetails] -> Encoding # omitField :: NameDetails -> Bool # | |
| Show NameDetails Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> NameDetails -> ShowS # show :: NameDetails -> String # showList :: [NameDetails] -> ShowS # | |
| Eq NameDetails Source # | |
Defined in Development.IDE.Plugin.Completions.Types | |
newtype QualCompls Source #
Constructors
| QualCompls | |
Fields
| |
Instances
| Monoid QualCompls Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods mempty :: QualCompls # mappend :: QualCompls -> QualCompls -> QualCompls # mconcat :: [QualCompls] -> QualCompls # | |
| Semigroup QualCompls Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods (<>) :: QualCompls -> QualCompls -> QualCompls # sconcat :: NonEmpty QualCompls -> QualCompls # stimes :: Integral b => b -> QualCompls -> QualCompls # | |
| Show QualCompls Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> QualCompls -> ShowS # show :: QualCompls -> String # showList :: [QualCompls] -> ShowS # | |
data PosPrefixInfo Source #
Describes the line at the current cursor position
Constructors
| PosPrefixInfo | |
Fields
| |
Instances
| Show PosPrefixInfo Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods showsPrec :: Int -> PosPrefixInfo -> ShowS # show :: PosPrefixInfo -> String # showList :: [PosPrefixInfo] -> ShowS # | |
| Eq PosPrefixInfo Source # | |
Defined in Development.IDE.Plugin.Completions.Types Methods (==) :: PosPrefixInfo -> PosPrefixInfo -> Bool # (/=) :: PosPrefixInfo -> PosPrefixInfo -> Bool # | |
data CompletionResolveData Source #
The data that is actually 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
| FromJSON CompletionResolveData Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods parseJSON :: Value -> Parser CompletionResolveData # parseJSONList :: Value -> Parser [CompletionResolveData] # | |||||
| ToJSON CompletionResolveData Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Methods toJSON :: CompletionResolveData -> Value # toEncoding :: CompletionResolveData -> Encoding # toJSONList :: [CompletionResolveData] -> Value # toEncodingList :: [CompletionResolveData] -> Encoding # omitField :: CompletionResolveData -> Bool # | |||||
| Generic CompletionResolveData Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types Associated Types
Methods from :: CompletionResolveData -> Rep CompletionResolveData x # to :: Rep CompletionResolveData x -> CompletionResolveData # | |||||
| type Rep CompletionResolveData Source # | |||||
Defined in Development.IDE.Plugin.Completions.Types type Rep CompletionResolveData = D1 ('MetaData "CompletionResolveData" "Development.IDE.Plugin.Completions.Types" "ghcide-2.13.0.0-3xOdL4E2K8pFtuI1JRT6Li" '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)))) | |||||