Provides JSON as a mean to store graphs.

Introduced classes

class JsonGraphStore

neo4j :: JsonGraphStore

Save or load a graph using a JSON document.

Redefined classes

redef class NeoEdge

neo4j :: json_graph_store $ NeoEdge

A relationship between two nodes.
redef abstract class NeoEntity

neo4j :: json_graph_store $ NeoEntity

The fundamental units that form a graph are nodes and relationships.
redef class NeoGraph

neo4j :: json_graph_store $ NeoGraph

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

neo4j :: json_graph_store $ NeoNode

Make NeoNode Serializable.
redef abstract class NeoNodeCollection

neo4j :: json_graph_store $ NeoNodeCollection

All the nodes in a NeoGraph.

All class definitions

class JsonGraphStore

neo4j $ JsonGraphStore

Save or load a graph using a JSON document.
redef class NeoEdge

neo4j :: json_graph_store $ NeoEdge

A relationship between two nodes.
redef abstract class NeoEntity

neo4j :: json_graph_store $ NeoEntity

The fundamental units that form a graph are nodes and relationships.
redef class NeoGraph

neo4j :: json_graph_store $ NeoGraph

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

neo4j :: json_graph_store $ NeoNode

Make NeoNode Serializable.
redef abstract class NeoNodeCollection

neo4j :: json_graph_store $ NeoNodeCollection

All the nodes in a NeoGraph.
package_diagram neo4j::json_graph_store json_graph_store neo4j\>graph\> graph neo4j::json_graph_store->neo4j\>graph\> neo4j neo4j neo4j\>graph\>->neo4j progression progression neo4j\>graph\>->progression pipeline pipeline neo4j\>graph\>->pipeline ...neo4j ... ...neo4j->neo4j ...progression ... ...progression->progression ...pipeline ... ...pipeline->pipeline a_star-m a_star-m a_star-m->neo4j::json_graph_store

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 curl

curl :: curl

Data transfer powered by the native curl library
module curl_json

neo4j :: curl_json

cURL requests compatible with the JSON REST APIs.
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

json :: error

Intro JsonParseError which is exposed by all JSON reading APIs
module error

neo4j :: error

Errors thrown by the neo4j library.
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 json

json :: json

Read and write JSON formatted text using the standard serialization services
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 native_curl

curl :: native_curl

Binding of C libCurl which allow us to interact with network.
module neo4j

neo4j :: neo4j

Neo4j connector through its JSON REST API using curl.
module numeric

core :: numeric

Advanced services for Numeric types
module parser_base

parser_base :: parser_base

Simple base for hand-made parsers of all kinds
module poset

poset :: poset

Pre order sets and partial order set (ie hierarchies)
module progression

progression :: progression

Event-based interface to track the progression of an operation.
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 safe

serialization :: safe

Services for safer deserialization engines
module serialization

serialization :: serialization

General serialization services
module serialization_core

serialization :: serialization_core

Abstract services to serialize Nit objects to different formats
module serialization_read

json :: serialization_read

Services to read JSON: deserialize_json and JsonDeserializer
module serialization_write

json :: serialization_write

Services to write Nit objects to JSON strings: serialize_to_json and JsonSerializer
module sorter

core :: sorter

This module contains classes used to compare things and sorts arrays.
module static

json :: static

Static interface to read Nit objects from JSON strings
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 graph

neo4j :: graph

Provides an interface for services on a Neo4j graphs.

Children

module a_star-m

a_star-m

# Provides JSON as a mean to store graphs.
module neo4j::graph::json_graph_store

import graph

