MapRead are abstract associative collections: key -> item.

Introduced properties

abstract fun [](key: nullable Object): V

core :: MapRead :: []

Get the item at key
fun filter_keys(keys: Collection[nullable Object]): Array[K]

core :: MapRead :: filter_keys

Return all elements of keys that have a value.
fun get_or_default(key: nullable Object, default: V): V

core :: MapRead :: get_or_default

Get the item at key or return default if not in map
fun get_or_null(key: nullable Object): nullable V

core :: MapRead :: get_or_null

Get the item at key or null if key is not in the map.
fun has_key(key: nullable Object): Bool

core :: MapRead :: has_key

Is there an item associated with key?
abstract fun is_empty: Bool

core :: MapRead :: is_empty

Is there no item in the collection?
abstract fun iterator: MapIterator[K, V]

core :: MapRead :: iterator

Get a new iterator on the map.
abstract fun keys: Collection[K]

core :: MapRead :: keys

Return the point of view of self on the keys only.
fun keys_sorted_by_values(comparator: Comparator): Array[K]

core :: MapRead :: keys_sorted_by_values

Return an array of all keys sorted with their values using comparator.
abstract fun length: Int

core :: MapRead :: length

Number of items in the collection.
fun lookup_all_values(pe: POSetElement[K]): Set[V]

core :: MapRead :: lookup_all_values

Search all the values in pe.greaters.
fun lookup_values(pe: POSetElement[K]): Set[V]

core :: MapRead :: lookup_values

Combine the values in pe.greaters from the most smaller elements that have a value.
fun not_empty: Bool

core :: MapRead :: not_empty

Alias for not is_empty.
protected fun provide_default_value(key: nullable Object): V

core :: MapRead :: provide_default_value

Called by the underling implementation of [] to provide a default value when a key has no value
fun to_map_comparator(comparator: Comparator): MapComparator[K, V]

core :: MapRead :: to_map_comparator

A comparator that compares things with their values in self.
abstract fun values: Collection[V]

core :: MapRead :: values

Return the point of view of self on the values only.
fun values_sorted_by_key(comparator: Comparator): Array[V]

core :: MapRead :: values_sorted_by_key

Return an array of all values sorted with their keys using comparator.

Redefined properties

redef fun ==(other: nullable Object): Bool

core $ MapRead :: ==

Does self and other have the same keys associated with the same values?
redef type SELF: MapRead[K, V]

core $ MapRead :: SELF

Type of this instance, automatically specialized in every class
redef fun hash: Int

core $ MapRead :: hash

A hashcode based on the hashcode of the keys and the values.

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
abstract fun [](key: nullable Object): V

core :: MapRead :: []

Get the item at key
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 filter_keys(keys: Collection[nullable Object]): Array[K]

core :: MapRead :: filter_keys

Return all elements of keys that have a value.
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun get_or_default(key: nullable Object, default: V): V

core :: MapRead :: get_or_default

Get the item at key or return default if not in map
fun get_or_null(key: nullable Object): nullable V

core :: MapRead :: get_or_null

Get the item at key or null if key is not in the map.
fun has_key(key: nullable Object): Bool

core :: MapRead :: has_key

Is there an item associated with key?
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".
abstract fun is_empty: Bool

core :: MapRead :: 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: MapIterator[K, V]

core :: MapRead :: iterator

Get a new iterator on the map.
abstract fun keys: Collection[K]

core :: MapRead :: keys

Return the point of view of self on the keys only.
fun keys_sorted_by_values(comparator: Comparator): Array[K]

core :: MapRead :: keys_sorted_by_values

Return an array of all keys sorted with their values using comparator.
abstract fun length: Int

core :: MapRead :: length

Number of items in the collection.
fun lookup_all_values(pe: POSetElement[K]): Set[V]

core :: MapRead :: lookup_all_values

Search all the values in pe.greaters.
fun lookup_values(pe: POSetElement[K]): Set[V]

core :: MapRead :: lookup_values

Combine the values in pe.greaters from the most smaller elements that have a value.
fun not_empty: Bool

core :: MapRead :: not_empty

