Instances of this class can be passed to Serializer::serialize

Introduced properties

protected fun accept_json_serializer(v: JsonSerializer)

serialization :: Serializable :: accept_json_serializer

Refinable service to customize the serialization of this class to JSON
protected fun accept_msgpack_attribute_counter(v: AttributeCounter)

serialization :: Serializable :: accept_msgpack_attribute_counter

Hook to customize the behavior of the AttributeCounter
protected fun accept_msgpack_serializer(v: MsgPackSerializer)

serialization :: Serializable :: accept_msgpack_serializer

Hook to customize the serialization of this class to MessagePack
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
fun core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
init from_deserializer(deserializer: Deserializer)

serialization :: Serializable :: from_deserializer

Create an instance of this class from the deserializer
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
fun serialize_msgpack(plain: nullable Bool): Bytes

serialization :: Serializable :: serialize_msgpack

Serialize self to MessagePack bytes
fun serialize_to(serializer: Serializer)

serialization :: Serializable :: serialize_to

Serialize self to serializer
fun serialize_to_json(plain: nullable Bool, pretty: nullable Bool): String

serialization :: Serializable :: serialize_to_json

Serialize self to JSON
fun to_json: String

serialization :: Serializable :: to_json

Serialize self to plain JSON
fun to_pretty_json: String

serialization :: Serializable :: to_pretty_json

Serialize self to plain pretty JSON

Redefined properties

redef type SELF: Serializable

serialization $ Serializable :: SELF

Type of this instance, automatically specialized in every class
redef fun inspect: String

serialization :: inspect $ Serializable :: inspect

Improve the default inspection reading serializable attributes

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 accept_json_serializer(v: JsonSerializer)

serialization :: Serializable :: accept_json_serializer

Refinable service to customize the serialization of this class to JSON
protected fun accept_msgpack_attribute_counter(v: AttributeCounter)

serialization :: Serializable :: accept_msgpack_attribute_counter

Hook to customize the behavior of the AttributeCounter
protected fun accept_msgpack_serializer(v: MsgPackSerializer)

serialization :: Serializable :: accept_msgpack_serializer

Hook to customize the serialization of this class to MessagePack
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
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 core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
init from_deserializer(deserializer: Deserializer)

serialization :: Serializable :: from_deserializer

Create an instance of this class from the deserializer
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.
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
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
fun serialize_msgpack(plain: nullable Bool): Bytes

serialization :: Serializable :: serialize_msgpack

Serialize self to MessagePack bytes
fun serialize_to(serializer: Serializer)

serialization :: Serializable :: serialize_to

Serialize self to serializer
fun serialize_to_json(plain: nullable Bool, pretty: nullable Bool): String

serialization :: Serializable :: serialize_to_json

Serialize self to JSON
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun to_json: String

serialization :: Serializable :: to_json

Serialize self to plain JSON
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_pretty_json: String

serialization :: Serializable :: to_pretty_json

Serialize self to plain pretty JSON
fun to_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram serialization::Serializable Serializable core::Object Object serialization::Serializable->core::Object serialization::Serializable... ... serialization::Serializable...->serialization::Serializable

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class AStarPath[N: nullable Object]

a_star :: AStarPath

Result from path finding and a walkable path
class BestDistance[E: nullable Object]

more_collections :: BestDistance

Keep track of the best elements according to a distance value.
abstract class Comment

github :: Comment

A Github comment
class CommitStatus

github :: CommitStatus

Status of a commit
class ContributorWeek

github :: ContributorWeek

Contributor stats weekly hash
class Couple[F: nullable Object, S: nullable Object]

core :: Couple

Two objects in a simple structure.
abstract class Deserializer

serialization :: Deserializer

Abstract deserialization service
interface DirectSerializable

serialization :: DirectSerializable

Instances of this class are not delayed and instead serialized immediately
abstract class E

serialization :: E

The root class of the business objects.
class Error

core :: Error

Standard class for error messages
interface GameEvent

bucketed_game :: GameEvent

Game related event
class GitCommit

github :: GitCommit

A Git Commit representation
class GitUser

github :: GitUser

Git user authoring data
class GithubEvent

github :: GithubEvent

Github event stub.
class GithubFile

github :: GithubFile

A Github file representation.
class Graph[N: Node, L: Link]

