hexpat-0.12: wrapper for expat, the fast XML parserSource codeContentsIndex
Text.XML.Expat.SAX
Contents
XML primitives
SAX-style parse
Variants that throw exceptions
Deprecated parse functions
Abstraction of string types
Description
This module provides functions to parse an XML document to a lazy stream of SAX events.
Synopsis
data Encoding
= ASCII
| UTF8
| UTF16
| ISO88591
data XMLParseError = XMLParseError String XMLParseLocation
data XMLParseLocation = XMLParseLocation {
xmlLineNumber :: Int64
xmlColumnNumber :: Int64
xmlByteIndex :: Int64
xmlByteCount :: Int64
}
data ParserOptions tag text = ParserOptions {
parserEncoding :: Maybe Encoding
entityDecoder :: Maybe (tag -> Maybe text)
}
data SAXEvent tag text
= StartElement tag [(tag, text)]
| EndElement tag
| CharacterData text
| FailDocument XMLParseError
mkText :: GenericXMLString text => CString -> IO text
parse :: (GenericXMLString tag, GenericXMLString text) => ParserOptions tag text -> ByteString -> [SAXEvent tag text]
parseLocations :: (GenericXMLString tag, GenericXMLString text) => ParserOptions tag text -> ByteString -> [(SAXEvent tag text, XMLParseLocation)]
parseLocationsThrowing :: (GenericXMLString tag, GenericXMLString text) => ParserOptions tag text -> ByteString -> [(SAXEvent tag text, XMLParseLocation)]
parseThrowing :: (GenericXMLString tag, GenericXMLString text) => ParserOptions tag text -> ByteString -> [SAXEvent tag text]
defaultParserOptions :: ParserOptions tag text
data XMLParseException = XMLParseException XMLParseError
parseSAX :: (GenericXMLString tag, GenericXMLString text) => Maybe Encoding -> ByteString -> [SAXEvent tag text]
parseSAXLocations :: (GenericXMLString tag, GenericXMLString text) => Maybe Encoding -> ByteString -> [(SAXEvent tag text, XMLParseLocation)]
parseSAXLocationsThrowing :: (GenericXMLString tag, GenericXMLString text) => Maybe Encoding -> ByteString -> [(SAXEvent tag text, XMLParseLocation)]
parseSAXThrowing :: (GenericXMLString tag, GenericXMLString text) => Maybe Encoding -> ByteString -> [SAXEvent tag text]
class (Monoid s, Eq s) => GenericXMLString s where
gxNullString :: s -> Bool
gxToString :: s -> String
gxFromString :: String -> s
gxFromChar :: Char -> s
gxHead :: s -> Char
gxTail :: s -> s
gxBreakOn :: Char -> s -> (s, s)
gxFromCStringLen :: CStringLen -> IO s
gxToByteString :: s -> ByteString
XML primitives
data Encoding Source
Encoding types available for the document encoding.
Constructors
ASCII
UTF8
UTF16
ISO88591
data XMLParseError Source
Parse error, consisting of message text and error location
Constructors
XMLParseError String XMLParseLocation
show/hide Instances
data XMLParseLocation Source
Specifies a location of an event within the input text
Constructors
XMLParseLocation
xmlLineNumber :: Int64Line number of the event
xmlColumnNumber :: Int64Column number of the event
xmlByteIndex :: Int64Byte index of event from start of document
xmlByteCount :: Int64The number of bytes in the event
show/hide Instances
SAX-style parse
data ParserOptions tag text Source
Constructors
ParserOptions
parserEncoding :: Maybe EncodingThe encoding parameter, if provided, overrides the document's encoding declaration.
entityDecoder :: Maybe (tag -> Maybe text)If provided, entity references (i.e.   and friends) will be decoded into text using the supplied lookup function
data SAXEvent tag text Source
Constructors
StartElement tag [(tag, text)]
EndElement tag
CharacterData text
FailDocument XMLParseError
show/hide Instances
(Eq tag, Eq text) => Eq (SAXEvent tag text)
(Show tag, Show text) => Show (SAXEvent tag text)
(NFData tag, NFData text) => NFData (SAXEvent tag text)
mkText :: GenericXMLString text => CString -> IO textSource
Converts a CString to a GenericXMLString type.
parseSource
:: (GenericXMLString tag, GenericXMLString text)
=> ParserOptions tag textParser options
-> ByteStringInput text (a lazy ByteString)
-> [SAXEvent tag text]
Lazily parse XML to SAX events. In the event of an error, FailDocument is the last element of the output list.
parseLocationsSource
:: (GenericXMLString tag, GenericXMLString text)
=> ParserOptions tag textParser options
-> ByteStringInput text (a lazy ByteString)
-> [(SAXEvent tag text, XMLParseLocation)]
A variant of parseSAX that gives a document location with each SAX event.
parseLocationsThrowingSource
:: (GenericXMLString tag, GenericXMLString text)
=> ParserOptions tag textOptional encoding override
-> ByteStringInput text (a lazy ByteString)
-> [(SAXEvent tag text, XMLParseLocation)]

