A counter counts occurrences of things

Use this instead of a HashMap[E, Int]

var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
assert c["a"]   == 2
assert c["b"]   == 3
assert c["c"]   == 1
assert c["d"]   == 0

The counter class can also be used to gather statistical informations.

assert c.length == 3   # because 3 distinct values
assert c.max    == "b" # because "b" has the most count (3)
assert c.avg    == 2.0

Introduced properties

fun avg: Float

counter :: Counter :: avg

Values average (aka. arithmetic mean)
fun dec(e: E)

counter :: Counter :: dec

Decrement the value of e by 1
fun dec_all(es: Collection[E])

counter :: Counter :: dec_all

Decrement the value for each element of es
protected fun element_to_s(e: E): String

counter :: Counter :: element_to_s

The method used to display an element
fun entropy: Float

counter :: Counter :: entropy

The information entropy (Shannon entropy) of the elements in the counter (in bits).
init from(es: Collection[E])

counter :: Counter :: from

A new Counter initialized with inc_all.
fun inc(e: E)

counter :: Counter :: inc

Count one more occurrence of e
fun inc_all(es: Collection[E])

counter :: Counter :: inc_all

Count one more for each element of es
fun max: nullable E

counter :: Counter :: max

Return the element with the highest value (aka. the mode)
fun min: nullable E

counter :: Counter :: min

Return the couple with the lowest value
fun pack: Array[Array[E]]

counter :: Counter :: pack

Packs elements into separate arrays based on their occurences
fun print_content

counter :: Counter :: print_content

Prints the content of the counter along with statistics
fun print_elements(count: Int)

counter :: Counter :: print_elements

Display up to count most used elements and count least used elements
fun print_summary

counter :: Counter :: print_summary

Display statistical information
fun sort: Array[E]

counter :: Counter :: sort

Return an array of elements sorted by occurrences
fun std_dev: Float

counter :: Counter :: std_dev

The standard derivation of the counter values
fun sum: Int

counter :: Counter :: sum

Total number of counted occurrences
protected fun sum=(sum: Int)

counter :: Counter :: sum=

Total number of counted occurrences

Redefined properties

redef type SELF: Counter[E]

counter $ Counter :: SELF

Type of this instance, automatically specialized in every class
redef fun [](e: nullable Object): Int

counter $ Counter :: []

The number of counted occurrences of e
redef fun []=(e: E, value: Int)

counter $ Counter :: []=

Set the value at key.
redef fun add_all(other: MapRead[E, Int])

counter $ Counter :: add_all

Add each (key,value) of map into self.
redef fun clear

counter $ Counter :: clear

Remove all items
redef fun is_empty: Bool

counter $ Counter :: is_empty

Is there no item in the collection?
redef fun iterator: MapIterator[E, Int]

counter $ Counter :: iterator

Get a new iterator on the map.
redef fun keys: Collection[E]

counter $ Counter :: keys

Return the point of view of self on the keys only.
redef fun length: Int

counter $ Counter :: length

Number of items in the collection.
redef fun values: Collection[Int]

counter $ Counter :: values

Return the point of view of self on the values only.

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
abstract fun []=(key: K, value: V)

core :: Map :: []=

Set the value at key.
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
fun add_all(map: MapRead[K, V])

core :: Map :: add_all

Add each (key,value) of map into self.
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
fun avg: Float

counter :: Counter :: avg

Values average (aka. arithmetic mean)
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 :: Map :: clear

Remove all items
fun core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
fun dec(e: E)

counter :: Counter :: dec

Decrement the value of e by 1
fun dec_all(es: Collection[E])

counter :: Counter :: dec_all

Decrement the value for each element of es
protected fun element_to_s(e: E): String

counter :: Counter :: element_to_s

The method used to display an element
fun entropy: Float

counter :: Counter :: entropy

The information entropy (Shannon entropy) of the elements in the counter (in bits).
fun filter_keys(keys: Collection[nullable Object]): Array[K]

core :: MapRead :: filter_keys

Return all elements of keys that have a value.
init from(es: Collection[E])

counter :: Counter :: from

A new Counter initialized with inc_all.
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 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.
fun inc(e: E)

counter :: Counter :: inc

Count one more occurrence of e
fun inc_all(es: Collection[E])

counter :: Counter :: inc_all

Count one more for each element of es
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 join(sep: String, couple_sep: String): String

core :: Map :: join

Concatenate couples of key value.
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 max: nullable E

counter :: Counter :: max

Return the element with the highest value (aka. the mode)
fun min: nullable E

counter :: Counter :: min

Return the couple with the lowest value
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
init new: Map[K, V]

core :: Map :: new

