xml-html-conduit-lens-0.3.0.0: Optics for xml-conduit and html-conduit

Safe HaskellNone

Text.Xml.Lens

Contents

Description

Optics for xml-conduit and html-conduit

Synopsis

Document

xml :: AsXmlDocument t => Traversal' t ElementSource

A Traversal into XML document root node

>>> ("<foo/>" :: TL.Text) ^? xml.name
Just "foo"
>>> ("<foo><bar/><baz/></foo>" :: TL.Text) ^? xml.name
Just "foo"
>>> ("<foo/>" :: TL.Text) & xml.name .~ "boo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><boo/>"

html :: AsHtmlDocument t => Fold t ElementSource

A Fold into HTML document root node

Not every parseable HTML document is a valid XML document:

>>> let quasiXml = "<html><br><br></html>" :: BL.ByteString
>>> quasiXml ^.. html...name
["br","br"]
>>> quasiXml ^? xml...name
Nothing

renderWith :: AsXmlDocument t => (RenderSettings -> RenderSettings) -> Fold Element tSource

Fold Element into the XML document

Convenience function mostly useful because xml-conduit does not provide handy method to convert Element into text. Assumes empty XML prolog

See also render

>>> :{
  let
    bare l   = (l, Data.Map.empty, [])
    tag l    = _Element # bare l
    subtag l = _NodeElement._Element # bare l
    doc      = tag "root"
        & elementNodes <>~ [subtag "child1", subtag "child2", subtag "child3"]
        & elementNodes %~ (subtag "child0" <|)
:}
>>> Data.Text.Lazy.IO.putStr $ doc ^. render
<?xml version="1.0" encoding="UTF-8"?><root><child0/><child1/><child2/><child3/></root>
>>> Data.Text.Lazy.IO.putStr $ doc ^. renderWith (rsPretty .~ True)
<?xml version="1.0" encoding="UTF-8"?>
<root>
    <child0/>
    <child1/>
    <child2/>
    <child3/>
</root>

render :: AsXmlDocument t => Fold Element tSource

Fold Element into the XML document with the default rendering settings

prolog :: AsXmlDocument t => Traversal' t PrologueSource

A Traversal into XML prolog

epilog :: AsXmlDocument t => Traversal' t [Miscellaneous]Source

A Traversal into XML epilog

>>> let doc = "<root/><!--qux--><?foo bar?><!--quux-->" :: TL.Text
>>> doc ^.. epilog.folded.comments
["qux","quux"]
>>> doc ^.. epilog.folded.instructions.target
["foo"]
>>> doc & epilog .~ []
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root/>"

class AsXmlDocument t whereSource

XML document parsing and rendering overloading

This is a general version; for parsing/rendering with the default options see _XmlDocument

_XmlDocument :: AsXmlDocument t => Prism' t DocumentSource

XML document parsing and rendering with the default settings

class AsHtmlDocument t whereSource

HTML document parsing overloading

Doctype

data Doctype

Note: due to the incredible complexity of DTDs, this type only supports external subsets. I've tried adding internal subset types, but they quickly gain more code than the rest of this module put together.

It is possible that some future version of this library might support internal subsets, but I am no longer actively working on adding them.

doctype :: Lens' Prologue (Maybe Doctype)Source

A Lens into XML DOCTYPE declaration

>>> let doc = "<!DOCTYPE foo><root/>" :: TL.Text
>>> doc ^? prolog.doctype.folded.doctypeName
Just "foo"
>>> doc & prolog.doctype.traverse.doctypeName .~ "moo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><!DOCTYPE moo><root/>"

Since doctype's a Lens, it's possible to attach DOCTYPE declaration to an XML document which didn't have it before:

>>> ("<root/>" :: TL.Text) & prolog.doctype ?~ XML.Doctype "moo" Nothing
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><!DOCTYPE moo><root/>"

beforeDoctype :: Lens' Prologue [Miscellaneous]Source

A Lens into nodes before XML DOCTYPE declaration

