BlogLiterately-0.8.3.1: A tool for posting Haskelly articles to blogs

Copyright(c) 2008-2010 Robert Greayer 2012 Brent Yorgey
LicenseGPL (see LICENSE)
MaintainerBrent Yorgey <byorgey@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Text.BlogLiterately.Highlight

Description

Syntax highlighting.

Synopsis

Documentation

data HsHighlight Source #

Four modes for highlighting Haskell.

Constructors

HsColourInline StylePrefs

Use hscolour and inline the styles.

HsColourCSS

Use hscolour in conjunction with an external CSS style sheet.

HsKate

Use highlighting-kate.

HsNoHighlight

Do not highlight Haskell.

Instances

Eq HsHighlight Source # 
Data HsHighlight Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsHighlight -> c HsHighlight #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsHighlight #

toConstr :: HsHighlight -> Constr #

dataTypeOf :: HsHighlight -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c HsHighlight) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsHighlight) #

gmapT :: (forall b. Data b => b -> b) -> HsHighlight -> HsHighlight #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsHighlight -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsHighlight -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsHighlight -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsHighlight -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsHighlight -> m HsHighlight #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsHighlight -> m HsHighlight #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsHighlight -> m HsHighlight #

Show HsHighlight Source # 

colourIt :: Bool -> String -> String Source #

Use hscolour to syntax highlight some Haskell code. The first argument indicates whether the code is literate Haskell.

litify :: String -> String Source #

Prepend literate Haskell markers to some source code.

type StylePrefs = [(String, String)] Source #

Style preferences are specified as a list of mappings from class attributes to CSS style attributes.

defaultStylePrefs :: StylePrefs Source #

A default style that produces something that looks like the source listings on Hackage.

getStylePrefs :: Maybe FilePath -> IO StylePrefs Source #

Read style preferences in from a file using the Read instance for StylePrefs, or return the default style if the file name is empty.

bakeStyles :: StylePrefs -> String -> String Source #

Take a String of HTML produced by hscolour, and "bake" styles into it by replacing class attributes with appropriate style attributes.

replaceBreaks :: String -> String Source #

Replace <br/> tags with newlines.

colouriseCodeBlock :: HsHighlight -> Bool -> Block -> Block Source #

Transform a CodeBlock into a RawHtml block, where the content contains marked up Haskell (possibly with literate markers), or marked up non-Haskell, if highlighting of non-Haskell has been selected.

colourisePandoc :: HsHighlight -> Bool -> Pandoc -> Pandoc Source #

Perform syntax highlighting on an entire Pandoc document.