Copyright | Copyright (C) 2008-2018 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Exports functions for syntax highlighting.
Synopsis
- highlightingStyles :: [(String, Style)]
- languages :: [String]
- languagesByExtension :: String -> [String]
- highlight :: SyntaxMap -> (FormatOptions -> [SourceLine] -> a) -> Attr -> String -> Either String a
- formatLaTeXInline :: FormatOptions -> [SourceLine] -> Text
- formatLaTeXBlock :: FormatOptions -> [SourceLine] -> Text
- styleToLaTeX :: Style -> Text
- formatHtmlInline :: FormatOptions -> [SourceLine] -> Html
- formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html
- styleToCss :: Style -> String
- pygments :: Style
- espresso :: Style
- zenburn :: Style
- tango :: Style
- kate :: Style
- monochrome :: Style
- breezeDark :: Style
- haddock :: Style
- data Style
- fromListingsLanguage :: String -> Maybe String
- toListingsLanguage :: String -> Maybe String
Documentation
highlightingStyles :: [(String, Style)] Source #
languagesByExtension :: String -> [String] Source #
:: SyntaxMap | |
-> (FormatOptions -> [SourceLine] -> a) | Formatter |
-> Attr | Attributes of the CodeBlock |
-> String | Raw contents of the CodeBlock |
-> Either String a |
formatLaTeXInline :: FormatOptions -> [SourceLine] -> Text #
Formats tokens as LaTeX using custom commands inside
|
characters. Assumes that |
is defined as a short verbatim
command by the macros produced by styleToLaTeX
.
A KeywordTok
is rendered using \KeywordTok{..}
, and so on.
formatLaTeXBlock :: FormatOptions -> [SourceLine] -> Text #
Format tokens as a LaTeX Highlighting
environment inside a
Shaded
environment. Highlighting
and Shaded
are
defined by the macros produced by styleToLaTeX
. Highlighting
is a verbatim environment using fancyvrb
; \
, {
, and }
have their normal meanings inside this environment, so that
formatting commands work. Shaded
is either nothing
(if the style's background color is default) or a snugshade
environment from framed
, providing a background color
for the whole code block, even if it spans multiple pages.
styleToLaTeX :: Style -> Text #
Converts a Style
to a set of LaTeX macro definitions,
which should be placed in the document's preamble.
Note: default LaTeX setup doesn't allow boldface typewriter font.
To make boldface work in styles, you need to use a different typewriter
font. This will work for computer modern:
\DeclareFontShape{OT1}{cmtt}{bx}{n}{<5><6><7><8><9><10><10.95><12><14.4><17.28><20.74><24.88>cmttb10}{}
Or, with xelatex:
\usepackage{fontspec} \setmainfont[SmallCapsFont={* Caps}]{Latin Modern Roman} \setsansfont{Latin Modern Sans} \setmonofont[SmallCapsFont={Latin Modern Mono Caps}]{Latin Modern Mono Light}
formatHtmlInline :: FormatOptions -> [SourceLine] -> Html #
Format tokens using HTML spans inside code
tags. For example,
A KeywordTok
is rendered as a span with class kw
.
Short class names correspond to TokenType
s as follows:
KeywordTok
= kw
,
DataTypeTok
= dt
,
DecValTok
= dv
,
BaseNTok
= bn
,
FloatTok
= fl
,
CharTok
= ch
,
StringTok
= st
,
CommentTok
= co
,
OtherTok
= ot
,
AlertTok
= al
,
FunctionTok
= fu
,
RegionMarkerTok
= re
,
ErrorTok
= er
,
ConstantTok
= cn
,
SpecialCharTok
= sc
,
VerbatimStringTok
= vs
,
SpecialStringTok
= ss
,
ImportTok
= im
,
DocumentationTok
= do
,
AnnotationTok
= an
,
CommentVarTok
= cv
,
VariableTok
= va
,
ControlFlowTok
= cf
,
OperatorTok
= op
,
BuiltInTok
= bu
,
ExtensionTok
= ex
,
PreprocessorTok
= pp
,
AttributeTok
= at
,
InformationTok
= in
,
WarningTok
= wa
.
A NormalTok
is not marked up at all.
formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html #
Format tokens as an HTML pre
block. Each line is wrapped in an a
element with the class ‘source-line’. If line numbering
is selected, the surrounding pre is given the class ‘numberSource’,
and the resulting html will display line numbers thanks to the included
CSS. See the documentation for formatHtmlInline
for information about how
tokens are encoded.
styleToCss :: Style -> String #
Returns CSS for styling highlighted code according to the given style.
monochrome :: Style #
Style with no colors.
breezeDark :: Style #
Style from the breeze-dark KDE syntax highlighting theme.
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 | |
Data Style | |
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 | |
Read Style | |
Show Style | |
Generic Style | |
ToJSON Style | |
Defined in Skylighting.Types | |
FromJSON Style | The FromJSON instance for |
Binary Style | |
type Rep Style | |
Defined in Skylighting.Types type Rep Style = D1 (MetaData "Style" "Skylighting.Types" "skylighting-core-0.7.3-43YO9tYr1jWIN8jyNc9WQM" 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)))))) |