skylighting-core-0.14.3: syntax highlighting library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Skylighting.Types

Description

Basic types for Skylighting.

Synopsis

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 

Instances

Instances details
Data KeywordAttr Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeywordAttr Source #

toConstr :: KeywordAttr -> Constr Source #

dataTypeOf :: KeywordAttr -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KeywordAttr) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeywordAttr) Source #

gmapT :: (forall b. Data b => b -> b) -> KeywordAttr -> KeywordAttr Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> KeywordAttr -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeywordAttr -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr Source #

Generic KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep KeywordAttr :: Type -> Type Source #

Read KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

Show KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

Binary KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

Eq KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

Ord KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

type Rep KeywordAttr Source # 
Instance details

Defined in Skylighting.Types

type Rep KeywordAttr = D1 ('MetaData "KeywordAttr" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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))))

data WordSet a Source #

A set of "words," possibly case insensitive.

Instances

Instances details
(Data a, Ord a) => Data (WordSet a) Source # 
Instance details

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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WordSet a) Source #

toConstr :: WordSet a -> Constr Source #

dataTypeOf :: WordSet a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WordSet a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WordSet a)) Source #

gmapT :: (forall b. Data b => b -> b) -> WordSet a -> WordSet a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WordSet a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WordSet a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WordSet a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WordSet a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) Source #

Generic (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep (WordSet a) :: Type -> Type Source #

Methods

from :: WordSet a -> Rep (WordSet a) x Source #

to :: Rep (WordSet a) x -> WordSet a Source #

(Read a, Ord a) => Read (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

Show a => Show (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

Binary a => Binary (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

Methods

put :: WordSet a -> Put Source #

get :: Get (WordSet a) Source #

putList :: [WordSet a] -> Put Source #

Eq a => Eq (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: WordSet a -> WordSet a -> Bool Source #

(/=) :: WordSet a -> WordSet a -> Bool Source #

Ord a => Ord (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

type Rep (WordSet a) Source # 
Instance details

Defined in Skylighting.Types

type Rep (WordSet a) = D1 ('MetaData "WordSet" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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 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.

data ListItem Source #

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

Instances details
Data ListItem Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListItem Source #

toConstr :: ListItem -> Constr Source #

dataTypeOf :: ListItem -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ListItem) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListItem) Source #

gmapT :: (forall b. Data b => b -> b) -> ListItem -> ListItem Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListItem -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListItem -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ListItem -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListItem -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListItem -> m ListItem Source #

Generic ListItem Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep ListItem :: Type -> Type Source #

Read ListItem Source # 
Instance details

Defined in Skylighting.Types

Show ListItem Source # 
Instance details

Defined in Skylighting.Types

Binary ListItem Source # 
Instance details

Defined in Skylighting.Types

Eq ListItem Source # 
Instance details

Defined in Skylighting.Types

Ord ListItem Source # 
Instance details

Defined in Skylighting.Types

type Rep ListItem Source # 
Instance details

Defined in Skylighting.Types

type Rep ListItem = D1 ('MetaData "ListItem" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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))))

data Matcher Source #

Matchers correspond to the element types in a context.

Instances

Instances details
Data Matcher Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Matcher Source #

toConstr :: Matcher -> Constr Source #

dataTypeOf :: Matcher -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Matcher) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Matcher) Source #

gmapT :: (forall b. Data b => b -> b) -> Matcher -> Matcher Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Matcher -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Matcher -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Matcher -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Matcher -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Matcher -> m Matcher Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Matcher -> m Matcher Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Matcher -> m Matcher Source #

Generic Matcher Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Matcher :: Type -> Type Source #

Read Matcher Source # 
Instance details

Defined in Skylighting.Types

Show Matcher Source # 
Instance details

Defined in Skylighting.Types

Binary Matcher Source # 
Instance details

Defined in Skylighting.Types

Eq Matcher Source # 
Instance details

Defined in Skylighting.Types

Ord Matcher Source # 
Instance details

Defined in Skylighting.Types

type Rep Matcher Source # 
Instance details

Defined in Skylighting.Types

type Rep Matcher = D1 ('MetaData "Matcher" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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))))))

data Rule Source #

A rule corresponds to one of the elements of a Kate syntax highlighting "context."

Instances

Instances details
Data Rule Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rule Source #

toConstr :: Rule -> Constr Source #

dataTypeOf :: Rule -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rule) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule) Source #

gmapT :: (forall b. Data b => b -> b) -> Rule -> Rule Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Rule -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rule -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rule -> m Rule Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule Source #

Generic Rule Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Rule :: Type -> Type Source #

Methods

from :: Rule -> Rep Rule x Source #

to :: Rep Rule x -> Rule Source #

Read Rule Source # 
Instance details

Defined in Skylighting.Types

Show Rule Source # 
Instance details

Defined in Skylighting.Types

Binary Rule Source # 
Instance details

Defined in Skylighting.Types

Eq Rule Source # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: Rule -> Rule -> Bool Source #

(/=) :: Rule -> Rule -> Bool Source #

Ord Rule Source # 
Instance details

Defined in Skylighting.Types

type Rep Rule Source # 
Instance details

Defined in Skylighting.Types

data Context Source #

A Context corresponds to a context element in a Kate syntax description.

Instances

Instances details
Data Context Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Context Source #

toConstr :: Context -> Constr Source #

dataTypeOf :: Context -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Context) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Context) Source #

gmapT :: (forall b. Data b => b -> b) -> Context -> Context Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Context -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Context -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Context -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Context -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Context -> m Context Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Context -> m Context Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Context -> m Context Source #

Generic Context Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Context :: Type -> Type Source #

Read Context Source # 
Instance details

Defined in Skylighting.Types

Show Context Source # 
Instance details

Defined in Skylighting.Types

Binary Context Source # 
Instance details

Defined in Skylighting.Types

Eq Context Source # 
Instance details

Defined in Skylighting.Types

Ord Context Source # 
Instance details

Defined in Skylighting.Types

type Rep Context Source # 
Instance details

Defined in Skylighting.Types

data ContextSwitch Source #

A context switch, either pops or pushes a context.

Constructors

Pop 
Push !ContextName 

Instances

Instances details
Data ContextSwitch Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContextSwitch Source #

toConstr :: ContextSwitch -> Constr Source #

dataTypeOf :: ContextSwitch -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ContextSwitch) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContextSwitch) Source #

