key -> item.The main operator over maps is [].
var map: Map[String, Int] = new ArrayMap[String, Int]
# ...
map["one"] = 1      # Associate 'one' to '1'
map["two"] = 2      # Associate 'two' to '2'
assert map["one"]             ==  1
assert map["two"]             ==  2Instances of maps can be used with the for structure
for key, value in map do
    assert (key == "one" and value == 1) or (key == "two" and value == 2)
endThe keys and values in the map can also be manipulated directly with the keys and values methods.
assert map.keys.has("one")    ==  true
assert map.keys.has("tree")   ==  false
assert map.values.has(1)      ==  true
assert map.values.has(3)      ==  falsejson :: serialization_write $ Map :: accept_json_serializer
Refinable service to customize the serialization of this class to JSONmsgpack :: serialization_write $ Map :: accept_msgpack_serializer
Hook to customize the serialization of this class to MessagePackjson :: serialization_read $ Map :: from_deserializer
Create an instance of this class from thedeserializer
			msgpack :: serialization_read $ Map :: from_deserializer
Create an instance of this class from thedeserializer
			msgpack :: serialization_write $ Map :: msgpack_extra_array_items
Hook to request a larger than usual metadata arrayserialization :: Serializable :: accept_json_serializer
Refinable service to customize the serialization of this class to JSONserialization :: Serializable :: accept_msgpack_attribute_counter
Hook to customize the behavior of theAttributeCounter
			serialization :: Serializable :: accept_msgpack_serializer
Hook to customize the serialization of this class to MessagePackserialization :: Serializable :: add_to_bundle
Called by[]= to dynamically choose the appropriate method according
			core :: Object :: class_factory
Implementation used byget_class to create the specific class.
			serialization :: Serializable :: core_serialize_to
Actual serialization ofself to serializer
			core :: Object :: defaultinit
core :: MapRead :: defaultinit
core :: Map :: defaultinit
core :: MapRead :: filter_keys
Return all elements ofkeys that have a value.
			serialization :: Serializable :: from_deserializer
Create an instance of this class from thedeserializer
			core :: MapRead :: get_or_default
Get the item atkey or return default if not in map
			core :: MapRead :: get_or_null
Get the item atkey or null if key is not in the map.
			core :: Object :: is_same_instance
Return true ifself and other are the same instance (i.e. same identity).
			core :: Object :: is_same_serialized
Isself the same as other in a serialization context?
			core :: Object :: is_same_type
Return true ifself and other have the same dynamic type.
			core :: MapRead :: keys_sorted_by_values
Return an array of all keys sorted with their values usingcomparator.
			core :: MapRead :: lookup_all_values
Search all the values inpe.greaters.
			core :: MapRead :: lookup_values
Combine the values inpe.greaters from the most smaller elements that have a value.
			serialization :: Serializable :: msgpack_extra_array_items
Hook to request a larger than usual metadata arraycore :: Object :: output_class_name
Display class name on stdout (debug only).core :: MapRead :: provide_default_value
Called by the underling implementation of[] to provide a default value when a key has no value
			serialization :: Serializable :: serialize_msgpack
Serializeself to MessagePack bytes
			serialization :: Serializable :: serialize_to
Serializeself to serializer
			serialization :: Serializable :: serialize_to_json
Serializeself to JSON
			core :: MapRead :: to_map_comparator
A comparator that compares things with their values in self.serialization :: Serializable :: to_pretty_json
Serializeself to plain pretty JSON
			core :: MapRead :: values_sorted_by_key
Return an array of all values sorted with their keys usingcomparator.
			Serializer::serialize
			dot :: AttributeMap
Map of graph/node/edge attribute that can be rendered to dot.more_collections :: DefaultMap
A map with a default value.more_collections :: MultiHashMap
Simple way to store anHashMap[K, Array[V]]
			ShaderVariable instances by their name
			serialization :: StrictHashMap
Maps instances to a value, usesis_same_serialized and serialization_hash.
			
