skylighting-0.5: syntax highlighting library

Safe HaskellNone
LanguageHaskell2010

Skylighting.Types

Contents

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.

Instances

Eq KeywordAttr Source # 
Data KeywordAttr Source # 

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 :: (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 # 
Read KeywordAttr Source # 
Show KeywordAttr Source # 
Generic KeywordAttr Source # 

Associated Types

type Rep KeywordAttr :: * -> * #

Binary KeywordAttr Source # 
type Rep KeywordAttr Source # 
type Rep KeywordAttr = D1 (MetaData "KeywordAttr" "Skylighting.Types" "skylighting-0.5-2VXnaQQisn4DMP23E04Zw" False) (C1 (MetaCons "KeywordAttr" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "keywordCaseSensitive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "keywordDelims") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Char)))))

data WordSet a Source #

A set of "words," possibly case insensitive.

Instances

Eq a => Eq (WordSet a) Source # 

Methods

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

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

(Ord a, Data a) => Data (WordSet a) Source # 

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 :: (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 # 

Methods

compare :: WordSet a -> WordSet a -> Ordering #

(<) :: WordSet a -> WordSet a -> Bool #

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

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

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

max :: WordSet a -> WordSet a -> WordSet a #

min :: WordSet a -> WordSet a -> WordSet a #

(Ord a, Read a) => Read (WordSet a) Source # 
Show a => Show (WordSet a) Source # 

Methods

showsPrec :: Int -> WordSet a -> ShowS #

show :: WordSet a -> String #

showList :: [WordSet a] -> ShowS #

Generic (WordSet a) Source # 

Associated Types

type Rep (WordSet a) :: * -> * #

Methods

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

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

Binary a => Binary (WordSet a) Source # 

Methods

put :: WordSet a -> Put #

get :: Get (WordSet a) #

putList :: [WordSet a] -> Put #

type Rep (WordSet a) Source # 
type Rep (WordSet a) = D1 (MetaData "WordSet" "Skylighting.Types" "skylighting-0.5-2VXnaQQisn4DMP23E04Zw" False) ((:+:) (C1 (MetaCons "CaseSensitiveWords" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set a)))) (C1 (MetaCons "CaseInsensitiveWords" PrefixI False) (S1 (MetaSel (Nothing 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.

data Matcher Source #

Matchers correspond to the element types in a context.

Instances

Eq Matcher Source # 

Methods

(==) :: Matcher -> Matcher -> Bool #

(/=) :: Matcher -> Matcher -> Bool #

Data Matcher Source # 

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 #

toConstr :: Matcher -> Constr #

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 :: (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 # 
Show Matcher Source # 
Generic Matcher Source # 

Associated Types

type Rep Matcher :: * -> * #

Methods

from :: Matcher -> Rep Matcher x #

to :: Rep Matcher x -> Matcher #

Binary Matcher Source # 

Methods

put :: Matcher -> Put #

get :: Get Matcher #

putList :: [Matcher] -> Put #

type Rep Matcher Source # 
type Rep Matcher = D1 (MetaData "Matcher" "Skylighting.Types" "skylighting-0.5-2VXnaQQisn4DMP23E04Zw" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DetectChar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))) (C1 (MetaCons "Detect2Chars" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))))) ((:+:) (C1 (MetaCons "AnyChar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Char]))) (C1 (MetaCons "RangeDetect" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)))))) ((:+:) ((:+:) (C1 (MetaCons "StringDetect" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "WordDetect" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) ((:+:) (C1 (MetaCons "RegExpr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RE))) ((:+:) (C1 (MetaCons "Keyword" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KeywordAttr)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (WordSet Text))))) (C1 (MetaCons "Int" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Float" PrefixI False) U1) (C1 (MetaCons "HlCOct" PrefixI False) U1)) ((:+:) (C1 (MetaCons "HlCHex" PrefixI False) U1) (C1 (MetaCons "HlCStringChar" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "HlCChar" PrefixI False) U1) (C1 (MetaCons "LineContinue" PrefixI False) U1)) ((:+:) (C1 (MetaCons "IncludeRules" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContextName))) ((:+:) (C1 (MetaCons "DetectSpaces" PrefixI False) U1) (C1 (MetaCons "DetectIdentifier" PrefixI False) U1))))))

data Rule Source #

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

Instances

Eq Rule Source # 

Methods

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

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

Data Rule Source # 

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 #

toConstr :: Rule -> Constr #

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 :: (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 # 

Methods

compare :: Rule -> Rule -> Ordering #

(<) :: Rule -> Rule -> Bool #

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

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

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

max :: Rule -> Rule -> Rule #

min :: Rule -> Rule -> Rule #

Read Rule Source # 
Show Rule Source # 

Methods

showsPrec :: Int -> Rule -> ShowS #

show :: Rule -> String #

showList :: [Rule] -> ShowS #

Generic Rule Source # 

Associated Types

type Rep Rule :: * -> * #

Methods

from :: Rule -> Rep Rule x #

to :: Rep Rule x -> Rule #

Binary Rule Source # 

Methods

put :: Rule -> Put #

get :: Get Rule #

putList :: [Rule] -> Put #

type Rep Rule Source # 

data Context Source #

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

Instances

Eq Context Source # 

Methods

(==) :: Context -> Context -> Bool #

(/=) :: Context -> Context -> Bool #

Data Context Source # 

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 #

toConstr :: Context -> Constr #

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 :: (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 # 
Show Context Source # 
Generic Context Source # 

Associated Types

type Rep Context :: * -> * #

Methods

from :: Context -> Rep Context x #

to :: Rep Context x -> Context #

Binary Context Source # 

Methods

put :: Context -> Put #

get :: Get Context #

putList :: [Context] -> Put #

type Rep Context Source # 

data ContextSwitch Source #

A context switch, either pops or pushes a context.

Constructors

Pop 
Push ContextName 

Instances

Eq ContextSwitch Source # 
Data ContextSwitch Source # 

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 :: (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 # 
Read ContextSwitch Source # 
Show ContextSwitch Source # 
Generic ContextSwitch Source # 

Associated Types

type Rep ContextSwitch :: * -> * #

Binary ContextSwitch Source # 
type Rep ContextSwitch Source # 
type Rep ContextSwitch = D1 (MetaData "ContextSwitch" "Skylighting.Types" "skylighting-0.5-2VXnaQQisn4DMP23E04Zw" False) ((:+:) (C1 (MetaCons "Pop" PrefixI False) U1) (C1 (MetaCons "Push" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContextName))))

data Syntax Source #

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

Instances

Eq Syntax Source # 

Methods

(==) :: Syntax -> Syntax -> Bool #

(/=) :: Syntax -> Syntax -> Bool #

Data Syntax Source # 

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 #

toConstr :: Syntax -> Constr #

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 :: (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 # 
Show Syntax Source # 
Generic Syntax Source # 

Associated Types

type Rep Syntax :: * -> * #

Methods

from :: Syntax -> Rep Syntax x #

to :: Rep Syntax x -> Syntax #

Binary Syntax Source # 

Methods

put :: Syntax -> Put #

get :: Get Syntax #

putList :: [Syntax] -> Put #

type Rep Syntax Source # 

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

Enum TokenType Source # 
Eq TokenType Source # 
Data TokenType Source # 

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 :: (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 # 
Read TokenType Source # 
Show TokenType Source # 
Generic TokenType Source # 

Associated Types

type Rep TokenType :: * -> * #

FromJSON TokenType Source # 
FromJSONKey TokenType Source #

JSON Keyword corresponds to KeywordTok, and so on.

ToJSON TokenType Source # 
ToJSONKey TokenType Source # 
Binary TokenType Source # 
type Rep TokenType Source # 
type Rep TokenType = D1 (MetaData "TokenType" "Skylighting.Types" "skylighting-0.5-2VXnaQQisn4DMP23E04Zw" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "KeywordTok" PrefixI False) U1) ((:+:) (C1 (MetaCons "DataTypeTok" PrefixI False) U1) (C1 (MetaCons "DecValTok" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "BaseNTok" PrefixI False) U1) (C1 (MetaCons "FloatTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ConstantTok" PrefixI False) U1) (C1 (MetaCons "CharTok" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SpecialCharTok" PrefixI False) U1) (C1 (MetaCons "StringTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VerbatimStringTok" PrefixI False) U1) (C1 (MetaCons "SpecialStringTok" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "ImportTok" PrefixI False) U1) (C1 (MetaCons "CommentTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DocumentationTok" PrefixI False) U1) (C1 (MetaCons "AnnotationTok" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CommentVarTok" PrefixI False) U1) (C1 (MetaCons "OtherTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FunctionTok" PrefixI False) U1) (C1 (MetaCons "VariableTok" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "ControlFlowTok" PrefixI False) U1) (C1 (MetaCons "OperatorTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BuiltInTok" PrefixI False) U1) (C1 (MetaCons "ExtensionTok" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PreprocessorTok" PrefixI False) U1) (C1 (MetaCons "AttributeTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RegionMarkerTok" PrefixI False) U1) (C1 (MetaCons "InformationTok" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "WarningTok" PrefixI False) U1) (C1 (MetaCons "AlertTok" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ErrorTok" PrefixI False) U1) (C1 (MetaCons "NormalTok" PrefixI False) U1))))))

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

Eq TokenStyle Source # 
Data TokenStyle Source # 

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 :: (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 # 
Read TokenStyle Source # 
Show TokenStyle Source # 
Generic TokenStyle Source # 

Associated Types

type Rep TokenStyle :: * -> * #

FromJSON TokenStyle Source #

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

ToJSON TokenStyle Source # 
Binary TokenStyle Source # 
type Rep TokenStyle Source # 

defStyle :: TokenStyle Source #

Default style.

data Color Source #

A color (redgreenblue).

Constructors

RGB Word8 Word8 Word8 

Instances

Eq Color Source # 

Methods

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

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

Data Color Source # 

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 #

toConstr :: Color -> Constr #

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 :: (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 # 

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

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

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

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color Source # 
Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 

Associated Types

type Rep Color :: * -> * #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

FromJSON Color Source #

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

ToJSON Color Source # 
Binary Color Source # 

Methods

put :: Color -> Put #

get :: Get Color #

putList :: [Color] -> Put #

type Rep Color Source # 

class ToColor a where Source #

Things that can be converted to a color.

Minimal complete definition

toColor

Methods

toColor :: a -> Maybe Color Source #

class FromColor a where Source #

Different representations of a Color.

Minimal complete definition

fromColor

Methods

fromColor :: Color -> a Source #

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

Eq Style Source # 

Methods

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

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

Data Style Source # 

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 #

toConstr :: Style -> Constr #

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 :: (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 # 

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

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

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

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

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

Read Style Source # 
Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style Source # 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

FromJSON Style Source #

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

ToJSON Style Source # 
Binary Style Source # 

Methods

put :: Style -> Put #

get :: Get Style #

putList :: [Style] -> Put #

type Rep Style Source # 

Format options

data FormatOptions Source #

Options for formatting source code.

Constructors

FormatOptions 

Fields

Instances

Eq FormatOptions Source # 
Data FormatOptions Source # 

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 :: (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 # 
Read FormatOptions Source # 
Show FormatOptions Source # 
Generic FormatOptions Source # 

Associated Types

type Rep FormatOptions :: * -> * #

Binary FormatOptions Source # 
type Rep FormatOptions Source # 

defaultFormatOpts :: FormatOptions Source #

Default formatting options.