highlighting-kate-0.6.2.1: Syntax highlighting

CopyrightCopyright (C) 2008 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Text.Highlighting.Kate.Types

Description

Definitions for data structures needed by highlighting-kate.

Synopsis

Documentation

type Context = (String, String) Source #

A context: pair of syntax name and context name.

type ContextStack = [Context] Source #

A stack of contexts. (Language-specific context stacks must be maintained because of IncludeRules.)

data SyntaxState Source #

State for syntax parser.

Constructors

SyntaxState 

Fields

type Token = (TokenType, String) Source #

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

data TokenType Source #

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 #

Read TokenType Source # 
Show TokenType Source # 

type SourceLine = [Token] Source #

A line of source, list of labeled source items.

data TokenStyle Source #

Instances

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 #

Read TokenStyle Source # 
Show TokenStyle Source # 

data Color Source #

Constructors

RGB Word8 Word8 Word8 

Instances

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 #

Read Color Source # 
Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

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 #

Instances

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 #

Read Style Source # 
Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

data FormatOptions Source #

Options for formatting source code.

Constructors

FormatOptions 

Fields