Alias for not is_empty.
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).
protected fun provide_default_value(key: nullable Object): V

core :: MapRead :: provide_default_value

Called by the underling implementation of [] to provide a default value when a key has no value
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
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_map_comparator(comparator: Comparator): MapComparator[K, V]

core :: MapRead :: to_map_comparator

A comparator that compares things with their values in self.
fun to_s: String

core :: Object :: to_s

User readable representation of self.
abstract fun values: Collection[V]

core :: MapRead :: values

Return the point of view of self on the values only.
fun values_sorted_by_key(comparator: Comparator): Array[V]

core :: MapRead :: values_sorted_by_key

Return an array of all values sorted with their keys using comparator.
package_diagram core::MapRead MapRead core::Object Object core::MapRead->core::Object core::Map Map core::Map->core::MapRead json::JsonMapRead JsonMapRead json::JsonMapRead->core::MapRead core::CoupleMap CoupleMap core::CoupleMap->core::Map core::HashMap HashMap core::HashMap->core::Map trees::TreeMap TreeMap trees::TreeMap->core::Map counter::Counter Counter counter::Counter->core::Map trees::Trie Trie trees::Trie->core::Map core::CoupleMap... ... core::CoupleMap...->core::CoupleMap core::HashMap... ... core::HashMap...->core::HashMap trees::TreeMap... ... trees::TreeMap...->trees::TreeMap counter::Counter... ... counter::Counter...->counter::Counter trees::Trie... ... trees::Trie...->trees::Trie json::JsonObject JsonObject json::JsonObject->json::JsonMapRead json::JsonObject... ... json::JsonObject...->json::JsonObject

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

interface JsonMapRead[K: String, V: nullable Serializable]

json :: JsonMapRead

A map that can be translated into a JSON object.
interface Map[K: nullable Object, V: nullable Object]

core :: Map

Maps are associative collections: key -> item.

Descendants

class ArrayMap[K: nullable Object, E: nullable Object]

core :: ArrayMap

Associative arrays implemented with an array of (key, value) pairs.
class AttributeMap

dot :: AttributeMap

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

gamnit :: AttributeMap

Map to organize Attribute instances by their name
class BinTreeMap[K: Comparable, E: nullable Object]

trees :: BinTreeMap

Binary Tree Map
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 DefaultMap[K: nullable Object, V: nullable Object]

more_collections :: DefaultMap

A map with a default value.
class HashMap[K: nullable Object, V: nullable Object]

core :: HashMap

A Map implemented with a hash table.
class IniFile

ini :: IniFile

Read and write INI configuration files
class IniSection

ini :: IniSection

A section in a IniFile
class JsonObject

json :: JsonObject

A JSON Object.
class MongoGroup

mongodb :: MongoGroup

Mongo pipeline group stage
class MongoMatch

mongodb :: MongoMatch

A basic match query
class MultiHashMap[K: nullable Object, V: nullable Object]

more_collections :: MultiHashMap

Simple way to store an HashMap[K, Array[V]]
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 RBTreeMap[K: Comparable, E: nullable Object]

trees :: RBTreeMap

Red-Black Tree Map
abstract class ShaderVariableMap[A: ShaderVariable]

gamnit :: ShaderVariableMap

Map to organize ShaderVariable instances by their name
class StrictHashMap[K: nullable Object, V: nullable Object]

serialization :: StrictHashMap

Maps instances to a value, uses is_same_serialized and serialization_hash.
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 UniformMap

gamnit :: UniformMap

Map to organize Uniform instances by their name
class Vector

vsm :: Vector

A n-dimensions vector

Class definitions