a_star :: Graph

General graph
class HashMap2[K1: nullable Object, K2: nullable Object, V: nullable Object]

more_collections :: HashMap2

Simple way to store an HashMap[K1, HashMap[K2, V]]
class HashMap3[K1: nullable Object, K2: nullable Object, K3: nullable Object, V: nullable Object]

more_collections :: HashMap3

Simple way to store an HashMap[K1, HashMap[K2, HashMap[K3, V]]]
class HashMap4[K1: nullable Object, K2: nullable Object, K3: nullable Object, K4: nullable Object, V: nullable Object]

more_collections :: HashMap4

Simple way to store an HashMap[K1, HashMap[K2, HashMap[K3, HashMap[K4, V]]]]
class HttpRequest

nitcorn :: HttpRequest

A request received over HTTP, is build by HttpRequestParser
class HttpResponse

nitcorn :: HttpResponse

A response to send over HTTP
interface ILine[N: Numeric]

geometry :: ILine

Abstract 2D line segment between two ordered points
interface IPoint[N: Numeric]

geometry :: IPoint

Abstract 2d point, strongly linked to its implementation Point
class ImprovedNoise

noise :: ImprovedNoise

Direct translation of Ken Perlin's improved noise Java implementation
interface JsonMapRead[K: String, V: nullable Serializable]

json :: JsonMapRead

A map that can be translated into a JSON object.
class JsonSequenceRead[E: nullable Serializable]

json :: JsonSequenceRead

A sequence that can be translated into a JSON array.
class Label

github :: Label

A Github label.
class Location

parser_base :: Location

Information about the location of an entity in a source document
interface Map[K: nullable Object, V: nullable Object]

core :: Map

Maps are associative collections: key -> item.
class Milestone

github :: Milestone

A Github milestone.
class MsgPackExt

msgpack :: MsgPackExt

Application specific MessagePack extension
class MyData

nitcorn :: MyData

Simple data structure for MyAction::complex_args
class NeoGraph

neo4j :: NeoGraph

A Neo4j graph with a local identification scheme for its nodes.
class NeoNode

neo4j :: NeoNode

Nodes are used to represent entities stored in base.
class Node

a_star :: Node

General graph node
abstract class Noise

noise :: Noise

2D noise generator
class POSet[E: nullable Object]

poset :: POSet

Pre-order set graph.
class POSetElement[E: nullable Object]

poset :: POSetElement

View of an object in a poset
abstract class PathContext

a_star :: PathContext

Context related to an evocation of pathfinding
class Person

curl :: Person

class Position

nitcc_runtime :: Position

A position into a input stream
class ProcessorInfo

mpi :: ProcessorInfo

Simple class transfered between processors
class PullRef

github :: PullRef

A pull request reference (used for head and base).
class Ref[E: nullable Object]

core :: Ref

A collection that contains only one item.
class RenameAction

github :: RenameAction

A rename action maintains the name before and after a renaming action.
class Repo

github :: Repo

A Github repository.
abstract class RepoObject

popcorn :: RepoObject

Base serializable entity that can go into a JsonRepository
class RepoStatus

github :: RepoStatus

Sub status of a CommitStatus
class SearchResults

github :: SearchResults

A list of results returned buy /search
interface SimpleCollection[E: nullable Object]

core :: SimpleCollection

Items can be added to these collections.
abstract class TargetCondition[N: Node]

a_star :: TargetCondition

Advanced path conditions with customizable accept states
class ThinGame

bucketed_game :: ThinGame

Game logic on the client
class ThinGameTurn[G: ThinGame]

bucketed_game :: ThinGameTurn

Game turn on the client
abstract class Turnable[G: Game]

bucketed_game :: Turnable

Something acting on the game
class ValidationResult

popcorn :: ValidationResult

Validation Result representation

Descendants

class A

serialization :: A

A business object, with an integer information
abstract class AbstractArray[E: nullable Object]

core :: AbstractArray

Resizable one dimension array of objects.
class Array[E: nullable Object]

core :: Array

Resizable one dimension array of objects.
class ArrayCmp[E: nullable Comparable]

core :: ArrayCmp

Comparable array for comparable elements.
class ArrayMap[K: nullable Object, E: nullable Object]

core :: ArrayMap

