hexpat-0.19.3: XML parser/formatter based on expat

Text.XML.Expat.Internal.IO

Contents

Description

Low-level interface to Expat. Unless speed is paramount, this should normally be avoided in favour of the interfaces provided by Text.XML.Expat.SAX and Text.XML.Expat.Tree, etc. Basic usage is:

  1. Make a new parser: newParser.
  2. Set up callbacks on the parser: setStartElementHandler, etc.
  3. Feed data into the parser: parse, parse' or parseChunk. Some of these functions must be wrapped in withParser.

Synopsis

Parser Setup

data Parser Source

Instances

Parsing

parse :: Parser -> ByteString -> IO (Maybe XMLParseError)Source

parse data feeds lazy ByteString data into a Parser. It returns Nothing on success, or Just the parse error.

parse' :: Parser -> ByteString -> IO (Maybe XMLParseError)Source

parse data feeds strict ByteString data into a Parser. It returns Nothing on success, or Just the parse error.

withParserSource

Arguments

:: Parser 
-> (ParserPtr -> IO a)

Computation where parseChunk and other low-level functions may be used

-> IO a 

Most of the low-level functions take a ParserPtr so are required to be called inside withParser.

data Parser_struct Source

Opaque parser type.

parseChunk :: ParserPtr -> ByteString -> Bool -> IO (Maybe XMLParseError)Source

parseChunk data False feeds strict ByteString data into a Parser. The end of the data is indicated by passing True for the final parameter. It returns Nothing on success, or Just the parse error.

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

data XMLParseLocation Source

Specifies a location of an event within the input text

Constructors

XMLParseLocation 

Fields

xmlLineNumber :: Int64

Line number of the event

xmlColumnNumber :: Int64

Column number of the event

xmlByteIndex :: Int64

Byte index of event from start of document

xmlByteCount :: Int64

The number of bytes in the event

Parser Callbacks

type XMLDeclarationHandler = ParserPtr -> CString -> CString -> CInt -> IO BoolSource

The type of the "XML declaration" callback. Parameters are version, encoding (which can be nullPtr), and standalone declaration, where -1 = no declaration, 0 = no and 1 = yes. Return True to continue parsing as normal, or False to terminate the parse.

type StartElementHandler = ParserPtr -> CString -> [(CString, CString)] -> IO BoolSource

The type of the "element started" callback. The first parameter is the element name; the second are the (attribute, value) pairs. Return True to continue parsing as normal, or False to terminate the parse.

type EndElementHandler = ParserPtr -> CString -> IO BoolSource

The type of the "element ended" callback. The parameter is the element name. Return True to continue parsing as normal, or False to terminate the parse.

type CharacterDataHandler = ParserPtr -> CStringLen -> IO BoolSource

The type of the "character data" callback. The parameter is the character data processed. This callback may be called more than once while processing a single conceptual block of text. Return True to continue parsing as normal, or False to terminate the parse.

type ExternalEntityRefHandler = Parser -> CString -> CString -> CString -> CString -> IO BoolSource

The type of the "external entity reference" callback. See the expat documentation.

type SkippedEntityHandler = ParserPtr -> CString -> Int -> IO BoolSource

Set a skipped entity handler. This is called in two situations:

  1. An entity reference is encountered for which no declaration has been read and this is not an error.
  2. An internal entity reference is read, but not expanded, because XML_SetDefaultHandler has been called.

type StartCDataHandler = ParserPtr -> IO BoolSource

The type of the "start cdata" callback. Return True to continue parsing as normal, or False to terminate the parse.

type EndCDataHandler = ParserPtr -> IO BoolSource

The type of the "end cdata" callback. Return True to continue parsing as normal, or False to terminate the parse.

type CommentHandler = ParserPtr -> CString -> IO BoolSource

The type of the "comment" callback. The parameter is the comment text. Return True to continue parsing as normal, or False to terminate the parse.

type ProcessingInstructionHandler = ParserPtr -> CString -> CString -> IO BoolSource

The type of the "processing instruction" callback. The first parameter is the first word in the processing instruction. The second parameter is the rest of the characters in the processing instruction after skipping all whitespace after the initial word. Return True to continue parsing as normal, or False to terminate the parse.

setXMLDeclarationHandler :: Parser -> XMLDeclarationHandler -> IO ()Source

Attach a XMLDeclarationHandler to a Parser.

setStartElementHandler :: Parser -> StartElementHandler -> IO ()Source

Attach a StartElementHandler to a Parser.

setEndElementHandler :: Parser -> EndElementHandler -> IO ()Source

Attach an EndElementHandler to a Parser.

setCharacterDataHandler :: Parser -> CharacterDataHandler -> IO ()Source

Attach an CharacterDataHandler to a Parser.

setStartCDataHandler :: Parser -> StartCDataHandler -> IO ()Source

Attach a StartCDataHandler to a Parser.

setEndCDataHandler :: Parser -> EndCDataHandler -> IO ()Source

Attach a EndCDataHandler to a Parser.

setProcessingInstructionHandler :: Parser -> ProcessingInstructionHandler -> IO ()Source

Attach a ProcessingInstructionHandler to a Parser.

setCommentHandler :: Parser -> CommentHandler -> IO ()Source

Attach a CommentHandler to a Parser.

Lower-level interface

parseExternalEntityReferenceSource

Arguments

:: Parser 
-> CString

context

-> Maybe Encoding

encoding

-> CStringLen

text

-> IO Bool 

Helpers