gmapT :: (forall b. Data b => b -> b) -> ContextSwitch -> ContextSwitch Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ContextSwitch -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContextSwitch -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch Source #

Generic ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep ContextSwitch :: Type -> Type Source #

Read ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

Show ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

Binary ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

Eq ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

Ord ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

type Rep ContextSwitch Source # 
Instance details

Defined in Skylighting.Types

type Rep ContextSwitch = D1 ('MetaData "ContextSwitch" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" 'False) (C1 ('MetaCons "Pop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Push" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContextName)))

data Syntax Source #

A syntax corresponds to a complete Kate syntax description. The sShortname field is derived from the filename.

Instances

Instances details
Data Syntax Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Syntax Source #

toConstr :: Syntax -> Constr Source #

dataTypeOf :: Syntax -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Syntax) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Syntax) Source #

gmapT :: (forall b. Data b => b -> b) -> Syntax -> Syntax Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Syntax -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Syntax -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Syntax -> m Syntax Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Syntax -> m Syntax Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Syntax -> m Syntax Source #

Generic Syntax Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Syntax :: Type -> Type Source #

Read Syntax Source # 
Instance details

Defined in Skylighting.Types

Show Syntax Source # 
Instance details

Defined in Skylighting.Types

Binary Syntax Source # 
Instance details

Defined in Skylighting.Types

Eq Syntax Source # 
Instance details

Defined in Skylighting.Types

Ord Syntax Source # 
Instance details

Defined in Skylighting.Types

type Rep Syntax Source # 
Instance details

Defined in Skylighting.Types

type SyntaxMap = Map Text Syntax Source #

A map of syntaxes, keyed by full name.

Tokens

type Token = (TokenType, Text) Source #

A pair consisting of a list of attributes and some text.

data TokenType Source #

KeywordTok corresponds to dsKeyword in Kate syntax descriptions, and so on.

Instances

Instances details
FromJSON TokenType Source # 
Instance details

Defined in Skylighting.Types

FromJSONKey TokenType Source #