>>> let doc = "<!--foo--><!DOCTYPE bar><!--baz--><root/>" :: TL.Text
>>> doc ^? prolog.beforeDoctype.folded.comments
Just "foo"
>>> doc & prolog.beforeDoctype.traverse.comments %~ Text.toUpper
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><!--FOO--><!DOCTYPE bar><!--baz--><root/>"

afterDoctype :: Lens' Prologue [Miscellaneous]Source

A Lens into nodes after XML DOCTYPE declaration

>>> let doc = "<!--foo--><!DOCTYPE bar><!--baz--><root/>" :: TL.Text
>>> doc ^? prolog.afterDoctype.folded.comments
Just "baz"
>>> doc & prolog.afterDoctype.traverse.comments %~ Text.toUpper
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><!--foo--><!DOCTYPE bar><!--BAZ--><root/>"

Element

data Element

Instances

Eq Element 
Data Element 
Ord Element 
Show Element 
Typeable Element 
ToMarkup Element

Note that the special element name {http:www.snoyman.com/xml2html}ie-cond with the single attribute cond is used to indicate an IE conditional comment.

NFData Element 
Ixed Element

Index child Elements by an Int

>>> let doc = "<root>zero<foo>one</foo><bar>two</bar>three<baz/>four</root>" :: TL.Text
>>> doc ^? xml.parts.ix 1.text
Just "two"

To index subnodes indexed by a Traversal', use ixOf

Plated Element

Traverse immediate children

>>> let doc = "<root><foo>4</foo><foo>7</foo><bar>11</bar></root>" :: TL.Text
>>> doc ^.. xml...name
["foo","foo","bar"]
>>> doc & partsOf (root...name) .~ ["boo", "hoo", "moo"]
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><boo>4</boo><hoo>7</hoo><moo>11</moo></root>"
HasName Element 
HasInstructions Element 
HasComments Element 

ixOf :: Traversal' Node a -> Index Element -> Traversal' Element aSource

Index subnodes selected with a Traversal by an Int

>>> let doc = "<root>zero<foo>one</foo><bar>two</bar>three<baz/>four</root>" :: TL.Text
>>> doc ^? xml.ixOf _NodeContent 2
Just "four"

node :: Name -> Traversal' Element ElementSource

Traverse immediate children with a specific name

>>> let doc = "<root><foo>boo</foo><foo>hoo</foo><bar>moo</bar></root>" :: TL.Text
>>> doc ^. xml.node "foo".text
"boohoo"
>>> doc ^? xml.node "bar".text
Just "moo"
>>> doc ^? xml.node "baz".text
Nothing

named :: Fold Name a -> Traversal' Element ElementSource

Select nodes by name

>>> let doc = "<root><foo>4</foo><foo>7</foo><bar>11</bar><bar xmlns=\"zap\">28</bar></root>" :: TL.Text
>>> doc ^.. xml...named (only "foo").name
["foo","foo"]
>>> doc ^? xml...named (namespace.traverse.only "zap").text
Just "28"
>>> doc ^? xml...named (only "baz").name
Nothing

attrs :: IndexedTraversal' Name Element TextSource

Traverse node attributes

>>> let doc = "<root><foo bar=\"baz\" qux=\"zap\"/><foo quux=\"xyzzy\"/></root>" :: TL.Text
>>> doc ^.. xml...attrs.indices (has (name.unpacked.prefixed "qu"))
["zap","xyzzy"]
>>> doc & xml...attrs %~ Text.toUpper
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><foo bar=\"BAZ\" qux=\"ZAP\"/><foo quux=\"XYZZY\"/></root>"

attr :: Name -> Lens' Element (Maybe Text)Source

Traverse node attributes with a specific name