# Maps are associative collections: `key` -> `item`.
#
# The main operator over maps is [].
#
#     var map: Map[String, Int] = new ArrayMap[String, Int]
#     # ...
#     map["one"] = 1      # Associate 'one' to '1'
#     map["two"] = 2      # Associate 'two' to '2'
#     assert map["one"]             ==  1
#     assert map["two"]             ==  2
#
# Instances of maps can be used with the for structure
#
#     for key, value in map do
#         assert (key == "one" and value == 1) or (key == "two" and value == 2)
#     end
#
# The keys and values in the map can also be manipulated directly with the `keys` and `values` methods.
#
#     assert map.keys.has("one")    ==  true
#     assert map.keys.has("tree")   ==  false
#     assert map.values.has(1)      ==  true
#     assert map.values.has(3)      ==  false
#
interface Map[K, V]
	super MapRead[K, V]
	# Set the `value` at `key`.
	#
	# Values can then get retrieved with `[]`.
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     assert x["four"]   == 4
	#
	# If the key was associated with a value, this old value is discarded
	# and replaced with the new one.
	#
	#     x["four"] = 40
	#     assert x["four"]         == 40
	#     assert x.values.has(4)   == false
	#
	fun []=(key: K, value: V) is abstract
	# Add each (key,value) of `map` into `self`.
	# If a same key exists in `map` and `self`, then the value in self is discarded.
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     x["five"] = 5
	#     var y = new HashMap[String, Int]
	#     y["four"] = 40
	#     y["nine"] = 90
	#     x.add_all y
	#     assert x["four"]  == 40
	#     assert x["five"]  == 5
	#     assert x["nine"]  == 90
	fun add_all(map: MapRead[K, V])
	do
		var i = map.iterator
		while i.is_ok do
			self[i.key] = i.item
			i.next
		end
	end
	# Alias for `add_all`
	fun recover_with(map: MapRead[K, V]) is deprecated do add_all(map)
	# Remove all items
	#
	#     var x = new HashMap[String, Int]
	#     x["four"] = 4
	#     x.clear
	#     assert x.keys.has("four") == false
	#
	# ENSURE `is_empty`
	fun clear is abstract
	redef fun values: RemovableCollection[V] is abstract
	redef fun keys: RemovableCollection[K] is abstract
end
					lib/core/collection/abstract_collection.nit:684,1--766,3
				
redef class Map[K,V]
	# Concatenate couples of key value.
	# Key and value are separated by `couple_sep`.
	# Couples are separated by `sep`.
	#
	# ~~~
	# var m = new HashMap[Int, String]
	# m[1] = "one"
	# m[10] = "ten"
	# assert m.join("; ", "=") == "1=one; 10=ten"
	# ~~~
	fun join(sep, couple_sep: String): String is abstract
end
					lib/core/text/abstract_text.nit:2414,1--2426,3
				
redef class Map[K,V]
	redef fun join(sep, couple_sep)
	do
		if is_empty then return ""
		var s = new Buffer # Result
		# Concat first item
		var i = iterator
		var k = i.key
		var e = i.item
		s.append("{k or else "<null>"}{couple_sep}{e or else "<null>"}")
		# Concat other _items
		i.next
		while i.is_ok do
			s.append(sep)
			k = i.key
			e = i.item
			s.append("{k or else "<null>"}{couple_sep}{e or else "<null>"}")
			i.next
		end
		return s.to_s
	end
end
					lib/core/text/flat.nit:1570,1--1594,3
				
redef class Map[K, V] super Serializable end
					lib/serialization/serialization_core.nit:266,1--44
				
redef class Map[K, V]
	redef fun accept_json_serializer(v)
	do
		# Register as pseudo object
		var id = v.cache.new_id_for(self)
		v.stream.write "\{"
		v.indent_level += 1
		if v.plain_json then
			var first = true
			for key, val in self do
				if not first then
					v.stream.write ","
				else first = false
				v.new_line_and_indent
				var k = key or else "null"
				k.to_s.accept_json_serializer v
				v.stream.write ":"
				if v.pretty_json then v.stream.write " "
				if not v.try_to_serialize(val) then
					assert val != null # null would have been serialized
					v.warn("element of type {val.class_name} is not serializable.")
					v.stream.write "null"
				end
			end
		else
			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 """", "__length": """
			v.stream.write length.to_s
			v.stream.write ","
			v.new_line_and_indent
			v.stream.write """"__keys": """
			keys.serialize_to_pure_json v
			v.stream.write ","
			v.new_line_and_indent
			v.stream.write """"__values": """
			values.serialize_to_pure_json v
			core_serialize_to v
		end
		v.indent_level -= 1
		v.new_line_and_indent
		v.stream.write "\}"
	end
end
					lib/json/serialization_write.nit:360,1--413,3
				
redef class Map[K, V]
	redef fun accept_inspect_serializer_core(v)
	do
		v.stream.write " \{"
		var first = true
		for key, val in self do
			if not first then
				v.stream.write ", "
			else first = false
			if not v.try_to_serialize(key) then
				assert key != null
				v.stream.write key.inspect
			end
			v.stream.write ":"
			if not v.try_to_serialize(val) then
				assert val != null
				v.stream.write val.inspect
			end
		end
		v.stream.write "\}"
	end
