MessagePack deserialization engine

Introduced properties

fun cache_metadata_strings: Bool

msgpack :: MsgPackSerializer :: cache_metadata_strings

Should strings declaring the objects type and attributes name be cached?
fun cache_metadata_strings=(cache_metadata_strings: Bool)

msgpack :: MsgPackSerializer :: cache_metadata_strings=

Should strings declaring the objects type and attributes name be cached?
protected fun current_object=(current_object: nullable Object)

msgpack :: MsgPackSerializer :: current_object=

fun plain_msgpack: Bool

msgpack :: MsgPackSerializer :: plain_msgpack

Write plain MessagePack without metadata for deserialization?
fun plain_msgpack=(plain_msgpack: Bool)

msgpack :: MsgPackSerializer :: plain_msgpack=

Write plain MessagePack without metadata for deserialization?
fun stream: Writer

msgpack :: MsgPackSerializer :: stream

Target writing stream
protected fun stream=(stream: Writer)

msgpack :: MsgPackSerializer :: stream=

Target writing stream

Redefined properties

redef type SELF: MsgPackSerializer

msgpack $ MsgPackSerializer :: SELF

Type of this instance, automatically specialized in every class
redef fun current_object: nullable Object

msgpack $ MsgPackSerializer :: current_object

The object currently serialized by serialized
redef fun serialize(object: nullable Serializable)

msgpack $ MsgPackSerializer :: serialize

Entry point method of this service, serialize the object
redef fun serialize_attribute(name: String, value: nullable Object)

msgpack $ MsgPackSerializer :: serialize_attribute

Serialize an attribute to compose a serializable object
redef fun serialize_reference(object: Serializable)

msgpack $ MsgPackSerializer :: serialize_reference

Serialize an object, with full serialization or a simple reference

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 cache: SerializerCache

serialization :: CachingSerializer :: cache

Cache of known objects
fun cache=(cache: SerializerCache)

serialization :: CachingSerializer :: cache=

Cache of known objects
fun cache_metadata_strings: Bool

msgpack :: MsgPackSerializer :: cache_metadata_strings

Should strings declaring the objects type and attributes name be cached?
fun cache_metadata_strings=(cache_metadata_strings: Bool)

msgpack :: MsgPackSerializer :: cache_metadata_strings=

Should strings declaring the objects type and attributes name be cached?
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.
protected abstract fun current_object: nullable Object

serialization :: Serializer :: current_object

The object currently serialized by serialized
protected fun current_object=(current_object: nullable Object)

msgpack :: MsgPackSerializer :: current_object=

fun ext_typ_byte: Int

msgpack :: MsgPackEngine :: ext_typ_byte

ext type byte to identify a byte, defaults to 0x7Eu8 or '|'
fun ext_typ_byte=(ext_typ_byte: Int)

msgpack :: MsgPackEngine :: ext_typ_byte=

ext type byte to identify a byte, defaults to 0x7Eu8 or '|'
fun ext_typ_char: Int

msgpack :: MsgPackEngine :: ext_typ_char

ext type byte to identify a char, defaults to 0x7Cu8 or '~'
fun ext_typ_char=(ext_typ_char: Int)

msgpack :: MsgPackEngine :: ext_typ_char=

ext type byte to identify a char, defaults to 0x7Cu8 or '~'
fun ext_typ_obj: Int

msgpack :: MsgPackEngine :: ext_typ_obj

ext type byte for object definitions, defaults to 0x7Bu8 or '{'
fun ext_typ_obj=(ext_typ_obj: Int)

msgpack :: MsgPackEngine :: ext_typ_obj=

ext type byte for object definitions, defaults to 0x7Bu8 or '{'
fun ext_typ_ref: Int

msgpack :: MsgPackEngine :: ext_typ_ref

ext type byte for object references, defaults to 0x7Du8 or '}'
fun ext_typ_ref=(ext_typ_ref: Int)

msgpack :: MsgPackEngine :: ext_typ_ref=

ext type byte for object references, defaults to 0x7Du8 or '}'
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.
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 plain_msgpack: Bool

msgpack :: MsgPackSerializer :: plain_msgpack

Write plain MessagePack without metadata for deserialization?
fun plain_msgpack=(plain_msgpack: Bool)

msgpack :: MsgPackSerializer :: plain_msgpack=

Write plain MessagePack without metadata for deserialization?
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
abstract fun serialize(object: nullable Serializable)

serialization :: Serializer :: serialize

Entry point method of this service, serialize the object
fun serialize_attribute(name: String, value: nullable Object)

serialization :: Serializer :: serialize_attribute

Serialize an attribute to compose a serializable object
fun serialize_core(value: Serializable)

serialization :: Serializer :: serialize_core

The method is called when a standard value is serialized
protected abstract fun serialize_reference(object: Serializable)

serialization :: Serializer :: serialize_reference

Serialize an object, with full serialization or a simple reference
fun stream: Writer