A variant of parseSAX that gives a document location with each SAX event. In the event of an error, throw XMLParseException.

parseLocationsThrowing can throw an exception from pure code, which is generally a bad way to handle errors, because Haskell's lazy evaluation means it's hard to predict where it will be thrown from. However, it may be acceptable in situations where it's not expected during normal operation, depending on the design of your program.

parseThrowingSource
:: (GenericXMLString tag, GenericXMLString text)
=> ParserOptions tag textParser options
-> ByteStringinput text (a lazy ByteString)
-> [SAXEvent tag text]

Lazily parse XML to SAX events. In the event of an error, throw XMLParseException.

parseThrowing can throw an exception from pure code, which is generally a bad way to handle errors, because Haskell's lazy evaluation means it's hard to predict where it will be thrown from. However, it may be acceptable in situations where it's not expected during normal operation, depending on the design of your program.

defaultParserOptions :: ParserOptions tag textSource
Variants that throw exceptions
data XMLParseException Source
An exception indicating an XML parse error, used by the ..Throwing variants.
Constructors
XMLParseException XMLParseError
show/hide Instances
Deprecated parse functions
parseSAXSource
:: (GenericXMLString tag, GenericXMLString text)
=> Maybe EncodingOptional encoding override
-> ByteStringInput text (a lazy ByteString)
-> [SAXEvent tag text]

DEPRECATED: Use parse instead.

Lazily parse XML to SAX events. In the event of an error, FailDocument is the last element of the output list. Deprecated in favour of new parse

parseSAXLocationsSource
:: (GenericXMLString tag, GenericXMLString text)
=> Maybe EncodingOptional encoding override
-> ByteStringInput text (a lazy ByteString)
-> [(SAXEvent tag text, XMLParseLocation)]

DEPRECATED: Use parseLocations instead.

A variant of parseSAX that gives a document location with each SAX event.

parseSAXLocationsThrowingSource
:: (GenericXMLString tag, GenericXMLString text)
=> Maybe EncodingOptional encoding override
-> ByteStringInput text (a lazy ByteString)
-> [(SAXEvent tag text, XMLParseLocation)]

DEPRECATED: Used parseLocationsThrowing instead.

A variant of parseSAX that gives a document location with each SAX event. In the event of an error, throw XMLParseException.

parseSAXThrowingSource
:: (GenericXMLString tag, GenericXMLString text)
=> Maybe EncodingOptional encoding override
-> ByteStringInput text (a lazy ByteString)
-> [SAXEvent tag text]

DEPRECATED: Use parseThrowing instead.

Lazily parse XML to SAX events. In the event of an error, throw XMLParseException.

Abstraction of string types
class (Monoid s, Eq s) => GenericXMLString s whereSource
An abstraction for any string type you want to use as xml text (that is, attribute values or element text content). If you want to use a new string type with hexpat, you must make it an instance of GenericXMLString.
Methods
gxNullString :: s -> BoolSource
gxToString :: s -> StringSource
gxFromString :: String -> sSource
gxFromChar :: Char -> sSource
gxHead :: s -> CharSource
gxTail :: s -> sSource
gxBreakOn :: Char -> s -> (s, s)Source
gxFromCStringLen :: CStringLen -> IO sSource
gxToByteString :: s -> ByteStringSource
show/hide Instances
Produced by Haddock version 2.6.1