Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
Synopsis
- 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
- toEvents :: Document -> [Event]
- elementToEvents :: Element -> [Event]
- fromEvents :: MonadThrow m => ConduitT EventPos o m Document
- 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
- def :: Default a => a
- data ParseSettings
- psDecodeEntities :: ParseSettings -> DecodeEntities
- psRetainNamespaces :: ParseSettings -> Bool
- data RenderSettings
- rsPretty :: RenderSettings -> Bool
- rsNamespaces :: RenderSettings -> [(Text, Text)]
Non-streaming functions
Lazy bytestrings
renderLBS :: RenderSettings -> Document -> ByteString Source #
parseLBS_ :: ParseSettings -> ByteString -> Document Source #
Text
parseText :: ParseSettings -> Text -> Either SomeException Document Source #
parseText_ :: ParseSettings -> Text -> Document Source #
sinkTextDoc :: MonadThrow m => ParseSettings -> ConduitT Text o m Document Source #
Byte streams
sinkDoc :: MonadThrow m => ParseSettings -> ConduitT ByteString o m Document Source #
Streaming functions
elementToEvents :: Element -> [Event] Source #
Render a document element into events.
Since: 1.3.5
fromEvents :: MonadThrow m => ConduitT EventPos o m Document Source #
Parse a document from a stream of events.
elementFromEvents :: MonadThrow m => ConduitT EventPos o m (Maybe Element) Source #
Try to parse a document element (as defined in XML) from a stream of events.
Since: 1.3.5
renderBuilder :: Monad m => RenderSettings -> Document -> ConduitT i Builder m () Source #
renderBytes :: PrimMonad m => RenderSettings -> Document -> ConduitT i ByteString m () Source #
renderText :: (MonadThrow m, PrimMonad m) => RenderSettings -> Document -> ConduitT i Text m () Source #
Exceptions
data InvalidEventStream Source #
ContentAfterRoot EventPos | |
MissingRootElement | |
InvalidInlineDoctype EventPos | |
MissingEndElement Name (Maybe EventPos) | |
UnterminatedInlineDoctype |
Instances
Exception InvalidEventStream Source # | |
Defined in Text.XML.Unresolved | |
Show InvalidEventStream Source # | |
Defined in Text.XML.Unresolved showsPrec :: Int -> InvalidEventStream -> ShowS # show :: InvalidEventStream -> String # showList :: [InvalidEventStream] -> ShowS # |
Settings
Parse
data ParseSettings Source #
Instances
Default ParseSettings Source # | |
Defined in Text.XML.Stream.Parse def :: ParseSettings # |
psRetainNamespaces :: ParseSettings -> Bool Source #
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
Render
data RenderSettings Source #
Instances
Default RenderSettings Source # | |
Defined in Text.XML.Stream.Render def :: RenderSettings # |
rsPretty :: RenderSettings -> Bool Source #
rsNamespaces :: RenderSettings -> [(Text, Text)] Source #
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.