Data structure to keep track of elements partitioned into disjoint subsets

var s = new DisjointSet[Int]
s.add(1)
s.add(2)
assert not s.in_same_subset(1,2)
s.union(1,2)
assert s.in_same_subset(1,2)

in_same_subset is transitive, reflexive and symmetric

s.add(3)
assert not s.in_same_subset(1,3)
s.union(3,2)
assert s.in_same_subset(1,3)

Unlike theoretical Disjoint-set data structures, the underling implementation is opaque making the traditional find method unavailable for clients. The methods in_same_subset, to_partitions, and their variations are offered instead.

Introduced properties

fun all_in_same_subset(es: Collection[E]): Bool

core :: DisjointSet :: all_in_same_subset

Are all elements of es in the same subset?
init from(other: DisjointSet[E])

core :: DisjointSet :: from

Copy constructor
fun in_same_subset(e: E, f: E): Bool

core :: DisjointSet :: in_same_subset

Are two elements in the same subset?
fun number_of_subsets: Int

core :: DisjointSet :: number_of_subsets

The number of subsets in the partition
protected fun number_of_subsets=(number_of_subsets: Int)

core :: DisjointSet :: number_of_subsets=

The number of subsets in the partition
fun to_partitions: Collection[Set[E]]

core :: DisjointSet :: to_partitions

Construct the current partitionning
fun to_subpartition(es: Collection[E]): Collection[Set[E]]

core :: DisjointSet :: to_subpartition

Construct a partitioning on es, a subset of elements
fun union(e: E, f: E)

core :: DisjointSet :: union

Combine the subsets of e and f
fun union_all(es: Collection[E])

core :: DisjointSet :: union_all

Combine the subsets of all elements of es

Redefined properties

redef type SELF: DisjointSet[E]

core $ DisjointSet :: SELF

Type of this instance, automatically specialized in every class
redef fun add(e: E)

core $ DisjointSet :: add

Add a new element in the structure.
redef fun clone: SELF

core $ DisjointSet :: clone

Shallow copy
redef fun has(e: nullable Object): Bool

core $ DisjointSet :: has

Is the element in the structure
redef fun iterator: Iterator[E]

core $ DisjointSet :: iterator

Get a new iterator on the collection.

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 CONCURRENT: ConcurrentCollection[E]

core :: Collection :: CONCURRENT

Type of the concurrent variant of this collection
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
abstract fun add(item: E)

core :: SimpleCollection :: add

Add item to this collection.
fun add_all(coll: Collection[E])

core :: SimpleCollection :: add_all

Add each item of coll.
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
fun all_in_same_subset(es: Collection[E]): Bool

core :: DisjointSet :: all_in_same_subset

Are all elements of es in the same subset?
fun as_random: Queue[E]

core :: SimpleCollection :: as_random

Return a random proxy queue where result.take is random.
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.
abstract fun clear

core :: RemovableCollection :: clear

Remove all items
abstract fun clone: SELF

core :: Cloneable :: clone

Duplicate self
fun combinations(r: Int): Collection[SequenceRead[E]]

core :: Collection :: combinations

All r-length combinations on self (in same order) without repeated elements.
fun combinations_with_replacement(r: Int): Collection[SequenceRead[E]]

core :: Collection :: combinations_with_replacement

All r-length combination on self (in same order) with repeated elements.
fun core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
fun count(item: nullable Object): Int

core :: Collection :: count

How many occurrences of item are in the collection?
fun first: E

core :: Collection :: first

Return the first item of the collection
init from(other: DisjointSet[E])

core :: DisjointSet :: from

Copy constructor
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 has(item: nullable Object): Bool

core :: Collection :: has

Is item in the collection ?
fun has_all(other: Collection[nullable Object]): Bool

core :: Collection :: has_all

Does the collection contain at least each element of other?
fun has_any(other: Collection[nullable Object]): Bool

core :: Collection :: has_any

Does the collection contain at least one element of other?
fun has_exactly(other: Collection[nullable Object]): Bool

core :: Collection :: has_exactly

Does the collection contain exactly all the elements of other?
fun has_only(item: nullable Object): Bool

core :: Collection :: has_only

Is the collection contain only item?
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun in_same_subset(e: E, f: E): Bool

core :: DisjointSet :: in_same_subset

Are two elements in the same subset?
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".
fun is_empty: Bool

core :: Collection :: is_empty

Is there no item in the collection?
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.
abstract fun iterator: Iterator[E]

core :: Collection :: iterator

Get a new iterator on the collection.
fun join(separator: nullable Text, last_separator: nullable Text): String

core :: Collection :: join

Concatenate and separate each elements with separator.
fun length: Int

core :: Collection :: length

Number of items in the collection.
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
fun not_empty: Bool

core :: Collection :: not_empty