core $ MapRead
# MapRead are abstract associative collections: `key` -> `item`.
interface MapRead[K, V]
	# Get the item at `key`
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x["four"] == 4
	#     # assert x["five"] #=> abort
	#
	# If the key is not in the map, `provide_default_value` is called (that aborts by default)
	# See `get_or_null` and `get_or_default` for safe variations.
	fun [](key: nullable Object): V is abstract

	# Get the item at `key` or null if `key` is not in the map.
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x.get_or_null("four") == 4
	#     assert x.get_or_null("five") == null
	#
	# Note: use `has_key` and `[]` if you need the distinction between a key associated with null, and no key.
	fun get_or_null(key: nullable Object): nullable V
	do
		if has_key(key) then return self[key]
		return null
	end

	# Get the item at `key` or return `default` if not in map
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x.get_or_default("four", 40) == 4
	#     assert x.get_or_default("five", 50) == 50
	#
	fun get_or_default(key: nullable Object, default: V): V
	do
		if has_key(key) then return self[key]
		return default
	end

	# Is there an item associated with `key`?
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x.has_key("four") == true
	#     assert x.has_key("five") == false
	#
	# By default it is a synonymous to `keys.has` but could be redefined with a direct implementation.
	fun has_key(key: nullable Object): Bool do return self.keys.has(key)

	# Get a new iterator on the map.
	fun iterator: MapIterator[K, V] is abstract

	# Return the point of view of self on the values only.
	# Note that `self` and `values` are views on the same data;
	# therefore any modification of one is visible on the other.
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x.values.has(4) == true
	#     assert x.values.has(5) == false
	fun values: Collection[V] is abstract

	# Return the point of view of self on the keys only.
	# Note that `self` and `keys` are views on the same data;
	# therefore any modification of one is visible on the other.
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x.keys.has("four") == true
	#     assert x.keys.has("five") == false
	fun keys: Collection[K] is abstract

	# Is there no item in the collection?
	#
	#     var x = new HashMap[String, Int]
	#     assert x.is_empty  == true
	#     x["four"] = 4
	#     assert x.is_empty  == false
	fun is_empty: Bool is abstract

	# Alias for `not is_empty`.
	#
	# Some people prefer to have conditions grammatically easier to read.
	#
	#     var map = new HashMap[String, Int]
	#     assert map.not_empty == false
	#     map["one"] = 1
	#     assert map.not_empty == true
	fun not_empty: Bool do return not self.is_empty

	# Number of items in the collection.
	#
	#     var x = new HashMap[String, Int]
	#     assert x.length  == 0
	#     x["four"] = 4
	#     assert x.length  == 1
	#     x["five"] = 5
	#     assert x.length  == 2
	fun length: Int is abstract

	# Called by the underling implementation of `[]` to provide a default value when a `key` has no value
	# By default the behavior is to abort.
	#
	# Note: the value is returned *as is*, implementations may want to store the value in the map before returning it
	# @toimplement
	protected fun provide_default_value(key: nullable Object): V do abort

	# Does `self` and `other` have the same keys associated with the same values?
	#
	# ~~~
	# var a = new HashMap[String, Int]
	# var b = new ArrayMap[Object, Numeric]
	# assert a == b
	# a["one"] = 1
	# assert a != b
	# b["one"] = 1
	# assert a == b
	# b["one"] = 2
	# assert a != b
	# ~~~
	redef fun ==(other)
	do
		if not other isa MapRead[nullable Object, nullable Object] then return false
		if other.length != self.length then return false
		for k, v in self do
			if not other.has_key(k) then return false
			if other[k] != v then return false
		end
		return true
	end

	# A hashcode based on the hashcode of the keys and the values.
	#
	# ~~~
	# var a = new HashMap[String, Int]
	# var b = new ArrayMap[Object, Numeric]
	# a["one"] = 1
	# b["one"] = 1
	# assert a.hash == b.hash
	# ~~~
	redef fun hash
	do
		var res = length
		for k, v in self do
			if k != null then res += k.hash * 7
			if v != null then res += v.hash * 11
		end
		return res
	end
end
lib/core/collection/abstract_collection.nit:532,1--682,3

