-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Pure-Haskell utilities for dealing with XML with the conduit package. -- -- Hackage documentation generation is not reliable. For up to date -- documentation, please see: -- http://www.stackage.org/package/xml-conduit. @package xml-conduit @version 1.9.1.3 -- | Generalized cursors to be applied to different nodes. module Text.XML.Cursor.Generic -- | A cursor: contains an XML Node and pointers to its children, -- ancestors and siblings. data Cursor node type Axis node = Cursor node -> [Cursor node] toCursor :: (node -> [node]) -> node -> Cursor node -- | The current node. node :: Cursor node -> node -- | The child axis. XPath: the child axis contains the children of the -- context node. child :: Cursor node -> [Cursor node] -- | The parent axis. As described in XPath: the parent axis contains -- the parent of the context node, if there is one. -- -- Every node but the root element of the document has a parent. Parent -- nodes will always be NodeElements. parent :: Axis node -- | The preceding-sibling axis. XPath: the preceding-sibling axis -- contains all the preceding siblings of the context node [...]. precedingSibling :: Axis node -- | The following-sibling axis. XPath: the following-sibling axis -- contains all the following siblings of the context node [...]. followingSibling :: Axis node -- | The ancestor axis. XPath: the ancestor axis contains the ancestors -- of the context node; the ancestors of the context node consist of the -- parent of context node and the parent's parent and so on; thus, the -- ancestor axis will always include the root node, unless the context -- node is the root node. ancestor :: Axis node -- | The descendant axis. XPath: the descendant axis contains the -- descendants of the context node; a descendant is a child or a child of -- a child and so on; thus the descendant axis never contains attribute -- or namespace nodes. descendant :: Axis node -- | Modify an axis by adding the context node itself as the first element -- of the result list. orSelf :: Axis node -> Axis node -- | The preceding axis. XPath: the preceding axis contains all nodes in -- the same document as the context node that are before the context node -- in document order, excluding any ancestors and excluding attribute -- nodes and namespace nodes. preceding :: Axis node -- | The following axis. XPath: the following axis contains all nodes in -- the same document as the context node that are after the context node -- in document order, excluding any descendants and excluding attribute -- nodes and namespace nodes. following :: Axis node -- | Apply a function to the result of an axis. (&|) :: (Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b] infixr 1 &| -- | Combine two axes so that the second works on the children of the -- results of the first. (&/) :: Axis node -> (Cursor node -> [a]) -> Cursor node -> [a] infixr 1 &/ -- | Combine two axes so that the second works on the descendants of the -- results of the first. (&//) :: Axis node -> (Cursor node -> [a]) -> Cursor node -> [a] infixr 1 &// -- | Combine two axes so that the second works on both the result nodes, -- and their descendants. (&.//) :: Axis node -> (Cursor node -> [a]) -> Cursor node -> [a] infixr 1 &.// -- | Apply an axis to a 'Cursor node'. ($|) :: Cursor node -> (Cursor node -> a) -> a infixr 1 $| -- | Apply an axis to the children of a 'Cursor node'. ($/) :: Cursor node -> (Cursor node -> [a]) -> [a] infixr 1 $/ -- | Apply an axis to the descendants of a 'Cursor node'. ($//) :: Cursor node -> (Cursor node -> [a]) -> [a] infixr 1 $// -- | Apply an axis to a 'Cursor node' as well as its descendants. ($.//) :: Cursor node -> (Cursor node -> [a]) -> [a] infixr 1 $.// -- | Left-to-right composition of Kleisli arrows. -- -- '(bs >=> cs) a' can be understood as the -- do expression -- --
--   do b <- bs a
--      cs b
--   
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 >=> instance GHC.Show.Show node => GHC.Show.Show (Text.XML.Cursor.Generic.Cursor node) -- | Enumeratees to render XML Events. Unlike -- libxml-enumerator and expat-enumerator, this module does not provide -- IO and ST variants, since the underlying rendering operations are pure -- functions. module Text.XML.Stream.Render -- | Render a stream of Events into a stream of Builders. -- Builders are from the blaze-builder package, and allow the create of -- optimally sized ByteStrings with minimal buffer copying. renderBuilder :: Monad m => RenderSettings -> ConduitT Event Builder m () -- | Same as renderBuilder but allows you to flush XML stream to -- ensure that all events at needed point are rendered. renderBuilderFlush :: Monad m => RenderSettings -> ConduitT (Flush Event) (Flush Builder) m () -- | Render a stream of Events into a stream of ByteStrings. -- This function wraps around renderBuilder and -- builderToByteString, so it produces optimally sized -- ByteStrings with minimal buffer copying. -- -- The output is UTF8 encoded. renderBytes :: PrimMonad m => RenderSettings -> ConduitT Event ByteString m () -- | Render a stream of Events into a stream of Texts. This -- function wraps around renderBuilder, builderToByteString -- and renderBytes, so it produces optimally sized Texts -- with minimal buffer copying. renderText :: (PrimMonad m, MonadThrow m) => RenderSettings -> ConduitT Event Text m () -- | Convert a stream of Events into a prettified one, adding extra -- whitespace. Note that this can change the meaning of your XML. prettify :: Monad m => ConduitT (Flush Event) (Flush Event) m () data RenderSettings -- | The default value for this type. def :: Default a => a rsPretty :: RenderSettings -> Bool -- | Defines some top level namespace definitions to be used, in the form -- of (prefix, namespace). This has absolutely no impact on the meaning -- of your documents, but can increase readability by moving commonly -- used namespace declarations to the top level. rsNamespaces :: RenderSettings -> [(Text, Text)] -- | Specify how to turn the unordered attributes used by the -- Text.XML module into an ordered list. rsAttrOrder :: RenderSettings -> Name -> Map Name Text -> [(Name, Text)] -- | Determines if for a given text content the renderer should use a CDATA -- node. -- -- Default: False rsUseCDATA :: RenderSettings -> Content -> Bool -- | Determines whether the XML declaration will be output. -- -- Default: True rsXMLDeclaration :: RenderSettings -> Bool -- | Convenience function to create an ordering function suitable for use -- as the value of rsAttrOrder. The ordering function is created -- from an explicit ordering of the attributes, specified as a list of -- tuples, as follows: In each tuple, the first component is the -- Name of an element, and the second component is a list of -- attributes names. When the given element is rendered, the attributes -- listed, when present, appear first in the given order, followed by any -- other attributes in arbitrary order. If an element does not appear, -- all of its attributes are rendered in arbitrary order. orderAttrs :: [(Name, [Name])] -> Name -> Map Name Text -> [(Name, Text)] -- | Generate a complete XML Element. tag :: Monad m => Name -> Attributes -> ConduitT i Event m () -> ConduitT i Event m () -- | Generate a textual EventContent. content :: Monad m => Text -> ConduitT i Event m () -- | A list of attributes. data Attributes -- | Generate a single attribute. attr :: Name -> Text -> Attributes -- | Helper function that generates a valid attribute if input isn't -- Nothing, or mempty otherwise. optionalAttr :: Name -> Maybe Text -> Attributes instance GHC.Base.Monoid Text.XML.Stream.Render.Attributes instance GHC.Base.Semigroup Text.XML.Stream.Render.Attributes instance Data.Default.Class.Default Text.XML.Stream.Render.RenderSettings -- | This module provides both a native Haskell solution for parsing XML -- documents into a stream of events, and a set of parser combinators for -- dealing with a stream of events. -- -- As a simple example: -- --
--   >>> :set -XOverloadedStrings
--   
--   >>> import Conduit (runConduit, (.|))
--   
--   >>> import Data.Text (Text, unpack)
--   
--   >>> import Data.XML.Types (Event)
--   
--   >>> data Person = Person Int Text Text deriving Show
--   
--   >>> :{
--   let parsePerson :: MonadThrow m => ConduitT Event o m (Maybe Person)
--       parsePerson = tag' "person" parseAttributes $ \(age, goodAtHaskell) -> do
--         name <- content
--         return $ Person (read $ unpack age) name goodAtHaskell
--         where parseAttributes = (,) <$> requireAttr "age" <*> requireAttr "goodAtHaskell" <* ignoreAttrs
--       parsePeople :: MonadThrow m => ConduitT Event o m (Maybe [Person])
--       parsePeople = tagNoAttr "people" $ many parsePerson
--       inputXml = mconcat
--         [ "<?xml version=\"1.0\" encoding=\"utf-8\"?>"
--         , "<people>"
--         , "  <person age=\"25\" goodAtHaskell=\"yes\">Michael</person>"
--         , "  <person age=\"2\" goodAtHaskell=\"might become\">Eliezer</person>"
--         , "</people>"
--         ]
--   :}
--   
-- --
--   >>> runConduit $ parseLBS def inputXml .| force "people required" parsePeople
--   [Person 25 "Michael" "yes",Person 2 "Eliezer" "might become"]
--   
-- -- This module also supports streaming results using yield. This -- allows parser results to be processed using conduits while a -- particular parser (e.g. many) is still running. Without using -- streaming results, you have to wait until the parser finished before -- you can process the result list. Large XML files might be easier to -- process by using streaming results. See -- http://stackoverflow.com/q/21367423/2597135 for a related -- discussion. -- --
--   >>> import Data.Conduit.List as CL
--   
--   >>> :{
--   let parsePeople' :: MonadThrow m => ConduitT Event Person m (Maybe ())
--       parsePeople' = tagNoAttr "people" $ manyYield parsePerson
--   :}
--   
-- --
--   >>> runConduit $ parseLBS def inputXml .| force "people required" parsePeople' .| CL.mapM_ print
--   Person 25 "Michael" "yes"
--   Person 2 "Eliezer" "might become"
--   
-- -- Previous versions of this module contained a number of more -- sophisticated functions written by Aristid Breitkreuz and Dmitry -- Olshansky. To keep this package simpler, those functions are being -- moved to a separate package. This note will be updated with the name -- of the package(s) when available. module Text.XML.Stream.Parse -- | Parses a byte stream into Events. This function is implemented -- fully in Haskell using attoparsec-text for parsing. The produced error -- messages do not give line/column information, so you may prefer to -- stick with the parser provided by libxml-enumerator. However, this has -- the advantage of not relying on any C libraries. -- -- This relies on detectUtf to determine character encoding, and -- parseText to do the actual parsing. parseBytes :: MonadThrow m => ParseSettings -> ConduitT ByteString Event m () parseBytesPos :: MonadThrow m => ParseSettings -> ConduitT ByteString EventPos m () -- | Parses a character stream into Events. This function is -- implemented fully in Haskell using attoparsec-text for parsing. The -- produced error messages do not give line/column information, so you -- may prefer to stick with the parser provided by libxml-enumerator. -- However, this has the advantage of not relying on any C libraries. -- -- Since 1.2.4 parseText :: MonadThrow m => ParseSettings -> ConduitT Text Event m () -- | Same as parseText, but includes the position of each event. -- -- Since 1.2.4 parseTextPos :: MonadThrow m => ParseSettings -> ConduitT Text EventPos m () -- | Automatically determine which UTF variant is being used. This function -- first checks for BOMs, removing them as necessary, and then check for -- the equivalent of <?xml for each of UTF-8, UTF-16LEBE, and -- UTF-32LEBE. It defaults to assuming UTF-8. detectUtf :: MonadThrow m => ConduitT ByteString Text m () -- | A helper function which reads a file from disk using -- enumFile, detects character encoding using detectUtf, -- parses the XML using parseBytes, and then hands off control to -- your supplied parser. parseFile :: MonadResource m => ParseSettings -> FilePath -> ConduitT i Event m () -- | Parse an event stream from a lazy ByteString. parseLBS :: MonadThrow m => ParseSettings -> ByteString -> ConduitT i Event m () data ParseSettings -- | The default value for this type. def :: Default a => a type DecodeEntities = Text -> Content type DecodeIllegalCharacters = Int -> Maybe Char psDecodeEntities :: ParseSettings -> DecodeEntities -- | How to decode illegal character references (&#[0-9]+; or -- &#x[0-9a-fA-F]+;). -- -- Character references within the legal ranges defined by the -- standard are automatically parsed. Others are passed to this -- function. -- -- Default: const Nothing -- -- Since 1.7.1 psDecodeIllegalCharacters :: ParseSettings -> DecodeIllegalCharacters -- | Whether the original xmlns attributes should be retained in the parsed -- values. For more information on motivation, see: -- -- https://github.com/snoyberg/xml/issues/38 -- -- Default: False -- -- Since 1.2.1 psRetainNamespaces :: ParseSettings -> Bool -- | Maximum number of characters allowed in expanding an internal entity. -- This is intended to protect against the billion laughs attack. -- -- Default: 8192 -- -- Since 1.9.1 psEntityExpansionSizeLimit :: ParseSettings -> Int -- | Whether to resolve any but the predefined entities. -- -- Default: False psIgnoreInternalEntityDeclarations :: ParseSettings -> Bool -- | Default implementation of DecodeEntities, which leaves the -- entity as-is. Numeric character references and the five standard -- entities (lt, gt, amp, quot, pos) are handled internally by the -- parser. decodeXmlEntities :: DecodeEntities -- | HTML4-compliant entity decoder. Handles the additional 248 entities -- defined by HTML 4 and XHTML 1. -- -- Note that HTML 5 introduces a drastically larger number of entities, -- and this code does not recognize most of them. decodeHtmlEntities :: DecodeEntities -- | The most generic way to parse a tag. It takes a NameMatcher to -- check whether this is a correct tag name, an AttrParser to -- handle attributes, and then a parser to deal with content. -- -- Events are consumed if and only if the tag name and its -- attributes match. -- -- This function automatically absorbs its balancing closing tag, and -- will throw an exception if not all of the attributes or child elements -- are consumed. If you want to allow extra attributes, see -- ignoreAttrs. -- -- This function automatically ignores comments, instructions and -- whitespace. tag :: MonadThrow m => NameMatcher a -> (a -> AttrParser b) -> (b -> ConduitT Event o m c) -> ConduitT Event o m (Maybe c) -- | A simplified version of tag where the NameMatcher result -- isn't forwarded to the attributes parser. -- -- Since 1.5.0 tag' :: MonadThrow m => NameMatcher a -> AttrParser b -> (b -> ConduitT Event o m c) -> ConduitT Event o m (Maybe c) -- | A further simplified tag parser, which requires that no attributes -- exist. tagNoAttr :: MonadThrow m => NameMatcher a -> ConduitT Event o m b -> ConduitT Event o m (Maybe b) -- | A further simplified tag parser, which ignores all attributes, if any -- exist tagIgnoreAttrs :: MonadThrow m => NameMatcher a -> ConduitT Event o m b -> ConduitT Event o m (Maybe b) -- | Grabs the next piece of content. If none if available, returns -- empty. This is simply a wrapper around contentMaybe. content :: MonadThrow m => ConduitT Event o m Text -- | Grabs the next piece of content if available. This function skips over -- any comments, instructions or entities, and concatenates all content -- until the next start or end tag. contentMaybe :: MonadThrow m => ConduitT Event o m (Maybe Text) -- | Ignore an empty tag and all of its attributes. This does not ignore -- the tag recursively (i.e. it assumes there are no child elements). -- This function returns Just () if the tag matched. -- -- Since 1.5.0 ignoreEmptyTag :: MonadThrow m => NameMatcher a -> ConduitT Event o m (Maybe ()) -- | Same as takeTree, without yielding Events. -- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| (ignoreTree "a" ignoreAttrs >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "b", ...}) [],EventEndElement (Name {nameLocalName = "b", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "<a>content</a>" .| (ignoreTree "b" ignoreAttrs >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "a", ...}) [],EventContent (ContentText "content"),EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "content<a></a>" .| (ignoreTree anyName ignoreAttrs >> sinkList)
--   [EventContent (ContentText "content"),EventBeginElement (Name {nameLocalName = "a", ...}) [],EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- -- Since 1.9.0 ignoreTree :: MonadThrow m => NameMatcher a -> AttrParser b -> ConduitT Event o m (Maybe ()) -- | Same as takeContent, without yielding Events. -- --
--   >>> runConduit $ parseLBS def "<a>content</a>" .| (ignoreContent >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "a", ...}) [],EventContent (ContentText "content"),EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "content<a></a>" .| (ignoreContent >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "a", ...}) [],EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "content<a></a>" .| (ignoreContent >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "a", ...}) [],EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- -- Since 1.9.0 ignoreContent :: MonadThrow m => ConduitT Event o m (Maybe ()) -- | Same as takeTreeContent, without yielding Events. -- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| (ignoreTreeContent "a" ignoreAttrs >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "b", ...}) [],EventEndElement (Name {nameLocalName = "b", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "<a>content</a>" .| (ignoreTreeContent "b" ignoreAttrs >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "a", ...}) [],EventContent (ContentText "content"),EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "content<a></a>" .| (ignoreTreeContent anyName ignoreAttrs >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "a", ...}) [],EventEndElement (Name {nameLocalName = "a", ...}),EventEndDocument]
--   
-- -- Since 1.5.0 ignoreTreeContent :: MonadThrow m => NameMatcher a -> AttrParser b -> ConduitT Event o m (Maybe ()) -- | Same as takeAnyTreeContent, without yielding Events. -- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| (ignoreAnyTreeContent >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "b", ...}) [],EventEndElement (Name {nameLocalName = "b", ...}),EventEndDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "text<b></b>" .| (ignoreAnyTreeContent >> sinkList)
--   [EventBeginElement (Name {nameLocalName = "b", ...}) [],EventEndElement (Name {nameLocalName = "b", ...}),EventEndDocument]
--   
-- -- Since 1.5.0 ignoreAnyTreeContent :: MonadThrow m => ConduitT Event o m (Maybe ()) -- | Stream a single content Event. -- -- Returns Just () if a content Event was consumed, -- Nothing otherwise. -- --
--   >>> runConduit $ parseLBS def "content<a></a>" .| void takeContent .| sinkList
--   [EventBeginDocument,EventContent (ContentText "content")]
--   
-- -- If next event isn't a content, nothing is consumed. -- --
--   >>> runConduit $ parseLBS def "<a>content</a>" .| void takeContent .| sinkList
--   [EventBeginDocument]
--   
-- -- Since 1.5.0 takeContent :: MonadThrow m => ConduitT Event Event m (Maybe ()) -- | Stream Events corresponding to a single XML element that -- matches given NameMatcher and AttrParser, from the -- opening- to the closing-tag. -- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| void (takeTree "a" ignoreAttrs) .| sinkList
--   [EventBeginDocument,EventBeginElement (Name {nameLocalName = "a", ...}) [],EventContent (ContentText "content"),EventEndElement (Name {nameLocalName = "a", ...})]
--   
-- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| void (takeTree "b" ignoreAttrs) .| sinkList
--   [EventBeginDocument]
--   
-- -- If next Event isn't an element, nothing is consumed. -- --
--   >>> runConduit $ parseLBS def "text<a></a>" .| void (takeTree "a" ignoreAttrs) .| sinkList
--   [EventBeginDocument]
--   
-- -- If an opening-tag is consumed but no matching closing-tag is found, an -- XmlException is thrown. -- --
--   >>> runConduit $ parseLBS def "<a><b></b>" .| void (takeTree "a" ignoreAttrs) .| sinkList
--   *** Exception: InvalidEndElement (Name {nameLocalName = "a", nameNamespace = Nothing, namePrefix = Nothing}) Nothing
--   
-- -- This function automatically ignores comments, instructions and -- whitespace. -- -- Returns Just () if an element was consumed, Nothing -- otherwise. -- -- Since 1.5.0 takeTree :: MonadThrow m => NameMatcher a -> AttrParser b -> ConduitT Event Event m (Maybe ()) -- | Like takeTree, but can also stream a content Event. -- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| void (takeTreeContent "a" ignoreAttrs) .| sinkList
--   [EventBeginDocument,EventBeginElement (Name {nameLocalName = "a", ...}) [],EventContent (ContentText "content"),EventEndElement (Name {nameLocalName = "a", ...})]
--   
-- --
--   >>> runConduit $ parseLBS def "<a>content</a><b></b>" .| void (takeTreeContent "b" ignoreAttrs) .| sinkList
--   [EventBeginDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "content<a></a><b></b>" .| void (takeTreeContent "a" ignoreAttrs) .| sinkList
--   [EventBeginDocument,EventContent (ContentText "content")]
--   
-- -- Since 1.5.0 takeTreeContent :: MonadThrow m => NameMatcher a -> AttrParser b -> ConduitT Event Event m (Maybe ()) -- | Like takeTreeContent, without checking for tag name or -- attributes. -- --
--   >>> runConduit $ parseLBS def "text<a></a>" .| void takeAnyTreeContent .| sinkList
--   [EventBeginDocument,EventContent (ContentText "text")]
--   
-- --
--   >>> runConduit $ parseLBS def "</a><b></b>" .| void takeAnyTreeContent .| sinkList
--   [EventBeginDocument]
--   
-- --
--   >>> runConduit $ parseLBS def "<b><c></c></b></a>text" .| void takeAnyTreeContent .| sinkList
--   [EventBeginDocument,EventBeginElement (Name {nameLocalName = "b", ...}) [],EventBeginElement (Name {nameLocalName = "c", ...}) [],EventEndElement (Name {nameLocalName = "c", ...}),EventEndElement (Name {nameLocalName = "b", ...})]
--   
-- -- Since 1.5.0 takeAnyTreeContent :: MonadThrow m => ConduitT Event Event m (Maybe ()) -- | A NameMatcher describes which names a tag parser is allowed -- to match. -- -- Since 1.5.0 newtype NameMatcher a NameMatcher :: (Name -> Maybe a) -> NameMatcher a [runNameMatcher] :: NameMatcher a -> Name -> Maybe a -- | matching f matches name iff f name is true. -- Returns the matched Name. -- -- Since 1.5.0 matching :: (Name -> Bool) -> NameMatcher Name -- | Matches any Name from the given list. Returns the matched -- Name. -- -- Since 1.5.0 anyOf :: [Name] -> NameMatcher Name -- | Matches any Name. Returns the matched Name. -- -- Since 1.5.0 anyName :: NameMatcher Name -- | A monad for parsing attributes. By default, it requires you to deal -- with all attributes present on an element, and will throw an exception -- if there are unhandled attributes. Use the requireAttr, -- attr et al functions for handling an attribute, and -- ignoreAttrs if you would like to skip the rest of the -- attributes on an element. -- -- Alternative instance behaves like First monoid: it -- chooses first parser which doesn't fail. data AttrParser a -- | Return the value for an attribute if present. attr :: Name -> AttrParser (Maybe Text) -- | Shortcut composition of force and attr. requireAttr :: Name -> AttrParser Text -- | Deprecated: Please use attr. optionalAttr :: Name -> AttrParser (Maybe Text) requireAttrRaw :: String -> ((Name, [Content]) -> Maybe b) -> AttrParser b optionalAttrRaw :: ((Name, [Content]) -> Maybe b) -> AttrParser (Maybe b) -- | Skip the remaining attributes on an element. Since this will clear the -- list of attributes, you must call this after any calls to -- requireAttr, optionalAttr, etc. ignoreAttrs :: AttrParser () -- | Get the value of the first parser which returns Just. If no -- parsers succeed (i.e., return Just), this function returns -- Nothing. -- --
--   orE a b = choose [a, b]
--   
-- -- Warning: orE doesn't backtrack. See choose for detailed -- explanation. orE :: Monad m => ConduitT Event o m (Maybe a) -> ConduitT Event o m (Maybe a) -> ConduitT Event o m (Maybe a) -- | Get the value of the first parser which returns Just. If no -- parsers succeed (i.e., return Just), this function returns -- Nothing. -- -- Warning: choose doesn't backtrack. If a parser consumed some -- events, subsequent parsers will continue from the following events. -- This can be a problem if parsers share an accepted prefix of events, -- so an earlier (failing) parser will discard the events that the later -- parser could potentially succeed on. -- -- An other problematic case is using choose to implement -- order-independent parsing using a set of parsers, with a final -- trailing ignore-anything-else action. In this case, certain trees -- might be skipped. -- --
--   >>> :{
--   let parse2Tags name1 name2 = do
--         tag1 <- tagNoAttr name1 (pure ())
--         tag2 <- tagNoAttr name2 (pure tag1)
--         return $ join tag2
--   :}
--   
-- --
--   >>> :{
--   runConduit $ parseLBS def "<a></a><b></b>" .| choose
--     [ parse2Tags "a" "b"
--     , parse2Tags "a" "c"
--     ]
--   :}
--   Just ()
--   
-- --
--   >>> :{
--   runConduit $ parseLBS def "<a></a><b></b>" .| choose
--     [ parse2Tags "a" "c"
--     , parse2Tags "a" "b"
--     ]
--   :}
--   Nothing
--   
choose :: Monad m => [ConduitT Event o m (Maybe a)] -> ConduitT Event o m (Maybe a) -- | Keep parsing elements as long as the parser returns Just. many :: Monad m => ConduitT Event o m (Maybe a) -> ConduitT Event o m [a] -- | Like many but discards the results without building an -- intermediate list. -- -- Since 1.5.0 many_ :: MonadThrow m => ConduitT Event o m (Maybe a) -> ConduitT Event o m () -- | Keep parsing elements as long as the parser returns Just or the -- ignore parser returns Just. manyIgnore :: Monad m => ConduitT Event o m (Maybe a) -> ConduitT Event o m (Maybe b) -> ConduitT Event o m [a] -- | Like many, but any tags and content the consumer doesn't -- match on are silently ignored. many' :: MonadThrow m => ConduitT Event o m (Maybe a) -> ConduitT Event o m [a] -- | Force an optional parser into a required parser. All of the tag -- functions, attr, choose and many deal with -- Maybe parsers. Use this when you want to finally force -- something to happen. force :: MonadThrow m => String -> m (Maybe a) -> m a -- | Like many, but uses yield so the result list can be -- streamed to downstream conduits without waiting for manyYield -- to finish manyYield :: Monad m => ConduitT a b m (Maybe b) -> ConduitT a b m () -- | Like many', but uses yield so the result list can be -- streamed to downstream conduits without waiting for manyYield' -- to finish manyYield' :: MonadThrow m => ConduitT Event b m (Maybe b) -> ConduitT Event b m () -- | Like manyIgnore, but uses yield so the result list can -- be streamed to downstream conduits without waiting for -- manyIgnoreYield to finish manyIgnoreYield :: MonadThrow m => ConduitT Event b m (Maybe b) -> ConduitT Event b m (Maybe ()) -> ConduitT Event b m () data XmlException XmlException :: String -> Maybe Event -> XmlException [xmlErrorMessage] :: XmlException -> String [xmlBadInput] :: XmlException -> Maybe Event InvalidEndElement :: Name -> Maybe Event -> XmlException InvalidEntity :: String -> Maybe Event -> XmlException MissingAttribute :: String -> XmlException UnparsedAttributes :: [(Name, [Content])] -> XmlException data PositionRange type EventPos = (Maybe PositionRange, Event) instance GHC.Show.Show Text.XML.Stream.Parse.XmlException instance GHC.Base.Functor Text.XML.Stream.Parse.NameMatcher instance GHC.Base.Monad Text.XML.Stream.Parse.AttrParser instance GHC.Base.Functor Text.XML.Stream.Parse.AttrParser instance GHC.Base.Applicative Text.XML.Stream.Parse.AttrParser instance GHC.Base.Alternative Text.XML.Stream.Parse.AttrParser instance Control.Monad.Catch.MonadThrow Text.XML.Stream.Parse.AttrParser instance GHC.Base.Applicative Text.XML.Stream.Parse.NameMatcher instance GHC.Base.Alternative Text.XML.Stream.Parse.NameMatcher instance (a GHC.Types.~ Data.XML.Types.Name) => Data.String.IsString (Text.XML.Stream.Parse.NameMatcher a) instance GHC.Exception.Type.Exception Text.XML.Stream.Parse.XmlException instance Data.Default.Class.Default Text.XML.Stream.Parse.ParseSettings -- | DOM-based XML parsing and rendering. -- -- In this module, attribute values and content nodes can contain either -- raw text or entities. In most cases, these can be fully resolved at -- parsing. If that is the case for your documents, the Text.XML -- module provides simplified datatypes that only contain raw text. module Text.XML.Unresolved writeFile :: RenderSettings -> FilePath -> Document -> IO () readFile :: ParseSettings -> FilePath -> IO Document renderLBS :: RenderSettings -> Document -> ByteString parseLBS :: ParseSettings -> ByteString -> Either SomeException Document parseLBS_ :: ParseSettings -> ByteString -> Document parseText :: ParseSettings -> Text -> Either SomeException Document parseText_ :: ParseSettings -> Text -> Document sinkTextDoc :: MonadThrow m => ParseSettings -> ConduitT Text o m Document sinkDoc :: MonadThrow m => ParseSettings -> ConduitT ByteString o m Document -- | Render a document into events. toEvents :: Document -> [Event] -- | Render a document element into events. elementToEvents :: Element -> [Event] -- | Parse a document from a stream of events. fromEvents :: MonadThrow m => ConduitT EventPos o m Document -- | Try to parse a document element (as defined in XML) from a stream of -- events. elementFromEvents :: MonadThrow m => ConduitT EventPos o m (Maybe Element) renderBuilder :: Monad m => RenderSettings -> Document -> ConduitT i Builder m () renderBytes :: PrimMonad m => RenderSettings -> Document -> ConduitT i ByteString m () renderText :: (MonadThrow m, PrimMonad m) => RenderSettings -> Document -> ConduitT i Text m () data InvalidEventStream ContentAfterRoot :: EventPos -> InvalidEventStream MissingRootElement :: InvalidEventStream InvalidInlineDoctype :: EventPos -> InvalidEventStream MissingEndElement :: Name -> Maybe EventPos -> InvalidEventStream UnterminatedInlineDoctype :: InvalidEventStream -- | The default value for this type. def :: Default a => a data ParseSettings psDecodeEntities :: ParseSettings -> DecodeEntities -- | Whether the original xmlns attributes should be retained in the parsed -- values. For more information on motivation, see: -- -- https://github.com/snoyberg/xml/issues/38 -- -- Default: False -- -- Since 1.2.1 psRetainNamespaces :: ParseSettings -> Bool data RenderSettings rsPretty :: RenderSettings -> Bool -- | Defines some top level namespace definitions to be used, in the form -- of (prefix, namespace). This has absolutely no impact on the meaning -- of your documents, but can increase readability by moving commonly -- used namespace declarations to the top level. rsNamespaces :: RenderSettings -> [(Text, Text)] instance GHC.Exception.Type.Exception Text.XML.Unresolved.InvalidEventStream instance GHC.Show.Show Text.XML.Unresolved.InvalidEventStream -- | DOM-based parsing and rendering. -- -- This module requires that all entities be resolved at parsing. If you -- need to interact with unresolved entities, please use -- Text.XML.Unresolved. This is the recommended module for most -- uses cases. -- -- While many of the datatypes in this module are simply re-exported from -- Data.XML.Types, Document, Node and -- Element are all redefined here to disallow the possibility of -- unresolved entities. Conversion functions are provided to switch -- between the two sets of datatypes. -- -- For simpler, bidirectional traversal of the DOM tree, see the -- Text.XML.Cursor module. module Text.XML data Document Document :: Prologue -> Element -> [Miscellaneous] -> Document [documentPrologue] :: Document -> Prologue [documentRoot] :: Document -> Element [documentEpilogue] :: Document -> [Miscellaneous] data Prologue Prologue :: [Miscellaneous] -> Maybe Doctype -> [Miscellaneous] -> Prologue [prologueBefore] :: Prologue -> [Miscellaneous] [prologueDoctype] :: Prologue -> Maybe Doctype [prologueAfter] :: Prologue -> [Miscellaneous] data Instruction Instruction :: Text -> Text -> Instruction [instructionTarget] :: Instruction -> Text [instructionData] :: Instruction -> Text data Miscellaneous MiscInstruction :: Instruction -> Miscellaneous MiscComment :: Text -> Miscellaneous data Node NodeElement :: Element -> Node NodeInstruction :: Instruction -> Node NodeContent :: Text -> Node NodeComment :: Text -> Node data Element Element :: Name -> Map Name Text -> [Node] -> Element [elementName] :: Element -> Name [elementAttributes] :: Element -> Map Name Text [elementNodes] :: Element -> [Node] -- | 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"
--   
data Name Name :: Text -> Maybe Text -> Maybe Text -> Name [nameLocalName] :: Name -> Text [nameNamespace] :: Name -> Maybe Text [namePrefix] :: Name -> Maybe Text -- | 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. data Doctype Doctype :: Text -> Maybe ExternalID -> Doctype [doctypeName] :: Doctype -> Text [doctypeID] :: Doctype -> Maybe ExternalID data ExternalID SystemID :: Text -> ExternalID PublicID :: Text -> Text -> ExternalID readFile :: ParseSettings -> FilePath -> IO Document parseLBS :: ParseSettings -> ByteString -> Either SomeException Document parseLBS_ :: ParseSettings -> ByteString -> Document sinkDoc :: MonadThrow m => ParseSettings -> ConduitT ByteString o m Document parseText :: ParseSettings -> Text -> Either SomeException Document parseText_ :: ParseSettings -> Text -> Document sinkTextDoc :: MonadThrow m => ParseSettings -> ConduitT Text o m Document fromEvents :: MonadThrow m => ConduitT EventPos o m Document data UnresolvedEntityException UnresolvedEntityException :: Set Text -> UnresolvedEntityException data XMLException InvalidXMLFile :: FilePath -> SomeException -> XMLException writeFile :: RenderSettings -> FilePath -> Document -> IO () renderLBS :: RenderSettings -> Document -> ByteString renderText :: RenderSettings -> Document -> Text renderBytes :: PrimMonad m => RenderSettings -> Document -> ConduitT i ByteString m () -- | The default value for this type. def :: Default a => a data ParseSettings psDecodeEntities :: ParseSettings -> DecodeEntities -- | Whether the original xmlns attributes should be retained in the parsed -- values. For more information on motivation, see: -- -- https://github.com/snoyberg/xml/issues/38 -- -- Default: False -- -- Since 1.2.1 psRetainNamespaces :: ParseSettings -> Bool -- | Default implementation of DecodeEntities, which leaves the -- entity as-is. Numeric character references and the five standard -- entities (lt, gt, amp, quot, pos) are handled internally by the -- parser. decodeXmlEntities :: DecodeEntities -- | HTML4-compliant entity decoder. Handles the additional 248 entities -- defined by HTML 4 and XHTML 1. -- -- Note that HTML 5 introduces a drastically larger number of entities, -- and this code does not recognize most of them. decodeHtmlEntities :: DecodeEntities data RenderSettings rsPretty :: RenderSettings -> Bool -- | Defines some top level namespace definitions to be used, in the form -- of (prefix, namespace). This has absolutely no impact on the meaning -- of your documents, but can increase readability by moving commonly -- used namespace declarations to the top level. rsNamespaces :: RenderSettings -> [(Text, Text)] -- | Specify how to turn the unordered attributes used by the -- Text.XML module into an ordered list. rsAttrOrder :: RenderSettings -> Name -> Map Name Text -> [(Name, Text)] -- | Determines if for a given text content the renderer should use a CDATA -- node. -- -- Default: False rsUseCDATA :: RenderSettings -> Content -> Bool -- | Determines whether the XML declaration will be output. -- -- Default: True rsXMLDeclaration :: RenderSettings -> Bool -- | Convenience function to create an ordering function suitable for use -- as the value of rsAttrOrder. The ordering function is created -- from an explicit ordering of the attributes, specified as a list of -- tuples, as follows: In each tuple, the first component is the -- Name of an element, and the second component is a list of -- attributes names. When the given element is rendered, the attributes -- listed, when present, appear first in the given order, followed by any -- other attributes in arbitrary order. If an element does not appear, -- all of its attributes are rendered in arbitrary order. orderAttrs :: [(Name, [Name])] -> Name -> Map Name Text -> [(Name, Text)] toXMLDocument :: Document -> Document fromXMLDocument :: Document -> Either (Set Text) Document toXMLNode :: Node -> Node fromXMLNode :: Node -> Either (Set Text) Node toXMLElement :: Element -> Element fromXMLElement :: Element -> Either (Set Text) Element instance Data.Data.Data Text.XML.Node instance GHC.Classes.Ord Text.XML.Node instance GHC.Classes.Eq Text.XML.Node instance GHC.Show.Show Text.XML.Node instance Data.Data.Data Text.XML.Element instance GHC.Classes.Ord Text.XML.Element instance GHC.Classes.Eq Text.XML.Element instance GHC.Show.Show Text.XML.Element instance Data.Data.Data Text.XML.Document instance GHC.Classes.Eq Text.XML.Document instance GHC.Show.Show Text.XML.Document instance GHC.Show.Show Text.XML.UnresolvedEntityException instance GHC.Exception.Type.Exception Text.XML.UnresolvedEntityException instance GHC.Show.Show Text.XML.XMLException instance GHC.Exception.Type.Exception Text.XML.XMLException instance Control.DeepSeq.NFData Text.XML.Document instance Text.Blaze.ToMarkup Text.XML.Document instance Control.DeepSeq.NFData Text.XML.Node instance Control.DeepSeq.NFData Text.XML.Element instance Text.Blaze.ToMarkup Text.XML.Element instance Text.Blaze.ToMarkup Text.XML.Node -- | This module provides for simple DOM traversal. It is inspired by -- XPath. There are two central concepts here: -- -- -- -- The terminology used in this module is taken directly from the XPath -- specification: http://www.w3.org/TR/xpath/. For those familiar -- with XPath, the one major difference is that attributes are not -- considered nodes in this module. module Text.XML.Cursor -- | A cursor: contains an XML Node and pointers to its children, -- ancestors and siblings. type Cursor = Cursor Node -- | The type of an Axis that returns a list of Cursors. They are roughly -- modeled after http://www.w3.org/TR/xpath/#axes. -- -- Axes can be composed with >=>, where e.g. f >=> -- g means that on all results of the f axis, the -- g axis will be applied, and all results joined together. -- Because Axis is just a type synonym for Cursor -> -- [Cursor], it is possible to use other standard functions like -- >>= or concatMap similarly. -- -- The operators &|, &/, &// and -- &.// can be used to combine axes so that the second axis -- works on the context nodes, children, descendants, respectively the -- context node as well as its descendants of the results of the first -- axis. -- -- The operators $|, $/, $// and $.// -- can be used to apply an axis (right-hand side) to a cursor so that it -- is applied on the cursor itself, its children, its descendants, -- respectively itself and its descendants. -- -- Note that many of these operators also work on generalised Axes -- that can return lists of something other than Cursors, for example -- Content elements. type Axis = Cursor -> [Cursor] -- | Convert a Document to a Cursor. It will point to the -- document root. fromDocument :: Document -> Cursor -- | Convert a Node to a Cursor (without parents). fromNode :: Node -> Cursor -- | Cut a cursor off from its parent. The idea is to allow restricting the -- scope of queries on it. cut :: Cursor -> Cursor -- | The parent axis. As described in XPath: the parent axis contains -- the parent of the context node, if there is one. -- -- Every node but the root element of the document has a parent. Parent -- nodes will always be NodeElements. parent :: Axis node -- | The preceding-sibling axis. XPath: the preceding-sibling axis -- contains all the preceding siblings of the context node [...]. precedingSibling :: Axis node -- | The following-sibling axis. XPath: the following-sibling axis -- contains all the following siblings of the context node [...]. followingSibling :: Axis node -- | The child axis. XPath: the child axis contains the children of the -- context node. child :: Cursor node -> [Cursor node] -- | The current node. node :: Cursor node -> node -- | The preceding axis. XPath: the preceding axis contains all nodes in -- the same document as the context node that are before the context node -- in document order, excluding any ancestors and excluding attribute -- nodes and namespace nodes. preceding :: Axis node -- | The following axis. XPath: the following axis contains all nodes in -- the same document as the context node that are after the context node -- in document order, excluding any descendants and excluding attribute -- nodes and namespace nodes. following :: Axis node -- | The ancestor axis. XPath: the ancestor axis contains the ancestors -- of the context node; the ancestors of the context node consist of the -- parent of context node and the parent's parent and so on; thus, the -- ancestor axis will always include the root node, unless the context -- node is the root node. ancestor :: Axis node -- | The descendant axis. XPath: the descendant axis contains the -- descendants of the context node; a descendant is a child or a child of -- a child and so on; thus the descendant axis never contains attribute -- or namespace nodes. descendant :: Axis node -- | Modify an axis by adding the context node itself as the first element -- of the result list. orSelf :: Axis node -> Axis node -- | Filter cursors that don't pass a check. check :: Boolean b => (Cursor -> b) -> Axis -- | Filter nodes that don't pass a check. checkNode :: Boolean b => (Node -> b) -> Axis -- | Filter elements that don't pass a check, and remove all non-elements. checkElement :: Boolean b => (Element -> b) -> Axis -- | Filter elements that don't pass a name check, and remove all -- non-elements. checkName :: Boolean b => (Name -> b) -> Axis -- | Remove all non-elements. Compare roughly to XPath: A node test * is -- true for any node of the principal node type. For example, child::* -- will select all element children of the context node [...]. anyElement :: Axis -- | Select only those elements with a matching tag name. XPath: A node -- test that is a QName is true if and only if the type of the node (see -- [5 Data Model]) is the principal node type and has an expanded-name -- equal to the expanded-name specified by the QName. element :: Name -> Axis -- | Select only those elements with a loosely matching tag name. Namespace -- and case are ignored. XPath: A node test that is a QName is true if -- and only if the type of the node (see [5 Data Model]) is the principal -- node type and has an expanded-name equal to the expanded-name -- specified by the QName. laxElement :: Text -> Axis -- | Select only text nodes, and directly give the Content values. -- XPath: The node test text() is true for any text node. -- -- Note that this is not strictly an Axis, but will work with most -- combinators. content :: Cursor -> [Text] -- | Select attributes on the current element (or nothing if it is not an -- element). XPath: the attribute axis contains the attributes of the -- context node; the axis will be empty unless the context node is an -- element -- -- Note that this is not strictly an Axis, but will work with most -- combinators. -- -- The return list of the generalised axis contains as elements lists of -- Content elements, each full list representing an attribute -- value. attribute :: Name -> Cursor -> [Text] -- | Select attributes on the current element (or nothing if it is not an -- element). Namespace and case are ignored. XPath: the attribute axis -- contains the attributes of the context node; the axis will be empty -- unless the context node is an element -- -- Note that this is not strictly an Axis, but will work with most -- combinators. -- -- The return list of the generalised axis contains as elements lists of -- Content elements, each full list representing an attribute -- value. laxAttribute :: Text -> Cursor -> [Text] -- | Select only those element nodes with the given attribute. hasAttribute :: Name -> Axis -- | Select only those element nodes containing the given attribute -- key/value pair. attributeIs :: Name -> Text -> Axis -- | Apply a function to the result of an axis. (&|) :: (Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b] infixr 1 &| -- | Combine two axes so that the second works on the children of the -- results of the first. (&/) :: Axis node -> (Cursor node -> [a]) -> Cursor node -> [a] infixr 1 &/ -- | Combine two axes so that the second works on the descendants of the -- results of the first. (&//) :: Axis node -> (Cursor node -> [a]) -> Cursor node -> [a] infixr 1 &// -- | Combine two axes so that the second works on both the result nodes, -- and their descendants. (&.//) :: Axis node -> (Cursor node -> [a]) -> Cursor node -> [a] infixr 1 &.// -- | Apply an axis to a 'Cursor node'. ($|) :: Cursor node -> (Cursor node -> a) -> a infixr 1 $| -- | Apply an axis to the children of a 'Cursor node'. ($/) :: Cursor node -> (Cursor node -> [a]) -> [a] infixr 1 $/ -- | Apply an axis to the descendants of a 'Cursor node'. ($//) :: Cursor node -> (Cursor node -> [a]) -> [a] infixr 1 $// -- | Apply an axis to a 'Cursor node' as well as its descendants. ($.//) :: Cursor node -> (Cursor node -> [a]) -> [a] infixr 1 $.// -- | Left-to-right composition of Kleisli arrows. -- -- '(bs >=> cs) a' can be understood as the -- do expression -- --
--   do b <- bs a
--      cs b
--   
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 >=> -- | Something that can be used in a predicate check as a boolean. class Boolean a bool :: Boolean a => a -> Bool force :: (Exception e, MonadThrow f) => e -> [a] -> f a forceM :: (Exception e, MonadThrow f) => e -> [f a] -> f a instance Text.XML.Cursor.Boolean GHC.Types.Bool instance Text.XML.Cursor.Boolean [a] instance Text.XML.Cursor.Boolean (GHC.Maybe.Maybe a) instance Text.XML.Cursor.Boolean (Data.Either.Either a b)