xml-html-qq-0.1.0.1: Quasi-quoters for XML and HTML Documents

CopyrightDennis Gosnell 2017
LicenseBSD3
MaintainerDennis Gosnell (cdep.illabout@gmail.com)
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Text.HTML.QQ

Contents

Description

This module provides a quasi-quoter for HTML Documents. See the html function for some examples.

See Text.XML.QQ for an explanation of the difference between Text.HTML.QQ and Text.XML.QQ.

Synopsis

Documentation

html :: QuasiQuoter Source #

This QuasiQuoter produces HTML Documents.

This QuasiQuoter produces expressions of type Document.

Here's a simple example of using it:

>>> [html|<html></html>|] :: Document
Document {documentPrologue = Prologue {prologueBefore = [], prologueDoctype = Nothing, prologueAfter = []}, documentRoot = Element {elementName = Name {nameLocalName = "html", nameNamespace = Nothing, namePrefix = Nothing}, elementAttributes = fromList [], elementNodes = []}, documentEpilogue = []}

Internally, this function is using the heterocephalus package. This means you can use variable interpolation, as well as forall, if, and case control statements. Checkout the heterocephalus README for more info.

>>> let a = "hello world"
>>> [html|<html>#{a}</html>|]
Document ...

Even invalid HTML will still parse.

>>> [html|<html </html>|]
Document ...

Here's an example of a template that can be parsed as an HTML Document, but not as an XML Document:

>>> [html|<html><br></html>|]
Document ...

htmlRaw :: QuasiQuoter Source #

This function is the same as html, but doesn't allow variable interpolation or control statements. It also produces expressions of type Document.

Here's a simple example of using it:

>>> [htmlRaw|<html></html>|] :: Document
Document ...

Types

data Document :: * #

Instances

Eq Document 
Data Document 

Methods

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

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

toConstr :: Document -> Constr #

dataTypeOf :: Document -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Document 
ToMarkup Document 
NFData Document 

Methods

rnf :: Document -> () #