Base class for deriving an XML filter.

This class is designed to sit between an XMLReader and the client application's event handlers. By default, it does nothing but pass requests up to the reader and events on to the handlers unmodified, but subclasses can override specific methods to modify the event stream or the configuration requests as they pass through.

Note: The original source code and documentation of this class comes, in part, from SAX 2.0.

Introduced properties

init with_parent(parent_reader: XMLReader)

sax :: XMLFilterImpl :: with_parent

Construct an XML filter with the specified parent.

Redefined properties

redef type SELF: XMLFilterImpl

sax $ XMLFilterImpl :: SELF

Type of this instance, automatically specialized in every class
redef fun characters(str: String)

sax $ XMLFilterImpl :: characters

Receive notification of character data.
redef fun content_handler: nullable ContentHandler

sax $ XMLFilterImpl :: content_handler

Return the current content handler.
redef fun content_handler=(content_handler: nullable ContentHandler)

sax $ XMLFilterImpl :: content_handler=

Allow an application to register a content event handler.
redef fun document_locator=(locator: SAXLocator)

sax $ XMLFilterImpl :: document_locator=

Receive an object for locating the origin of SAX document events.
redef fun dtd_handler: nullable DTDHandler

sax $ XMLFilterImpl :: dtd_handler

Return the current DTD handler.
redef fun dtd_handler=(dtd_handler: nullable DTDHandler)

sax $ XMLFilterImpl :: dtd_handler=

Allow an application to register a DTD event handler.
redef fun end_document

sax $ XMLFilterImpl :: end_document

Receive notification of the end of a document.
redef fun end_element(uri: String, local_name: String, qname: String)

sax $ XMLFilterImpl :: end_element

Receive notification of the end of an element.
redef fun end_prefix_mapping(prefix: String)

sax $ XMLFilterImpl :: end_prefix_mapping

End the scope of a prefix-URI mapping.
redef fun entity_resolver: nullable EntityResolver

sax $ XMLFilterImpl :: entity_resolver

Return the current entity resolver.
redef fun entity_resolver=(entity_resolver: nullable EntityResolver)

sax $ XMLFilterImpl :: entity_resolver=

Allow an application to register an entity resolver.
redef fun error(exception: SAXParseException)

sax $ XMLFilterImpl :: error

Receive notification of a recoverable error.
redef fun error_handler: nullable ErrorHandler

sax $ XMLFilterImpl :: error_handler

Return the current error handler.
redef fun error_handler=(error_handler: nullable ErrorHandler)

sax $ XMLFilterImpl :: error_handler=

Allow an application to register an error event handler.
redef fun fatal_error(exception: SAXParseException)

sax $ XMLFilterImpl :: fatal_error

Receive notification of a non-recoverable error.
redef fun feature(name: String): Bool

sax $ XMLFilterImpl :: feature

Look up the value of a feature.
redef fun feature=(name: String, value: Bool)

sax $ XMLFilterImpl :: feature=

Set the value of a feature.
redef fun feature_readable(name: String): Bool

sax $ XMLFilterImpl :: feature_readable

Is the retrieval of the specified feature flag supported given the current context?
redef fun feature_recognized(name: String): Bool

sax $ XMLFilterImpl :: feature_recognized

Is the specified feature flag recognized by this parser?
redef fun feature_writable(name: String): Bool

sax $ XMLFilterImpl :: feature_writable

Is the modification of the specified feature flag supported given the current context?
redef fun ignorable_whitespace(str: String)

sax $ XMLFilterImpl :: ignorable_whitespace

Receive notification of ignorable whitespace in element content.
redef init init

sax $ XMLFilterImpl :: init

Construct an empty XML filter, with no parent.
redef fun notation_decl(name: String, public_id: String, system_id: String)

sax $ XMLFilterImpl :: notation_decl

Receive notification of a notation declaration event.
redef fun parent: nullable XMLReader

sax $ XMLFilterImpl :: parent

Get the parent reader.
redef fun parent=(parent: nullable XMLReader)

sax $ XMLFilterImpl :: parent=

