Basic blocks for DOM-XML representation

DOM entities are defined in this module, specifically:

Introduced classes

class BadXMLAttribute

dom :: BadXMLAttribute

Badly formed XML attribute
class CDATA

dom :: CDATA

CDATA are regions in which no xml entity is parsed, all is ignored
class PCDATA

dom :: PCDATA

PCDATA is any kind of non-xml formatted text
abstract class XMLAttrTag

dom :: XMLAttrTag

Any kind of XML tag with attributes
abstract class XMLAttribute

dom :: XMLAttribute

Attributes are contained in tags, they provide meta-information on a tag
class XMLCommentTag

dom :: XMLCommentTag

An XML comment tag
class XMLDoctypeTag

dom :: XMLDoctypeTag

A DOCTYPE Tag
class XMLDocument

dom :: XMLDocument

Top XML Document-Object Model element
class XMLEndTag

dom :: XMLEndTag

An end Tag (starting with </)
abstract class XMLEntity

dom :: XMLEntity

Any kind of XML Entity
class XMLError

dom :: XMLError

Any XML Error that happens when parsing
class XMLOnelinerTag

dom :: XMLOnelinerTag

One-liner XML Tag (Ends with />)
class XMLProcessingInstructionTag

dom :: XMLProcessingInstructionTag

Processing instructions start with <? and are to be read by a third-party application
class XMLPrologTag

dom :: XMLPrologTag

Any prolog style-Tag (starting with <?xml)
class XMLSpecialTag

dom :: XMLSpecialTag

A Special Tag (starts with !)
class XMLStartTag

dom :: XMLStartTag

A (potentially) multi-line spanning XML Tag start
class XMLStringAttr

dom :: XMLStringAttr

An attribute with a String value
abstract class XMLTag

dom :: XMLTag

A Tag is a node in a DOM tree

All class definitions

class BadXMLAttribute

dom $ BadXMLAttribute

Badly formed XML attribute
class CDATA

dom $ CDATA

CDATA are regions in which no xml entity is parsed, all is ignored
class PCDATA

dom $ PCDATA

PCDATA is any kind of non-xml formatted text
abstract class XMLAttrTag

dom $ XMLAttrTag

Any kind of XML tag with attributes
abstract class XMLAttribute

dom $ XMLAttribute

Attributes are contained in tags, they provide meta-information on a tag
class XMLCommentTag

dom $ XMLCommentTag

An XML comment tag
class XMLDoctypeTag

dom $ XMLDoctypeTag

A DOCTYPE Tag
class XMLDocument

dom $ XMLDocument

Top XML Document-Object Model element
class XMLEndTag

dom $ XMLEndTag

An end Tag (starting with </)
abstract class XMLEntity

dom $ XMLEntity

Any kind of XML Entity
class XMLError

dom $ XMLError

Any XML Error that happens when parsing
class XMLOnelinerTag

dom $ XMLOnelinerTag

One-liner XML Tag (Ends with />)
class XMLProcessingInstructionTag

dom $ XMLProcessingInstructionTag

Processing instructions start with <? and are to be read by a third-party application
class XMLPrologTag

dom $ XMLPrologTag

Any prolog style-Tag (starting with <?xml)
class XMLSpecialTag

dom $ XMLSpecialTag

A Special Tag (starts with !)
class XMLStartTag

dom $ XMLStartTag

A (potentially) multi-line spanning XML Tag start
class XMLStringAttr

dom $ XMLStringAttr

An attribute with a String value
abstract class XMLTag

dom $ XMLTag

A Tag is a node in a DOM tree
package_diagram dom::xml_entities xml_entities parser_base parser_base dom::xml_entities->parser_base serialization serialization parser_base->serialization ...serialization ... ...serialization->serialization dom::parser parser dom::parser->dom::xml_entities dom::dom dom dom::dom->dom::parser dom::dom... ... dom::dom...->dom::dom

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 bitset

core :: bitset

Services to handle BitSet
module bytes

core :: bytes

Services for byte streams and arrays
module caching

serialization :: caching

Services for caching serialization engines
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 engine_tools

serialization :: engine_tools

Advanced services for serialization engines
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 inspect

serialization :: inspect

Refine Serializable::inspect to show more useful information
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 meta

meta :: meta

Simple user-defined meta-level to manipulate types of instances as object.
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 serialization

serialization :: serialization

General serialization services
module serialization_core

