skylighting-core-0.8.4: syntax highlighting library
Safe HaskellNone
LanguageHaskell2010

Skylighting.Types

Description

Basic types for Skylighting.

Synopsis

Syntax descriptions

type ContextName = (Text, Text) #

Full name of a context: the first member of the pair is the full syntax name, the second the context name within that syntax.

data KeywordAttr #

Attributes controlling how keywords are interpreted.

Constructors

KeywordAttr 

Fields

Instances

Instances details
Eq KeywordAttr # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: KeywordAttr -> KeywordAttr -> Bool

(/=) :: KeywordAttr -> KeywordAttr -> Bool

Data KeywordAttr # 
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

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 # 
Instance details

Defined in Skylighting.Types

Read KeywordAttr # 
Instance details

Defined in Skylighting.Types

Show KeywordAttr # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> KeywordAttr -> ShowS

show :: KeywordAttr -> String

showList :: [KeywordAttr] -> ShowS

Generic KeywordAttr # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep KeywordAttr :: Type -> Type

Methods

from :: KeywordAttr -> Rep KeywordAttr x

to :: Rep KeywordAttr x -> KeywordAttr

Binary KeywordAttr # 
Instance details

Defined in Skylighting.Types

Methods

put :: KeywordAttr -> Put

get :: Get KeywordAttr

putList :: [KeywordAttr] -> Put

type Rep KeywordAttr # 
Instance details

Defined in Skylighting.Types

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

data WordSet a #

A set of "words," possibly case insensitive.

Constructors

CaseSensitiveWords (Set a) 
CaseInsensitiveWords (Set a) 

Instances

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

Defined in Skylighting.Types

Methods

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

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

(Data a, Ord a) => Data (WordSet a) # 
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)

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) # 
Instance details

Defined in Skylighting.Types

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

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

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS (WordSet a) #

readList :: ReadS [WordSet a] #

readPrec :: ReadPrec (WordSet a) #

readListPrec :: ReadPrec [WordSet a] #

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

Defined in Skylighting.Types

Methods

showsPrec :: Int -> WordSet a -> ShowS

show :: WordSet a -> String

showList :: [WordSet a] -> ShowS

Generic (WordSet a) # 
Instance details

Defined in Skylighting.Types

Associated Types

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

Methods

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

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

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

Defined in Skylighting.Types

Methods

put :: WordSet a -> Put

get :: Get (WordSet a)

putList :: [WordSet a] -> Put

type Rep (WordSet a) # 
Instance details

Defined in Skylighting.Types

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

A set of words to match (either case-sensitive or case-insensitive).

inWordSet :: (FoldCase a, Ord a) => a -> WordSet a -> Bool #

Test for membership in a WordSet.

data Matcher #

Matchers correspond to the element types in a context.

Instances

Instances details
Eq Matcher # 
Instance details

Defined in Skylighting.Types

Methods

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

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

Data Matcher # 
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

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 :: 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 # 
Instance details

Defined in Skylighting.Types

Methods

compare :: Matcher -> Matcher -> Ordering

(<) :: Matcher -> Matcher -> Bool

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

(>) :: Matcher -> Matcher -> Bool

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

max :: Matcher -> Matcher -> Matcher

min :: Matcher -> Matcher -> Matcher

Read Matcher # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS Matcher #

readList :: ReadS [Matcher] #

readPrec :: ReadPrec Matcher #

readListPrec :: ReadPrec [Matcher] #

Show Matcher # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Matcher -> ShowS

show :: Matcher -> String

showList :: [Matcher] -> ShowS

Generic Matcher # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Matcher :: Type -> Type

Methods

from :: Matcher -> Rep Matcher x

to :: Rep Matcher x -> Matcher

Binary Matcher # 
Instance details

Defined in Skylighting.Types

Methods

put :: Matcher -> Put

get :: Get Matcher

putList :: [Matcher] -> Put

type Rep Matcher # 
Instance details

Defined in Skylighting.Types

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

data Rule #

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

Constructors

Rule 

Fields

Instances

Instances details
Eq Rule # 
Instance details

Defined in Skylighting.Types

Methods

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

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

Data Rule # 
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

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 :: 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 # 
Instance details

