pandoc-3.1.12.3: Conversion between markup formats
CopyrightCopyright (C) 2008-2023 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc.Highlighting

Description

Exports functions for syntax highlighting.

Synopsis

Documentation

highlight Source #

Arguments

:: SyntaxMap 
-> (FormatOptions -> [SourceLine] -> a)

Formatter

-> Attr

Attributes of the CodeBlock

-> Text

Raw contents of the CodeBlock

-> Either Text a 

Formats

LaTeX

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}

HTML

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 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.

formatHtml4Block :: FormatOptions -> [SourceLine] -> Html #

Like formatHtmlBlock but uses only attributes valid in HTML 4 (so, aria-hidden is not used in empty line number spans).

styleToCss :: Style -> String #

Returns CSS for styling highlighted code according to the given style.

ConTeXt

formatConTeXtInline :: FormatOptions -> [SourceLine] -> Text #

Formats tokens as ConTeXt using custom commands inside a type{}. A KeywordTok is rendered using \KeywordTok{..}, and so on.

formatConTeXtBlock :: FormatOptions -> [SourceLine] -> Text #

Format tokens as a ConTeXt highlighting typing environment. The highlighting environemnt is defined by the macros produced by styleToConTeXt; it is a typing environment with default escaping enabled, i.e., / is the escape character.

styleToConTeXt :: Style -> Text #

Converts a Style to a set of ConTeXt command definitions, which should be placed in the document's preamble.

Styles

pygments :: Style #

Style based on pygments's default colors.

espresso :: Style #

Style based on ultraviolet's espresso_libre.css (dark background).

zenburn :: Style #

Style based on the popular zenburn vim color scheme

tango :: Style #

Style based on pygments's tango colors.

kate :: Style #

Style based on kate's default colors.

monochrome :: Style #

Style with no colors.

breezeDark :: Style #

Style from the breeze-dark KDE syntax highlighting theme.

haddock :: Style #

Style based on haddock's source highlighting.

data Style #

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

Instances details
FromJSON Style

The FromJSON instance for Style is designed so that a KDE syntax theme (JSON) can be decoded directly as a Style.

Instance details

Defined in Skylighting.Types

ToJSON Style 
Instance details

Defined in Skylighting.Types

Data Style 
Instance details

Defined in Skylighting.Types

Methods

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 #

toConstr :: Style -> Constr #

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 :: forall r r'. (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 #

Generic Style 
Instance details

Defined in Skylighting.Types

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Read Style 
Instance details

Defined in Skylighting.Types

Show Style 
Instance details

Defined in Skylighting.Types

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Binary Style 
Instance details

Defined in Skylighting.Types

Methods

put :: Style -> Put #

get :: Get Style #

putList :: [Style] -> Put #

Eq Style 
Instance details

Defined in Skylighting.Types

Methods

(==) :: Style -> Style -> Bool #

(/=) :: Style -> Style -> Bool #

Ord Style 
Instance details

Defined in Skylighting.Types

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

(<=) :: Style -> Style -> Bool #

(>) :: Style -> Style -> Bool #

(>=) :: Style -> Style -> Bool #

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

type Rep Style 
Instance details

Defined in Skylighting.Types

type Rep Style = D1 ('MetaData "Style" "Skylighting.Types" "skylighting-core-0.14.1.1-8Y0bK6G1wEn1oMzMugnjtP" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenStyles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map TokenType TokenStyle)) :*: S1 ('MetaSel ('Just "defaultColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color))) :*: (S1 ('MetaSel ('Just "backgroundColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color)) :*: (S1 ('MetaSel ('Just "lineNumberColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color)) :*: S1 ('MetaSel ('Just "lineNumberBackgroundColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Color))))))

lookupHighlightingStyle :: PandocMonad m => String -> m Style Source #

Lookup style from a name. If the name is a standard style, load it; if it ends in ".theme", attempt to load a KDE theme from the file path specified.

fromListingsLanguage :: Text -> Maybe Text Source #

Determine skylighting language name from listings language name.

toListingsLanguage :: Text -> Maybe Text Source #

Determine listings language name from skylighting language name.