Get a HashMap[K, V] as default implementation
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).
fun pack: Array[Array[E]]

counter :: Counter :: pack

Packs elements into separate arrays based on their occurences
fun print_content

counter :: Counter :: print_content

Prints the content of the counter along with statistics
fun print_elements(count: Int)

counter :: Counter :: print_elements

Display up to count most used elements and count least used elements
fun print_summary

counter :: Counter :: print_summary

Display statistical information
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 recover_with(map: MapRead[K, V])

core :: Map :: recover_with

Alias for add_all
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
fun sort: Array[E]

counter :: Counter :: sort

Return an array of elements sorted by occurrences
fun std_dev: Float

counter :: Counter :: std_dev

The standard derivation of the counter values
fun sum: Int

counter :: Counter :: sum

Total number of counted occurrences
protected fun sum=(sum: Int)

counter :: Counter :: sum=

Total number of counted occurrences
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_map_comparator(comparator: Comparator): MapComparator[K, V]

core :: MapRead :: to_map_comparator

A comparator that compares things with their values in self.
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.
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 counter::Counter Counter core::Map Map counter::Counter->core::Map serialization::Serializable Serializable core::Map->serialization::Serializable core::MapRead MapRead core::Map->core::MapRead ...serialization::Serializable ... ...serialization::Serializable->serialization::Serializable ...core::MapRead ... ...core::MapRead->core::MapRead

Ancestors

interface MapRead[K: nullable Object, V: nullable Object]

core :: MapRead

MapRead are abstract associative collections: key -> item.
interface Object

core :: Object

The root of the class hierarchy.
interface Serializable

serialization :: Serializable

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

Parents

interface Map[K: nullable Object, V: nullable Object]

core :: Map

Maps are associative collections: key -> item.

Class definitions

