| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Skylighting.Types
Description
Basic types for Skylighting.
Synopsis
- type ContextName = (Text, Text)
- data KeywordAttr = KeywordAttr {
- keywordCaseSensitive :: !Bool
- keywordDelims :: !(Set Char)
- data WordSet a
- = CaseSensitiveWords !(Set a)
- | CaseInsensitiveWords !(Set a)
- makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a
- inWordSet :: (FoldCase a, Ord a) => a -> WordSet a -> Bool
- data ListItem
- = Item !Text
- | IncludeList !(Text, Text)
- data Matcher
- = DetectChar !Char
- | Detect2Chars !Char !Char
- | AnyChar !(Set Char)
- | RangeDetect !Char !Char
- | StringDetect !Text
- | WordDetect !Text
- | RegExpr !RE
- | Keyword !KeywordAttr (Either Text (WordSet Text))
- | Int
- | Float
- | HlCOct
- | HlCHex
- | HlCStringChar
- | HlCChar
- | LineContinue
- | IncludeRules !ContextName
- | DetectSpaces
- | DetectIdentifier
- data Rule = Rule {
- rMatcher :: !Matcher
- rAttribute :: !TokenType
- rIncludeAttribute :: !Bool
- rWeakDeliminators :: Set Char
- rDynamic :: !Bool
- rCaseSensitive :: !Bool
- rChildren :: ![Rule]
- rLookahead :: !Bool
- rFirstNonspace :: !Bool
- rColumn :: !(Maybe Int)
- rContextSwitch :: ![ContextSwitch]
- data Context = Context {
- cName :: !Text
- cSyntax :: !Text
- cRules :: ![Rule]
- cAttribute :: !TokenType
- cLineEmptyContext :: ![ContextSwitch]
- cLineEndContext :: ![ContextSwitch]
- cLineBeginContext :: ![ContextSwitch]
- cFallthrough :: !Bool
- cFallthroughContext :: ![ContextSwitch]
- cDynamic :: !Bool
- data ContextSwitch
- = Pop
- | Push !ContextName
- data Syntax = Syntax {
- sName :: !Text
- sFilename :: !String
- sShortname :: !Text
- sLists :: !(Map Text [ListItem])
- sContexts :: !(Map Text Context)
- sAuthor :: !Text
- sVersion :: !Text
- sLicense :: !Text
- sExtensions :: ![String]
- sStartingContext :: !Text
- type SyntaxMap = Map Text Syntax
- type Token = (TokenType, Text)
- data TokenType
- = KeywordTok
- | DataTypeTok
- | DecValTok
- | BaseNTok
- | FloatTok
- | ConstantTok
- | CharTok
- | SpecialCharTok
- | StringTok
- | VerbatimStringTok
- | SpecialStringTok
- | ImportTok
- | CommentTok
- | DocumentationTok
- | AnnotationTok
- | CommentVarTok
- | OtherTok
- | FunctionTok
- | VariableTok
- | ControlFlowTok
- | OperatorTok
- | BuiltInTok
- | ExtensionTok
- | PreprocessorTok
- | AttributeTok
- | RegionMarkerTok
- | InformationTok
- | WarningTok
- | AlertTok
- | ErrorTok
- | NormalTok
- type SourceLine = [Token]
- newtype LineNo = LineNo {
- lineNo :: Int
- data TokenStyle = TokenStyle {
- tokenColor :: !(Maybe Color)
- tokenBackground :: !(Maybe Color)
- tokenBold :: !Bool
- tokenItalic :: !Bool
- tokenUnderline :: !Bool
- defStyle :: TokenStyle
- data Color = RGB Word8 Word8 Word8
- class ToColor a where
- class FromColor a where
- data Style = Style {
- tokenStyles :: !(Map TokenType TokenStyle)
- defaultColor :: !(Maybe Color)
- backgroundColor :: !(Maybe Color)
- lineNumberColor :: !(Maybe Color)
- lineNumberBackgroundColor :: !(Maybe Color)
- data ANSIColorLevel
- data FormatOptions = FormatOptions {
- numberLines :: !Bool
- startNumber :: !Int
- lineAnchors :: !Bool
- titleAttributes :: !Bool
- codeClasses :: ![Text]
- containerClasses :: ![Text]
- lineIdPrefix :: !Text
- ansiColorLevel :: !ANSIColorLevel
- defaultFormatOpts :: FormatOptions
Syntax descriptions
type ContextName = (Text, Text) #
Full name of a context: the first member of the pair is the full syntax name, the second the context name within that syntax.
data KeywordAttr #
Attributes controlling how keywords are interpreted.
Constructors
| KeywordAttr | |
Fields
| |
Instances
| Data KeywordAttr # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeywordAttr -> c KeywordAttr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeywordAttr toConstr :: KeywordAttr -> Constr dataTypeOf :: KeywordAttr -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KeywordAttr) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeywordAttr) gmapT :: (forall b. Data b => b -> b) -> KeywordAttr -> KeywordAttr gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r gmapQ :: (forall d. Data d => d -> u) -> KeywordAttr -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> KeywordAttr -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr | |
| Generic KeywordAttr # | |
Defined in Skylighting.Types Associated Types type Rep KeywordAttr :: Type -> Type | |
| Read KeywordAttr # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS KeywordAttr readList :: ReadS [KeywordAttr] readPrec :: ReadPrec KeywordAttr readListPrec :: ReadPrec [KeywordAttr] | |
| Show KeywordAttr # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> KeywordAttr -> ShowS show :: KeywordAttr -> String showList :: [KeywordAttr] -> ShowS | |
| Binary KeywordAttr # | |
Defined in Skylighting.Types | |
| Eq KeywordAttr # | |
Defined in Skylighting.Types | |
| Ord KeywordAttr # | |
Defined in Skylighting.Types Methods compare :: KeywordAttr -> KeywordAttr -> Ordering (<) :: KeywordAttr -> KeywordAttr -> Bool (<=) :: KeywordAttr -> KeywordAttr -> Bool (>) :: KeywordAttr -> KeywordAttr -> Bool (>=) :: KeywordAttr -> KeywordAttr -> Bool max :: KeywordAttr -> KeywordAttr -> KeywordAttr min :: KeywordAttr -> KeywordAttr -> KeywordAttr | |
| type Rep KeywordAttr # | |
Defined in Skylighting.Types type Rep KeywordAttr = D1 ('MetaData "KeywordAttr" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "KeywordAttr" 'PrefixI 'True) (S1 ('MetaSel ('Just "keywordCaseSensitive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keywordDelims") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Char)))) | |
A set of "words," possibly case insensitive.
Constructors
| CaseSensitiveWords !(Set a) | |
| CaseInsensitiveWords !(Set a) |
Instances
| (Data a, Ord a) => Data (WordSet a) # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WordSet a -> c (WordSet a) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WordSet a) toConstr :: WordSet a -> Constr dataTypeOf :: WordSet a -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WordSet a)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WordSet a)) gmapT :: (forall b. Data b => b -> b) -> WordSet a -> WordSet a gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WordSet a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WordSet a -> r gmapQ :: (forall d. Data d => d -> u) -> WordSet a -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> WordSet a -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) | |
| Generic (WordSet a) # | |
| (Read a, Ord a) => Read (WordSet a) # | |
Defined in Skylighting.Types | |
| Show a => Show (WordSet a) # | |
| Binary a => Binary (WordSet a) # | |
| Eq a => Eq (WordSet a) # | |
| Ord a => Ord (WordSet a) # | |
Defined in Skylighting.Types | |
| type Rep (WordSet a) # | |
Defined in Skylighting.Types type Rep (WordSet a) = D1 ('MetaData "WordSet" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "CaseSensitiveWords" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set a))) :+: C1 ('MetaCons "CaseInsensitiveWords" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set a)))) | |
makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a #
A set of words to match (either case-sensitive or case-insensitive).
A list item is either just a textual value or an included list. IncludeList (x,y) includes list y from syntax with full name x.
Constructors
| Item !Text | |
| IncludeList !(Text, Text) |
Instances
| Data ListItem # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListItem -> c ListItem gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListItem toConstr :: ListItem -> Constr dataTypeOf :: ListItem -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListItem) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListItem) gmapT :: (forall b. Data b => b -> b) -> ListItem -> ListItem gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListItem -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListItem -> r gmapQ :: (forall d. Data d => d -> u) -> ListItem -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> ListItem -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem | |
| Generic ListItem # | |
| Read ListItem # | |
Defined in Skylighting.Types | |
| Show ListItem # | |
| Binary ListItem # | |
| Eq ListItem # | |
| Ord ListItem # | |
| type Rep ListItem # | |
Defined in Skylighting.Types type Rep ListItem = D1 ('MetaData "ListItem" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "Item" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "IncludeList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Text, Text)))) | |
Matchers correspond to the element types in a context.
Constructors
| DetectChar !Char | |
| Detect2Chars !Char !Char | |
| AnyChar !(Set Char) | |
| RangeDetect !Char !Char | |
| StringDetect !Text | |
| WordDetect !Text | |
| RegExpr !RE | |
| Keyword !KeywordAttr (Either Text (WordSet Text)) | |
| Int | |
| Float | |
| HlCOct | |
| HlCHex | |
| HlCStringChar | |
| HlCChar | |
| LineContinue | |
| IncludeRules !ContextName | |
| DetectSpaces | |
| DetectIdentifier |
Instances
| Data Matcher # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Matcher -> c Matcher gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Matcher dataTypeOf :: Matcher -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Matcher) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Matcher) gmapT :: (forall b. Data b => b -> b) -> Matcher -> Matcher gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Matcher -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Matcher -> r gmapQ :: (forall d. Data d => d -> u) -> Matcher -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Matcher -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Matcher -> m Matcher gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Matcher -> m Matcher gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Matcher -> m Matcher | |
| Generic Matcher # | |
| Read Matcher # | |
Defined in Skylighting.Types | |
| Show Matcher # | |
| Binary Matcher # | |
| Eq Matcher # | |
| Ord Matcher # | |
| type Rep Matcher # | |
Defined in Skylighting.Types type Rep Matcher = D1 ('MetaData "Matcher" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) ((((C1 ('MetaCons "DetectChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "Detect2Chars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char))) :+: (C1 ('MetaCons "AnyChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Char))) :+: C1 ('MetaCons "RangeDetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char)))) :+: ((C1 ('MetaCons "StringDetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "WordDetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "RegExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RE)) :+: (C1 ('MetaCons "Keyword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KeywordAttr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Either Text (WordSet Text)))) :+: C1 ('MetaCons "Int" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Float" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HlCOct" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HlCHex" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HlCStringChar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HlCChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineContinue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IncludeRules" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContextName)) :+: (C1 ('MetaCons "DetectSpaces" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DetectIdentifier" 'PrefixI 'False) (U1 :: Type -> Type)))))) | |
A rule corresponds to one of the elements of a Kate syntax highlighting "context."
Constructors
| Rule | |
Fields
| |
Instances
| Data Rule # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rule -> c Rule gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rule dataTypeOf :: Rule -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rule) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule) gmapT :: (forall b. Data b => b -> b) -> Rule -> Rule gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r gmapQ :: (forall d. Data d => d -> u) -> Rule -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Rule -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rule -> m Rule gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule | |
| Generic Rule # | |
| Read Rule # | |
Defined in Skylighting.Types | |
| Show Rule # | |
| Binary Rule # | |
| Eq Rule # | |
| Ord Rule # | |
| type Rep Rule # | |
Defined in Skylighting.Types type Rep Rule = D1 ('MetaData "Rule" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "Rule" 'PrefixI 'True) (((S1 ('MetaSel ('Just "rMatcher") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Matcher) :*: S1 ('MetaSel ('Just "rAttribute") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenType)) :*: (S1 ('MetaSel ('Just "rIncludeAttribute") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "rWeakDeliminators") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set Char)) :*: S1 ('MetaSel ('Just "rDynamic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "rCaseSensitive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "rChildren") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Rule]) :*: S1 ('MetaSel ('Just "rLookahead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "rFirstNonspace") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "rColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "rContextSwitch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ContextSwitch])))))) | |
A Context corresponds to a context element in a Kate syntax description.
Constructors
| Context | |
Fields
| |
Instances
| Data Context # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Context -> c Context gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Context dataTypeOf :: Context -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Context) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Context) gmapT :: (forall b. Data b => b -> b) -> Context -> Context gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Context -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Context -> r gmapQ :: (forall d. Data d => d -> u) -> Context -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Context -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Context -> m Context gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Context -> m Context gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Context -> m Context | |
| Generic Context # | |
| Read Context # | |
Defined in Skylighting.Types | |
| Show Context # | |
| Binary Context # | |
| Eq Context # | |
| Ord Context # | |
| type Rep Context # | |
Defined in Skylighting.Types type Rep Context = D1 ('MetaData "Context" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "Context" 'PrefixI 'True) (((S1 ('MetaSel ('Just "cName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "cSyntax") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "cRules") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Rule]) :*: (S1 ('MetaSel ('Just "cAttribute") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenType) :*: S1 ('MetaSel ('Just "cLineEmptyContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ContextSwitch])))) :*: ((S1 ('MetaSel ('Just "cLineEndContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ContextSwitch]) :*: S1 ('MetaSel ('Just "cLineBeginContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ContextSwitch])) :*: (S1 ('MetaSel ('Just "cFallthrough") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "cFallthroughContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ContextSwitch]) :*: S1 ('MetaSel ('Just "cDynamic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))) | |
data ContextSwitch #
A context switch, either pops or pushes a context.
Constructors
| Pop | |
| Push !ContextName |
Instances
| Data ContextSwitch # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContextSwitch -> c ContextSwitch gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContextSwitch toConstr :: ContextSwitch -> Constr dataTypeOf :: ContextSwitch -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ContextSwitch) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContextSwitch) gmapT :: (forall b. Data b => b -> b) -> ContextSwitch -> ContextSwitch gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r gmapQ :: (forall d. Data d => d -> u) -> ContextSwitch -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> ContextSwitch -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch | |
| Generic ContextSwitch # | |
Defined in Skylighting.Types Associated Types type Rep ContextSwitch :: Type -> Type | |
| Read ContextSwitch # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS ContextSwitch readList :: ReadS [ContextSwitch] readPrec :: ReadPrec ContextSwitch readListPrec :: ReadPrec [ContextSwitch] | |
| Show ContextSwitch # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> ContextSwitch -> ShowS show :: ContextSwitch -> String showList :: [ContextSwitch] -> ShowS | |
| Binary ContextSwitch # | |
Defined in Skylighting.Types | |
| Eq ContextSwitch # | |
Defined in Skylighting.Types | |
| Ord ContextSwitch # | |
Defined in Skylighting.Types Methods compare :: ContextSwitch -> ContextSwitch -> Ordering (<) :: ContextSwitch -> ContextSwitch -> Bool (<=) :: ContextSwitch -> ContextSwitch -> Bool (>) :: ContextSwitch -> ContextSwitch -> Bool (>=) :: ContextSwitch -> ContextSwitch -> Bool max :: ContextSwitch -> ContextSwitch -> ContextSwitch min :: ContextSwitch -> ContextSwitch -> ContextSwitch | |
| type Rep ContextSwitch # | |
Defined in Skylighting.Types type Rep ContextSwitch = D1 ('MetaData "ContextSwitch" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "Pop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Push" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContextName))) | |
A syntax corresponds to a complete Kate syntax description.
The sShortname field is derived from the filename.
Constructors
| Syntax | |
Fields
| |
Instances
| Data Syntax # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Syntax -> c Syntax gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Syntax dataTypeOf :: Syntax -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Syntax) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Syntax) gmapT :: (forall b. Data b => b -> b) -> Syntax -> Syntax gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r gmapQ :: (forall d. Data d => d -> u) -> Syntax -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Syntax -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Syntax -> m Syntax gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Syntax -> m Syntax gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Syntax -> m Syntax | |
| Generic Syntax # | |
| Read Syntax # | |
Defined in Skylighting.Types | |
| Show Syntax # | |
| Binary Syntax # | |
| Eq Syntax # | |
| Ord Syntax # | |
| type Rep Syntax # | |
Defined in Skylighting.Types type Rep Syntax = D1 ('MetaData "Syntax" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "Syntax" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sFilename") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :*: (S1 ('MetaSel ('Just "sShortname") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sLists") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Text [ListItem])) :*: S1 ('MetaSel ('Just "sContexts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Text Context))))) :*: ((S1 ('MetaSel ('Just "sAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "sLicense") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sExtensions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String]) :*: S1 ('MetaSel ('Just "sStartingContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))) | |
Tokens
KeywordTok corresponds to dsKeyword in Kate syntax
descriptions, and so on.
Constructors
Instances
| FromJSON TokenType # | |
Defined in Skylighting.Types | |
| FromJSONKey TokenType # | JSON |
Defined in Skylighting.Types Methods | |
| ToJSON TokenType # | |
Defined in Skylighting.Types | |
| ToJSONKey TokenType # | |
Defined in Skylighting.Types | |
| Data TokenType # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenType -> c TokenType gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenType toConstr :: TokenType -> Constr dataTypeOf :: TokenType -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenType) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType) gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r gmapQ :: (forall d. Data d => d -> u) -> TokenType -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenType -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType | |
| Bounded TokenType # | |
Defined in Skylighting.Types | |
| Enum TokenType # | |
Defined in Skylighting.Types | |
| Generic TokenType # | |
| Read TokenType # | |
Defined in Skylighting.Types | |
| Show TokenType # | |
| Binary TokenType # | |
| Eq TokenType # | |
| Ord TokenType # | |
Defined in Skylighting.Types | |
| type Rep TokenType # | |
Defined in Skylighting.Types type Rep TokenType = D1 ('MetaData "TokenType" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) ((((C1 ('MetaCons "KeywordTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataTypeTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecValTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BaseNTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FloatTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ConstantTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharTok" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "SpecialCharTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StringTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VerbatimStringTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpecialStringTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ImportTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommentTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DocumentationTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnnotationTok" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "CommentVarTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FunctionTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VariableTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControlFlowTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OperatorTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BuiltInTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtensionTok" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "PreprocessorTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AttributeTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RegionMarkerTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InformationTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WarningTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlertTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NormalTok" 'PrefixI 'False) (U1 :: Type -> Type)))))) | |
type SourceLine = [Token] #
A line of source: a list of labeled tokens.
Line numbers
Instances
| Enum LineNo # | |
Defined in Skylighting.Types | |
| Show LineNo # | |
Styles
data TokenStyle #
A TokenStyle determines how a token is to be rendered.
Constructors
| TokenStyle | |
Fields
| |
Instances
| FromJSON TokenStyle # | The keywords used in KDE syntax
themes are used, e.g. |
Defined in Skylighting.Types Methods parseJSON :: Value -> Parser TokenStyle # parseJSONList :: Value -> Parser [TokenStyle] # omittedField :: Maybe TokenStyle # | |
| ToJSON TokenStyle # | |
Defined in Skylighting.Types Methods toJSON :: TokenStyle -> Value # toEncoding :: TokenStyle -> Encoding # toJSONList :: [TokenStyle] -> Value # toEncodingList :: [TokenStyle] -> Encoding # omitField :: TokenStyle -> Bool # | |
| Data TokenStyle # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenStyle -> c TokenStyle gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenStyle toConstr :: TokenStyle -> Constr dataTypeOf :: TokenStyle -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenStyle) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenStyle) gmapT :: (forall b. Data b => b -> b) -> TokenStyle -> TokenStyle gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenStyle -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenStyle -> r gmapQ :: (forall d. Data d => d -> u) -> TokenStyle -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenStyle -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle | |
| Generic TokenStyle # | |
Defined in Skylighting.Types Associated Types type Rep TokenStyle :: Type -> Type | |
| Read TokenStyle # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS TokenStyle readList :: ReadS [TokenStyle] readPrec :: ReadPrec TokenStyle readListPrec :: ReadPrec [TokenStyle] | |
| Show TokenStyle # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> TokenStyle -> ShowS show :: TokenStyle -> String showList :: [TokenStyle] -> ShowS | |
| Binary TokenStyle # | |
Defined in Skylighting.Types | |
| Eq TokenStyle # | |
Defined in Skylighting.Types | |
| Ord TokenStyle # | |
Defined in Skylighting.Types Methods compare :: TokenStyle -> TokenStyle -> Ordering (<) :: TokenStyle -> TokenStyle -> Bool (<=) :: TokenStyle -> TokenStyle -> Bool (>) :: TokenStyle -> TokenStyle -> Bool (>=) :: TokenStyle -> TokenStyle -> Bool max :: TokenStyle -> TokenStyle -> TokenStyle min :: TokenStyle -> TokenStyle -> TokenStyle | |
| type Rep TokenStyle # | |
Defined in Skylighting.Types type Rep TokenStyle = D1 ('MetaData "TokenStyle" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "TokenStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "tokenBackground") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "tokenBold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "tokenItalic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "tokenUnderline") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))) | |
defStyle :: TokenStyle #
Default style.
A color (red, green, blue).
Constructors
| RGB Word8 Word8 Word8 |
Instances
| FromJSON Color # | JSON |
Defined in Skylighting.Types | |
| ToJSON Color # | |
Defined in Skylighting.Types | |
| Data Color # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Color -> c Color gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Color dataTypeOf :: Color -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Color) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color) gmapT :: (forall b. Data b => b -> b) -> Color -> Color gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r gmapQ :: (forall d. Data d => d -> u) -> Color -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Color -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Color -> m Color gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color | |
| Generic Color # | |
| Read Color # | |
Defined in Skylighting.Types | |
| Show Color # | |
| Binary Color # | |
| Eq Color # | |
| Ord Color # | |
| type Rep Color # | |
Defined in Skylighting.Types type Rep Color = D1 ('MetaData "Color" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "RGB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word8) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word8)))) | |
Things that can be converted to a color.
Instances
| ToColor String # | |
Defined in Skylighting.Types | |
| ToColor Int # | |
Defined in Skylighting.Types | |
| (RealFrac a, Floating a) => ToColor (Colour a) # | |
Defined in Skylighting.Types | |
| ToColor (Word8, Word8, Word8) # | |
Defined in Skylighting.Types | |
| ToColor (Double, Double, Double) # | |
Defined in Skylighting.Types | |
Different representations of a Color.
Instances
| FromColor String # | |
Defined in Skylighting.Types | |
| (Ord a, Floating a) => FromColor (Colour a) # | |
Defined in Skylighting.Types | |
| FromColor (Word8, Word8, Word8) # | |
Defined in Skylighting.Types | |
| FromColor (Double, Double, Double) # | |
Defined in Skylighting.Types | |
A rendering style. This determines how each kind of token is to be rendered, and sets a default color and background color for normal tokens. Line numbers can have a different color and background color.
Constructors
| Style | |
Fields
| |
Instances
| FromJSON Style # | The FromJSON instance for |
Defined in Skylighting.Types | |
| ToJSON Style # | |
Defined in Skylighting.Types | |
| Data Style # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Style -> c Style gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Style dataTypeOf :: Style -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Style) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style) gmapT :: (forall b. Data b => b -> b) -> Style -> Style gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r gmapQ :: (forall d. Data d => d -> u) -> Style -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Style -> m Style gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style | |
| Generic Style # | |
| Read Style # | |
Defined in Skylighting.Types | |
| Show Style # | |
| Binary Style # | |
| Eq Style # | |
| Ord Style # | |
| type Rep Style # | |
Defined in Skylighting.Types type Rep Style = D1 ('MetaData "Style" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenStyles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map TokenType TokenStyle)) :*: S1 ('MetaSel ('Just "defaultColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "backgroundColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "lineNumberColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "lineNumberBackgroundColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color)))))) | |
data ANSIColorLevel #
The available levels of color complexity in ANSI terminal output.
Constructors
| ANSI16Color | 16-color mode |
| ANSI256Color | 256-color mode |
| ANSITrueColor | True-color mode |
Instances
| Data ANSIColorLevel # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ANSIColorLevel -> c ANSIColorLevel gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ANSIColorLevel toConstr :: ANSIColorLevel -> Constr dataTypeOf :: ANSIColorLevel -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ANSIColorLevel) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ANSIColorLevel) gmapT :: (forall b. Data b => b -> b) -> ANSIColorLevel -> ANSIColorLevel gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r gmapQ :: (forall d. Data d => d -> u) -> ANSIColorLevel -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> ANSIColorLevel -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> ANSIColorLevel -> m ANSIColorLevel gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ANSIColorLevel -> m ANSIColorLevel gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ANSIColorLevel -> m ANSIColorLevel | |
| Bounded ANSIColorLevel # | |
Defined in Skylighting.Types | |
| Enum ANSIColorLevel # | |
Defined in Skylighting.Types Methods succ :: ANSIColorLevel -> ANSIColorLevel pred :: ANSIColorLevel -> ANSIColorLevel toEnum :: Int -> ANSIColorLevel fromEnum :: ANSIColorLevel -> Int enumFrom :: ANSIColorLevel -> [ANSIColorLevel] enumFromThen :: ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel] enumFromTo :: ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel] enumFromThenTo :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel] | |
| Generic ANSIColorLevel # | |
Defined in Skylighting.Types Associated Types type Rep ANSIColorLevel :: Type -> Type | |
| Read ANSIColorLevel # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS ANSIColorLevel readList :: ReadS [ANSIColorLevel] readPrec :: ReadPrec ANSIColorLevel readListPrec :: ReadPrec [ANSIColorLevel] | |
| Show ANSIColorLevel # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> ANSIColorLevel -> ShowS show :: ANSIColorLevel -> String showList :: [ANSIColorLevel] -> ShowS | |
| Binary ANSIColorLevel # | |
Defined in Skylighting.Types | |
| Eq ANSIColorLevel # | |
Defined in Skylighting.Types Methods (==) :: ANSIColorLevel -> ANSIColorLevel -> Bool (/=) :: ANSIColorLevel -> ANSIColorLevel -> Bool | |
| Ord ANSIColorLevel # | |
Defined in Skylighting.Types Methods compare :: ANSIColorLevel -> ANSIColorLevel -> Ordering (<) :: ANSIColorLevel -> ANSIColorLevel -> Bool (<=) :: ANSIColorLevel -> ANSIColorLevel -> Bool (>) :: ANSIColorLevel -> ANSIColorLevel -> Bool (>=) :: ANSIColorLevel -> ANSIColorLevel -> Bool max :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel min :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel | |
| type Rep ANSIColorLevel # | |
Defined in Skylighting.Types type Rep ANSIColorLevel = D1 ('MetaData "ANSIColorLevel" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "ANSI16Color" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ANSI256Color" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ANSITrueColor" 'PrefixI 'False) (U1 :: Type -> Type))) | |
Format options
data FormatOptions #
Options for formatting source code.
Constructors
| FormatOptions | |
Fields
| |
Instances
| Data FormatOptions # | |
Defined in Skylighting.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FormatOptions -> c FormatOptions gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FormatOptions toConstr :: FormatOptions -> Constr dataTypeOf :: FormatOptions -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FormatOptions) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FormatOptions) gmapT :: (forall b. Data b => b -> b) -> FormatOptions -> FormatOptions gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FormatOptions -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FormatOptions -> r gmapQ :: (forall d. Data d => d -> u) -> FormatOptions -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> FormatOptions -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions | |
| Generic FormatOptions # | |
Defined in Skylighting.Types Associated Types type Rep FormatOptions :: Type -> Type | |
| Read FormatOptions # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS FormatOptions readList :: ReadS [FormatOptions] readPrec :: ReadPrec FormatOptions readListPrec :: ReadPrec [FormatOptions] | |
| Show FormatOptions # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> FormatOptions -> ShowS show :: FormatOptions -> String showList :: [FormatOptions] -> ShowS | |
| Binary FormatOptions # | |
Defined in Skylighting.Types | |
| Eq FormatOptions # | |
Defined in Skylighting.Types | |
| Ord FormatOptions # | |
Defined in Skylighting.Types Methods compare :: FormatOptions -> FormatOptions -> Ordering (<) :: FormatOptions -> FormatOptions -> Bool (<=) :: FormatOptions -> FormatOptions -> Bool (>) :: FormatOptions -> FormatOptions -> Bool (>=) :: FormatOptions -> FormatOptions -> Bool max :: FormatOptions -> FormatOptions -> FormatOptions min :: FormatOptions -> FormatOptions -> FormatOptions | |
| type Rep FormatOptions # | |
Defined in Skylighting.Types type Rep FormatOptions = D1 ('MetaData "FormatOptions" "Skylighting.Types" "skylighting-core-0.14-2VFtdFvK2VbBi7Hr1W0TBh" 'False) (C1 ('MetaCons "FormatOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "numberLines") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "startNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "lineAnchors") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "titleAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "codeClasses") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "containerClasses") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Text])) :*: (S1 ('MetaSel ('Just "lineIdPrefix") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "ansiColorLevel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ANSIColorLevel))))) | |
defaultFormatOpts :: FormatOptions #
Default formatting options.