Interface for reading an XML document using callbacks.

Introduced classes

interface XMLReader

sax :: XMLReader

Interface for reading an XML document using callbacks.

All class definitions

interface XMLReader

sax $ XMLReader

Interface for reading an XML document using callbacks.
package_diagram sax::xml_reader xml_reader sax::entity_resolver entity_resolver sax::xml_reader->sax::entity_resolver sax::dtd_handler dtd_handler sax::xml_reader->sax::dtd_handler sax::content_handler content_handler sax::xml_reader->sax::content_handler sax::error_handler error_handler sax::xml_reader->sax::error_handler sax::input_source input_source sax::entity_resolver->sax::input_source core core sax::dtd_handler->core sax::attributes attributes sax::content_handler->sax::attributes sax::sax_locator sax_locator sax::content_handler->sax::sax_locator sax::sax_parse_exception sax_parse_exception sax::error_handler->sax::sax_parse_exception ...sax::input_source ... ...sax::input_source->sax::input_source ...core ... ...core->core ...sax::attributes ... ...sax::attributes->sax::attributes ...sax::sax_locator ... ...sax::sax_locator->sax::sax_locator ...sax::sax_parse_exception ... ...sax::sax_parse_exception->sax::sax_parse_exception sax::xml_filter xml_filter sax::xml_filter->sax::xml_reader sax::sax sax sax::sax->sax::xml_filter sax::xml_filter_impl xml_filter_impl sax::xml_filter_impl->sax::xml_filter sax::sax... ... sax::sax...->sax::sax sax::xml_filter_impl... ... sax::xml_filter_impl...->sax::xml_filter_impl

Ancestors

module abstract_collection

core :: abstract_collection

Abstract collection classes and services.
module abstract_text

core :: abstract_text

Abstract class for manipulation of sequences of characters
module array

core :: array

This module introduces the standard array structure.
module attributes

sax :: attributes

Interface for a list of XML attributes.
module bitset

core :: bitset

Services to handle BitSet
module bytes

core :: bytes

Services for byte streams and arrays
module circular_array

core :: circular_array

Efficient data structure to access both end of the sequence.
module codec_base

core :: codec_base

Base for codecs to use with streams
module codecs

core :: codecs

Group module for all codec-related manipulations
module collection

core :: collection

This module define several collection classes.
module core

core :: core

Standard classes and methods used by default by Nit programs and libraries.
module environ

core :: environ

Access to the environment variables of the process
module error

core :: error

Standard error-management infrastructure.
module exec

core :: exec

Invocation and management of operating system sub-processes.
module file

core :: file

File manipulations (create, read, write, etc.)
module fixed_ints

core :: fixed_ints

Basic integers of fixed-precision
module fixed_ints_text

core :: fixed_ints_text

Text services to complement fixed_ints
module flat

core :: flat

All the array-based text representations
module gc

core :: gc

Access to the Nit internal garbage collection mechanism
module hash_collection

core :: hash_collection

Introduce HashMap and HashSet.
module input_source

sax :: input_source

A single input source for an XML entity.
module iso8859_1

core :: iso8859_1

Codec for ISO8859-1 I/O
module kernel

core :: kernel

Most basic classes and methods.
module list

core :: list

This module handle double linked lists
module math

core :: math

Mathematical operations
module native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module protocol

core :: protocol

module queue

core :: queue

Queuing data structures and wrappers
module range

core :: range

Module for range of discrete objects.
module re

core :: re

Regular expression support for all services based on Pattern
module ropes

core :: ropes

Tree-based representation of a String.
module sax_locator

sax :: sax_locator

Interface for associating a SAX event with a document location.
module sax_parse_exception

sax :: sax_parse_exception

Encapsulates an XML parse error or warning.
module sorter

core :: sorter

This module contains classes used to compare things and sorts arrays.
module stream

core :: stream

Input and output streams of characters
module text

core :: text

All the classes and methods related to the manipulation of text entities
module time

core :: time

Management of time and dates
module union_find

core :: union_find

union–find algorithm using an efficient disjoint-set data structure
module utf8

core :: utf8

Codec for UTF-8 I/O

Parents

module content_handler

sax :: content_handler

Receives notification of the logical content of a document.
module dtd_handler

sax :: dtd_handler

Receives notification of basic DTD-related events.
module entity_resolver

sax :: entity_resolver

Basic interface for resolving entities.
module error_handler

sax :: error_handler

Basic interface for SAX error handlers.

Children

module xml_filter

sax :: xml_filter

Interface for an XML filter.

Descendants

module a_star-m