Defined in Skylighting.Types

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 # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS Rule #

readList :: ReadS [Rule] #

readPrec :: ReadPrec Rule #

readListPrec :: ReadPrec [Rule] #

Show Rule # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Rule -> ShowS

show :: Rule -> String

showList :: [Rule] -> ShowS

Generic Rule # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Rule :: Type -> Type

Methods

from :: Rule -> Rep Rule x

to :: Rep Rule x -> Rule

Binary Rule # 
Instance details

Defined in Skylighting.Types

Methods

put :: Rule -> Put

get :: Get Rule

putList :: [Rule] -> Put

type Rep Rule # 
Instance details

Defined in Skylighting.Types

type Rep Rule = D1 ('MetaData "Rule" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" '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]))))))

data Context #

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

Instances

Instances details
Eq Context # 
Instance details

Defined in Skylighting.Types

Methods

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

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

Data Context # 
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

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 :: 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 # 
Instance details

Defined in Skylighting.Types

Methods

compare :: Context -> Context -> Ordering

(<) :: Context -> Context -> Bool

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

(>) :: Context -> Context -> Bool

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

max :: Context -> Context -> Context

min :: Context -> Context -> Context

Read Context # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS Context #

readList :: ReadS [Context] #

readPrec :: ReadPrec Context #

readListPrec :: ReadPrec [Context] #

Show Context # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Context -> ShowS

show :: Context -> String

showList :: [Context] -> ShowS

Generic Context # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Context :: Type -> Type

Methods

from :: Context -> Rep Context x

to :: Rep Context x -> Context

Binary Context # 
Instance details

Defined in Skylighting.Types

Methods

put :: Context -> Put

get :: Get Context

putList :: [Context] -> Put

type Rep Context # 
Instance details

Defined in Skylighting.Types

type Rep Context = D1 ('MetaData "Context" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" '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 #

A context switch, either pops or pushes a context.

Constructors

Pop 
Push ContextName 

Instances

Instances details
Eq ContextSwitch # 
Instance details

Defined in Skylighting.Types

Data ContextSwitch # 
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

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 # 
Instance details

Defined in Skylighting.Types

Read ContextSwitch # 
Instance details

Defined in Skylighting.Types

Show ContextSwitch # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> ContextSwitch -> ShowS

show :: ContextSwitch -> String

showList :: [ContextSwitch] -> ShowS

Generic ContextSwitch # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep ContextSwitch :: Type -> Type

Binary ContextSwitch # 
Instance details

Defined in Skylighting.Types

Methods

put :: ContextSwitch -> Put

get :: Get ContextSwitch

putList :: [ContextSwitch] -> Put

type Rep ContextSwitch # 
Instance details

Defined in Skylighting.Types

type Rep ContextSwitch = D1 ('MetaData "ContextSwitch" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" 'False) (C1 ('MetaCons "Pop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Push" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ContextName)))

data Syntax #

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

Constructors

Syntax 

Fields

Instances

Instances details
Eq Syntax # 
Instance details

Defined in Skylighting.Types

Methods

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

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

Data Syntax # 
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

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 :: 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 # 
Instance details

Defined in Skylighting.Types

Methods

compare :: Syntax -> Syntax -> Ordering

(<) :: Syntax -> Syntax -> Bool

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

(>) :: Syntax -> Syntax -> Bool

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

max :: Syntax -> Syntax -> Syntax

min :: Syntax -> Syntax -> Syntax

Read Syntax # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS Syntax #

readList :: ReadS [Syntax] #

readPrec :: ReadPrec Syntax #

readListPrec :: ReadPrec [Syntax] #

Show Syntax # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Syntax -> ShowS

show :: Syntax -> String

showList :: [Syntax] -> ShowS

Generic Syntax # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Syntax :: Type -> Type

Methods

from :: Syntax -> Rep Syntax x

to :: Rep Syntax x -> Syntax

Binary Syntax # 
Instance details

Defined in Skylighting.Types

Methods

put :: Syntax -> Put

get :: Get Syntax

putList :: [Syntax] -> Put

type Rep Syntax # 
Instance details

Defined in Skylighting.Types

type Rep Syntax = D1 ('MetaData "Syntax" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" '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))))))