core :: sorter $ MapRead
redef class MapRead[K,V]
	# Return an array of all values sorted with their keys using `comparator`.
	#
	# ~~~
	# var map = new HashMap[Int, String]
	# map[10] = "ten"
	# map[2]  = "two"
	# map[1]  = "one"
	# assert map.values_sorted_by_key(default_comparator) == ["one", "two", "ten"]
	# assert map.values_sorted_by_key(alpha_comparator) == ["one", "ten", "two"]
	# ~~~
	fun values_sorted_by_key(comparator: Comparator): Array[V]
	do
		var keys = self.keys.to_a
		comparator.sort(keys)
		return [for k in keys do self[k]]
	end

	# Return an array of all keys sorted with their values using `comparator`.
	#
	# ~~~
	# var map = new HashMap[String, Int]
	# map["ten"] = 10
	# map["two"] = 2
	# map["one"] = 1
	# assert map.keys_sorted_by_values(default_comparator) == ["one", "two", "ten"]
	# assert map.keys_sorted_by_values(alpha_comparator) == ["one", "ten", "two"]
	# ~~~
	#
	# See: `to_map_comparator` to get the comparator used internally.
	fun keys_sorted_by_values(comparator: Comparator): Array[K]
	do
		var keys = self.keys.to_a
		var map_cmp = to_map_comparator(comparator)
		map_cmp.sort(keys)
		return keys
	end

	# A comparator that compares things with their values in self.
	#
	# See `MapComparator` for details.
	fun to_map_comparator(comparator: Comparator): MapComparator[K, V] do return new MapComparator[K,V](self, comparator)
end
lib/core/collection/sorter.nit:262,1--304,3

poset :: poset $ MapRead
redef class MapRead[K, V]
	# Return all elements of `keys` that have a value.
	#
	# ~~~
	# var map = new Map[String, String]
	# map["A"] = "a"
	# map["B"] = "b"
	# map["C"] = "c"
	#
	# assert map.filter_keys(["B"]) == ["B"]
	# assert map.filter_keys(["A", "Z", "C"]) == ["A", "C"]
	# assert map.filter_keys(["X", "Y", "Z"]).is_empty
	# ~~~
	#
	# `has_key` is used to filter.
	fun filter_keys(keys: Collection[nullable Object]): Array[K]
	do
		var res = new Array[K]
		for e in keys do
			if has_key(e) then res.add e
		end
		return res
	end

	# Search all the values in `pe.greaters`.
	#
	# Elements without values are ignored.
	#
	# Basically, values defined in all greater elements of `pe` are inherited.
	#
	# ~~~
	# var pos = new POSet[String]
	# pos.add_chain(["E", "D", "C", "B", "A"])
	# pos.add_chain(["D", "X", "B"])
	#
	# var map = new HashMap[String, String]
	# map["A"] = "a"
	# map["C"] = "c"
	# map["X"] = "x"
	# map["E"] = "e"
	#
	# assert map.lookup_all_values(pos["B"]).has_exactly(["a"])
	# assert map.lookup_all_values(pos["C"]).has_exactly(["a", "c"])
	# assert map.lookup_all_values(pos["D"]).has_exactly(["a", "c", "x"])
	# ~~~
	fun lookup_all_values(pe: POSetElement[K]): Set[V]
	do
		var res = new Set[V]
		for k in filter_keys(pe.greaters) do res.add self[k]
		return res
	end

	# Combine the values in `pe.greaters` from the most smaller elements that have a value.
	#
	# Elements without values are ignored.
	#
	# Basically, values defined in nearest greater elements of `pe` are inherited.
	#
	# ~~~
	# var pos = new POSet[String]
	# pos.add_chain(["E", "D", "C", "B", "A"])
	# pos.add_chain(["D", "X", "B"])
	#
	# var map = new HashMap[String, String]
	# map["A"] = "a"
	# map["C"] = "c"
	# map["X"] = "x"
	# map["E"] = "e"
	#
	# assert map.lookup_values(pos["B"]).has_exactly(["a"])
	# assert map.lookup_values(pos["C"]).has_exactly(["c"])
	# assert map.lookup_values(pos["D"]).has_exactly(["c", "x"])
	# ~~~
	fun lookup_values(pe: POSetElement[K]): Set[V]
	do
		var res = new Set[V]
		for k in pe.poset.select_smallest(filter_keys(pe.greaters)) do res.add self[k]
		return res
	end
end
lib/poset/poset.nit:733,1--812,3