Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic types for Skylighting.
- type ContextName = (Text, Text)
- data KeywordAttr = KeywordAttr {}
- data WordSet a
- makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a
- inWordSet :: (FoldCase a, Ord a) => a -> WordSet a -> Bool
- data Matcher
- data Rule = Rule {
- rMatcher :: Matcher
- rAttribute :: TokenType
- rIncludeAttribute :: Bool
- rDynamic :: Bool
- rCaseSensitive :: Bool
- rChildren :: [Rule]
- rLookahead :: Bool
- rFirstNonspace :: Bool
- rColumn :: Maybe Int
- rContextSwitch :: [ContextSwitch]
- data Context = Context {
- cName :: Text
- cSyntax :: Text
- cRules :: [Rule]
- cAttribute :: TokenType
- cLineEmptyContext :: [ContextSwitch]
- cLineEndContext :: [ContextSwitch]
- cLineBeginContext :: [ContextSwitch]
- cFallthrough :: Bool
- cFallthroughContext :: [ContextSwitch]
- cDynamic :: Bool
- data ContextSwitch
- = Pop
- | Push ContextName
- data Syntax = Syntax {}
- type SyntaxMap = Map Text Syntax
- type Token = (TokenType, Text)
- 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]
- 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 :: [Text]
- containerClasses :: [Text]
- defaultFormatOpts :: FormatOptions
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.
A set of "words," possibly case insensitive.
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
.
Matchers correspond to the element types in a context.
A rule corresponds to one of the elements of a Kate syntax highlighting "context."
Rule | |
|
A Context corresponds to a context element in a Kate syntax description.
Context | |
|
data ContextSwitch Source #
A context switch, either pops or pushes a context.
A syntax corresponds to a complete Kate syntax description.
The sShortname
field is derived from the filename.
Tokens
KeywordTok
corresponds to dsKeyword
in Kate syntax
descriptions, 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.
TokenStyle | |
|
Eq TokenStyle Source # | |
Data TokenStyle Source # | |
Ord TokenStyle Source # | |
Read TokenStyle Source # | |
Show TokenStyle Source # | |
Generic TokenStyle Source # | |
FromJSON TokenStyle Source # | The keywords used in KDE syntax
themes are used, e.g. |
Binary TokenStyle Source # | |
type Rep TokenStyle Source # | |
defStyle :: TokenStyle Source #
Default style.
A color (redgreenblue).
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.
Eq Style Source # | |
Data Style Source # | |
Ord Style Source # | |
Read Style Source # | |
Show Style Source # | |
Generic Style Source # | |
FromJSON Style Source # | The FromJSON instance for |
Binary Style Source # | |
type Rep Style Source # | |
Format options
data FormatOptions Source #
Options for formatting source code.
FormatOptions | |
|
defaultFormatOpts :: FormatOptions Source #
Default formatting options.