Associative arrays implemented with an array of (key, value) pairs.
class ArraySet[E: nullable Object]

core :: ArraySet

A set implemented with an Array.
abstract class AttributeError

serialization :: AttributeError

Deserialization error related to an attribute of receiver
class AttributeMap

gamnit :: AttributeMap

Map to organize Attribute instances by their name
class AttributeMap

dot :: AttributeMap

Map of graph/node/edge attribute that can be rendered to dot.
class AttributeMissingError

serialization :: AttributeMissingError

Missing attribute at deserialization
class AttributeTypeError

serialization :: AttributeTypeError

Invalid dynamic type for a deserialized attribute
class B

serialization :: B

A business object associated with an A.
class BinTreeMap[K: Comparable, E: nullable Object]

trees :: BinTreeMap

Binary Tree Map
class BlockingQueue[E: nullable Object]

pthreads :: BlockingQueue

A Blocking queue implemented from a ConcurrentList
enum Bool

core :: Bool

Native Booleans.
class BoxedArray[E: Boxed[Numeric]]

geometry :: BoxedArray

BoxedCollection implemented by an array
interface BoxedCollection[E: Boxed[Numeric]]

geometry :: BoxedCollection

Base for all data structures containing multiple Boxed Objects
class Branch

github :: Branch

A Github branch.
abstract class Bucketable[G: Game]

bucketed_game :: Bucketable

Something acting on the game from time to time
class Buckets[G: Game]

bucketed_game :: Buckets

Optimized organization of Bucketable instances
abstract class Buffer

core :: Buffer

A mutable sequence of characters.
enum Byte

core :: Byte

Native bytes.
class Bytes

core :: Bytes

A buffer containing Byte-manipulation facilities
extern class CString

core :: CString

C string char *
abstract class CachingDeserializer

serialization :: CachingDeserializer

A Deserializer with a cache
enum Char

core :: Char

Native characters.
class CircularArray[E: nullable Object]

core :: CircularArray

Efficient data structure to access both end of the sequence.
class Commit

github :: Commit

A Github commit.
class CommitComment

github :: CommitComment

A comment made on a commit.
class CommitCommentEvent

github :: CommitCommentEvent

Triggered when a commit comment is created.
class ConceptLattice[O: Object, A: Object]

fca :: ConceptLattice

Concept Lattice
class ConcurrentArray[E: nullable Object]

pthreads :: ConcurrentArray

A concurrent variant to the standard Array
class ConcurrentList[E: nullable Object]

pthreads :: ConcurrentList

A concurrent variant to the standard List
abstract class ConcurrentSequence[E: nullable Object]

pthreads :: ConcurrentSequence

A concurrent variant to the standard Sequence
class ConstantPathContext

a_star :: ConstantPathContext

Simple context with constant cost on each links
class Counter[E: nullable Object]

counter :: Counter

A counter counts occurrences of things
interface CoupleMap[K: nullable Object, V: nullable Object]

core :: CoupleMap

Associative arrays that internally uses couples to represent each (key, value) pairs.
class CreateEvent

github :: CreateEvent

Triggered when a repository, branch, or tag is created.
class DQuadTree[E: Boxed[Numeric]]

geometry :: DQuadTree

A dynamic implementation of the quadtree data structure
class DefaultMap[K: nullable Object, V: nullable Object]

more_collections :: DefaultMap

A map with a default value.
class DeleteEvent

github :: DeleteEvent

Triggered when a branch or a tag is deleted.
class DeploymentEvent

github :: DeploymentEvent

Triggered when a new snapshot is deployed.
class DeploymentStatusEvent

github :: DeploymentStatusEvent

Triggered when a deployement's status changes.
class DisjointSet[E: nullable Object]

core :: DisjointSet

Data structure to keep track of elements partitioned into disjoint subsets
class DummyArray

dummy_array :: DummyArray

A Set that contains only integers.
class FirstTurnEvent

bucketed_game :: FirstTurnEvent

Event raised at the first turn
class FlatBuffer

core :: FlatBuffer

Mutable strings of characters.
abstract class FlatString

core :: FlatString

Immutable strings of characters.
abstract class FlatText

core :: FlatText

All kinds of array-based text representations.
enum Float

core :: Float

Native floating point numbers.
class ForkEvent

github :: ForkEvent

Triggered when a user forks a repository.
class Game