type SyntaxMap = Map Text Syntax #

A map of syntaxes, keyed by full name.

Tokens

type Token = (TokenType, Text) #

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

data TokenType #

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

Instances

Instances details
Enum TokenType # 
Instance details

Defined in Skylighting.Types

Eq TokenType # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: TokenType -> TokenType -> Bool

(/=) :: TokenType -> TokenType -> Bool

Data TokenType # 
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

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 # 
Instance details

Defined in Skylighting.Types

Methods

compare :: TokenType -> TokenType -> Ordering

(<) :: TokenType -> TokenType -> Bool

(<=) :: TokenType -> TokenType -> Bool

(>) :: TokenType -> TokenType -> Bool

(>=) :: TokenType -> TokenType -> Bool

max :: TokenType -> TokenType -> TokenType

min :: TokenType -> TokenType -> TokenType

Read TokenType # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS TokenType #

readList :: ReadS [TokenType] #

readPrec :: ReadPrec TokenType #

readListPrec :: ReadPrec [TokenType] #

Show TokenType # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> TokenType -> ShowS

show :: TokenType -> String

showList :: [TokenType] -> ShowS

Generic TokenType # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep TokenType :: Type -> Type

Methods

from :: TokenType -> Rep TokenType x

to :: Rep TokenType x -> TokenType

Binary TokenType # 
Instance details

Defined in Skylighting.Types

Methods

put :: TokenType -> Put

get :: Get TokenType

putList :: [TokenType] -> Put

FromJSON TokenType # 
Instance details

Defined in Skylighting.Types

Methods

parseJSON :: Value -> Parser TokenType

parseJSONList :: Value -> Parser [TokenType]

FromJSONKey TokenType #

JSON Keyword corresponds to KeywordTok, and so on.

Instance details

Defined in Skylighting.Types

Methods

fromJSONKey :: FromJSONKeyFunction TokenType

fromJSONKeyList :: FromJSONKeyFunction [TokenType]

ToJSON TokenType # 
Instance details

Defined in Skylighting.Types

Methods

toJSON :: TokenType -> Value

toEncoding :: TokenType -> Encoding

toJSONList :: [TokenType] -> Value

toEncodingList :: [TokenType] -> Encoding

ToJSONKey TokenType # 
Instance details

Defined in Skylighting.Types

Methods

toJSONKey :: ToJSONKeyFunction TokenType

toJSONKeyList :: ToJSONKeyFunction [TokenType]

type Rep TokenType # 
Instance details

Defined in Skylighting.Types

