Copyright | Copyright (C) 2008 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
Definitions for data structures needed by highlighting-kate.
- type Context = (String, String)
- type ContextStack = [Context]
- data SyntaxState = SyntaxState {}
- defaultSyntaxState :: SyntaxState
- type Token = (TokenType, String)
- data TokenType
- = KeywordTok
- | DataTypeTok
- | DecValTok
- | BaseNTok
- | FloatTok
- | ConstantTok
- | CharTok
- | SpecialCharTok
- | StringTok
- | VerbatimStringTok
- | SpecialStringTok
- | ImportTok
- | CommentTok
- | DocumentationTok
- | AnnotationTok
- | CommentVarTok
- | OtherTok
- | FunctionTok
- | VariableTok
- | ControlFlowTok
- | OperatorTok
- | BuiltInTok
- | ExtensionTok
- | PreprocessorTok
- | AttributeTok
- | RegionMarkerTok
- | InformationTok
- | WarningTok
- | AlertTok
- | ErrorTok
- | NormalTok
- type SourceLine = [Token]
- type KateParser = GenParser Char SyntaxState
- data TokenStyle = TokenStyle {}
- defStyle :: TokenStyle
- data Color = RGB Word8 Word8 Word8
- class ToColor a where
- class FromColor a where
- data Style = Style {}
- data FormatOptions = FormatOptions {
- numberLines :: Bool
- startNumber :: Int
- lineAnchors :: Bool
- titleAttributes :: Bool
- codeClasses :: [String]
- containerClasses :: [String]
- defaultFormatOpts :: FormatOptions
Documentation
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.
SyntaxState | |
|
type SourceLine = [Token] Source
A line of source, list of labeled source items.
type KateParser = GenParser Char SyntaxState Source
data TokenStyle Source
TokenStyle | |
|
data FormatOptions Source
Options for formatting source code.
FormatOptions | |
|