bucketed_game :: Game

Full game logic
class GameTurn[G: Game]

bucketed_game :: GameTurn

Game turn on the full logic
class GithubAPIError

github :: GithubAPIError

An Error returned by https://api.github.com
class GithubDeserializer

github :: GithubDeserializer

JsonDeserializer specific for Github objects.
class GithubDeserializerErrors

github :: GithubDeserializerErrors

An Error returned while deserializing objects from the API
class GithubError

github :: GithubError

An Error returned by GithubAPI
class HashMap[K: nullable Object, V: nullable Object]

core :: HashMap

A Map implemented with a hash table.
class HashSet[E: nullable Object]

core :: HashSet

A Set implemented with a hash table.
interface ILine3d[N: Numeric]

geometry :: ILine3d

Abstract 3D line segment between two ordered points
class IOError

core :: IOError

Any kind of error that could be produced by an operation on Streams
interface IPoint3d[N: Numeric]

geometry :: IPoint3d

Abstract 3d point, strongly linked to its implementation Point3d
class IniError

ini :: IniError

Error for IniFile parsing
class IniFile

ini :: IniFile

Read and write INI configuration files
class IniSection

ini :: IniSection

A section in a IniFile
enum Int

core :: Int

Native integer numbers.
class Interfaces

nitcorn :: Interfaces

A list of interfaces with dynamic port listeners
class InterpolatedNoise

noise :: InterpolatedNoise

Simple interpolated noise
class Issue

github :: Issue

A Github issue.
class IssueComment

github :: IssueComment

Comments made on Github issue and pull request pages.
class IssueCommentEvent

github :: IssueCommentEvent

Triggered when an issue comment is created.
class IssueEvent

github :: IssueEvent

An event that occurs on a Github Issue.
class IssuesEvent

github :: IssuesEvent

Triggered when an event occurs on an issue.
class JsonArray

json :: JsonArray

A JSON array.
class JsonDeserializer

json :: JsonDeserializer

Deserializer from a Json string.
class JsonKeyError

json :: JsonKeyError

Key access error
class JsonObject

json :: JsonObject

A JSON Object.
class JsonParseError

json :: JsonParseError

JSON format error at parsing
class Line[N: Numeric]

geometry :: Line

2D line segment between two ordered points
class Line3d[N: Numeric]

geometry :: Line3d

3D line segment between two ordered points
class List[E: nullable Object]

core :: List

Double linked lists.
class LiveGroup[E: LiveObject]

scene2d :: LiveGroup

Organizational class to manage groups of sprites and other live objects.
class LoaderJob

github :: LoaderJob

Loader status by repo
class LogEntry

popcorn :: LogEntry

A tracker log entry used to store HTTP requests and their given HTTP responses
class Mailbox[E: nullable Object]

actors :: Mailbox

A Blocking queue implemented from a ConcurrentList
class MemberEvent

github :: MemberEvent

Triggered when a user is added as a collaborator to a repository.
class MinHeap[E: Object]

core :: MinHeap

A min-heap implemented over an array
class MongoGroup

mongodb :: MongoGroup

Mongo pipeline group stage
class MongoMatch

mongodb :: MongoMatch

A basic match query
class MongoPipeline

mongodb :: MongoPipeline

Mongo pipelines are arrays of aggregation stages
class MsgPackDeserializer

msgpack :: MsgPackDeserializer

Deserialize MessagePack format to full Nit objects
class MultiHashMap[K: nullable Object, V: nullable Object]

more_collections :: MultiHashMap

Simple way to store an HashMap[K, Array[V]]
class MyOtherData

nitcorn :: MyOtherData

Another data structure, subclass to MyData
class NamedNode

a_star :: NamedNode

Simple node with a name
class NeoError

neo4j :: NeoError

An error thrown by the neo4j API.
abstract class NeoNodeCollection

neo4j :: NeoNodeCollection

All the nodes in a NeoGraph.
class PRMap[V: nullable Object]

graph :: PRMap

Map each Vertice of a Digraph to it's PageRank.
class PerfMap

performance_analysis :: PerfMap

Collection of statistics on many events
class PerlinNoise

noise :: PerlinNoise

2D Perlin noise generator using layered InterpolatedNoise
class Point[N: Numeric]

geometry :: Point