Alias for not is_empty.
fun number_of_subsets: Int

core :: DisjointSet :: number_of_subsets

The number of subsets in the partition
protected fun number_of_subsets=(number_of_subsets: Int)

core :: DisjointSet :: number_of_subsets=

The number of subsets in the partition
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 permutations(r: Int): Collection[SequenceRead[E]]

core :: Collection :: permutations

All r-length permutations on self (all possible ordering) without repeated elements.
fun plain_to_s: String

core :: Collection :: plain_to_s

Concatenate elements without separators
fun product(r: Int): Collection[SequenceRead[E]]

core :: Collection :: product

Cartesian product, over r times self.
fun rand: E

core :: Collection :: rand

Return a random element form the collection
abstract fun remove(item: nullable Object)

core :: RemovableCollection :: remove

Remove an occurrence of item
fun remove_all(item: nullable Object)

core :: RemovableCollection :: remove_all

Remove all occurrences of item
fun sample(length: Int): Array[E]

core :: Collection :: sample

Return a new array made of (at most) length elements randomly chosen.
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_a: Array[E]

core :: Collection :: to_a

Build a new array from a collection
abstract fun to_concurrent: CONCURRENT

core :: Collection :: to_concurrent

Wraps self in a thread-safe collection
fun to_counter: Counter[E]

core :: Collection :: to_counter