serialization :: serialization_core

Abstract services to serialize Nit objects to different formats
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 parser_base

parser_base :: parser_base

Simple base for hand-made parsers of all kinds

Children

module parser

dom :: parser

XML DOM-parsing facilities

Descendants

module a_star-m

a_star-m

module bmfont

gamnit :: bmfont

Parse Angel Code BMFont format and draw text
module cardboard

gamnit :: cardboard

Update the orientation of world_camera at each frame using the head position given by android::cardboard
module checker

dom :: checker

Simple XML validity checker using the dom module
module depth

gamnit :: depth

Framework for 3D games in Nit
module dom

dom :: dom

Easy XML DOM parser
module flat

gamnit :: flat

Simple API for 2D games, built around Sprite and App::update
module more_materials

gamnit :: more_materials

Various material implementations
module more_models

gamnit :: more_models

Services to load models from the assets folder
module nlp

nlp :: nlp

Natural Language Processor based on the StanfordNLP core.
module nlp_index

nlp :: nlp_index

Example showing how to use a NLPFileIndex.
module selection

gamnit :: selection

Select Actor from a screen coordinate
module stanford

nlp :: stanford

Natural Language Processor based on the StanfordNLP core.
module stereoscopic_view

gamnit :: stereoscopic_view

Refine EulerCamera and App::frame_core_draw to get a stereoscopic view
module texture_atlas_parser

gamnit :: texture_atlas_parser

Tool to parse XML texture atlas and generated Nit code to access subtextures
module virtual_gamepad

gamnit :: virtual_gamepad

Virtual gamepad mapped to keyboard keys for quick and dirty mobile support
module vr

gamnit :: vr

VR support for gamnit depth, for Android only
# Basic blocks for DOM-XML representation
#
# DOM entities are defined in this module, specifically:
#
# * `XMLEntity`: Abstract kind of XML-related node
# * `XMLDocument`: A well-formed XML document, root of the tree
# * `PCDATA`: Raw XML-escaped character data
# * `CDATA`: Raw data, may contain invalid XML escape characters
# * `XMLTag`: Abstract XML tag element
# * `XMLAttrTag`: Abstract XML element, they may contain attributes
# * `XMLOnelinerTag`: Any tag contained on one-line only
# * `XMLStartTag`: A tag starting a new hierarchy level in the tree
# * `XMLPrologTag`: A tag containing meta-information on the document, must start with <?xml
# * `XMLProcessingInstructionTag`: Any XML tag starting with <? other than the prolog tag
# * `XMLEndTag`: A tag signaling the end of a block
# * `XMLCommentTag`: A comment tag
# * `XMLSpecialTag`: A special tag, which may contain meta-information
# * `XMLDoctypeTag`: A DOCTYPE tag, use to register a DTD
# * `XMLAttribute`: Any kind of attribute that may be attached to a tag
# * `XMLStringAttr`: An attribute containing a String
# * `XMLError`: Any kind of error thrown while parsing a document
module xml_entities

import parser_base

# Any kind of XML Entity
abstract class XMLEntity
	# Optional parent of `self`
	var parent: nullable XMLEntity = null is private writable(set_parent)

	# Optional location of the entity in source
	var location: nullable Location

	# The children of `self`
	var children: Sequence[XMLEntity] = new XMLEntities(self)

	# Sets the parent of `self` to `e`
	fun parent=(e: XMLEntity) do
		var parent = self.parent
		if parent != null then
			parent.children.remove(self)
		end
		e.children.add(self)
	end
end

# Proxy collection of XMLEntities, ordered, used for the children of an entity
private class XMLEntities
	super Sequence[XMLEntity]

	# The owner, aka, the parent
	var owner: XMLEntity

	var entities = new List[XMLEntity]

	redef fun length do return entities.length

	redef fun [](i) do return entities[i]

	redef fun []=(index, el) do
		var olde = self[index]
		var olde_parent = olde.parent
		if olde_parent != null then
			olde_parent.children.remove(el)
		end
		entities[index] = el
		el.set_parent owner
	end

	redef fun push(e) do
		if not entities.has(e) then
			entities.add e
			e.parent = owner
		end
	end


	redef fun remove(e) do
		if e isa XMLEntity then
			e.set_parent null
			entities.remove(e)
		end
	end

	redef fun has(e) do return entities.has(e)

	redef fun iterator do return entities.iterator

	redef fun reverse_iterator do return entities.reverse_iterator

	redef fun pop do
		var e = entities.pop
		e.set_parent null
		return e
	end

	redef fun unshift(e) do
		entities.unshift e
		e.set_parent owner
	end

	redef fun shift do
		var e = entities.shift
		e.set_parent null
		return e
	end

	redef fun insert(it, index) do
		entities.insert(it, index)
		it.set_parent owner
	end

	redef fun remove_at(ind) do
		var el = entities[ind]
		entities.remove_at(ind)
		el.set_parent null
	end