a_star-m

module ext

sax :: ext

Interfaces to optional SAX2 handlers.
module helpers

sax :: helpers

Contains "helper" classes, including support for bootstrapping SAX-based applications.
module lexer

saxophonit :: lexer

SAXophoNit’s lexer
module reader_model

saxophonit :: reader_model

Reader’s model.
module sax

sax :: sax

Core SAX APIs.
module saxophonit

saxophonit :: saxophonit

A SAX 2 parser in Nit.
module testing

saxophonit :: testing

Various utilities to help testing SAXophoNit (and SAX parsers in general).
module xml_filter_impl

sax :: xml_filter_impl

Base class for deriving an XML filter.
# Interface for reading an XML document using callbacks.
module sax::xml_reader

import entity_resolver
import dtd_handler
import content_handler
import error_handler

# Interface for reading an XML document using callbacks.
#
# `XMLReader` is the interface that an XML parser's SAX2 driver must
# implement. This interface allows an application to set and
# query features and properties in the parser, to register
# event handlers for document processing, and to initiate
# a document parse.
#
# All SAX interfaces are assumed to be synchronous: the
# `parse` methods must not return until parsing
# is complete, and readers must wait for an event-handler callback
# to return before reporting the next event.
#
# Note: The original documentation comes from [SAX 2.0](http://www.saxproject.org).
interface XMLReader

	# Is the specified feature flag recognized by this parser?
	#
	# Parameter:
	#
	# * `name`: feature name, which is a fully-qualified URI.
	fun feature_recognized(name: String): Bool is abstract

	# Is the retrieval of the specified feature flag supported given the current context?
	#
	# Parameter:
	#
	# * `name`: feature name, which is a fully-qualified URI.
	fun feature_readable(name: String): Bool is abstract

	# Is the modification of the specified feature flag supported given the current context?
	#
	# Parameter:
	#
	# * `name`: feature name, which is a fully-qualified URI.
	fun feature_writable(name: String): Bool is abstract

	# Look up the value of a feature flag.
	#
	# The feature name is any fully-qualified URI. It is
	# possible for an `XMLReader` to recognize a feature name but
	# temporarily be unable to return its value.
	# Some feature values may be available only in specific
	# contexts, such as before, during, or after a parse.
	# Also, some feature values may not be programmatically accessible.
	#
	# All XMLReaders are required to recognize the
	# `http://xml.org/sax/features/namespaces` and the
	# `http://xml.org/sax/features/namespace-prefixes` feature names.
	#
	# Implementors are free (and encouraged) to invent their own features,
	# using names built on their own URIs.
	#
	# Parameter:
	#
	# * `name`: feature name, which is a fully-qualified URI.
	#
	# Returns:
	#
	# The current value of the feature.
	#
	# SEE: `feature_recognized`
	#
	# SEE: `feature_readable`
	fun feature(name: String): Bool is abstract

	# Set the value of a feature flag.
	#
	# The feature name is any fully-qualified URI. It is
	# possible for an XMLReader to expose a feature value but
	# to be unable to change the current value.
	# Some feature values may be immutable or mutable only
	# in specific contexts, such as before, during, or after
	# a parse.
	#
	# All XMLReaders are required to support setting
	# http://xml.org/sax/features/namespaces to true and
	# http://xml.org/sax/features/namespace-prefixes to false.
	#
	# Parameters:
	#
	# * `name`: feature name, which is a fully-qualified URI.
	# * `value`: requested value of the feature.
	#
	# SEE: `feature_recognized`
	#
	# SEE: `feature_writable`
	fun feature=(name: String, value: Bool) is abstract

	# Is the specified property recognized by this parser?
	#
	# Parameter:
	#
	# * `name`: property name, which is a fully-qualified URI.
	fun property_recognized(name: String): Bool is abstract

	# Is the retrieval of the specified property supported given the current context?
	#
	# Parameter:
	#
	# * `name`: property name, which is a fully-qualified URI.
	fun property_readable(name: String): Bool is abstract

	# Is the modification of the specified property supported given the current context?
	#
	# Parameter:
	#
	# * `name`: property name, which is a fully-qualified URI.
	fun property_writable(name: String): Bool is abstract

	# Look up the value of a property.
	#
	# The property name is any fully-qualified URI. It is
	# possible for an `XMLReader` to recognize a property name but
	# temporarily be unable to return its value.
	# Some property values may be available only in specific
	# contexts, such as before, during, or after a parse.
	#
	# XMLReaders are not required to recognize any specific
	# property names, though an initial core set is documented for
	# SAX2.
	#
	# Implementors are free (and encouraged) to invent their own properties,
	# using names built on their own URIs.
	#
	# Parameter:
	#
	# * `name`: property name, which is a fully-qualified URI.
	#
	# Returns:
	#
	# The current value of the property.
	#
	# SEE: `property_recognized`
	#
	# SEE: `property_supported`
	fun property(name: String): nullable Object is abstract

	# Set the value of a property.
	#
	# The property name is any fully-qualified URI. It is
	# possible for an `XMLReader` to recognize a property name but
	# to be unable to change the current value.
	# Some property values may be immutable or mutable only
	# in specific contexts, such as before, during, or after
	# a parse.
	#
	# XMLReaders are not required to recognize setting
	# any specific property names, though a core set is defined by
	# SAX2.
	#
	# This method is also the standard mechanism for setting
	# extended handlers.
	#
	# Parameters:
	#
	# * `name`: property name, which is a fully-qualified URI.
	# * `value`: requested value for the property.
	#
	# SEE: `property_recognized`
	#
	# SEE: `property_writable`
	fun property=(name: String, value: nullable Object) is abstract

	# Allow an application to register an entity resolver.
	#
	# If the application does not register an entity resolver,
	# the XMLReader will perform its own default resolution.
	#
	# Applications may register a new or different resolver in the
	# middle of a parse, and the SAX parser must begin using the new
	# resolver immediately.
	fun entity_resolver=(resolver: nullable EntityResolver) is abstract

	# Return the current entity resolver.
	#
	# Return `null` if none has been registered.
	fun entity_resolver: nullable EntityResolver is abstract

	# Allow an application to register a DTD event handler.
	#
	# If the application does not register a DTD handler, all DTD
	# events reported by the SAX parser will be silently ignored.
	#
	# Applications may register a new or different handler in the
	# middle of a parse, and the SAX parser must begin using the new
	# handler immediately.
	fun dtd_handler=(handler: nullable DTDHandler) is abstract

	# Return the current DTD handler.
	#
	# Return `null` if none has been registered.
	fun dtd_handler: nullable DTDHandler is abstract

	# Allow an application to register a content event handler.
	#
	# If the application does not register a content handler, all
	# content events reported by the SAX parser will be silently
	# ignored.
	#
	# Applications may register a new or different handler in the
	# middle of a parse, and the SAX parser must begin using the new
	# handler immediately.
	fun content_handler=(handler: nullable ContentHandler) is abstract

	# Return the current content handler.
	#
	# Return `null` if none has been registered.
	fun content_handler: nullable ContentHandler is abstract

	# Allow an application to register an error event handler.
	#
	# If the application does not register an error handler, all
	# error events reported by the SAX parser will be silently
	# ignored; however, normal processing may not continue. It is
	# highly recommended that all SAX applications implement an
	# error handler to avoid unexpected bugs.
	#
	# Applications may register a new or different handler in the
	# middle of a parse, and the SAX parser must begin using the new
	# handler immediately.
	fun error_handler=(handler: nullable ErrorHandler) is abstract

	# Return the current error handler.
	#
	# Return `null` if none has been registered.
	fun error_handler: nullable ErrorHandler is abstract

	# Parse an XML document.
	#
	# The application can use this method to instruct the XML
	# reader to begin parsing an XML document from any valid input
	# source (a byte stream or an URI).
	#
	# Applications may not invoke this method while a parse is in
	# progress (they should create a new `XMLReader` instead for each
	# nested XML document). Once a parse is complete, an
	# application may reuse the same `XMLReader` object, possibly with a
	# different input source.
	#
	# During the parse, the `XMLReader` will provide information
	# about the XML document through the registered event
	# handlers.
	#
	# This method is synchronous: it will not return until parsing
	# has ended. If a client application wants to terminate
	# parsing early, it should throw an exception.
	#
	# Parameters:
	#
	# * `source`: input source for the top-level of the XML document.
	fun parse(input: InputSource) is abstract

	# Parse an XML document from a system identifier (URI).
	#
	# This method is a shortcut for the common case of reading a
	# document from a system identifier. It is the exact
	# equivalent of the following:
	#
	# ~~~nitish
	# var source = new InputSouce
	# source.system_id = system_id
	# parse(source)
	# ~~~
	#
	# If the system identifier is a URL, it must be fully resolved
	# by the application before it is passed to the parser.
	#
	# Parameters:
	#
	# * `systemId`: The system identifier (URI).
	fun parse_file(system_id: String) is abstract
end
lib/sax/xml_reader.nit:11,1--291,3