JSON Keyword corresponds to KeywordTok, and so on.

Instance details

Defined in Skylighting.Types

ToJSON TokenType Source # 
Instance details

Defined in Skylighting.Types

ToJSONKey TokenType Source # 
Instance details

Defined in Skylighting.Types

Data TokenType Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenType Source #

toConstr :: TokenType -> Constr Source #

dataTypeOf :: TokenType -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenType) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType) Source #

gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TokenType -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenType -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType Source #

Bounded TokenType Source # 
Instance details

Defined in Skylighting.Types

Enum TokenType Source # 
Instance details

Defined in Skylighting.Types

Generic TokenType Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep TokenType :: Type -> Type Source #

Read TokenType Source # 
Instance details

Defined in Skylighting.Types

Show TokenType Source # 
Instance details

Defined in Skylighting.Types

Binary TokenType Source # 
Instance details

Defined in Skylighting.Types

Eq TokenType Source # 
Instance details

Defined in Skylighting.Types

Ord TokenType Source # 
Instance details

Defined in Skylighting.Types

type Rep TokenType Source # 
Instance details

Defined in Skylighting.Types

type Rep TokenType = D1 ('MetaData "TokenType" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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.

newtype LineNo Source #

Line numbers

Constructors

LineNo 

Fields

Styles

data TokenStyle Source #

A TokenStyle determines how a token is to be rendered.

Instances

Instances details
FromJSON TokenStyle Source #

The keywords used in KDE syntax themes are used, e.g. text-color for default token color.

Instance details

Defined in Skylighting.Types

ToJSON TokenStyle Source # 
Instance details

Defined in Skylighting.Types

Data TokenStyle Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenStyle Source #

toConstr :: TokenStyle -> Constr Source #

dataTypeOf :: TokenStyle -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenStyle) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenStyle) Source #

gmapT :: (forall b. Data b => b -> b) -> TokenStyle -> TokenStyle Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenStyle -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenStyle -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TokenStyle -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenStyle -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle Source #

Generic TokenStyle Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep TokenStyle :: Type -> Type Source #

Read TokenStyle Source # 
Instance details

Defined in Skylighting.Types

Show TokenStyle Source # 
Instance details

Defined in Skylighting.Types

Binary TokenStyle Source # 
Instance details

Defined in Skylighting.Types

Eq TokenStyle Source # 
Instance details

Defined in Skylighting.Types

Ord TokenStyle Source # 
Instance details

Defined in Skylighting.Types

type Rep TokenStyle Source # 
Instance details

Defined in Skylighting.Types

type Rep TokenStyle = D1 ('MetaData "TokenStyle" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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 Source #

Default style.

data Color Source #

A color (red, green, blue).

Constructors

RGB Word8 Word8 Word8 

Instances

Instances details
FromJSON Color Source #

JSON "#1aff2b" corresponds to the color RGB 0x1a 0xff 0x2b.

Instance details

Defined in Skylighting.Types

ToJSON Color Source # 
Instance details

Defined in Skylighting.Types

Data Color Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Color Source #

toConstr :: Color -> Constr Source #

dataTypeOf :: Color -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Color) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color) Source #

gmapT :: (forall b. Data b => b -> b) -> Color -> Color Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Color -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Color -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Color -> m Color Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color Source #

Generic Color Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Color :: Type -> Type Source #

Methods

from :: Color -> Rep Color x Source #

to :: Rep Color x -> Color Source #

Read Color Source # 
Instance details

Defined in Skylighting.Types

Show Color Source # 
Instance details

Defined in Skylighting.Types

Binary Color Source # 
Instance details

Defined in Skylighting.Types

Eq Color Source # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: Color -> Color -> Bool Source #

(/=) :: Color -> Color -> Bool Source #

Ord Color Source # 
Instance details

Defined in Skylighting.Types

type Rep Color Source # 
Instance details

Defined in Skylighting.Types

class ToColor a where Source #

Things that can be converted to a color.

Methods

toColor :: a -> Maybe Color Source #

Instances

Instances details
ToColor String Source # 
Instance details

Defined in Skylighting.Types

ToColor Int Source # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: Int -> Maybe Color Source #

(RealFrac a, Floating a) => ToColor (Colour a) Source # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: Colour a -> Maybe Color Source #