type Rep TokenType = D1 ('MetaData "TokenType" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" 'False) ((((C1 ('MetaCons "KeywordTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataTypeTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecValTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BaseNTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FloatTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ConstantTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharTok" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "SpecialCharTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StringTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VerbatimStringTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpecialStringTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ImportTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CommentTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DocumentationTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnnotationTok" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "CommentVarTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FunctionTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VariableTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControlFlowTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OperatorTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BuiltInTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtensionTok" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "PreprocessorTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AttributeTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RegionMarkerTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InformationTok" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WarningTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlertTok" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorTok" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NormalTok" 'PrefixI 'False) (U1 :: Type -> Type))))))

type SourceLine = [Token] #

A line of source: a list of labeled tokens.

newtype LineNo #

Line numbers

Constructors

LineNo 

Fields

Instances

Instances details
Enum LineNo # 
Instance details

Defined in Skylighting.Types

Show LineNo # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> LineNo -> ShowS

show :: LineNo -> String

showList :: [LineNo] -> ShowS

Styles

data TokenStyle #

A TokenStyle determines how a token is to be rendered.

Constructors

TokenStyle 

Fields

Instances

Instances details
Eq TokenStyle # 
Instance details

Defined in Skylighting.Types

Methods

(==) :: TokenStyle -> TokenStyle -> Bool

(/=) :: TokenStyle -> TokenStyle -> Bool

Data TokenStyle # 
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

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 # 
Instance details

Defined in Skylighting.Types

Read TokenStyle # 
Instance details

Defined in Skylighting.Types

Show TokenStyle # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> TokenStyle -> ShowS

show :: TokenStyle -> String

showList :: [TokenStyle] -> ShowS

Generic TokenStyle # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep TokenStyle :: Type -> Type

Methods

from :: TokenStyle -> Rep TokenStyle x

to :: Rep TokenStyle x -> TokenStyle

Binary TokenStyle # 
Instance details

Defined in Skylighting.Types

Methods

put :: TokenStyle -> Put

get :: Get TokenStyle

putList :: [TokenStyle] -> Put

FromJSON TokenStyle #

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

Instance details

Defined in Skylighting.Types

Methods

parseJSON :: Value -> Parser TokenStyle

parseJSONList :: Value -> Parser [TokenStyle]

ToJSON TokenStyle # 
Instance details

Defined in Skylighting.Types

Methods

toJSON :: TokenStyle -> Value

toEncoding :: TokenStyle -> Encoding

toJSONList :: [TokenStyle] -> Value

toEncodingList :: [TokenStyle] -> Encoding

type Rep TokenStyle # 
Instance details

Defined in Skylighting.Types

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

Default style.

data Color #

A color (redgreenblue).

Constructors

RGB Word8 Word8 Word8 

Instances

Instances details
Eq Color # 
Instance details

Defined in Skylighting.Types

Methods

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

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

Data Color # 
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

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 :: 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 # 
Instance details

Defined in Skylighting.Types

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 # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS Color #

readList :: ReadS [Color] #

readPrec :: ReadPrec Color #

readListPrec :: ReadPrec [Color] #

Show Color # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Color -> ShowS

show :: Color -> String

showList :: [Color] -> ShowS

Generic Color # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Color :: Type -> Type

Methods

from :: Color -> Rep Color x

to :: Rep Color x -> Color

Binary Color # 
Instance details

Defined in Skylighting.Types

Methods

put :: Color -> Put

get :: Get Color

putList :: [Color] -> Put

FromJSON Color #

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

Instance details

Defined in Skylighting.Types

Methods

parseJSON :: Value -> Parser Color

parseJSONList :: Value -> Parser [Color]

ToJSON Color # 
Instance details

Defined in Skylighting.Types

Methods

toJSON :: Color -> Value

toEncoding :: Color -> Encoding

toJSONList :: [Color] -> Value

toEncodingList :: [Color] -> Encoding

type Rep Color # 
Instance details

Defined in Skylighting.Types

type Rep Color = D1 ('MetaData "Color" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" '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 #

Things that can be converted to a color.

Methods

toColor :: a -> Maybe Color #

Instances

Instances details
ToColor Int # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: Int -> Maybe Color #

ToColor String # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: String -> Maybe Color #

ToColor Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: Xterm256ColorCode -> Maybe Color #

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

Defined in Skylighting.Types

Methods

toColor :: Colour a -> Maybe Color #

ToColor (ColorIntensity, Color) # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: (ColorIntensity, Color) -> Maybe Color0 #

ToColor (Double, Double, Double) # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: (Double, Double, Double) -> Maybe Color #

ToColor (Word8, Word8, Word8) # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: (Word8, Word8, Word8) -> Maybe Color #

class FromColor a where #

Different representations of a Color.

Methods

fromColor :: Color -> a #

Instances

Instances details
FromColor String # 
Instance details

Defined in Skylighting.Types

Methods

fromColor :: Color -> String #

FromColor Xterm256ColorCode #

Warning: this conversion is noticeably approximate!

Instance details

Defined in Skylighting.Types

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

Defined in Skylighting.Types

Methods

fromColor :: Color -> Colour a #

FromColor (ColorIntensity, Color) #

Warning: this conversion is extremely approximate!

Instance details

Defined in Skylighting.Types

FromColor (Double, Double, Double) # 
Instance details

Defined in Skylighting.Types

Methods

fromColor :: Color -> (Double, Double, Double) #

FromColor (Word8, Word8, Word8) # 
Instance details

Defined in Skylighting.Types

Methods

fromColor :: Color -> (Word8, Word8, Word8) #

data Style #

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
Eq Style # 
Instance details

Defined in Skylighting.Types

Methods

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

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

Data Style # 
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

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 :: 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 # 
Instance details

Defined in Skylighting.Types

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 # 
Instance details

Defined in Skylighting.Types

Methods

readsPrec :: Int -> ReadS Style #

readList :: ReadS [Style] #

readPrec :: ReadPrec Style #

readListPrec :: ReadPrec [Style] #

Show Style # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Style -> ShowS

show :: Style -> String

showList :: [Style] -> ShowS

Generic Style # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Style :: Type -> Type

Methods

from :: Style -> Rep Style x

to :: Rep Style x -> Style

Binary Style # 
Instance details

Defined in Skylighting.Types

Methods

put :: Style -> Put

get :: Get Style

putList :: [Style] -> Put

FromJSON Style #

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

Methods

parseJSON :: Value -> Parser Style

parseJSONList :: Value -> Parser [Style]

ToJSON Style # 
Instance details

Defined in Skylighting.Types

Methods

toJSON :: Style -> Value

toEncoding :: Style -> Encoding

toJSONList :: [Style] -> Value

toEncodingList :: [Style] -> Encoding

type Rep Style # 
Instance details

Defined in Skylighting.Types

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

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
Bounded ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Enum ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Eq ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Data ANSIColorLevel # 
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

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 # 
Instance details

Defined in Skylighting.Types

Read ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Show ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> ANSIColorLevel -> ShowS

show :: ANSIColorLevel -> String

showList :: [ANSIColorLevel] -> ShowS

Generic ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep ANSIColorLevel :: Type -> Type

Binary ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

Methods

put :: ANSIColorLevel -> Put

get :: Get ANSIColorLevel

putList :: [ANSIColorLevel] -> Put

type Rep ANSIColorLevel # 
Instance details

Defined in Skylighting.Types

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

Constructors

Xterm256ColorCode 

Fields

Instances

Instances details
Bounded Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Enum Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Eq Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Data Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Xterm256ColorCode -> c Xterm256ColorCode

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Xterm256ColorCode

toConstr :: Xterm256ColorCode -> Constr

dataTypeOf :: Xterm256ColorCode -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Xterm256ColorCode)

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

gmapT :: (forall b. Data b => b -> b) -> Xterm256ColorCode -> Xterm256ColorCode

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xterm256ColorCode -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xterm256ColorCode -> r

gmapQ :: (forall d. Data d => d -> u) -> Xterm256ColorCode -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Xterm256ColorCode -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Xterm256ColorCode -> m Xterm256ColorCode

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Xterm256ColorCode -> m Xterm256ColorCode

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Xterm256ColorCode -> m Xterm256ColorCode

Ord Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Read Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Show Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Generic Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Xterm256ColorCode :: Type -> Type

Binary Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

FromColor Xterm256ColorCode #

Warning: this conversion is noticeably approximate!

Instance details

Defined in Skylighting.Types

ToColor Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

Methods

toColor :: Xterm256ColorCode -> Maybe Color #

type Rep Xterm256ColorCode # 
Instance details

Defined in Skylighting.Types

type Rep Xterm256ColorCode = D1 ('MetaData "Xterm256ColorCode" "Skylighting.Types" "skylighting-core-0.8.4-7diFu8365y4CXA46I2rja" 'True) (C1 ('MetaCons "Xterm256ColorCode" 'PrefixI 'True) (S1 ('MetaSel ('Just "getXterm256ColorCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))

Format options

data FormatOptions #

Options for formatting source code.

Constructors

FormatOptions 

Fields

Instances

Instances details
Eq FormatOptions # 
Instance details

Defined in Skylighting.Types

Data FormatOptions # 
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

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 # 
Instance details

Defined in Skylighting.Types

Read FormatOptions # 
Instance details

Defined in Skylighting.Types

Show FormatOptions # 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> FormatOptions -> ShowS

show :: FormatOptions -> String

showList :: [FormatOptions] -> ShowS

Generic FormatOptions # 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep FormatOptions :: Type -> Type

Binary FormatOptions # 
Instance details

Defined in Skylighting.Types

Methods

put :: FormatOptions -> Put

get :: Get FormatOptions

putList :: [FormatOptions] -> Put

type Rep FormatOptions # 
Instance details

Defined in Skylighting.Types

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

Default formatting options.