Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic types for Skylighting.
Synopsis
- type ContextName = (Text, Text)
- data KeywordAttr = KeywordAttr {}
- data WordSet a
- = CaseSensitiveWords (Set a)
- | CaseInsensitiveWords (Set 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.
Instances
A set of "words," possibly case insensitive.
CaseSensitiveWords (Set a) | |
CaseInsensitiveWords (Set a) |
Instances
Eq a => Eq (WordSet a) Source # | |
(Data a, Ord a) => Data (WordSet a) Source # | |
Defined in Skylighting.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WordSet a -> c (WordSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WordSet a) # toConstr :: WordSet a -> Constr # dataTypeOf :: WordSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WordSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WordSet a)) # gmapT :: (forall b. Data b => b -> b) -> WordSet a -> WordSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WordSet a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WordSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> WordSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WordSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a) # | |
Ord a => Ord (WordSet a) Source # | |
Defined in Skylighting.Types | |
(Read a, Ord a) => Read (WordSet a) Source # | |
Show a => Show (WordSet a) Source # | |
Generic (WordSet a) Source # | |
Binary a => Binary (WordSet a) Source # | |
type Rep (WordSet a) Source # | |
Defined in Skylighting.Types type Rep (WordSet a) = D1 (MetaData "WordSet" "Skylighting.Types" "skylighting-core-0.8.4-B0bu5PAYjOv7iL26gQFNV9" False) (C1 (MetaCons "CaseSensitiveWords" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set a))) :+: C1 (MetaCons "CaseInsensitiveWords" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set a)))) |
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.
Instances
A rule corresponds to one of the elements of a Kate syntax highlighting "context."
Rule | |
|
Instances
A Context corresponds to a context element in a Kate syntax description.
Context | |
|
Instances
data ContextSwitch Source #
A context switch, either pops or pushes a context.
Instances
A syntax corresponds to a complete Kate syntax description.
The sShortname
field is derived from the filename.
Instances
Tokens
KeywordTok
corresponds to dsKeyword
in Kate syntax
descriptions, and so on.
Instances
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 | |
|
Instances
defStyle :: TokenStyle Source #
Default style.
A color (redgreenblue).
Instances
Eq Color Source # | |
Data Color Source # | |
Defined in Skylighting.Types 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 # 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 # | |
Read Color Source # | |
Show Color Source # | |
Generic Color Source # | |
ToJSON Color Source # | |
Defined in Skylighting.Types | |
FromJSON Color Source # | JSON |
Binary Color Source # | |
type Rep Color Source # | |
Defined in Skylighting.Types type Rep Color = D1 (MetaData "Color" "Skylighting.Types" "skylighting-core-0.8.4-B0bu5PAYjOv7iL26gQFNV9" False) (C1 (MetaCons "RGB" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)))) |
class ToColor a where Source #
Things that can be converted to a color.
Instances
ToColor Int Source # | |
ToColor String Source # | |
ToColor Xterm256ColorCode Source # | |
Defined in Skylighting.Types | |
(RealFrac a, Floating a) => ToColor (Colour a) Source # | |
ToColor (ColorIntensity, Color) Source # | |
Defined in Skylighting.Types | |
ToColor (Double, Double, Double) Source # | |
ToColor (Word8, Word8, Word8) Source # | |
class FromColor a where Source #
Different representations of a Color
.
Instances
FromColor String Source # | |
FromColor Xterm256ColorCode Source # | Warning: this conversion is noticeably approximate! |
Defined in Skylighting.Types fromColor :: Color -> Xterm256ColorCode Source # | |
(Ord a, Floating a) => FromColor (Colour a) Source # | |
FromColor (ColorIntensity, Color) Source # | Warning: this conversion is extremely approximate! |
Defined in Skylighting.Types | |
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.
Instances
Eq Style Source # | |
Data Style Source # | |
Defined in Skylighting.Types 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 # 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 # | |
Read Style Source # | |
Show Style Source # | |
Generic Style Source # | |
ToJSON Style Source # | |
Defined in Skylighting.Types | |
FromJSON Style Source # | The FromJSON instance for |
Binary Style Source # | |
type Rep Style Source # | |
Defined in Skylighting.Types type Rep Style = D1 (MetaData "Style" "Skylighting.Types" "skylighting-core-0.8.4-B0bu5PAYjOv7iL26gQFNV9" False) (C1 (MetaCons "Style" PrefixI True) ((S1 (MetaSel (Just "tokenStyles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map TokenType TokenStyle)) :*: S1 (MetaSel (Just "defaultColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color))) :*: (S1 (MetaSel (Just "backgroundColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: (S1 (MetaSel (Just "lineNumberColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)) :*: S1 (MetaSel (Just "lineNumberBackgroundColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Color)))))) |
data ANSIColorLevel Source #
The available levels of color complexity in ANSI terminal output.
ANSI16Color | 16-color mode |
ANSI256Color | 256-color mode |
ANSITrueColor | True-color mode |
Instances
newtype Xterm256ColorCode Source #
Instances
Format options
data FormatOptions Source #
Options for formatting source code.
FormatOptions | |
|
Instances
defaultFormatOpts :: FormatOptions Source #
Default formatting options.