end

# Top XML Document-Object Model element
class XMLDocument
	super XMLEntity

	redef fun to_s do return children.join
end

# PCDATA is any kind of non-xml formatted text
class PCDATA
	super XMLEntity

	# Any string containing non XML-reserved characters
	var content: String

	redef fun to_s do return content
end

# CDATA are regions in which no xml entity is parsed, all is ignored
class CDATA
	super XMLEntity

	# Any string contained within a CDATA block, may contain XML-reserved characters
	var content: String

	redef fun to_s do return "<![CDATA[{content}]]>"
end

# A Tag is a node in a DOM tree
abstract class XMLTag
	super XMLEntity

	# The name of the tag
	var tag_name: String
end

# Any kind of XML tag with attributes
abstract class XMLAttrTag
	super XMLTag

	# List of attributes in a Tag
	var attributes: Array[XMLAttribute]
end

# One-liner XML Tag (Ends with />)
class XMLOnelinerTag
	super XMLAttrTag

	redef fun to_s do
		var s = "<{tag_name}"
		if not attributes.is_empty then
			s += " "
			s += attributes.join(" ")
		end
		s += "/>"
		return s
	end
end

# A (potentially) multi-line spanning XML Tag start
class XMLStartTag
	super XMLAttrTag

	# Optional matching tag, must be matched for the document to be well-formed
	var matching: nullable XMLEndTag

	redef fun to_s do
		var s = "<{tag_name}"
		if not attributes.is_empty then
			s += " "
			s += attributes.join(" ")
		end
		s += ">"
		for i in children do s += i.to_s
		var matching = self.matching
		if matching != null then s += matching.to_s
		return s
	end
end

# Any prolog style-Tag (starting with <?xml)
class XMLPrologTag
	super XMLAttrTag

	redef fun to_s do return """<?{{{tag_name}}} {{{attributes.join(" ")}}}?>"""
end

# Processing instructions start with <? and are to be read by a third-party application
class XMLProcessingInstructionTag
	super XMLTag

	# Raw content usable by the third-party application
	var content: String

	redef fun to_s do return "<?{tag_name} {content}?>"
end

# An end Tag (starting with </)
class XMLEndTag
	super XMLTag

	# Optional matching tag, must be matched for the document to be well-formed
	var matching: nullable XMLStartTag

	redef fun to_s do return "</{tag_name}>"
end

# An XML comment tag
class XMLCommentTag
	super XMLTag

	redef fun to_s do return "<!--{tag_name}-->"
end

# A DOCTYPE Tag
class XMLDoctypeTag
	super XMLTag

	# Raw content
	var content: String

	redef fun to_s do return "<!DOCTYPE {content}>"
end

# A Special Tag (starts with !)
#
# TODO: Support the remaining ! tags
class XMLSpecialTag
	super XMLTag

	redef fun to_s do return "<!{tag_name}>"
end

# Attributes are contained in tags, they provide meta-information on a tag
abstract class XMLAttribute
	super XMLEntity

	# Name of the attribute
	var name: String
end

# An attribute with a String value
class XMLStringAttr
	super XMLAttribute

	# Value of the attribute without the double quotes
	var value: String

	# Type of delimiter (can be either " or ')
	var delimiter: Char

	redef fun to_s do return "{name}={delimiter}{value}{delimiter}"
end

# Badly formed XML attribute
class BadXMLAttribute
	super XMLAttribute

	redef fun to_s do return name
end

# Internal use only, shows the end of an attribute block
private class XMLAttributeEnd
	super XMLAttribute
end

# Any XML Error that happens when parsing
class XMLError
	super XMLEntity

	# Error message reported by the parser
	var message: String

	redef fun to_s do
		var l = self.location
		if l == null then
			return "XML Error: {message}"
		else
			return "XML Error: {message} at {l}"
		end
	end
end
lib/dom/xml_entities.nit:11,1--310,3