>>> let doc = "<root><foo bar=\"baz\" qux=\"quux\"/><foo qux=\"xyzzy\"/></root>" :: TL.Text
>>> doc ^.. xml...attr "qux".traverse
["quux","xyzzy"]
>>> doc ^.. xml...attr "bar"
[Just "baz",Nothing]
>>> doc & xml...attr "qux".traverse %~ Text.reverse
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><foo bar=\"baz\" qux=\"xuuq\"/><foo qux=\"yzzyx\"/></root>"
>>> doc & xml.ix 1.attr "bar" ?~ "bazzy"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><foo bar=\"baz\" qux=\"quux\"/><foo bar=\"bazzy\" qux=\"xyzzy\"/></root>"

attributed :: Fold (Map Name Text) a -> Traversal' Element ElementSource

Select nodes by attributes' values

>>> let doc = "<root><foo bar=\"baz\">4</foo><foo bar=\"quux\">7</foo><bar bar=\"baz\">11</bar></root>" :: TL.Text
>>> doc ^.. xml...attributed (ix "bar".only "baz").text
["4","11"]
>>> doc ^? xml...attributed (folded.to Text.length.only 4).text
Just "7"

text :: Traversal' Element TextSource

Traverse node text contents

>>> let doc = "<root>boo</root>" :: TL.Text
>>> doc ^? xml.text
Just "boo"
>>> doc & xml.text <>~ "hoo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root>boohoo</root>"

class HasComments t whereSource

Anything that has comments

class HasInstructions t whereSource

Anything that has processing instructions

Name

data Name

A fully qualified name.

Prefixes are not semantically important; they are included only to simplify pass-through parsing. When comparing names with Eq or Ord methods, prefixes are ignored.

The IsString instance supports Clark notation; see http://www.jclark.com/xml/xmlns.htm and http://infohost.nmt.edu/tcc/help/pubs/pylxml/etree-QName.html. Use the OverloadedStrings language extension for very simple Name construction:

 myname :: Name
 myname = "{http://example.com/ns/my-namespace}my-name"

name :: HasName t => Lens' t TextSource

A Lens into node name

>>> ("<root/>" :: TL.Text) ^. xml.name
"root"
>>> ("<root><foo/><bar/><baz/></root>" :: TL.Text) ^.. xml...name
["foo","bar","baz"]
>>> ("<root><foo/><bar/><baz></root>" :: TL.Text) & xml.partsOf (plate.name) .~ ["boo", "hoo", "moo"]
"<root><foo/><bar/><baz></root>"

namespace :: HasName t => Lens' t (Maybe Text)Source

A Lens into node namespace

>>> ("<root/>" :: TL.Text) ^. xml.namespace
Nothing
>>> ("<root/>" :: TL.Text) & xml.namespace ?~ "foo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root xmlns=\"foo\"/>"
>>> ("<root xmlns=\"foo\"/>" :: TL.Text) & xml.namespace .~ Nothing
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root/>"

prefix :: HasName t => Lens' t (Maybe Text)Source

A Lens into node namespace

>>> ("<root/>" :: TL.Text) ^. xml.prefix
Nothing
>>> ("<root/>" :: TL.Text) & xml.prefix ?~ "foo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root/>"
>>> ("<root xmlns=\"foo\"/>" :: TL.Text) & xml.prefix ?~ "foo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><foo:root xmlns:foo=\"foo\"/>"
>>> ("<?xml version=\"1.0\" encoding=\"UTF-8\"?><foo:root xmlns:foo=\"foo\"/>" :: TL.Text) & xml.prefix .~ Nothing
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root xmlns=\"foo\"/>"

class HasName t whereSource

Anything that has a name

Instruction

target :: Traversal' Instruction TextSource

Processing instruction target

>>> let doc = "<root><?foo bar?></root>" :: TL.Text
>>> doc ^? xml.instructions.target
Just "foo"
>>> doc & xml.instructions.target .~ "boo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><?boo bar?></root>"

data_ :: Traversal' Instruction TextSource

Processing instruction data

>>> let doc = "<root><?foo bar?></root>" :: TL.Text
>>> doc ^? xml.instructions.data_
Just "bar"
>>> doc & xml.instructions.data_ .~ "hoo"
"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><?foo hoo?></root>"

exceptions

class AsXMLException t whereSource

xml-conduit general XML exception overloading