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

Contents

Description

This module provides a quasi-quoter for XML Documents. See the xml function for some examples.

The difference between Text.XML.QQ and Text.HTML.QQ is the function that is used to parse the input String into a Document.

xml uses parseText to parse the input String. parseText returns an error on a malformed document. This is generally what you want for XML documents.

html uses parseLT to parse the input String. parseLT will parse any HTML document, skipping parts of the document that are malformed. This is generally what you want for HTML documents.

Synopsis

Documentation

xml :: QuasiQuoter Source #

This QuasiQuoter produces XML Documents.

This QuasiQuoter produces expressions of type Either SomeException Document. It produces a Left SomeException when the input string cannot be parsed into an XML Document.

Here's a simple example of using it:

>>> [xml|<html></html>|] :: Either SomeException Document
Right (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"
>>> [xml|<html>#{a}</html>|]
Right ...

Here's an example of invalue XML that will produce a Left value:

>>> [xml|<html </html>|]
Left ...

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

>>> [xml|<html><br></html>|]
Left ...

xmlUnsafe :: QuasiQuoter Source #

This function is just like xml, but produces expressions of type Document.

If your input string cannot be parsed into a valid Document, an error will be thrown at runtime with error.

This function is nice to use in GHCi or tests, but should NOT be used in production code.

Here's a simple example of using it:

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

xmlRaw :: QuasiQuoter Source #

This function is similar to xml, but doesn't allow variable interpolation or control statements. It produces expressions of type Document.

An error will be thrown at compile-time if the input string cannot be parsed into a Document.

Unlike xmlUnsafe, this function is safe to use in production code.

Here's a simple example of using it:

>>> [xmlRaw|<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 -> () #

data SomeException :: * #

The SomeException type is the root of the exception type hierarchy. When an exception of type e is thrown, behind the scenes it is encapsulated in a SomeException.