# Save or load a graph using a JSON document.
#
# The graph (or the specified part of it) is stored as a JSON object with the
# following properties:
#
# * `"nodes"`: An array with all nodes. Each node is an object with the
# following properties:
#	* `"labels"`: An array of all applied labels.
#	* `"properties"`: An object mapping each defined property to its value.
# * `"edges"`: An array with all relationships. Each relationship is an object
# with the following properties:
#	* `"type"`: The type (`String`) of the relationship.
#	* `"properties"`: An object mapping each defined property to its value.
#	* `"from"`: The local ID of the source node.
#	* `"to"`: The local ID of the destination node.
#
# ~~~nit
# import neo4j::graph::sequential_id
#
# var graph = new NeoGraph(new SequentialNodeCollection("nid"))
# var a = new NeoNode
# a.labels.add "Foo"
# a["answer"] = 42
# a["Ultimate question of"] = new JsonArray.from(["life",
#		"the Universe", "and Everything."])
# graph.nodes.register a
# var b = graph.create_node
# b.labels.add "Foo"
# b.labels.add "Bar"
# graph.edges.add new NeoEdge(a, "BAZ", b)
#
# var ostream = new StringWriter
# var store = new JsonGraphStore(graph)
# store.ostream = ostream
# store.save
# assert ostream.to_s == """{"nodes":[""" + """
# {"labels":["Foo"],"properties":{"answer":42,""" + """
# "Ultimate question of":["life","the Universe","and Everything."],""" + """
# "nid":1}},""" + """
# {"labels":["Foo","Bar"],"properties":{"nid":2}}],""" + """
# "edges":[{"type":"BAZ","properties":{},"from":1,"to":2}]}"""
#
# graph.nodes.clear
# graph.edges.clear
# store.istream = new StringReader(ostream.to_s)
# store.load
# assert 1 == graph.edges.length
# for edge in graph.edges do
#	assert "BAZ" == edge.rel_type
#	assert a.labels == edge.from.labels
#	for k, v in a.properties do assert v == edge.from.properties[k]
#	assert b.labels == edge.to.labels
#	for k, v in b.properties do assert v == edge.to.properties[k]
# end
# assert 2 == graph.nodes.length
# ~~~
class JsonGraphStore
	super GraphStore

	# The stream to use for `load`.
	var istream: nullable Reader = null is writable

	# The stream to use for `save` and `save_part`.
	var ostream: nullable Writer = null is writable

	# Use the specified `Duplex`.
	init from_io(graph: NeoGraph, iostream: Duplex) do
		init(graph)
		istream = iostream
		ostream = iostream
	end

	# Use the specified string to load the graph.
	init from_string(graph: NeoGraph, string: String) do
		init(graph)
		istream = new StringReader(string)
	end

	redef fun isolated_save do return true

	redef fun load do
		var istream = self.istream
		assert istream isa Reader
		fire_started
		graph.load_json(istream.read_all)
		fire_done
	end

	redef fun save_part(nodes, edges) do
		var ostream = self.ostream
		assert ostream isa Writer
		fire_started
		ostream.write(graph.to_json)
		fire_done
	end
end

redef class NeoGraph
	super Serializable

	# Retrieve the graph from the specified JSON document.
	#
	# For the expected format, see `JsonGraphStore`.
	#
	# ~~~nit
	# import neo4j::graph::sequential_id
	#
	# var graph = new NeoGraph(new SequentialNodeCollection("node_id"))
	# var a = new NeoNode
	# a.labels.add "Foo"
	# a["answer"] = 42
	# a["Ultimate question of"] = new JsonArray.from(["life",
	#		"the Universe", "and Everything."])
	# graph.nodes.register a
	# var b = graph.create_node
	# b.labels.add "Foo"
	# b.labels.add "Bar"
	# graph.edges.add new NeoEdge(a, "BAZ", b)
	#
	# graph = new NeoGraph.from_json(
	#		new SequentialNodeCollection("node_id"), graph.to_json)
	# assert 1 == graph.edges.length
	# for edge in graph.edges do
	#	assert "BAZ" == edge.rel_type
	#	assert a.labels == edge.from.labels
	#	for k, v in a.properties do assert v == edge.from.properties[k]
	#	assert b.labels == edge.to.labels
	#	for k, v in b.properties do assert v == edge.to.properties[k]
	# end
	# assert 2 == graph.nodes.length
	# ~~~
	init from_json(nodes: NeoNodeCollection, t: Text) do
		from_json_object(nodes, t.parse_json.as(JsonObject))
	end

	# Retrieve the graph from the specified JSON object.
	#
	# For the expected format, see `JsonGraphStore`.
	init from_json_object(nodes: NeoNodeCollection, o: JsonObject) do
		init(nodes)
		load_json_object(o)
	end

	# Retrieve a part of the graph from the specified JSON document.
	#
	# For the expected format, see `JsonGraphStore`.
	fun load_json(t: Text) do
		load_json_object(t.parse_json.as(JsonObject))
	end

	# Retrieve a part of the graph from the specified JSON object.
	#
	# For the expected format, see `JsonGraphStore`.
	fun load_json_object(o: JsonObject) do
		var json_nodes = o["nodes"].as(JsonArray)
		var nodes = self.nodes
		nodes.enlarge(nodes.length)
		for json_node in json_nodes do
			assert json_node isa JsonObject
			var node = new NeoNode.from_json_object(json_node)
			nodes.add node
		end

		var json_edges = o["edges"].as(JsonArray)
		var edges = self.edges
		if edges isa AbstractArray[NeoEdge] then edges.enlarge(edges.length)
		for json_edge in json_edges do
			assert json_edge isa JsonObject
			var from = nodes[nodes.id_from_jsonable(json_edge["from"])]
			var to = nodes[nodes.id_from_jsonable(json_edge["to"])]
			var rel_type = json_edge["type"].as(String)
			var json_properties = json_edge["properties"].as(JsonObject)
			var edge = new NeoEdge(from, rel_type, to)
			edge.properties.add_all(json_properties)
			edges.add edge
		end
	end

	redef fun accept_json_serializer(v) do
		v.stream.write "\{\"nodes\":["
		append_entities_json(nodes, v)
		v.stream.write "],\"edges\":["
		append_entities_json(edges, v)
		v.stream.write "]\}"
	end

	# Encode `self` in JSON.
	#
	# For a description of the format, see `JsonGraphStore`.
	private fun append_entities_json(entities: Collection[NeoEntity], v: JsonSerializer) do
		var i = entities.iterator
		if i.is_ok then
			i.item.append_json_for(self, v)
			i.next
			for entity in i do
				v.stream.write ","
				entity.append_json_for(self, v)
			end
		end
	end
