Receives notification of basic DTD-related events.

If a SAX application needs information about notations and unparsed entities, then the application implements this interface and registers an instance with the SAX parser using the parser's dtd_handler property. The parser uses the instance to report notation and unparsed entity declarations to the application.

Note that this interface includes only those DTD events that the XML recommendation requires processors to report: notation and unparsed entity declarations.

The SAX parser may report these events in any order, regardless of the order in which the notations and unparsed entities were declared; however, all DTD events must be reported after the document handler's start_document event, and before the first start_element event. (If the sax::ext::LexicalHandler is used, these events must also be reported before the end_dtd event.)

It is up to the application to store the information for future use (perhaps in a hash table or object tree). If the application encounters attributes of type NOTATION, ENTITY, or ENTITIES, it can use the information that it obtained through this interface to find the entity and/or notation corresponding with the attribute value.

Note: The original documentation comes from SAX 2.0.

SEE: sax::XMLReader.dtd_handler

Introduced properties

fun notation_decl(name: String, public_id: String, system_id: String)

sax :: DTDHandler :: notation_decl

Receive notification of a notation declaration event.
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.

Redefined properties

redef type SELF: DTDHandler

sax $ DTDHandler :: SELF

Type of this instance, automatically specialized in every class

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
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.
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.
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).
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
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.
package_diagram sax::DTDHandler DTDHandler core::Object Object sax::DTDHandler->core::Object sax::XMLFilterImpl XMLFilterImpl sax::XMLFilterImpl->sax::DTDHandler saxophonit::SAXEventLogger SAXEventLogger saxophonit::SAXEventLogger->sax::XMLFilterImpl saxophonit::SAXEventLogger... ... saxophonit::SAXEventLogger...->saxophonit::SAXEventLogger

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class XMLFilterImpl

sax :: XMLFilterImpl

Base class for deriving an XML filter.

Descendants

class SAXEventLogger

saxophonit :: SAXEventLogger

A filter that internally log events it recieves.

Class definitions

sax $ DTDHandler
# Receives notification of basic DTD-related events.
#
# If a SAX application needs information about notations and
# unparsed entities, then the application implements this
# interface and registers an instance with the SAX parser using
# the parser's `dtd_handler` property. The parser uses the
# instance to report notation and unparsed entity declarations to
# the application.
#
# Note that this interface includes only those DTD events that
# the XML recommendation *requires* processors to report:
# notation and unparsed entity declarations.
#
# The SAX parser may report these events in any order, regardless
# of the order in which the notations and unparsed entities were
# declared; however, all DTD events must be reported after the
# document handler's `start_document` event, and before the first
# `start_element` event.
# (If the `sax::ext::LexicalHandler` is
# used, these events must also be reported before the `end_dtd` event.)
#
# It is up to the application to store the information for
# future use (perhaps in a hash table or object tree).
# If the application encounters attributes of type `NOTATION`,
# `ENTITY`, or `ENTITIES`, it can use the information that it
# obtained through this interface to find the entity and/or
# notation corresponding with the attribute value.
#
# Note: The original documentation comes from [SAX 2.0](http://www.saxproject.org).
#
# SEE: `sax::XMLReader.dtd_handler`
abstract class DTDHandler

	# Receive notification of a notation declaration event.
	#
	# It is up to the application to record the notation for later
	# reference, if necessary;
	# notations may appear as attribute values and in unparsed entity
	# declarations, and are sometime used with processing instruction
	# target names.
	#
	# At least one of `public_id` and `system_id` must be non-null.
	# If a system identifier is present, and it is a URL, the SAX
	# parser must resolve it fully before passing it to the
	# application through this event.
	#
	# There is no guarantee that the notation declaration will be
	# reported before any unparsed entities that use it.
	#
	# Parameters:
	#
	# * `name`: notation name.
	# * `public_id`: notation's public identifier, or null if none was given.
	# * `system_id`: notation's system identifier, or null if none was given.
	#
	# SEE: `sax::Attributes`
	fun notation_decl(name: String, public_id: String, system_id: String) do end

	# Receive notification of an unparsed entity declaration event.
	#
	# Note that the notation name corresponds to a notation
	# reported by the `notation_decl` event.
	# It is up to the application to record the entity for later
	# reference, if necessary;
	# unparsed entities may appear as attribute values.
	#
	# If the system identifier is a URL, the parser must resolve it
	# fully before passing it to the application.
	#
	# Parameters:
	#
	# * `name`: unparsed entity's name.
	# * `public_id`: entity's public identifier, or null if none was given.
	# * `system_id`: entity's system identifier, or null if none was given.
	#
	# SEE: `sax::Attributes`
	fun unparsed_entity_decl(name: String, public_id: String,
			system_id: String) do end
end
lib/sax/dtd_handler.nit:14,1--92,3