Set the parent reader.
redef fun parse(input: InputSource)

sax $ XMLFilterImpl :: parse

Parse an XML document.
redef fun parse_file(system_id: String)

sax $ XMLFilterImpl :: parse_file

Parse an XML document from a system identifier (URI).
redef fun processing_instruction(target: String, data: nullable String)

sax $ XMLFilterImpl :: processing_instruction

Receive notification of a processing instruction.
redef fun property(name: String): nullable Object

sax $ XMLFilterImpl :: property

Look up the value of a property.
redef fun property=(name: String, value: nullable Object)

sax $ XMLFilterImpl :: property=

Set the value of a property.
redef fun property_readable(name: String): Bool

sax $ XMLFilterImpl :: property_readable

Is the retrieval of the specified property supported given the current context?
redef fun property_recognized(name: String): Bool

sax $ XMLFilterImpl :: property_recognized

Is the specified property recognized by this parser?
redef fun property_writable(name: String): Bool

sax $ XMLFilterImpl :: property_writable

Is the modification of the specified property supported given the current context?
redef fun resolve_entity(public_id: nullable String, system_id: nullable String): nullable InputSource

sax $ XMLFilterImpl :: resolve_entity

Allow the application to resolve external entities.
redef fun skipped_entity(name: String)

sax $ XMLFilterImpl :: skipped_entity

Receive notification of a skipped entity.
redef fun start_document

sax $ XMLFilterImpl :: start_document

Receive notification of the beginning of a document.
redef fun start_element(uri: String, local_name: String, qname: String, atts: Attributes)

sax $ XMLFilterImpl :: start_element

Receive notification of the beginning of an element.
redef fun start_prefix_mapping(prefix: String, uri: String)

sax $ XMLFilterImpl :: start_prefix_mapping

Begin the scope of a prefix-URI Namespace mapping.
redef fun unparsed_entity_decl(name: String, public_id: String, system_id: String)

sax $ XMLFilterImpl :: unparsed_entity_decl

Receive notification of an unparsed entity declaration event.
redef fun warning(exception: SAXParseException)

sax $ XMLFilterImpl :: warning

Receive notification of a warning.

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun characters(str: String)

sax :: ContentHandler :: characters

Receive notification of character data.
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
abstract fun content_handler: nullable ContentHandler

sax :: XMLReader :: content_handler

Return the current content handler.
abstract fun content_handler=(handler: nullable ContentHandler)

sax :: XMLReader :: content_handler=

Allow an application to register a content event handler.
fun document_locator=(locator: SAXLocator)

sax :: ContentHandler :: document_locator=

Receive an object for locating the origin of SAX document events.
abstract fun dtd_handler: nullable DTDHandler

sax :: XMLReader :: dtd_handler

Return the current DTD handler.
abstract fun dtd_handler=(handler: nullable DTDHandler)

sax :: XMLReader :: dtd_handler=

Allow an application to register a DTD event handler.
fun end_document

sax :: ContentHandler :: end_document

Receive notification of the end of a document.
fun end_element(uri: String, local_name: String, qname: String)

sax :: ContentHandler :: end_element

Receive notification of the end of an element.
fun end_prefix_mapping(prefix: String)

sax :: ContentHandler :: end_prefix_mapping

End the scope of a prefix-URI mapping.
abstract fun entity_resolver: nullable EntityResolver

sax :: XMLReader :: entity_resolver

Return the current entity resolver.
abstract fun entity_resolver=(resolver: nullable EntityResolver)

sax :: XMLReader :: entity_resolver=

Allow an application to register an entity resolver.
fun error(exception: SAXParseException)

sax :: ErrorHandler :: error

Receive notification of a recoverable error.
abstract fun error_handler: nullable ErrorHandler

sax :: XMLReader :: error_handler

Return the current error handler.
abstract fun error_handler=(handler: nullable ErrorHandler)

sax :: XMLReader :: error_handler=

Allow an application to register an error event handler.
fun fatal_error(exception: SAXParseException)

sax :: ErrorHandler :: fatal_error

Receive notification of a non-recoverable error.
abstract fun feature(name: String): Bool

