| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Skylighting.Types
Description
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]
- newtype LineNo = LineNo {}
- data TokenStyle = TokenStyle {}
- defStyle :: TokenStyle
- data Color = RGB Word8 Word8 Word8
- class ToColor a where
- class FromColor a where
- data Style = Style {}
- data ANSIColorLevel
- newtype Xterm256ColorCode = Xterm256ColorCode {}
- data FormatOptions = FormatOptions {- numberLines :: Bool
- startNumber :: Int
- lineAnchors :: Bool
- titleAttributes :: Bool
- codeClasses :: [Text]
- containerClasses :: [Text]
- lineIdPrefix :: Text
- ansiColorLevel :: ANSIColorLevel
 
- 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.
Constructors
| KeywordAttr | |
| Fields | |
Instances
A set of "words," possibly case insensitive.
Instances
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."
Constructors
| Rule | |
| Fields 
 | |
A Context corresponds to a context element in a Kate syntax description.
Constructors
| Context | |
| Fields 
 | |
data ContextSwitch Source #
A context switch, either pops or pushes a context.
Constructors
| Pop | |
| Push ContextName | 
A syntax corresponds to a complete Kate syntax description.
 The sShortname field is derived from the filename.
Constructors
| Syntax | |
Tokens
KeywordTok corresponds to dsKeyword in Kate syntax
 descriptions, and so on.
Constructors
Instances
| Enum TokenType Source # | |
| Eq TokenType Source # | |
| Data TokenType Source # | |
| Ord TokenType Source # | |
| Read TokenType Source # | |
| Show TokenType Source # | |
| Generic TokenType Source # | |
| ToJSON TokenType Source # | |
| ToJSONKey TokenType Source # | |
| FromJSON TokenType Source # | |
| FromJSONKey TokenType Source # | JSON  | 
| Binary TokenType Source # | |
| type Rep TokenType Source # | |
type SourceLine = [Token] Source #
A line of source: a list of labeled tokens.
Line numbers
Styles
data TokenStyle Source #
A TokenStyle determines how a token is to be rendered.
Constructors
| TokenStyle | |
| Fields 
 | |
Instances
| Eq TokenStyle Source # | |
| Data TokenStyle Source # | |
| Ord TokenStyle Source # | |
| Read TokenStyle Source # | |
| Show TokenStyle Source # | |
| Generic TokenStyle Source # | |
| ToJSON 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).
class FromColor a where Source #
Different representations of a Color.
Minimal complete definition
Instances
| FromColor String Source # | |
| FromColor Xterm256ColorCode Source # | Warning: this conversion is noticeably approximate! | 
| (Ord a, Floating a) => FromColor (Colour a) Source # | |
| FromColor (ColorIntensity, Color) Source # | Warning: this conversion is extremely approximate! | 
| FromColor (Double, Double, Double) Source # | |
| FromColor (Word8, Word8, Word8) 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.
Constructors
| Style | |
| Fields | |
Instances
| Eq Style Source # | |
| Data Style Source # | |
| Ord Style Source # | |
| Read Style Source # | |
| Show Style Source # | |
| Generic Style Source # | |
| ToJSON Style Source # | |
| FromJSON Style Source # | The FromJSON instance for  | 
| Binary Style Source # | |
| type Rep Style Source # | |
data ANSIColorLevel Source #
The available levels of color complexity in ANSI terminal output.
Constructors
| ANSI16Color | 16-color mode | 
| ANSI256Color | 256-color mode | 
| ANSITrueColor | True-color mode | 
Instances
newtype Xterm256ColorCode Source #
Constructors
| Xterm256ColorCode | |
| Fields | |
Instances
| Bounded Xterm256ColorCode Source # | |
| Enum Xterm256ColorCode Source # | |
| Eq Xterm256ColorCode Source # | |
| Data Xterm256ColorCode Source # | |
| Ord Xterm256ColorCode Source # | |
| Read Xterm256ColorCode Source # | |
| Show Xterm256ColorCode Source # | |
| Generic Xterm256ColorCode Source # | |
| Binary Xterm256ColorCode Source # | |
| FromColor Xterm256ColorCode Source # | Warning: this conversion is noticeably approximate! | 
| ToColor Xterm256ColorCode Source # | |
| type Rep Xterm256ColorCode Source # | |
Format options
data FormatOptions Source #
Options for formatting source code.
Constructors
| FormatOptions | |
| Fields 
 | |
defaultFormatOpts :: FormatOptions Source #
Default formatting options.