counter $ Counter
# A counter counts occurrences of things
# Use this instead of a `HashMap[E, Int]`
#
# ~~~
# var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
# assert c["a"]   == 2
# assert c["b"]   == 3
# assert c["c"]   == 1
# assert c["d"]   == 0
# ~~~
#
# The counter class can also be used to gather statistical informations.
#
# ~~~~
# assert c.length == 3   # because 3 distinct values
# assert c.max    == "b" # because "b" has the most count (3)
# assert c.avg    == 2.0 # because it is the mean of the counts
# ~~~~
class Counter[E]
	super Map[E, Int]

	# Total number of counted occurrences
	#
	# ~~~
	# var c = new Counter[String]
	# assert c.sum == 0
	# c.inc_all(["a", "a", "b", "b", "b", "c"])
	# assert c.sum == 6
	# ~~~
	var sum: Int = 0

	private var map = new HashMap[E, Int]

	redef fun iterator do return map.iterator

	# The number of counted occurrences of `e`
	redef fun [](e)
	do
		var map = self.map
		if map.has_key(e) then return map[e]
		return 0
	end

	redef fun []=(e, value)
	do
		sum -= self[e]
		self.map[e] = value
		sum += value
	end

	redef fun keys do return map.keys

	redef fun values do return map.values

	redef fun length do return map.length

	redef fun is_empty do return map.is_empty

	redef fun clear do
		sum = 0
		map.clear
	end

	redef fun add_all(other) do
		for k, v in other do
			self[k] += v
		end
	end

	# Count one more occurrence of `e`
	fun inc(e: E)
	do
		self.map[e] = self[e] + 1
		sum += 1
	end

	# Count one more for each element of `es`
	fun inc_all(es: Collection[E])
	do
		for e in es do inc(e)
	end

	# Decrement the value of `e` by 1
	fun dec(e: E) do
		if not has_key(e) then
			self.map[e] = 0
		else
			self.map[e] = self[e] - 1
			sum += - 1
		end
	end

	# Decrement the value for each element of `es`
	fun dec_all(es: Collection[E])
	do
		for e in es do dec(e)
	end

	# A new Counter initialized with `inc_all`.
	init from(es: Collection[E])
	do
		inc_all(es)
	end

	# Return an array of elements sorted by occurrences
	#
	# ~~~
	# var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
	# assert c.sort == ["c", "a", "b"]
	# ~~~
	fun sort: Array[E]
	do
		var res = map.keys.to_a
		var sorter = new CounterComparator[E](self)
		sorter.sort(res)
		return res
	end

	# The method used to display an element
	# @toimplement by default just call `to_s` on the element
	protected fun element_to_s(e: E): String
	do
		if e == null then return "null"
		return e.to_s
	end

	# Display statistical information
	fun print_summary
	do
		var list = self.sort
		print " population: {list.length}"
		if list.is_empty then return
		print " minimum value: {self[list.first]}"
		print " maximum value: {self[list.last]}"
		print " total value: {self.sum}"
		print " average value: {div(self.sum,list.length)}"
		print " distribution:"
		var count = 0
		var sum = 0
		var limit = self[list.first]
		for t in list do
			if self[t] > limit then
				print "  <={limit}: sub-population={count} ({div(count*100,list.length)}%); cumulated value={sum} ({div(sum*100,self.sum)}%)"
				count = 0
				sum = 0
				while self[t] > limit do
					limit = limit * 2
					if limit == 0 then limit = 1
				end
			end
			count += 1
			sum += self[t]
		end
		print "  <={limit}: sub-population={count} ({div(count*100,list.length)}%); cumulated value={sum} ({div(sum*100,self.sum)}%)"
	end

	# Display up to `count` most used elements and `count` least used elements
	# Use `element_to_s` to display the element
	fun print_elements(count: Int)
	do
		print " list:"
		var list = self.sort
		var min = count
		if list.length <= count*2 then min = list.length
		for i in [0..min[ do
			var t = list[list.length-i-1]
			print "  {element_to_s(t)}: {self[t]} ({div(self[t]*100,self.sum)}%)"
		end
		if list.length <= count*2 then return
		print "  ..."
		for i in [0..min[ do
			var t = list[min-i-1]
			print "  {element_to_s(t)}: {self[t]} ({div(self[t]*100,self.sum)}%)"
		end
	end

	# Return the element with the highest value (aka. the mode)
	#
	# ~~~
	# var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
	# assert c.max == "b"
	# ~~~
	#
	# If more than one max exists, the first one is returned.
	fun max: nullable E do
		var max: nullable Int = null
		var elem: nullable E = null
		for e in map.keys do
			var v = map[e]
			if max == null or v > max then
				max = v
				elem = e
			end
		end
		return elem
	end

	# Return the couple with the lowest value
	#
	# ~~~
	# var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
	# assert c.min == "c"
	# ~~~
	#
	# If more than one min exists, the first one is returned.
	fun min: nullable E do
		var min: nullable Int = null
		var elem: nullable E = null
		for e in map.keys do
			var v = map[e]
			if min == null or v < min then
				min = v
				elem = e
			end
		end
		return elem
	end

	# Values average (aka. arithmetic mean)
	#
	# ~~~
	# var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
	# assert c.avg == 2.0
	# ~~~
	fun avg: Float do
		if values.is_empty then return 0.0
		return (sum / values.length).to_f
	end

	# The standard derivation of the counter values
	#
	# ~~~
	# var c = new Counter[String].from(["a", "a", "b", "b", "b", "c"])
	# assert c.std_dev > 0.81
	# assert c.std_dev < 0.82
	# ~~~
	fun std_dev: Float do
		var avg = self.avg
		var sum = 0.0
		for value in map.values do
			sum += (value.to_f - avg).pow(2.0)
		end
		return (sum / map.length.to_f).sqrt
	end

	# The information entropy (Shannon entropy) of the elements in the counter (in bits).
	fun entropy: Float
	do
		var res = 0.0
		var sum = self.sum.to_f
		for k, v in self do
			var f = v.to_f / sum
			res = res - f * f.log_base(2.0)
		end
		return res
	end

	# Prints the content of the counter along with statistics
	#
	# Content is printed in order (if available) from lowest to highest on the keys.
	# Else, it is printed as-is
	fun print_content do
		var a = keys.to_a
		if a isa Array[Comparable] then default_comparator.sort(a)
		var subtotal = 0
		for i in a do
			subtotal += self[i]
			printn("* ", i or else "null", " = ", self[i], " => occurences ", self[i].to_f / sum.to_f * 100.0, "%, cumulative ", subtotal.to_f / sum.to_f * 100.0, "% \n")
		end
	end

	# Packs elements into separate arrays based on their occurences
	#
	# ~~~nit
	#	var x = "aaaabbbeeecccddhhgjt"
	#	var c = new Counter[Char]
	#	for i in x do c.inc i
	#	var ret = c.pack
	#	assert ret.join(", ") == """[t,g,j], [d,h], [c,b,e], [a]"""
	# ~~~
	fun pack: Array[Array[E]] do
		var ret = new Array[Array[E]]
		var base = self.sort
		if base.is_empty then return ret
		var curr = new Array[E]
		curr.push base.first
		var curr_score = self[base.first]
		base.shift
		for i in base do
			if self[i] == curr_score then
				curr.push i
				continue
			end
			curr_score = self[i]
			ret.push curr
			curr = new Array[E]
			curr.push i
		end
		if not curr.is_empty then ret.push curr
		return ret
	end
end
lib/counter/counter.nit:20,1--321,3