msgpack :: MsgPackSerializer :: stream

Target writing stream
protected fun stream=(stream: Writer)

msgpack :: MsgPackSerializer :: stream=

Target writing stream
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 try_to_serialize(value: nullable Object): Bool

serialization :: Serializer :: try_to_serialize

Serialize value is possible, i.e. it is Serializable or null
fun warn(msg: String)

serialization :: Serializer :: warn

Warn of problems and potential errors (such as if an attribute
package_diagram msgpack::MsgPackSerializer MsgPackSerializer serialization::CachingSerializer CachingSerializer msgpack::MsgPackSerializer->serialization::CachingSerializer msgpack::MsgPackEngine MsgPackEngine msgpack::MsgPackSerializer->msgpack::MsgPackEngine serialization::Serializer Serializer serialization::CachingSerializer->serialization::Serializer core::Object Object msgpack::MsgPackEngine->core::Object ...serialization::Serializer ... ...serialization::Serializer->serialization::Serializer ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.
interface Serializer

serialization :: Serializer

Abstract serialization service to be sub-classed by specialized services.

Parents

abstract class CachingSerializer

serialization :: CachingSerializer

A Serializer with a cache
abstract class MsgPackEngine

msgpack :: MsgPackEngine

MessagePack serialization or deserialization engine

Class definitions

msgpack $ MsgPackSerializer
# MessagePack deserialization engine
class MsgPackSerializer
	super CachingSerializer
	super MsgPackEngine

	# Target writing stream
	var stream: Writer

	# Write plain MessagePack without metadata for deserialization?
	#
	# If `false`, the default, serialize to support deserialization:
	#
	# * Each object is encapsulated in an array that contains metadata and
	#   the actual object attributes in a map. The metadata includes the type
	#   name and references to already serialized object. This information
	#   supports deserializing the message, including cycles.
	# * Preserve the Nit `Char` and `Byte` types as an object.
	# * The generated MessagePack is standard and can be read by non-Nit programs.
	#   However, it contains some complexity that may make it harder to use.
	#
	# If `true`, serialize only the real data or non-Nit programs:
	#
	# * Nit objects are serialized to pure and standard MessagePack so they can
	#   be easily read by non-Nit programs.
	# * Nit objects are serialized at every reference, so they may be duplicated.
	#   It is easier to read but it creates a larger output and it does not support
	#   cycles. Cyclic references are replaced by `null`.
	# * The serialized data can only be deserialized to their expected static
	#   types, losing the knowledge of their dynamic type.
	var plain_msgpack = false is writable

	# Should strings declaring the objects type and attributes name be cached?
	#
	# If `true` metadata strings are cached using `cache`.
	# The first occurrence is written as an object declaration,
	# successive occurrences are written as an object reference.
	#
	# If `false`, the default, metadata strings are written as pure MessagePack
	# strings, without their own metadata.
	#
	# Using the cache may save some space by avoiding the repetition of
	# names used by many types or attributes.
	# However, it adds complexity to the generated message and may be less
	# safe for versioning.
	var cache_metadata_strings = false is writable

	# List of the current open objects, the first is the main target of the serialization
	#
	# Used only when `plain_msgpack == true` to detect cycles in serialization.
	private var open_objects = new Array[Object]

	redef var current_object = null

	redef fun serialize(object)
	do
		if object == null then
			stream.write_msgpack_null
		else
			if plain_msgpack then
				for o in open_objects do
					if object.is_same_serialized(o) then
						# Cycle, can't be managed in plain_msgpack mode
						warn "Cycle detected in serialized object, replacing reference with 'null'."
						stream.write_msgpack_null
						return
					end
				end

				open_objects.add object
			end

			var last_object = current_object
			current_object = object
			object.accept_msgpack_serializer self
			current_object = last_object

			if plain_msgpack then open_objects.pop
		end
	end

	redef fun serialize_attribute(name, value)
	do
		serialize_meta_string name
		super
	end

	redef fun serialize_reference(object)
	do
		if not plain_msgpack and cache.has_object(object) then
			# if already serialized, add local reference
			var id = cache.id_for(object)
			stream.write_msgpack_ext(ext_typ_ref, id.to_bytes)
		else
			# serialize
			serialize object
		end
	end

	private fun serialize_meta_string(type_name: String)
	do
		if plain_msgpack or not cache_metadata_strings then
			# String only version
			stream.write_msgpack_str type_name
			return
		end

		if cache.has_object(type_name) then
			# if already serialized, add reference
			var id = cache.id_for(type_name)
			stream.write_msgpack_ext(ext_typ_ref, id.to_bytes)
		else
			# serialize
			var id = cache.new_id_for(type_name)
			stream.write_msgpack_array 2 # obj+id, type_name
			stream.write_msgpack_ext(ext_typ_obj, id.to_bytes)
			stream.write_msgpack_str type_name
		end
	end
end
lib/msgpack/serialization_write.nit:31,1--149,3