Safe Haskell | None |
---|---|
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 Matcher
- = DetectChar Char
- | Detect2Chars Char Char
- | AnyChar [Char]
- | RangeDetect Char Char
- | StringDetect Text
- | WordDetect Text
- | RegExpr RE
- | Keyword KeywordAttr (WordSet Text)
- | Int
- | Float
- | HlCOct
- | HlCHex
- | HlCStringChar
- | HlCChar
- | LineContinue
- | IncludeRules ContextName
- | DetectSpaces
- | DetectIdentifier
- data Rule = Rule {
- rMatcher :: Matcher
- rAttribute :: TokenType
- rIncludeAttribute :: Bool
- 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
- 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
- newtype Xterm256ColorCode = Xterm256ColorCode {
- getXterm256ColorCode :: Word8
- 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) Source #
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 Source #
Attributes controlling how keywords are interpreted.
Constructors
KeywordAttr | |
Fields
|
Instances
Eq KeywordAttr Source # | |
Defined in Skylighting.Types | |
Data KeywordAttr Source # | |
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 | |
Ord KeywordAttr Source # | |
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 | |
Read KeywordAttr Source # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS KeywordAttr readList :: ReadS [KeywordAttr] readPrec :: ReadPrec KeywordAttr readListPrec :: ReadPrec [KeywordAttr] | |
Show KeywordAttr Source # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> KeywordAttr -> ShowS show :: KeywordAttr -> String showList :: [KeywordAttr] -> ShowS | |
Generic KeywordAttr Source # | |
Defined in Skylighting.Types Associated Types type Rep KeywordAttr :: Type -> Type | |
Binary KeywordAttr Source # | |
Defined in Skylighting.Types | |
type Rep KeywordAttr Source # | |
Defined in Skylighting.Types type Rep KeywordAttr = D1 ('MetaData "KeywordAttr" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "KeywordAttr" 'PrefixI 'True) (S1 ('MetaSel ('Just "keywordCaseSensitive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keywordDelims") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Char)))) |
A set of "words," possibly case insensitive.
Constructors
CaseSensitiveWords (Set a) | |
CaseInsensitiveWords (Set a) |
Instances
Eq a => Eq (WordSet a) Source # | |
(Data a, Ord a) => Data (WordSet a) Source # | |
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) | |
Ord a => Ord (WordSet a) Source # | |
Defined in Skylighting.Types | |
(Read a, Ord a) => Read (WordSet a) Source # | |
Defined in Skylighting.Types | |
Show a => Show (WordSet a) Source # | |
Generic (WordSet a) Source # | |
Binary a => Binary (WordSet a) Source # | |
type Rep (WordSet a) Source # | |
Defined in Skylighting.Types type Rep (WordSet a) = D1 ('MetaData "WordSet" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "CaseSensitiveWords" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set a))) :+: C1 ('MetaCons "CaseInsensitiveWords" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set a)))) |
makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a Source #
A set of words to match (either case-sensitive or case-insensitive).
inWordSet :: (FoldCase a, Ord a) => a -> WordSet a -> Bool Source #
Test for membership in a WordSet
.
Matchers correspond to the element types in a context.
Constructors
DetectChar Char | |
Detect2Chars Char Char | |
AnyChar [Char] | |
RangeDetect Char Char | |
StringDetect Text | |
WordDetect Text | |
RegExpr RE | |
Keyword KeywordAttr (WordSet Text) | |
Int | |
Float | |
HlCOct | |
HlCHex | |
HlCStringChar | |
HlCChar | |
LineContinue | |
IncludeRules ContextName | |
DetectSpaces | |
DetectIdentifier |
Instances
Eq Matcher Source # | |
Data Matcher Source # | |
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 | |
Ord Matcher Source # | |
Read Matcher Source # | |
Defined in Skylighting.Types | |
Show Matcher Source # | |
Generic Matcher Source # | |
Binary Matcher Source # | |
type Rep Matcher Source # | |
Defined in Skylighting.Types type Rep Matcher = D1 ('MetaData "Matcher" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) ((((C1 ('MetaCons "DetectChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: C1 ('MetaCons "Detect2Chars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))) :+: (C1 ('MetaCons "AnyChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Char])) :+: C1 ('MetaCons "RangeDetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)))) :+: ((C1 ('MetaCons "StringDetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "WordDetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "RegExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RE)) :+: (C1 ('MetaCons "Keyword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeywordAttr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (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 'NoSourceStrictness 'DecidedLazy) (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
Eq Rule Source # | |
Data Rule Source # | |
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 | |
Ord Rule Source # | |
Read Rule Source # | |
Defined in Skylighting.Types | |
Show Rule Source # | |
Generic Rule Source # | |
Binary Rule Source # | |
type Rep Rule Source # | |
Defined in Skylighting.Types type Rep Rule = D1 ('MetaData "Rule" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "Rule" 'PrefixI 'True) (((S1 ('MetaSel ('Just "rMatcher") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Matcher) :*: S1 ('MetaSel ('Just "rAttribute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TokenType)) :*: (S1 ('MetaSel ('Just "rIncludeAttribute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "rDynamic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "rCaseSensitive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "rChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rule]) :*: S1 ('MetaSel ('Just "rLookahead") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "rFirstNonspace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "rColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "rContextSwitch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ContextSwitch])))))) |
A Context corresponds to a context element in a Kate syntax description.
Constructors
Context | |
Fields
|
Instances
Eq Context Source # | |
Data Context Source # | |
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 | |
Ord Context Source # | |
Read Context Source # | |
Defined in Skylighting.Types | |
Show Context Source # | |
Generic Context Source # | |
Binary Context Source # | |
type Rep Context Source # | |
Defined in Skylighting.Types type Rep Context = D1 ('MetaData "Context" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "Context" 'PrefixI 'True) (((S1 ('MetaSel ('Just "cName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "cSyntax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "cRules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rule]) :*: (S1 ('MetaSel ('Just "cAttribute") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TokenType) :*: S1 ('MetaSel ('Just "cLineEmptyContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ContextSwitch])))) :*: ((S1 ('MetaSel ('Just "cLineEndContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ContextSwitch]) :*: S1 ('MetaSel ('Just "cLineBeginContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ContextSwitch])) :*: (S1 ('MetaSel ('Just "cFallthrough") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "cFallthroughContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ContextSwitch]) :*: S1 ('MetaSel ('Just "cDynamic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) |
data ContextSwitch Source #
A context switch, either pops or pushes a context.
Constructors
Pop | |
Push ContextName |
Instances
Eq ContextSwitch Source # | |
Defined in Skylighting.Types | |
Data ContextSwitch Source # | |
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 | |
Ord ContextSwitch Source # | |
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 | |
Read ContextSwitch Source # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS ContextSwitch readList :: ReadS [ContextSwitch] readPrec :: ReadPrec ContextSwitch readListPrec :: ReadPrec [ContextSwitch] | |
Show ContextSwitch Source # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> ContextSwitch -> ShowS show :: ContextSwitch -> String showList :: [ContextSwitch] -> ShowS | |
Generic ContextSwitch Source # | |
Defined in Skylighting.Types Associated Types type Rep ContextSwitch :: Type -> Type | |
Binary ContextSwitch Source # | |
Defined in Skylighting.Types | |
type Rep ContextSwitch Source # | |
Defined in Skylighting.Types type Rep ContextSwitch = D1 ('MetaData "ContextSwitch" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "Pop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Push" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ContextName))) |
A syntax corresponds to a complete Kate syntax description.
The sShortname
field is derived from the filename.
Constructors
Syntax | |
Fields
|
Instances
Eq Syntax Source # | |
Data Syntax Source # | |
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 | |
Ord Syntax Source # | |
Read Syntax Source # | |
Defined in Skylighting.Types | |
Show Syntax Source # | |
Generic Syntax Source # | |
Binary Syntax Source # | |
type Rep Syntax Source # | |
Defined in Skylighting.Types type Rep Syntax = D1 ('MetaData "Syntax" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "Syntax" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "sShortname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sContexts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Context)))) :*: ((S1 ('MetaSel ('Just "sAuthor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "sLicense") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "sStartingContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))) |
Tokens
KeywordTok
corresponds to dsKeyword
in Kate syntax
descriptions, and so on.
Constructors
Instances
Enum TokenType Source # | |
Defined in Skylighting.Types | |
Eq TokenType Source # | |
Data TokenType Source # | |
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 | |
Ord TokenType Source # | |
Defined in Skylighting.Types | |
Read TokenType Source # | |
Defined in Skylighting.Types | |
Show TokenType Source # | |
Generic TokenType Source # | |
FromJSON TokenType Source # | |
Defined in Skylighting.Types | |
FromJSONKey TokenType Source # | JSON |
Defined in Skylighting.Types Methods fromJSONKey :: FromJSONKeyFunction TokenType fromJSONKeyList :: FromJSONKeyFunction [TokenType] | |
ToJSON TokenType Source # | |
Defined in Skylighting.Types Methods toEncoding :: TokenType -> Encoding toJSONList :: [TokenType] -> Value toEncodingList :: [TokenType] -> Encoding | |
ToJSONKey TokenType Source # | |
Defined in Skylighting.Types | |
Binary TokenType Source # | |
type Rep TokenType Source # | |
Defined in Skylighting.Types type Rep TokenType = D1 ('MetaData "TokenType" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" '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] Source #
A line of source: a list of labeled tokens.
Styles
data TokenStyle Source #
A TokenStyle
determines how a token is to be rendered.
Constructors
TokenStyle | |
Fields
|
Instances
Eq TokenStyle Source # | |
Defined in Skylighting.Types | |
Data TokenStyle Source # | |
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 | |
Ord TokenStyle Source # | |
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 | |
Read TokenStyle Source # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS TokenStyle readList :: ReadS [TokenStyle] readPrec :: ReadPrec TokenStyle readListPrec :: ReadPrec [TokenStyle] | |
Show TokenStyle Source # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> TokenStyle -> ShowS show :: TokenStyle -> String showList :: [TokenStyle] -> ShowS | |
Generic TokenStyle Source # | |
Defined in Skylighting.Types Associated Types type Rep TokenStyle :: Type -> Type | |
FromJSON TokenStyle Source # | The keywords used in KDE syntax
themes are used, e.g. |
Defined in Skylighting.Types | |
ToJSON TokenStyle Source # | |
Defined in Skylighting.Types Methods toJSON :: TokenStyle -> Value toEncoding :: TokenStyle -> Encoding toJSONList :: [TokenStyle] -> Value toEncodingList :: [TokenStyle] -> Encoding | |
Binary TokenStyle Source # | |
Defined in Skylighting.Types | |
type Rep TokenStyle Source # | |
Defined in Skylighting.Types type Rep TokenStyle = D1 ('MetaData "TokenStyle" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "TokenStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "tokenBackground") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "tokenBold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "tokenItalic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "tokenUnderline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) |
defStyle :: TokenStyle Source #
Default style.
A color (redgreenblue).
Constructors
RGB Word8 Word8 Word8 |
Instances
Eq Color Source # | |
Data Color Source # | |
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 | |
Ord Color Source # | |
Read Color Source # | |
Defined in Skylighting.Types | |
Show Color Source # | |
Generic Color Source # | |
FromJSON Color Source # | JSON |
Defined in Skylighting.Types | |
ToJSON Color Source # | |
Defined in Skylighting.Types Methods toEncoding :: Color -> Encoding toJSONList :: [Color] -> Value toEncodingList :: [Color] -> Encoding | |
Binary Color Source # | |
type Rep Color Source # | |
Defined in Skylighting.Types type Rep Color = D1 ('MetaData "Color" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "RGB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))) |
class ToColor a where Source #
Things that can be converted to a color.
Instances
ToColor Int Source # | |
Defined in Skylighting.Types | |
ToColor String Source # | |
Defined in Skylighting.Types | |
ToColor Xterm256ColorCode Source # | |
Defined in Skylighting.Types Methods toColor :: Xterm256ColorCode -> Maybe Color Source # | |
(RealFrac a, Floating a) => ToColor (Colour a) Source # | |
Defined in Skylighting.Types | |
ToColor (ColorIntensity, Color) Source # | |
Defined in Skylighting.Types | |
ToColor (Double, Double, Double) Source # | |
Defined in Skylighting.Types | |
ToColor (Word8, Word8, Word8) Source # | |
Defined in Skylighting.Types |
class FromColor a where Source #
Different representations of a Color
.
Instances
FromColor String Source # | |
Defined in Skylighting.Types | |
FromColor Xterm256ColorCode Source # | Warning: this conversion is noticeably approximate! |
Defined in Skylighting.Types Methods fromColor :: Color -> Xterm256ColorCode Source # | |
(Ord a, Floating a) => FromColor (Colour a) Source # | |
Defined in Skylighting.Types | |
FromColor (ColorIntensity, Color) Source # | Warning: this conversion is extremely approximate! |
Defined in Skylighting.Types | |
FromColor (Double, Double, Double) Source # | |
Defined in Skylighting.Types | |
FromColor (Word8, Word8, Word8) Source # | |
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
Eq Style Source # | |
Data Style Source # | |
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 | |
Ord Style Source # | |
Read Style Source # | |
Defined in Skylighting.Types | |
Show Style Source # | |
Generic Style Source # | |
FromJSON Style Source # | The FromJSON instance for |
Defined in Skylighting.Types | |
ToJSON Style Source # | |
Defined in Skylighting.Types Methods toEncoding :: Style -> Encoding toJSONList :: [Style] -> Value toEncodingList :: [Style] -> Encoding | |
Binary Style Source # | |
type Rep Style Source # | |
Defined in Skylighting.Types type Rep Style = D1 ('MetaData "Style" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenStyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map TokenType TokenStyle)) :*: S1 ('MetaSel ('Just "defaultColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "backgroundColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "lineNumberColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "lineNumberBackgroundColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Color)))))) |
data ANSIColorLevel Source #
The available levels of color complexity in ANSI terminal output.
Constructors
ANSI16Color | 16-color mode |
ANSI256Color | 256-color mode |
ANSITrueColor | True-color mode |
Instances
Bounded ANSIColorLevel Source # | |
Defined in Skylighting.Types | |
Enum ANSIColorLevel Source # | |
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] | |
Eq ANSIColorLevel Source # | |
Defined in Skylighting.Types Methods (==) :: ANSIColorLevel -> ANSIColorLevel -> Bool (/=) :: ANSIColorLevel -> ANSIColorLevel -> Bool | |
Data ANSIColorLevel Source # | |
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 | |
Ord ANSIColorLevel Source # | |
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 | |
Read ANSIColorLevel Source # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS ANSIColorLevel readList :: ReadS [ANSIColorLevel] readPrec :: ReadPrec ANSIColorLevel readListPrec :: ReadPrec [ANSIColorLevel] | |
Show ANSIColorLevel Source # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> ANSIColorLevel -> ShowS show :: ANSIColorLevel -> String showList :: [ANSIColorLevel] -> ShowS | |
Generic ANSIColorLevel Source # | |
Defined in Skylighting.Types Associated Types type Rep ANSIColorLevel :: Type -> Type | |
Binary ANSIColorLevel Source # | |
Defined in Skylighting.Types | |
type Rep ANSIColorLevel Source # | |
Defined in Skylighting.Types type Rep ANSIColorLevel = D1 ('MetaData "ANSIColorLevel" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" '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))) |
newtype Xterm256ColorCode Source #
Constructors
Xterm256ColorCode | |
Fields
|
Instances
Format options
data FormatOptions Source #
Options for formatting source code.
Constructors
FormatOptions | |
Fields
|
Instances
Eq FormatOptions Source # | |
Defined in Skylighting.Types | |
Data FormatOptions Source # | |
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 | |
Ord FormatOptions Source # | |
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 | |
Read FormatOptions Source # | |
Defined in Skylighting.Types Methods readsPrec :: Int -> ReadS FormatOptions readList :: ReadS [FormatOptions] readPrec :: ReadPrec FormatOptions readListPrec :: ReadPrec [FormatOptions] | |
Show FormatOptions Source # | |
Defined in Skylighting.Types Methods showsPrec :: Int -> FormatOptions -> ShowS show :: FormatOptions -> String showList :: [FormatOptions] -> ShowS | |
Generic FormatOptions Source # | |
Defined in Skylighting.Types Associated Types type Rep FormatOptions :: Type -> Type | |
Binary FormatOptions Source # | |
Defined in Skylighting.Types | |
type Rep FormatOptions Source # | |
Defined in Skylighting.Types type Rep FormatOptions = D1 ('MetaData "FormatOptions" "Skylighting.Types" "skylighting-core-0.8.5-KgRoxuwbfovIpPCHBHpc92" 'False) (C1 ('MetaCons "FormatOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "numberLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "startNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "lineAnchors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "titleAttributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "codeClasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "containerClasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :*: (S1 ('MetaSel ('Just "lineIdPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ansiColorLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ANSIColorLevel))))) |
defaultFormatOpts :: FormatOptions Source #
Default formatting options.