Copyright | Copyright (C) 2008-2023 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Exports functions for syntax highlighting.
Synopsis
- highlightingStyles :: [(Text, Style)]
- languages :: SyntaxMap -> [Text]
- languagesByExtension :: SyntaxMap -> Text -> [Text]
- highlight :: SyntaxMap -> (FormatOptions -> [SourceLine] -> a) -> Attr -> Text -> Either Text a
- formatLaTeXInline :: FormatOptions -> [SourceLine] -> Text
- formatLaTeXBlock :: FormatOptions -> [SourceLine] -> Text
- styleToLaTeX :: Style -> Text
- formatHtmlInline :: FormatOptions -> [SourceLine] -> Html
- formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html
- formatHtml4Block :: FormatOptions -> [SourceLine] -> Html
- styleToCss :: Style -> String
- formatConTeXtInline :: FormatOptions -> [SourceLine] -> Text
- formatConTeXtBlock :: FormatOptions -> [SourceLine] -> Text
- styleToConTeXt :: Style -> Text
- pygments :: Style
- espresso :: Style
- zenburn :: Style
- tango :: Style
- kate :: Style
- monochrome :: Style
- breezeDark :: Style
- haddock :: Style
- data Style
- lookupHighlightingStyle :: PandocMonad m => String -> m Style
- fromListingsLanguage :: Text -> Maybe Text
- toListingsLanguage :: Text -> Maybe Text
Documentation
highlightingStyles :: [(Text, Style)] Source #
languagesByExtension :: SyntaxMap -> Text -> [Text] Source #
Formats
LaTeX
formatLaTeXInline :: FormatOptions -> [SourceLine] -> Text #
formatLaTeXBlock :: FormatOptions -> [SourceLine] -> Text #
styleToLaTeX :: Style -> Text #
HTML
formatHtmlInline :: FormatOptions -> [SourceLine] -> Html #
formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html #
formatHtml4Block :: FormatOptions -> [SourceLine] -> Html #
styleToCss :: Style -> String #
ConTeXt
formatConTeXtInline :: FormatOptions -> [SourceLine] -> Text #
formatConTeXtBlock :: FormatOptions -> [SourceLine] -> Text #
styleToConTeXt :: Style -> Text #
Styles
monochrome :: Style #
breezeDark :: Style #
Instances
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 :: 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 | |
Read Style | |
Show Style | |
Binary Style | |
Eq Style | |
Ord Style | |
FromJSON Style | |
Defined in Skylighting.Types parseJSON :: Value -> Parser Style parseJSONList :: Value -> Parser [Style] | |
ToJSON Style | |
Defined in Skylighting.Types | |
type Rep Style | |
Defined in Skylighting.Types type Rep Style = D1 ('MetaData "Style" "Skylighting.Types" "skylghtng-cr-0.13.2.1-4817bbdf" '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.