2D point with x and z
class Point3d[N: Numeric]

geometry :: Point3d

3D point with x, y and z
class PositionPathContext

a_star :: PositionPathContext

Context for a graph with positions
class PositionedNamedNode

a_star :: PositionedNamedNode

Node with a name and position
class PullComment

github :: PullComment

Comments made on Github pull request diffs.
class PullRequest

github :: PullRequest

A Github pull request.
class PullRequestEvent

github :: PullRequestEvent

Triggered when an event occurs on a pull request.
class PullRequestPullCommentEvent

github :: PullRequestPullCommentEvent

Triggered when a comment is created on a pull request diff.
class PushEvent

github :: PushEvent

Triggered when a repository branch is pushed to.
abstract class QuadTree[E: Boxed[Numeric]]

geometry :: QuadTree

Abstract QuadTree implementing the basic functions and data
interface Queue[E: nullable Object]

core :: Queue

Queues are collection that controls how elements are retrieved.
class RBTreeMap[K: Comparable, E: nullable Object]

trees :: RBTreeMap

Red-Black Tree Map
class ReverseBlockingQueue[E: nullable Object]

pthreads :: ReverseBlockingQueue

A collection which is_empty method blocks until it's empty
class SAXParseException

sax :: SAXParseException

Encapsulates an XML parse error or warning.
class SQuadTree[E: Boxed[Numeric]]

geometry :: SQuadTree

Static implementation of the quadtree structure
class SafeDeserializer

serialization :: SafeDeserializer

Deserialization engine limiting which types can be deserialized
interface Sequence[E: nullable Object]

core :: Sequence

Sequence are indexed collection.
class SequentialNodeCollection

neo4j :: SequentialNodeCollection

A Neo4j node collection using a sequential identification scheme.
interface Set[E: nullable Object]

core :: Set

Abstract sets.
abstract class ShaderVariableMap[A: ShaderVariable]

gamnit :: ShaderVariableMap

Map to organize ShaderVariable instances by their name
class SpriteSet

gamnit :: SpriteSet

Set of sprites sorting them into different SpriteContext
class StatusEvent

github :: StatusEvent

Triggered when the status of a Git commit changes.
class StrictHashMap[K: nullable Object, V: nullable Object]

serialization :: StrictHashMap

Maps instances to a value, uses is_same_serialized and serialization_hash.
abstract class String

core :: String

Immutable sequence of characters.
abstract class Text

core :: Text

High-level abstraction for all text representations
class TextureSet

gamnit :: TextureSet

Group of Texture
abstract class TreeMap[K: Comparable, E: nullable Object]

trees :: TreeMap

Abstract tree map structure
class Trie[E: nullable Object]

trees :: Trie

Trie data structure for prefix searches
class U16String

core :: U16String

UTF-16 encoded string
class UniformMap

gamnit :: UniformMap

Map to organize Uniform instances by their name
class UnrolledList[E: nullable Object]

more_collections :: UnrolledList

An unrolled linked list
class User

github :: User

A Github user
class Vector

vsm :: Vector

A n-dimensions vector
class VirtualHosts

nitcorn :: VirtualHosts

A list of virtual hosts with dynamic port listeners
class WeightedPathContext

a_star :: WeightedPathContext

A PathContext for graphs with WeightedLink

Class definitions

serialization $ Serializable
# Instances of this class can be passed to `Serializer::serialize`
interface Serializable
	# Serialize `self` to `serializer`
	#
	# This is a shortcut to `Serializer::serialize`.
	fun serialize_to(serializer: Serializer) do serializer.serialize(self)

	# Actual serialization of `self` to `serializer`
	#
	# This writes the full data of `self` to `serializer`.
	#
	# This method can be redefined in sub classes and refinements.
	# It should use `Serializer::serialize_attribute` to to register real or
	# logical attributes.
	#
	# Any refinement should have its equivalent refinement of
	# `Deserializer::deserialize_class` to support this custom deserialization.
	fun core_serialize_to(serializer: Serializer) do end

	# Accept references or force direct serialization (using `serialize_to`)
	#
	# The subclass change the default behavior, which will accept references,
	# to force to always serialize copies of `self`.
	private fun serialize_to_or_delay(v: Serializer) do v.serialize_reference(self)

	# Create an instance of this class from the `deserializer`
	#
	# This constructor is refined by subclasses to correctly build their instances.
	init from_deserializer(deserializer: Deserializer) is nosuper do end