Create and fill up a counter with the elements of `self.
fun to_curlslist: CURLSList

core :: Collection :: to_curlslist

Convert Collection[String] to CURLSList
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_partitions: Collection[Set[E]]

core :: DisjointSet :: to_partitions

Construct the current partitionning
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.
fun to_shuffle: Array[E]

core :: Collection :: to_shuffle

Return a new array made of elements in a random order.
fun to_subpartition(es: Collection[E]): Collection[Set[E]]

core :: DisjointSet :: to_subpartition

Construct a partitioning on es, a subset of elements
fun union(e: E, f: E)

core :: DisjointSet :: union

Combine the subsets of e and f
fun union_all(es: Collection[E])

core :: DisjointSet :: union_all

Combine the subsets of all elements of es
package_diagram core::DisjointSet DisjointSet core::SimpleCollection SimpleCollection core::DisjointSet->core::SimpleCollection core::Cloneable Cloneable core::DisjointSet->core::Cloneable serialization::Serializable Serializable core::SimpleCollection->serialization::Serializable core::RemovableCollection RemovableCollection core::SimpleCollection->core::RemovableCollection core::Object Object core::Cloneable->core::Object ...serialization::Serializable ... ...serialization::Serializable->serialization::Serializable ...core::RemovableCollection ... ...core::RemovableCollection->core::RemovableCollection ...core::Object ... ...core::Object->core::Object

Ancestors

interface Collection[E: nullable Object]

core :: Collection

The root of the collection hierarchy.
interface Object

core :: Object

The root of the class hierarchy.
interface RemovableCollection[E: nullable Object]

core :: RemovableCollection

Items can be removed from this collection
interface Serializable

serialization :: Serializable

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

Parents

interface Cloneable

core :: Cloneable

Something that can be cloned
interface SimpleCollection[E: nullable Object]

core :: SimpleCollection

Items can be added to these collections.

Class definitions

core $ DisjointSet
# Data structure to keep track of elements partitioned into disjoint subsets
#
#     var s = new DisjointSet[Int]
#     s.add(1)
#     s.add(2)
#     assert not s.in_same_subset(1,2)
#     s.union(1,2)
#     assert s.in_same_subset(1,2)
#
# `in_same_subset` is transitive, reflexive and symmetric
#
#     s.add(3)
#     assert not s.in_same_subset(1,3)
#     s.union(3,2)
#     assert s.in_same_subset(1,3)
#
# Unlike theoretical Disjoint-set data structures, the underling implementation is opaque
# making the traditional `find` method unavailable for clients.
# The methods `in_same_subset`, `to_partitions`, and their variations are offered instead.
class DisjointSet[E]
	super SimpleCollection[E]
	super Cloneable

	# The node in the hiearchical structure for each element
	private var nodes = new HashMap[E, DisjointSetNode]

	# Copy constructor
	init from(other: DisjointSet[E])
	do
		# Associate a root node in other to the associated root node in self
		var map = new HashMap[DisjointSetNode, DisjointSetNode]
		for e, v in other.nodes do
			# Create the associated node
			var n2 = new DisjointSetNode
			nodes[e] = n2

			# Get the root node in other and the associated one in self
			var p = other.find(e)
			var p2 = map.get_or_null(p)
			if p2 == null then
				# if no associated root node, then a new subset is created
				map[p] = n2.parent
				number_of_subsets += 1
			else
				# else attach the new node to the subset of the root node
				n2.parent = p2
			end
		end
	end

	# Shallow copy
	#
	#     var s = new DisjointSet[Int]
	#     s.add_all([1,2,3,4,5])
	#     s.union_all([1,4,5])
	#     var s2 = s.clone
	#     assert s2.number_of_subsets == 3
	#     assert s2.all_in_same_subset([1,4,5]) == true
	#     assert s2.in_same_subset(1,2) == false
	redef fun clone do return new DisjointSet[E].from(self)

	# The number of subsets in the partition
	#
	#     var s = new DisjointSet[Int]
	#     s.add_all([1,2,3,4,5])
	#     assert s.number_of_subsets == 5
	#     s.union_all([1,4,5])
	#     assert s.number_of_subsets == 3
	#     s.union(4,5)
	#     assert s.number_of_subsets == 3
	var number_of_subsets: Int = 0

	# Get the root node of an element
	# require: `has(e)`
	private fun find(e:E): DisjointSetNode
	do
		assert nodes.has_key(e)
		var ne = nodes[e]
		if ne.parent == ne then return ne
		var res = nfind(ne)
		nodes[e] = res
		return res
	end

	# Get the root node of a node
	# Use *path compression* to flatten the structure
	# ENSURE: `result.parent == result`
	private fun nfind(ne: DisjointSetNode): DisjointSetNode
	do
		var nf = ne.parent
		if nf == ne then return ne
		var ng = nfind(nf)
		ne.parent = ng
		return ng
	end

	# Is the element in the structure
	#
	#     var s = new DisjointSet[Int]
	#     assert not s.has(1)
	#     s.add(1)
	#     assert s.has(1)
	#     assert not s.has(2)
	redef fun has(e) do
		return nodes.has_key(e)
	end

	redef fun iterator do return nodes.keys.iterator

	# Add a new element in the structure.
	# Initially it is in its own disjoint subset
	#
	# ENSURE: `has(e)`
	redef fun add(e) do
		if nodes.has_key(e) then return
		var ne = new DisjointSetNode
		nodes[e] = ne
		number_of_subsets += 1
	end

	# Are two elements in the same subset?
	fun in_same_subset(e,f:E): Bool
	do
		return e == f or find(e) == find(f)
	end

	# Are all elements of `es` in the same subset?
	#
	#     var s = new DisjointSet[Int]
	#     s.add_all([1,2,3,4,5,6])
	#     s.union_all([1,2,3])
	#     assert not s.all_in_same_subset([2,3,4])
	#     s.union_all([1,4,5])
	#     assert s.all_in_same_subset([2,3,4])
	fun all_in_same_subset(es: Collection[E]): Bool
	do
		if es.is_empty then return true
		var nf = find(es.first)
		for e in es do
			var ne = find(e)
			if ne != nf then return false
		end
		return true
	end

	# Construct the current partitionning
	#
	#     var s = new DisjointSet[Int]
	#     s.add_all([1,2,3,4,5,6])
	#     s.union(1,2)
	#     s.union(1,3)
	#     s.union(4,5)
	#     var p = s.to_partitions
	#     assert p.length == 3
	fun to_partitions: Collection[Set[E]]
	do
		return to_subpartition(self)
	end

	# Construct a partitioning on `es`, a subset of elements
	#
	#     var s = new DisjointSet[Int]
	#     s.add_all([1,2,3,4,5,6])
	#     s.union(1,2)
	#     s.union(1,3)
	#     s.union(4,5)
	#     var p = s.to_subpartition([1,2,4])
	#     assert p.length == 2
	fun to_subpartition(es: Collection[E]): Collection[Set[E]]
	do
		var map = new HashMap[DisjointSetNode, Set[E]]
		for e in es do
			var ne = find(e)
			var set = map.get_or_null(ne)
			if set == null then
				set = new HashSet[E]
				map[ne] = set
			end
			set.add(e)
		end
		return map.values
	end

	# Combine the subsets of `e` and `f`
	# ENSURE: `in_same_subset(e,f)`
	fun union(e,f:E)
	do
		var ne = find(e)
		var nf = find(f)
		if ne == nf then return

		# merge them using *union by rank*
		# attach the smaller tree to the root of the deeper tree
		var er = ne.rank
		var fr = nf.rank
		if er < fr then
			ne.parent = nf
			nodes[e] = nf
		else
			nf.parent = ne
			nodes[f] = ne
			if er == fr then
				# The only case where the deep is increased is when both are equals
				ne.rank = er+1
			end
		end
		number_of_subsets -= 1
	end

	# Combine the subsets of all elements of `es`
	# ENSURE: `all_in_same_subset(cs)`
	fun union_all(es:Collection[E])
	do
		if es.is_empty then return
		var f = es.first
		for e in es do union(e,f)
	end
end
lib/core/collection/union_find.nit:16,1--233,3