Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Enumeratee
s to render XML Event
s. Unlike libxml-enumerator and
expat-enumerator, this module does not provide IO and ST variants, since the
underlying rendering operations are pure functions.
Synopsis
- renderBuilder :: Monad m => RenderSettings -> ConduitT Event Builder m ()
- renderBuilderFlush :: Monad m => RenderSettings -> ConduitT (Flush Event) (Flush Builder) m ()
- renderBytes :: PrimMonad m => RenderSettings -> ConduitT Event ByteString m ()
- renderText :: (PrimMonad m, MonadThrow m) => RenderSettings -> ConduitT Event Text m ()
- prettify :: Monad m => ConduitT (Flush Event) (Flush Event) m ()
- data RenderSettings
- def :: Default a => a
- rsPretty :: RenderSettings -> Bool
- rsNamespaces :: RenderSettings -> [(Text, Text)]
- rsAttrOrder :: RenderSettings -> Name -> Map Name Text -> [(Name, Text)]
- rsUseCDATA :: RenderSettings -> Content -> Bool
- rsXMLDeclaration :: RenderSettings -> Bool
- orderAttrs :: [(Name, [Name])] -> Name -> Map Name Text -> [(Name, Text)]
- tag :: Monad m => Name -> Attributes -> ConduitT i Event m () -> ConduitT i Event m ()
- content :: Monad m => Text -> ConduitT i Event m ()
- data Attributes
- attr :: Name -> Text -> Attributes
- optionalAttr :: Name -> Maybe Text -> Attributes
Rendering XML files
renderBuilder :: Monad m => RenderSettings -> ConduitT Event Builder m () Source #
Render a stream of Event
s into a stream of Builder
s. Builders are from
the blaze-builder package, and allow the create of optimally sized
ByteString
s with minimal buffer copying.
renderBuilderFlush :: Monad m => RenderSettings -> ConduitT (Flush Event) (Flush Builder) m () Source #
Same as renderBuilder
but allows you to flush XML stream to ensure that all
events at needed point are rendered.
Since: 1.3.5
renderBytes :: PrimMonad m => RenderSettings -> ConduitT Event ByteString m () Source #
Render a stream of Event
s into a stream of ByteString
s. This function
wraps around renderBuilder
and builderToByteString
, so it produces
optimally sized ByteString
s with minimal buffer copying.
The output is UTF8 encoded.
renderText :: (PrimMonad m, MonadThrow m) => RenderSettings -> ConduitT Event Text m () Source #
Render a stream of Event
s into a stream of Text
s. This function
wraps around renderBuilder
, builderToByteString
and renderBytes
, so it
produces optimally sized Text
s with minimal buffer copying.
prettify :: Monad m => ConduitT (Flush Event) (Flush Event) m () Source #
Convert a stream of Event
s into a prettified one, adding extra
whitespace. Note that this can change the meaning of your XML.
Renderer settings
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.
rsAttrOrder :: RenderSettings -> Name -> Map Name Text -> [(Name, Text)] Source #
Specify how to turn the unordered attributes used by the Text.XML module into an ordered list.
rsUseCDATA :: RenderSettings -> Content -> Bool Source #
Determines if for a given text content the renderer should use a CDATA node.
Default: False
Since: 1.3.3
rsXMLDeclaration :: RenderSettings -> Bool Source #
Determines whether the XML declaration will be output.
Default: True
Since: 1.5.1
orderAttrs :: [(Name, [Name])] -> Name -> Map Name Text -> [(Name, Text)] Source #
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.
Event rendering
:: Monad m | |
=> Name | |
-> Attributes | |
-> ConduitT i Event m () |
|
-> ConduitT i Event m () |
Generate a complete XML Element
.
Attribute rendering
data Attributes Source #
A list of attributes.
Instances
Monoid Attributes Source # | |
Defined in Text.XML.Stream.Render mempty :: Attributes # mappend :: Attributes -> Attributes -> Attributes # mconcat :: [Attributes] -> Attributes # | |
Semigroup Attributes Source # | |
Defined in Text.XML.Stream.Render (<>) :: Attributes -> Attributes -> Attributes # sconcat :: NonEmpty Attributes -> Attributes # stimes :: Integral b => b -> Attributes -> Attributes # |
:: Name | Attribute's name |
-> Text | Attribute's value |
-> Attributes |
Generate a single attribute.
optionalAttr :: Name -> Maybe Text -> Attributes Source #