end
lib/serialization/serialization_core.nit:219,1--248,3

json :: serialization_write $ Serializable
redef class Serializable

	# Serialize `self` to JSON
	#
	# Set `plain = true` to generate standard JSON, without deserialization metadata.
	# Use this option if the generated JSON will be read by other programs or humans.
	# Use the default, `plain = false`, if the JSON is to be deserialized by a Nit program.
	#
	# Set `pretty = true` to generate pretty JSON for human eyes.
	# Use the default, `pretty = false`, to generate minified JSON.
	#
	# This method should not be refined by subclasses,
	# instead `accept_json_serializer` can customize the serialization of an object.
	#
	# See: `JsonSerializer`
	fun serialize_to_json(plain, pretty: nullable Bool): String
	do
		var stream = new StringWriter
		var serializer = new JsonSerializer(stream)
		serializer.plain_json = plain or else false
		serializer.pretty_json = pretty or else false
		serializer.serialize self
		stream.close
		return stream.to_s
	end

	# Serialize `self` to plain JSON
	#
	# Compatibility alias for `serialize_to_json(plain=true)`.
	fun to_json: String do return serialize_to_json(plain=true)

	# Serialize `self` to plain pretty JSON
	#
	# Compatibility alias for `serialize_to_json(plain=true, pretty=true)`.
	fun to_pretty_json: String do return serialize_to_json(plain=true, pretty=true)

	# Refinable service to customize the serialization of this class to JSON
	#
	# This method can be refined to customize the serialization by either
	# writing pure JSON directly on the stream `v.stream` or
	# by using other services of `JsonSerializer`.
	#
	# Most of the time, it is preferable to refine the method `core_serialize_to`
	# which is used by all the serialization engines, not just JSON.
	protected fun accept_json_serializer(v: JsonSerializer)
	do
		v.stream.write "\{"
		v.indent_level += 1
		if not v.plain_json then
			var id = v.cache.new_id_for(self)
			v.new_line_and_indent
			v.stream.write "\"__kind\": \"obj\", \"__id\": "
			v.stream.write id.to_s
			v.stream.write ", \"__class\": \""
			v.stream.write class_name
			v.stream.write "\""
		end
		v.serialize_core(self)

		v.indent_level -= 1
		v.new_line_and_indent
		v.stream.write "\}"
	end
end
lib/json/serialization_write.nit:199,1--262,3

serialization :: inspect $ Serializable
redef class Serializable

	# Improve the default inspection reading serializable attributes
	#
	# Simple immutable data are inspected as they would be written in Nit code.
	#
	# ~~~
	# assert 123.inspect == "123"
	# assert 1.5.inspect == "1.5"
	# assert 0xa1u8.inspect == "0xa1u8"
	# assert 'c'.inspect == "'c'"
	# assert "asdf\n".inspect == "\"asdf\\n\""
	# ~~~
	#
	# Inspections of mutable serializable objects show their dynamic type,
	# their `object_id` and their first level attributes. When testing,
	# the `object_id` is replaced by an id unique to each call to `inspect`.
	#
	# ~~~
	# class MyClass
	#     serialize
	#
	#     var i: Int
	#     var o: nullable Object
	# end
	#
	# var class_with_null = new MyClass(123)
	# assert class_with_null.to_s == class_with_null.inspect
	# assert class_with_null.to_s == "<MyClass#0 i:123, o:null>"
	#
	# var class_with_other = new MyClass(456, class_with_null)
	# assert class_with_other.to_s == "<MyClass#0 i:456, o:<MyClass#1>>"
	#
	# var class_with_cycle = new MyClass(789)
	# class_with_cycle.o = class_with_cycle
	# assert class_with_cycle.to_s == "<MyClass#0 i:789, o:<MyClass#0>>"
	# ~~~
	#
	# Items of collections are flattened and appended to the output.
	#
	# ~~~
	# assert [1, 2, 3].inspect == "<Array[Int]#0 [1, 2, 3]>"
	#
	# var set = new HashSet[Object].from([1, 1.5, "two": Object])
	# assert set.inspect == """<HashSet[Object]#0 [1, 1.5, "two"]>"""
	#
	# var map = new Map[Int, String]
	# map[1] = "one"
	# map[2] = "two"
	# assert map.inspect == """<HashMap[Int, String]#0 {1:"one", 2:"two"}>"""
	# ~~~
	#
	# Inspections producing over 80 characters are cut short.
	#
	# ~~~
	# var long_class = new MyClass(123456789, "Some " + "very "*8 + "long string")
	# assert long_class.to_s == "<MyClass#0 i:123456789, o:\"Some very very very very very very very very long s…>"
	# ~~~
	redef fun inspect
	do
		var stream = new StringWriter
		var serializer = new InspectSerializer(stream)
		serializer.serialize self
		stream.close
		var str = stream.to_s

		# Cut long inspects
		var max_length = 80
		if str.length > max_length then
			str = str.substring(0, max_length-2) + "…>"
		end

		return str
	end

	private fun accept_inspect_serializer(v: InspectSerializer)
	do
		v.stream.write "<"

		v.stream.write class_name
		v.stream.write "#"

		var id = object_id
		if inspect_testing then id = v.cache.new_id_for(self)
		v.stream.write id.to_s

		accept_inspect_serializer_core v

		v.stream.write ">"
	end

	private fun accept_inspect_serializer_core(v: InspectSerializer)
	do v.serialize_core(self)