end

redef class NeoNodeCollection
	# Convert the specified JSON value into a local ID.
	fun id_from_jsonable(id: nullable Serializable): ID_TYPE do return id.as(ID_TYPE)
end

redef class NeoEntity

	# Append the JSON representation of the entity to the specified buffer.
	fun append_json_for(graph: NeoGraph, v: JsonSerializer) is abstract
end

# Make `NeoNode` `Serializable`.
redef class NeoNode
	super Serializable

	# Retrieve the node from the specified JSON value.
	#
	# Note: Here, the `"id"` is optional and ignored.
	#
	# SEE: `JsonGraph`
	#
	#     var node = new NeoNode.from_json("""
	#     {
	#	"labels": ["foo", "Bar"],
	#	"properties": {
	#		"baz": 42
	#	}
	#     }
	#     """)
	#     assert ["foo", "Bar"] == node.labels
	#     assert 42 == node["baz"]
	init from_json(t: Text) do
		from_json_object(t.parse_json.as(JsonObject))
	end

	# Retrieve the node from the specified JSON value.
	#
	# Note: Here, the `"id"` is optional and ignored.
	#
	# SEE: `JsonGraph`
	init from_json_object(o: JsonObject) do
		init
		var labels = o["labels"].as(JsonArray)
		for lab in labels do self.labels.add(lab.as(String))
		var json_properties = o["properties"].as(JsonObject)
		properties.add_all(json_properties)
	end

	redef fun accept_json_serializer(v) do
		v.stream.write "\{\"labels\":["
		var i = labels.iterator
		if i.is_ok then
			i.item.serialize_to v
			i.next
			for lab in i do
				v.stream.write ","
				lab.serialize_to v
			end
		end
		v.stream.write "],\"properties\":"
		properties.serialize_to v
		v.stream.write "}"
	end

	redef fun to_s do return to_json

	# Append the JSON representation of the node to the specified buffer.
	redef fun append_json_for(graph, v) do
		accept_json_serializer v
	end
end

redef class NeoEdge

	# Append the JSON representation of the relationship to the specified buffer.
	#
	# Use the IDs specfied by `graph.nodes`.
	redef fun append_json_for(graph, v) do
		v.stream.write "\{\"type\":"
		rel_type.as(not null).serialize_to(v)
		v.stream.write ",\"properties\":"
		properties.serialize_to(v)
		v.stream.write ",\"from\":"
		graph.nodes.id_of(from).serialize_to(v)
		v.stream.write ",\"to\":"
		graph.nodes.id_of(to).serialize_to(v)
		v.stream.write "}"
	end
end
lib/neo4j/graph/json_graph_store.nit:11,1--306,3