ToColor (Word8, Word8, Word8) Source # 
Instance details

Defined in Skylighting.Types

ToColor (Double, Double, Double) Source # 
Instance details

Defined in Skylighting.Types

class FromColor a where Source #

Different representations of a Color.

Methods

fromColor :: Color -> a Source #

Instances

Instances details
FromColor String Source # 
Instance details

Defined in Skylighting.Types

(Ord a, Floating a) => FromColor (Colour a) Source # 
Instance details

Defined in Skylighting.Types

Methods

fromColor :: Color -> Colour a Source #

FromColor (Word8, Word8, Word8) Source # 
Instance details

Defined in Skylighting.Types

FromColor (Double, Double, Double) Source # 
Instance details

Defined in Skylighting.Types

data Style Source #

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.

Instances

Instances details
FromJSON Style Source #

The FromJSON instance for Style is designed so that a KDE syntax theme (JSON) can be decoded directly as a Style.

Instance details

Defined in Skylighting.Types

ToJSON Style Source # 
Instance details

Defined in Skylighting.Types

Data Style Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Style Source #

toConstr :: Style -> Constr Source #

dataTypeOf :: Style -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Style) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style) Source #

gmapT :: (forall b. Data b => b -> b) -> Style -> Style Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Style -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Style -> m Style Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style Source #

Generic Style Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Style :: Type -> Type Source #

Methods

from :: Style -> Rep Style x Source #

to :: Rep Style x -> Style Source #

Read Style Source # 
Instance details

Defined in Skylighting.Types

Show Style Source # 
Instance details

Defined in Skylighting.Types

Binary Style Source # 
Instance details

Defined in Skylighting.Types

Eq Style Source # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: Style -> Style -> Bool Source #

(/=) :: Style -> Style -> Bool Source #

Ord Style Source # 
Instance details

Defined in Skylighting.Types

type Rep Style Source # 
Instance details

Defined in Skylighting.Types

type Rep Style = D1 ('MetaData "Style" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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 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

Instances details
Data ANSIColorLevel Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ANSIColorLevel Source #

toConstr :: ANSIColorLevel -> Constr Source #

dataTypeOf :: ANSIColorLevel -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ANSIColorLevel) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ANSIColorLevel) Source #

gmapT :: (forall b. Data b => b -> b) -> ANSIColorLevel -> ANSIColorLevel Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ANSIColorLevel -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ANSIColorLevel -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ANSIColorLevel -> m ANSIColorLevel Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ANSIColorLevel -> m ANSIColorLevel Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ANSIColorLevel -> m ANSIColorLevel Source #

Bounded ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Enum ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Generic ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep ANSIColorLevel :: Type -> Type Source #

Read ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Show ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Binary ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Eq ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

Ord ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

type Rep ANSIColorLevel Source # 
Instance details

Defined in Skylighting.Types

type Rep ANSIColorLevel = D1 ('MetaData "ANSIColorLevel" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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 Source #

Options for formatting source code.

Constructors

FormatOptions 

Fields

Instances

Instances details
Data FormatOptions Source # 
Instance details

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 Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FormatOptions Source #

toConstr :: FormatOptions -> Constr Source #

dataTypeOf :: FormatOptions -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FormatOptions) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FormatOptions) Source #

gmapT :: (forall b. Data b => b -> b) -> FormatOptions -> FormatOptions Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FormatOptions -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FormatOptions -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FormatOptions -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FormatOptions -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions Source #

Generic FormatOptions Source # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep FormatOptions :: Type -> Type Source #

Read FormatOptions Source # 
Instance details

Defined in Skylighting.Types

Show FormatOptions Source # 
Instance details

Defined in Skylighting.Types

Binary FormatOptions Source # 
Instance details

Defined in Skylighting.Types

Eq FormatOptions Source # 
Instance details

Defined in Skylighting.Types

Ord FormatOptions Source # 
Instance details

Defined in Skylighting.Types

type Rep FormatOptions Source # 
Instance details

Defined in Skylighting.Types

type Rep FormatOptions = D1 ('MetaData "FormatOptions" "Skylighting.Types" "skylighting-core-0.14.3-fHGReyGL10EpLOmm4HkSo" '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 Source #

Default formatting options.