S-Expression processor

Introduced properties

fun parse_entity: SExpEntity

sexp :: SExpProcessor :: parse_entity

Parses an S-Expression entity

Redefined properties

redef type SELF: SExpProcessor

sexp $ SExpProcessor :: 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 current_location: Location

parser_base :: StringProcessor :: current_location

Gives the current location in the src
protected fun eof: Bool

parser_base :: StringProcessor :: eof

Is pos at the end of the source?
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.
protected fun hot_location: Location

parser_base :: StringProcessor :: hot_location

Returns the current location as a Location object
protected fun ignore_until(s: String): Int

parser_base :: StringProcessor :: ignore_until

Reads characters until pattern s is found
protected fun ignore_until_whitespace: Int

parser_base :: StringProcessor :: ignore_until_whitespace

Ignores any printable character until a whitespace is encountered
protected fun ignore_until_whitespace_or_comment: Int

parser_base :: StringProcessor :: ignore_until_whitespace_or_comment

Advance pos until a whitespace or # is encountered
protected fun ignore_whitespaces

parser_base :: StringProcessor :: ignore_whitespaces

Advances in src until a non-whitespace character is encountered
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.
protected fun len: Int

parser_base :: StringProcessor :: len

Length of the source document
protected fun len=(len: Int)

parser_base :: StringProcessor :: len=

Length of the source document
protected fun line: Int

parser_base :: StringProcessor :: line

Current line in src
protected fun line=(line: Int)

parser_base :: StringProcessor :: line=

Current line in src
protected fun line_offset: Int

parser_base :: StringProcessor :: line_offset

Offset in the current line
protected fun line_start: Int

parser_base :: StringProcessor :: line_start

Position at which current line started
protected fun line_start=(line_start: Int)

parser_base :: StringProcessor :: line_start=

Position at which current line started
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 parse_entity: SExpEntity

sexp :: SExpProcessor :: parse_entity

Parses an S-Expression entity
protected fun pos: Int

parser_base :: StringProcessor :: pos

Current position in src
protected fun pos=(pos: Int)

parser_base :: StringProcessor :: pos=

Current position in src
protected fun read_number: Float

parser_base :: StringProcessor :: read_number

Read a token and parse it as a Float
protected fun read_token: String

parser_base :: StringProcessor :: read_token

Read a single token after skipping preceding whitespaces
protected fun read_until_eol_or_comment: String

parser_base :: StringProcessor :: read_until_eol_or_comment

Advance pos until the next end of line or a #
protected fun read_vec3: Vec3

parser_base :: StringProcessor :: read_vec3

Read 2 or 3 numbers and return them as a Vec3
protected fun read_vec4: Vec4

parser_base :: StringProcessor :: read_vec4

Read 3 or 4 numbers and return them as a Vec4
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
protected fun skip_eol

parser_base :: StringProcessor :: skip_eol

Advance pos to skip the next end of line
protected fun src: String

parser_base :: StringProcessor :: src

Source document to parse
protected fun src=(src: String)

parser_base :: StringProcessor :: src=

Source document to parse
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.
package_diagram sexp::SExpProcessor SExpProcessor parser_base::StringProcessor StringProcessor sexp::SExpProcessor->parser_base::StringProcessor core::Object Object parser_base::StringProcessor->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

class StringProcessor

parser_base :: StringProcessor

Basic facilities for common parser operations on String sources

Class definitions

sexp $ SExpProcessor
# S-Expression processor
class SExpProcessor
	super StringProcessor

	# Parses an S-Expression entity
	fun parse_entity: SExpEntity do
		var srclen = src.length
		var delims = once ['(', ')', '"']
		ignore_whitespaces
		if pos >= srclen then return new SExpError(new Location(line, line_offset), "Empty S-Expression")
		var c = src[pos]
		if c == '(' then
			var cnt = new SExp
			var loc = new Location(line, line_offset)
			pos += 1
			while pos < srclen and src[pos] != ')' do
				var p = parse_entity
				if p isa SExpError then break
				cnt.content.add p
				ignore_whitespaces
			end
			if pos < srclen and src[pos] == ')' then
				pos += 1
				return cnt
			else
				return new SExpError(loc, "Incomplete S-Expression")
			end
		else if c == '"' then
			var stdq = pos
			var loc = new Location(line, line_offset)
			pos += 1
			ignore_until("\"")
			pos += 1
			var endq = pos
			return new SExpDQString(loc, src.substring(stdq, endq - stdq))
		else
			var stid = pos
			var loc = new Location(line, line_offset)
			while pos < srclen and not c.is_whitespace and not delims.has(c) do
				c = src[pos]
				pos += 1
			end
			if delims.has(c) or c.is_whitespace then pos -= 1
			if pos >= srclen then return new SExpError(loc, "Invalid S-Expression")
			var endid = pos
			var cntstr = src.substring(stid, endid - stid)
			var cnt: SExpEntity
			if cntstr.is_numeric then
				cnt = new SExpFloat(loc, cntstr.to_f)
			else
				cnt = new SExpId(loc, cntstr)
			end
			return cnt
		end
	end
end
lib/sexp/sexp.nit:93,1--148,3