| Copyright | Copyright (C) 2008-2017 John MacFarlane | 
|---|---|
| License | GNU GPL, version 2 or above | 
| Maintainer | John MacFarlane <jgm@berkeley.edu> | 
| Stability | alpha | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Text.Pandoc.Highlighting
Description
Exports functions for syntax highlighting.
- 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
 - haddock :: Style
 - data Style :: *
 - fromListingsLanguage :: String -> Maybe String
 - toListingsLanguage :: String -> Maybe String
 
Documentation
highlightingStyles :: [(String, Style)] Source #
languagesByExtension :: String -> [String] Source #
Arguments
| :: 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 TokenTypes 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 a div
 with the class ‘source-line’. If line numbering
 is selected, this surrounding div is given the class ‘number-source’,
 and the resulting html will display line numbers thanks to the included
 css. Note that the html produced will always include the line numbers as
 the 'data-line-number' attribute.
 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.
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.