Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Ide.Plugin.SemanticTokens.Types
Synopsis
- data HsSemanticTokenType
- data SemanticTokensConfig = STC {
- stFunction :: !SemanticTokenTypes
- stVariable :: !SemanticTokenTypes
- stDataConstructor :: !SemanticTokenTypes
- stTypeVariable :: !SemanticTokenTypes
- stClassMethod :: !SemanticTokenTypes
- stPatternSynonym :: !SemanticTokenTypes
- stTypeConstructor :: !SemanticTokenTypes
- stClass :: !SemanticTokenTypes
- stTypeSynonym :: !SemanticTokenTypes
- stTypeFamily :: !SemanticTokenTypes
- stRecordField :: !SemanticTokenTypes
- data SemanticTokenOriginal tokenType = SemanticTokenOriginal {
- _tokenType :: tokenType
- _loc :: Loc
- _name :: String
- data Loc = Loc {}
- type NameSemanticMap = NameEnv HsSemanticTokenType
- data GetSemanticTokens = GetSemanticTokens
- data RangeHsSemanticTokenTypes = RangeHsSemanticTokenTypes {}
- data HieFunMaskKind kind where
- data SemanticLog
Documentation
data HsSemanticTokenType Source #
Constructors
TVariable | |
TFunction | |
TDataConstructor | |
TTypeVariable | |
TClassMethod | |
TPatternSynonym | |
TTypeConstructor | |
TClass | |
TTypeSynonym | |
TTypeFamily | |
TRecordField |
Instances
data SemanticTokensConfig Source #
SemanticTokensConfig_ is a configuration for the semantic tokens plugin. it contains map between the hs semantic token type and default token type.
Constructors
Instances
data SemanticTokenOriginal tokenType Source #
Constructors
SemanticTokenOriginal | |
Fields
|
Instances
data GetSemanticTokens Source #
Constructors
GetSemanticTokens |
Instances
Generic GetSemanticTokens Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Associated Types type Rep GetSemanticTokens :: Type -> Type # Methods from :: GetSemanticTokens -> Rep GetSemanticTokens x # to :: Rep GetSemanticTokens x -> GetSemanticTokens # | |
Show GetSemanticTokens Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Methods showsPrec :: Int -> GetSemanticTokens -> ShowS # show :: GetSemanticTokens -> String # showList :: [GetSemanticTokens] -> ShowS # | |
NFData GetSemanticTokens Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Methods rnf :: GetSemanticTokens -> () # | |
Eq GetSemanticTokens Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Methods (==) :: GetSemanticTokens -> GetSemanticTokens -> Bool # (/=) :: GetSemanticTokens -> GetSemanticTokens -> Bool # | |
Hashable GetSemanticTokens Source # | |
Defined in Ide.Plugin.SemanticTokens.Types | |
type Rep GetSemanticTokens Source # | |
type RuleResult GetSemanticTokens Source # | |
Defined in Ide.Plugin.SemanticTokens.Types |
data RangeHsSemanticTokenTypes Source #
Constructors
RangeHsSemanticTokenTypes | |
Fields |
Instances
Show RangeHsSemanticTokenTypes Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Methods showsPrec :: Int -> RangeHsSemanticTokenTypes -> ShowS # show :: RangeHsSemanticTokenTypes -> String # showList :: [RangeHsSemanticTokenTypes] -> ShowS # | |
NFData RangeHsSemanticTokenTypes Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Methods rnf :: RangeHsSemanticTokenTypes -> () # |
data HieFunMaskKind kind where Source #
Constructors
HieFreshFun :: HieFunMaskKind Type | |
HieFromDiskFun :: Array TypeIndex Bool -> HieFunMaskKind TypeIndex |
data SemanticLog Source #
Instances
Show SemanticLog Source # | |
Defined in Ide.Plugin.SemanticTokens.Types Methods showsPrec :: Int -> SemanticLog -> ShowS # show :: SemanticLog -> String # showList :: [SemanticLog] -> ShowS # | |
Pretty SemanticLog Source # | |
Defined in Ide.Plugin.SemanticTokens.Types |