end
					lib/serialization/inspect.nit:268,1--294,3
				
redef class Map[K, V]
	redef fun accept_msgpack_serializer(v)
	do
		if not v.plain_msgpack then
			# Add metadata and other attributes
			super
		end
		# Header
		v.stream.write_msgpack_map keys.length
		# Key / values, alternating
		for key, val in self do
			if not v.try_to_serialize(key) then
				assert val != null # null would have been serialized
				v.warn "element of type {val.class_name} is not serializable."
				v.stream.write_msgpack_null
			end
			if not v.try_to_serialize(val) then
				assert val != null # null would have been serialized
				v.warn "element of type {val.class_name} is not serializable."
				v.stream.write_msgpack_null
			end
		end
	end
	redef fun msgpack_extra_array_items do return 1
end
					lib/msgpack/serialization_write.nit:321,1--349,3
				
redef class Map[K, V]
	redef init from_deserializer(v)
	do
		super
		if v isa JsonDeserializer then
			v.notify_of_creation self
			init
			var keys_type_name = (new GetName[K]).to_s
			var values_type_name = (new GetName[V]).to_s
			var length = v.deserialize_attribute("__length")
			var keys = v.path.last.get_or_null("__keys")
			var values = v.path.last.get_or_null("__values")
			if keys == null and values == null then
				# Fallback to a plain object
				for key, value_src in v.path.last do
					var value = v.convert_object(value_src, values_type_name)
					if not key isa K then
						v.errors.add new AttributeTypeError(self, "keys", key, keys_type_name)
						continue
					end
					if not value isa V then
						v.errors.add new AttributeTypeError(self, "values", value, values_type_name)
						continue
					end
					self[key] = value
				end
				return
			end
			# Length is optional
			if length == null and keys isa SequenceRead[nullable Object] then length = keys.length
			# Consistency check
			if not length isa Int or length < 0 or
			   not keys isa SequenceRead[nullable Object] or
			   not values isa SequenceRead[nullable Object] or
			   keys.length != values.length or length != keys.length then
				# If there is nothing or length == 0, we consider that it is an empty Map.
				if (length != null and length != 0) or keys != null or values != null then
					v.errors.add new Error("Deserialization Error: invalid format in {self.class_name}")
				end
				return
			end
			# First, convert all keys to follow the order of the serialization
			var converted_keys = new Array[K]
			for i in length.times do
				var key = v.convert_object(keys[i], keys_type_name)
				if not key isa K then
					v.errors.add new AttributeTypeError(self, "keys", key, keys_type_name)
					continue
				end
				converted_keys.add key
			end
			# Then convert the values and build the map
			for i in length.times do
				var key = converted_keys[i]
				var value = v.convert_object(values[i], values_type_name)
				if not value isa V then
					v.errors.add new AttributeTypeError(self, "values", value, values_type_name)
					continue
				end
				if has_key(key) then
					v.errors.add new Error("Deserialization Error: duplicated key '{key or else "null"}' in {self.class_name}, previous value overwritten")
				end
				self[key] = value
			end
		end
	end
end
					lib/json/serialization_read.nit:419,1--503,3
				
redef class Map[K, V]
	redef init from_deserializer(v)
	do
		super
		if v isa MsgPackDeserializer then
			v.notify_of_creation self
			init
			var open_object = v.path_arrays.last
			var msgpack_items
			if open_object != null then
				# Metadata available
				msgpack_items = open_object.last
			else
				msgpack_items = v.path.last
			end
			if not msgpack_items isa Map[nullable Object, nullable Object] then
				v.errors.add new Error("Deserialization Error: no key/values in source of `{class_name}`")
				return
			end
			var keys_type_name = (new GetName[K]).to_s
			var values_type_name = (new GetName[V]).to_s
			for key_src, value_src in msgpack_items do
				var key = v.convert_object(key_src, keys_type_name)
				if not key isa K then
					v.errors.add new AttributeTypeError(self, "keys", key, keys_type_name)
					continue
				end
				var value = v.convert_object(value_src, values_type_name)
				if not value isa V then
					v.errors.add new AttributeTypeError(self, "values", value, values_type_name)
					continue
				end
				self[key] = value
			end
		end
	end
end
					lib/msgpack/serialization_read.nit:367,1--410,3