sax :: XMLReader :: feature

Look up the value of a feature flag.
abstract fun feature=(name: String, value: Bool)

sax :: XMLReader :: feature=

Set the value of a feature flag.
abstract fun feature_readable(name: String): Bool

sax :: XMLReader :: feature_readable

Is the retrieval of the specified feature flag supported given the current context?
abstract fun feature_recognized(name: String): Bool

sax :: XMLReader :: feature_recognized

Is the specified feature flag recognized by this parser?
abstract fun feature_writable(name: String): Bool

sax :: XMLReader :: feature_writable

Is the modification of the specified feature flag supported given the current context?
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun ignorable_whitespace(str: String)

sax :: ContentHandler :: ignorable_whitespace

Receive notification of ignorable whitespace in element content.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
fun notation_decl(name: String, public_id: String, system_id: String)

sax :: DTDHandler :: notation_decl

Receive notification of a notation declaration event.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
abstract fun parent: nullable XMLReader

sax :: XMLFilter :: parent

Get the parent reader.
abstract fun parent=(parent: nullable XMLReader)

sax :: XMLFilter :: parent=

Set the parent reader.
abstract fun parse(input: InputSource)

sax :: XMLReader :: parse

Parse an XML document.
abstract fun parse_file(system_id: String)

sax :: XMLReader :: parse_file

Parse an XML document from a system identifier (URI).
fun processing_instruction(target: String, data: nullable String)

sax :: ContentHandler :: processing_instruction

Receive notification of a processing instruction.
abstract fun property(name: String): nullable Object

sax :: XMLReader :: property

Look up the value of a property.
abstract fun property=(name: String, value: nullable Object)

sax :: XMLReader :: property=

Set the value of a property.
abstract fun property_readable(name: String): Bool

sax :: XMLReader :: property_readable

Is the retrieval of the specified property supported given the current context?
abstract fun property_recognized(name: String): Bool

sax :: XMLReader :: property_recognized

Is the specified property recognized by this parser?
abstract fun property_writable(name: String): Bool

sax :: XMLReader :: property_writable

Is the modification of the specified property supported given the current context?
fun resolve_entity(public_id: nullable String, system_id: nullable String): nullable InputSource

sax :: EntityResolver :: resolve_entity

Allow the application to resolve external entities.
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun skipped_entity(name: String)

sax :: ContentHandler :: skipped_entity

Receive notification of a skipped entity.
fun start_document

sax :: ContentHandler :: start_document

Receive notification of the beginning of a document.
fun start_element(uri: String, local_name: String, qname: String, atts: Attributes)

sax :: ContentHandler :: start_element

Receive notification of the beginning of an element.
fun start_prefix_mapping(prefix: String, uri: String)

sax :: ContentHandler :: start_prefix_mapping

Begin the scope of a prefix-URI Namespace mapping.
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun unparsed_entity_decl(name: String, public_id: String, system_id: String)

sax :: DTDHandler :: unparsed_entity_decl

Receive notification of an unparsed entity declaration event.
fun warning(exception: SAXParseException)

sax :: ErrorHandler :: warning

Receive notification of a warning.
init with_parent(parent_reader: XMLReader)

sax :: XMLFilterImpl :: with_parent

Construct an XML filter with the specified parent.
package_diagram sax::XMLFilterImpl XMLFilterImpl sax::XMLFilter XMLFilter sax::XMLFilterImpl->sax::XMLFilter sax::EntityResolver EntityResolver sax::XMLFilterImpl->sax::EntityResolver sax::DTDHandler DTDHandler sax::XMLFilterImpl->sax::DTDHandler sax::ContentHandler ContentHandler sax::XMLFilterImpl->sax::ContentHandler sax::ErrorHandler ErrorHandler sax::XMLFilterImpl->sax::ErrorHandler sax::XMLReader XMLReader sax::XMLFilter->sax::XMLReader core::Object Object sax::EntityResolver->core::Object sax::DTDHandler->core::Object sax::ContentHandler->core::Object sax::ErrorHandler->core::Object ...sax::XMLReader ... ...sax::XMLReader->sax::XMLReader ...core::Object ... ...core::Object->core::Object saxophonit::SAXEventLogger SAXEventLogger saxophonit::SAXEventLogger->sax::XMLFilterImpl

