| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Text.Xml.Lens
Description
Optics for xml-conduit and html-conduit
- data Document :: *
- xml :: AsXmlDocument t => Traversal' t Element
- html :: AsHtmlDocument t => Fold t Element
- root :: AsXmlDocument t => Traversal' t Element
- renderWith :: AsXmlDocument t => (RenderSettings -> RenderSettings) -> Fold Element t
- render :: AsXmlDocument t => Fold Element t
- data Prologue :: *
- prolog :: AsXmlDocument t => Traversal' t Prologue
- epilog :: AsXmlDocument t => Traversal' t [Miscellaneous]
- class AsXmlDocument t where
- _XmlDocumentWith :: (ParseSettings -> ParseSettings) -> (RenderSettings -> RenderSettings) -> Prism' t Document
- data ParseSettings :: *
- data RenderSettings :: *
- _XmlDocument :: AsXmlDocument t => Prism' t Document
- class AsHtmlDocument t where
- _HtmlDocument :: Fold t Document
- data Doctype :: *
- doctype :: Lens' Prologue (Maybe Doctype)
- beforeDoctype :: Lens' Prologue [Miscellaneous]
- afterDoctype :: Lens' Prologue [Miscellaneous]
- data Element :: *
- ixOf :: Traversal' Node a -> Index Element -> Traversal' Element a
- node :: Name -> Traversal' Element Element
- named :: Fold Name a -> Traversal' Element Element
- attrs :: IndexedTraversal' Name Element Text
- attr :: Name -> Lens' Element (Maybe Text)
- attributed :: Fold (Map Name Text) a -> Traversal' Element Element
- text :: Traversal' Element Text
- texts :: Traversal' Element Text
- class HasComments t where
- comments :: Traversal' t Text
- class HasInstructions t where
- instructions :: Traversal' t Instruction
- data Name :: *
- name :: HasName t => Lens' t Text
- namespace :: HasName t => Lens' t (Maybe Text)
- prefix :: HasName t => Lens' t (Maybe Text)
- class HasName t where
- data Instruction :: *
- target :: Traversal' Instruction Text
- data_ :: Traversal' Instruction Text
- data UnresolvedEntityException :: *
- data XMLException :: *
- _MissingRootElement :: AsInvalidEventStream t => Prism' t ()
- _ContentAfterRoot :: AsInvalidEventStream t => Prism' t EventPos
- _InvalidInlineDoctype :: AsInvalidEventStream t => Prism' t EventPos
- _MissingEndElement :: AsInvalidEventStream t => Prism' t (Name, Maybe EventPos)
- _UnterminatedInlineDoctype :: AsInvalidEventStream t => Prism' t ()
- class AsUnresolvedEntityException t where
- _UnresolvedEntityException :: Prism' t UnresolvedEntityException
- class AsXMLException t where
- _XMLException :: Prism' t XMLException
- class AsInvalidEventStream t where
- _InvalidEventStream :: Prism' t InvalidEventStream
- module Text.Xml.Lens.LowLevel
Document
data Document :: *
xml :: AsXmlDocument t => Traversal' t Element Source
A Traversal into XML document root node
>>>("<foo/>" :: TL.Text) ^? xml.nameJust "foo"
>>>("<foo><bar/><baz/></foo>" :: TL.Text) ^? xml.nameJust "foo"
>>>("<foo/>" :: TL.Text) & xml.name .~ "boo""<?xml version=\"1.0\" encoding=\"UTF-8\"?><boo/>"
html :: AsHtmlDocument t => Fold t Element Source
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...nameNothing
root :: AsXmlDocument t => Traversal' t Element Source
An alias for xml
renderWith :: AsXmlDocument t => (RenderSettings -> RenderSettings) -> Fold Element t Source
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 t Source
Fold Element into the XML document with the default rendering settings
data Prologue :: *
prolog :: AsXmlDocument t => Traversal' t Prologue Source
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 where Source
XML document parsing and rendering overloading
This is a general version; for parsing/rendering with the
default options see _XmlDocument
Minimal complete definition
Nothing
Methods
_XmlDocumentWith :: (ParseSettings -> ParseSettings) -> (RenderSettings -> RenderSettings) -> Prism' t Document Source
Instances
data ParseSettings :: *
Instances
| Default ParseSettings |
data RenderSettings :: *
Instances
| Default RenderSettings |
_XmlDocument :: AsXmlDocument t => Prism' t Document Source
XML document parsing and rendering with the default settings
class AsHtmlDocument t where Source
HTML document parsing overloading
Minimal complete definition
Nothing
Methods
_HtmlDocument :: Fold t Document Source
Instances
Doctype
data Doctype :: *
doctype :: Lens' Prologue (Maybe Doctype) Source
A Lens into XML DOCTYPE declaration
>>>let doc = "<!DOCTYPE foo><root/>" :: TL.Text
>>>doc ^? prolog.doctype.folded.doctypeNameJust "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.commentsJust "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.commentsJust "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 | |
| NFData Element | |
| Plated Element | Traverse immediate children
|
| Ixed Element | Index child
To index subnodes indexed by a Traversal', use |
| ToMarkup Element | |
| HasName Element | |
| HasInstructions Element | |
| HasComments Element | |
| Typeable * Element | |
| type IxValue Element = Element | |
| type Index Element = Int |
ixOf :: Traversal' Node a -> Index Element -> Traversal' Element a Source
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 2Just "four"
node :: Name -> Traversal' Element Element Source
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".textJust "moo"
>>>doc ^? xml.node "baz".textNothing
named :: Fold Name a -> Traversal' Element Element Source
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").textJust "28"
>>>doc ^? xml...named (only "baz").nameNothing
attrs :: IndexedTraversal' Name Element Text Source
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 Element Source
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).textJust "7"
text :: Traversal' Element Text Source
Traverse node text contents
>>>let doc = "<root>boo</root>" :: TL.Text
>>>doc ^? xml.textJust "boo"
>>>doc & xml.text <>~ "hoo""<?xml version=\"1.0\" encoding=\"UTF-8\"?><root>boohoo</root>"
texts :: Traversal' Element Text Source
Traverse node text contents recursively
>>>let doc = "<root>qux<foo>boo</foo><bar><baz>hoo</baz>quux</bar></root>" :: TL.Text
>>>doc ^.. xml.texts["qux","boo","hoo","quux"]
>>>doc & xml.texts %~ Text.toUpper"<?xml version=\"1.0\" encoding=\"UTF-8\"?><root>QUX<foo>BOO</foo><bar><baz>HOO</baz>QUUX</bar></root>"
class HasComments t where Source
Anything that has comments
Instances
| HasComments Miscellaneous | |
| HasComments Element |
class HasInstructions t where Source
Anything that has processing instructions
Methods
instructions :: Traversal' t Instruction Source
Instances
| HasInstructions Miscellaneous | |
| HasInstructions Element |
Name
data Name :: *
name :: HasName t => Lens' t Text Source
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.namespaceNothing
>>>("<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.prefixNothing
>>>("<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\"/>"
Anything that has a name
Instruction
data Instruction :: *
target :: Traversal' Instruction Text Source
Processing instruction target
>>>let doc = "<root><?foo bar?></root>" :: TL.Text
>>>doc ^? xml.instructions.targetJust "foo"
>>>doc & xml.instructions.target .~ "boo""<?xml version=\"1.0\" encoding=\"UTF-8\"?><root><?boo bar?></root>"
data_ :: Traversal' Instruction Text Source
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
data UnresolvedEntityException :: *
data XMLException :: *
_MissingRootElement :: AsInvalidEventStream t => Prism' t () Source
A Prism into MissingRootElement
_ContentAfterRoot :: AsInvalidEventStream t => Prism' t EventPos Source
A Prism into ContentAfterRoot
_InvalidInlineDoctype :: AsInvalidEventStream t => Prism' t EventPos Source
A Prism into InvalidInlineDoctype
_MissingEndElement :: AsInvalidEventStream t => Prism' t (Name, Maybe EventPos) Source
A Prism into MissingEndElement
_UnterminatedInlineDoctype :: AsInvalidEventStream t => Prism' t () Source
A Prism into UnterminatedInlineDoctype
class AsUnresolvedEntityException t where Source
xml-conduit entity resolving exceptions overloading
Minimal complete definition
Nothing
Methods
_UnresolvedEntityException :: Prism' t UnresolvedEntityException Source
class AsXMLException t where Source
xml-conduit general XML exception overloading
Minimal complete definition
Nothing
Methods
_XMLException :: Prism' t XMLException Source
class AsInvalidEventStream t where Source
xml-conduit XML parsing exceptions overloading
Minimal complete definition
Nothing
Methods
_InvalidEventStream :: Prism' t InvalidEventStream Source
Instances
| AsInvalidEventStream SomeException | |
| AsInvalidEventStream InvalidEventStream |
module Text.Xml.Lens.LowLevel