skylighting-0.1.1.1: syntax highlighting library

Safe HaskellNone
LanguageHaskell2010

Skylighting.Types

Contents

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

Instances

Show a => Show (WordSet a) Source # 

Methods

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

show :: WordSet a -> String #

showList :: [WordSet a] -> ShowS #

makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a Source #

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

data Rule Source #

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

Instances

data Context Source #

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

Instances

data Syntax Source #

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

Instances

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

JSON Keyword corresponds to KeywordTok, and so on.

type SourceLine = [Token] Source #

A line of source: a list of labeled tokens.

Styles

data TokenStyle Source #

A TokenStyle determines how a token is to be rendered.

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

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

defStyle :: TokenStyle Source #

Default style.

data Color Source #

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 #

FromJSON Color Source #

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

class ToColor a where Source #

Minimal complete definition

toColor

Methods

toColor :: a -> Maybe Color Source #

class FromColor a where Source #

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 #

FromJSON Style Source #

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

Format options

data FormatOptions Source #

Options for formatting source code.

Constructors

FormatOptions 

Fields