Ancestors

interface Object

core :: Object

The root of the class hierarchy.
interface XMLReader

sax :: XMLReader

Interface for reading an XML document using callbacks.

Parents

abstract class ContentHandler

sax :: ContentHandler

Receives notification of the logical content of a document.
abstract class DTDHandler

sax :: DTDHandler

Receives notification of basic DTD-related events.
abstract class EntityResolver

sax :: EntityResolver

Basic interface for resolving entities.
abstract class ErrorHandler

sax :: ErrorHandler

Basic interface for SAX error handlers.
interface XMLFilter

sax :: XMLFilter

Interface for an XML filter.

Children

class SAXEventLogger

saxophonit :: SAXEventLogger

A filter that internally log events it recieves.

Class definitions

sax $ XMLFilterImpl
# Base class for deriving an XML filter.
#
# This class is designed to sit between an `XMLReader`
# and the client application's event handlers. By default, it
# does nothing but pass requests up to the reader and events
# on to the handlers unmodified, but subclasses can override
# specific methods to modify the event stream or the configuration
# requests as they pass through.
#
# Note: The original source code and documentation of this class comes, in part,
# from [SAX 2.0](http://www.saxproject.org).
class XMLFilterImpl
	super XMLFilter
	super EntityResolver
	super DTDHandler
	super ContentHandler
	super ErrorHandler

	# XMLFilter

	redef var parent = null is writable

	# XMLReader

	redef var entity_resolver = null is writable
	redef var dtd_handler = null is writable
	redef var content_handler = null is writable
	redef var error_handler = null is writable


	############################################################################
	# XMLReader

	# Construct an empty XML filter, with no parent.
	#
	# This filter will have no parent: you must assign a parent
	# before you start a parse or do any configuration with
	# `feature=` or `property=`, unless you use this as
	# a pure event consumer rather than as an `XMLReader`.
	#
	# SEE: `parent`
	init do
	end

	# Construct an XML filter with the specified parent.
	#
	# SEE: `parent`
	init with_parent(parent_reader: XMLReader) do
		parent = parent_reader
	end

	redef fun feature_recognized(name) do
		if parent == null then
			return false
		else
			return parent.feature_recognized(name)
		end
	end

	redef fun feature_readable(name) do
		if parent == null then
			return false
		else
			return parent.feature_readable(name)
		end
	end

	redef fun feature_writable(name) do
		if parent == null then
			return false
		else
			return parent.feature_writable(name)
		end
	end

	# Look up the value of a feature.
	#
	# This will always fail if the parent is `null`.
	#
	# Parameters:
	#
	# * `name`: The feature name.
	#
	# Returns:
	#
	# The current value of the feature.
	#
	# SEE: `feature_recognized`
	#
	# SEE: `feature_readable`
	redef fun feature(name) do
		assert sax_recognized: parent != null else
			sys.stderr.write("Feature: {name}\n")
		end
		return parent.feature(name)
	end

	# Set the value of a feature.
	#
	# This will always fail if the parent is `null`.
	#
	# Parameters:
	#
	# * `name`: feature name.
	# * `value`: requested feature value.
	#
	# Returns:
	#
	# `true` if the feature is set; `false` if the feature can not be set given
	# the current context.
	#
	# SEE: `feature_recognized`
	#
	# SEE: `feature_writable`
	redef fun feature=(name, value) do
		assert sax_recognized: parent != null else
			sys.stderr.write("Feature: {name}\n")
		end
		parent.feature(name) = value
	end

	redef fun property_recognized(name) do
		if parent == null then
			return false
		else
			return parent.property_recognized(name)
		end
	end

	redef fun property_readable(name) do
		if parent == null then
			return false
		else
			return parent.property_readable(name)
		end
	end

	redef fun property_writable(name) do
		if parent == null then
			return false
		else
			return parent.property_writable(name)
		end
	end

	# Look up the value of a property.
	#
	# Parameters:
	#
	# * `name`: The property name.
	#
	# Returns:
	#
	# The current value of the property.
	#
	# SEE: `property_recognized`
	#
	# SEE: `property_readable`
	redef fun property(name) do
		assert sax_recognized: parent != null else
			sys.stderr.write("Property: {name}\n")
		end
		return parent.property(name)
	end

	# Set the value of a property.
	#
	# This will always fail if the parent is `null`.
	#
	# Parameters:
	#
	# * `name`: property name.
	# * `value`: requested feature value.
	#
	# Returns:
	#
	# `true` if the property is set; `false` if the property can not be set
	# given the current context.
	#
	# SEE: `property_recognized`
	#
	# SEE: `property_writable`
	redef fun property=(name, value) do
		assert sax_recognized: parent != null else
			sys.stderr.write("Property: {name}\n")
		end
		parent.property(name) = value
	end

	redef fun parse(input) do
		setup_parse
		parent.parse(input)
	end

	redef fun parse_file(system_id) do
		var source = new InputSource

		source.system_id = system_id
		parse(source)
	end


	############################################################################
	# EntityResolver

	redef fun resolve_entity(public_id, system_id) do
		if entity_resolver == null then
			return null
		else
			return entity_resolver.resolve_entity(public_id, system_id)
		end
	end


	############################################################################
	# DTDHandler

	redef fun notation_decl(name, public_id, system_id) do
		if dtd_handler != null then
			dtd_handler.notation_decl(name, public_id, system_id)
		end
	end

	redef fun unparsed_entity_decl(name, public_id, system_id) do
		if dtd_handler != null then
			dtd_handler.unparsed_entity_decl(name, public_id, system_id)
		end
	end


	############################################################################
	# ContentHandler

	redef fun document_locator=(locator) do
		if content_handler != null then
			content_handler.document_locator = locator
		end
	end

	redef fun start_document do
		if content_handler != null then
			content_handler.start_document
		end
	end

	redef fun end_document do
		if content_handler != null then
			content_handler.end_document
		end
	end

	redef fun start_prefix_mapping(prefix, uri) do
		if content_handler != null then
			content_handler.start_prefix_mapping(prefix, uri)
		end
	end

	redef fun end_prefix_mapping(prefix) do
		if content_handler != null then
			content_handler.end_prefix_mapping(prefix)
		end
	end

	redef fun start_element(uri, local_name, qname, atts) do
		if content_handler != null then
			content_handler.start_element(uri, local_name, qname, atts)
		end
	end

	redef fun end_element(uri, local_name, qname) do
		if content_handler != null then
			content_handler.end_element(uri, local_name, qname)
		end
	end

	redef fun characters(str) do
		if content_handler != null then
			content_handler.characters(str)
		end
	end

	redef fun ignorable_whitespace(str) do
		if content_handler != null then
			content_handler.ignorable_whitespace(str)
		end
	end

	redef fun processing_instruction(target, data) do
		if content_handler != null then
			content_handler.processing_instruction(target, data)
		end
	end

	redef fun skipped_entity(name) do
		if content_handler != null then
			content_handler.skipped_entity(name)
		end
	end


	############################################################################
	# ErrorHandler

	redef fun warning(exception) do
		if error_handler != null then
			error_handler.warning(exception)
		end
	end

	redef fun error(exception) do
		if error_handler != null then
			error_handler.error(exception)
		end
	end

	redef fun fatal_error(exception) do
		if error_handler != null then
			error_handler.fatal_error(exception)
		else
			exception.throw
		end
	end

	############################################################################
	# private

	# Set up before a parse.
	#
	# Before every parse, check whether the parent is
	# non-null, and re-register the filter for all of the
	# events.
	private fun setup_parse do
		assert parent_is_not_null: parent != 0 else
			sys.stderr.write("No parent for filter.")
		end
		parent.entity_resolver = self
		parent.dtd_handler = self
		parent.content_handler = self
		parent.error_handler = self
	end
end
lib/sax/helpers/xml_filter_impl.nit:25,1--365,3