end
lib/serialization/inspect.nit:96,1--189,3

msgpack :: serialization_write $ Serializable
redef class Serializable

	# Serialize `self` to MessagePack bytes
	#
	# Set `plain = true` to generate standard MessagePack, without deserialization metadata.
	# Use this option if the generated MessagePack will be read by non-Nit programs.
	# Use the default, `plain = false`, if the MessagePack bytes are to be deserialized by a Nit program.
	fun serialize_msgpack(plain: nullable Bool): Bytes
	do
		var stream = new BytesWriter
		stream.serialize_msgpack(self, plain)
		stream.close
		return stream.bytes
	end

	# Hook to customize the serialization of this class to MessagePack
	#
	# This method can be refined to customize the serialization by either
	# writing pure JSON directly on the stream `v.stream` or
	# by using other services of `MsgPackSerializer`.
	#
	# Most of the time, it is better to refine the method `core_serialize_to`
	# which is used by all the serialization engines, not just MessagePack.
	protected fun accept_msgpack_serializer(v: MsgPackSerializer)
	do

		# Count the number of attributes
		var attribute_counter = new AttributeCounter
		accept_msgpack_attribute_counter attribute_counter
		var n_attributes = attribute_counter.count

		if not v.plain_msgpack then

			var n_meta_items = 2
			if n_attributes > 0 then n_meta_items += 1
			n_meta_items += msgpack_extra_array_items # obj+id, class_name, attributes

			# Metadata
			var id = v.cache.new_id_for(self)
			v.stream.write_msgpack_array n_meta_items
			v.stream.write_msgpack_ext(v.ext_typ_obj, id.to_bytes)
			v.serialize_meta_string class_name

			if n_attributes > 0 then v.stream.write_msgpack_map n_attributes
		else
			v.stream.write_msgpack_map n_attributes
		end

		v.serialize_core self
	end

	# Hook to customize the behavior of the `AttributeCounter`
	#
	# By default, this method makes `v` visits all serializable attributes.
	protected fun accept_msgpack_attribute_counter(v: AttributeCounter)
	do
		v.serialize_core self
	end

	# Hook to request a larger than usual metadata array
	#
	# Use by `SimpleCollection` and `Map` to append the items after
	# the metadata and attributes.
	protected fun msgpack_extra_array_items: Int do return 0
end
lib/msgpack/serialization_write.nit:174,1--238,3

android :: bundle $ Serializable
redef class Serializable
	# Called by `Bundle::[]=` to dynamically choose the appropriate method according
	# to the value type to store
	# Non-primitive Object (`String` excluded) will be stored as a serialized json `String`
	# Refine your class to customize this method behaviour
	protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)
	do
		sys.jni_env.push_local_frame(1)
		var serialized_string = new StringWriter
		var serializer = new JsonSerializer(serialized_string)
		serializer.serialize(self)

		bundle.put_string(key, serialized_string.to_s.to_java_string)
	end
end
lib/android/bundle/bundle.nit:670,1--684,3