Have self and other the same value?

assert 1 + 1 == 2
assert not 1 == "1"
assert 1.to_s == "1"

The exact meaning of same value is left to the subclasses. Implicitly, the default implementation, is is_same_instance.

The laws of == are the following:

  • reflexivity a.is_same_instance(b) implies a == b
  • symmetry: (a == b) == (b == a)
  • transitivity: (a == b) and (b == c) implies (a == c)

== might not be constant on some objects overtime because of their evolution.

var a = [1]
var b = [1]
var c = [1,2]
assert a == b and not a == c
a.add 2
assert not a == b and a == c

Lastly, == is highly linked with hash and a specific redefinition of == should usually be associated with a specific redefinition of hash.

ENSURE result implies self.hash == other.hash

Property definitions

core $ Object :: ==
	# Have `self` and `other` the same value?
	#
	# ~~~
	# assert 1 + 1 == 2
	# assert not 1 == "1"
	# assert 1.to_s == "1"
	# ~~~
	#
	# The exact meaning of *same value* is left to the subclasses.
	# Implicitly, the default implementation, is `is_same_instance`.
	#
	# The laws of `==` are the following:
	#
	# * reflexivity `a.is_same_instance(b) implies a == b`
	# * symmetry: `(a == b) == (b == a)`
	# * transitivity: `(a == b) and (b == c) implies (a == c)`
	#
	# `==` might not be constant on some objects overtime because of their evolution.
	#
	# ~~~
	# var a = [1]
	# var b = [1]
	# var c = [1,2]
	# assert a == b and not a == c
	# a.add 2
	# assert not a == b and a == c
	# ~~~
	#
	# Lastly, `==` is highly linked with `hash` and a specific redefinition of `==` should
	# usually be associated with a specific redefinition of `hash`.
	#
	# ENSURE `result implies self.hash == other.hash`
	fun ==(other: nullable Object): Bool do return self.is_same_instance(other)
lib/core/kernel.nit:136,2--168,76

core $ MapRead :: ==
	# 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
lib/core/collection/abstract_collection.nit:640,2--662,4

core $ Pointer :: ==
	# Is equal to any instance pointing to the same address
	redef fun ==(o) do return o isa Pointer and native_equals(o)
lib/core/kernel.nit:1083,2--1084,61

core $ Path :: ==
	redef fun ==(other) do return other isa Path and simplified.path == other.simplified.path
lib/core/file.nit:756,2--90

glesv2 $ GLCap :: ==
	redef fun ==(o) do return o != null and is_same_type(o) and o.hash == self.hash
lib/glesv2/glesv2.nit:718,2--80

cartesian $ Pair :: ==
	# Untyped pair equality.
	#
	# ~~~
	# var p1 = new Pair[Object, Object](1, 2)
	# var p2 = new Pair[Int, Int](1, 2)
	# var p3 = new Pair[Int, Int](1, 3)
	#
	# assert p1 == p2
	# assert p2 != p3
	# ~~~
	#
	# Untyped because we want that `p1 == p2` above.
	# So the method just ignores the real types of `E` and `F`.
	redef fun ==(o) do return o isa Pair[nullable Object, nullable Object] and e == o.e and f == o.f
lib/cartesian/cartesian.nit:45,2--58,97

logic $ CNF :: ==
	redef fun ==(o) do return o isa CNF and data == o.data
lib/logic/lexpr.nit:377,2--55

rubix $ RubixCube :: ==
	# Checks if both objects are Rubix cubes and their content is equivalent
	#
	# NOTE: Rotationed versions are not yet considered equal
	redef fun ==(o) do
		if not o isa RubixCube then return false
		for mf in faces, tf in o.faces do
			for ml in mf, tl in tf do
				for mc in ml, tc in tl do if mc != tc then return false
			end
		end
		return true
	end
lib/rubix/rubix.nit:177,2--188,4

core $ SequenceRead :: ==
	# Two sequences are equals if they have the same items in the same order.
	#
	#     var a = new List[Int]
	#     a.add(1)
	#     a.add(2)
	#     a.add(3)
	#     assert a == [1,2,3]
	#     assert a != [1,3,2]
	redef fun ==(o)
	do
		if not o isa SequenceRead[nullable Object] then return false
		var l = length
		if o.length != l then return false
		var i = 0
		while i < l do
			if self[i] != o[i] then return false
			i += 1
		end
		return true
	end
lib/core/collection/abstract_collection.nit:1000,2--1019,4

core $ Range :: ==
	# Two ranges are equals if they have the same first and last elements.
	#
	#     var a = new Range[Int](10, 15)
	#     var b = new Range[Int].without_last(10, 15)
	#     assert a == [10..15]
	#     assert a == [10..16[
	#     assert not a == [10..15[
	#     assert b == [10..15[
	#     assert b == [10..14]
	#     assert not b == [10..15]
	redef fun ==(o) do
		return o isa Range[E] and self.first == o.first and self.last == o.last
	end
lib/core/collection/range.nit:113,2--125,4

core $ BM_Pattern :: ==
	redef fun ==(o) do return o isa BM_Pattern and o._motif == _motif
lib/core/text/string_search.nit:234,2--66

trees $ TreeNode :: ==
	# Nodes equality is done on `value` equality
	#
	# Redefine this method to change the default behavior.
	redef fun ==(o) do
		if not o isa N then return false
		return self.value == o.value
	end
lib/trees/abstract_tree.nit:89,2--95,4

ai $ Tile :: ==
	redef fun ==(o) do return o isa Tile and goal_idx == o.goal_idx
lib/ai/examples/puzzle.nit:224,2--64

glesv2 $ GLEnum :: ==
	redef fun ==(o) do return o != null and is_same_type(o) and o.hash == self.hash
lib/glesv2/glesv2.nit:508,2--80

matrix $ Matrix :: ==
	redef fun ==(other) do return other isa Matrix and
		width == other.width and height == other.height and
		items.equal_items(items, width*height)
lib/matrix/matrix.nit:255,2--257,40

date $ Time :: ==
	redef fun ==(d) do return d isa Time and time_eq(d)
lib/date/date.nit:70,2--52

date $ Date :: ==
	redef fun ==(d) do return d isa Date and self.diff_days(d) == 0
lib/date/date.nit:132,2--64

deriving $ DeriveEqual :: ==
	redef fun ==(other) do
		if not other isa Derivable then return false
		return derive_to_map == other.derive_to_map
	end
lib/deriving/deriving.nit:110,2--113,4

sdl2 $ MixInitFlags :: ==
	redef fun ==(o) do return o isa MixInitFlags and o.to_i == to_i
lib/sdl2/mixer.nit:216,2--64

msgpack $ MsgPackExt :: ==
	redef fun ==(o) do return o isa MsgPackExt and o.typ == typ and o.data == data
lib/msgpack/ext.nit:31,2--79

popcorn $ RepoObject :: ==
	# Base object comparison on ID
	#
	# Because multiple deserialization can exists of the same instance,
	# we use the ID to determine if two object are the same.
	redef fun ==(o) do return o isa SELF and id == o.id
lib/popcorn/pop_repos.nit:419,2--423,52

gtk $ GtkWidget :: ==
	redef fun ==(o) do return o isa GtkWidget and equal_to_gtk_widget(o)
lib/gtk/v3_4/gtk_core.nit:89,2--69

trees $ BKMatch :: ==
	redef fun ==(o) do return o isa BKMatch and distance == o.distance and key == o.key
lib/trees/bktree.nit:139,2--84

core $ Bool :: ==
	redef fun ==(b) is intern
lib/core/kernel.nit:501,2--26

functional :: test_iter_extras $ Ref :: ==
        redef fun ==(other) do
                if other isa Ref[E] then
                        return self.item == other.item
                end
                return false
        end
lib/functional/test_iter_extras.nit:23,9--28,11

geometry $ IPoint :: ==
	redef fun ==(o) do return o isa IPoint[Numeric] and o.x == x and o.y == y
lib/geometry/points_and_lines.nit:113,2--74

socket $ SocketAddress :: ==
	redef fun ==(o) do return o isa SocketAddress and o.address == address and o.port == port
lib/socket/socket.nit:489,2--90

core $ UInt32 :: ==
	redef fun ==(i) is intern
lib/core/fixed_ints.nit:598,2--26

core $ Int8 :: ==
	redef fun ==(i) is intern
lib/core/fixed_ints.nit:114,2--26

core $ Int16 :: ==
	redef fun ==(i) is intern
lib/core/fixed_ints.nit:235,2--26

core $ UInt16 :: ==
	redef fun ==(i) is intern
lib/core/fixed_ints.nit:356,2--26

core $ Int32 :: ==
	redef fun ==(i) is intern
lib/core/fixed_ints.nit:477,2--26

pthreads $ ConcurrentSequenceRead :: ==
	redef fun ==(o)
	do
		mutex.lock
		var r = real_collection == o
		mutex.unlock
		return r
	end
lib/pthreads/concurrent_collections.nit:188,2--194,4

date $ DateTime :: ==
	redef fun ==(other) do return other isa DateTime and diff_days(other) == 0 and time_eq(other)
lib/date/date.nit:173,2--94

ordered_tree $ OrderedTree :: ==
	# Two trees are equal if they have the same nodes in the same order
	#
	# ~~~
	# var t1 = new OrderedTree[Int]
	# t1.add_all(null, [1, 2])
	# t1.add_all(1, [11, 12])
	#
	# var t2 = new OrderedTree[Int]
	# t2.add_all(null, [1, 2])
	#
	# assert t1 != t2
	#
	# t2.add_all(1, [11, 12])
	#
	# assert t1 == t2
	# ~~~
	redef fun ==(other)
	do
		if not other isa OrderedTree[Object] then return false
		return roots == other.roots and sub == other.sub
	end
lib/ordered_tree/ordered_tree.nit:245,2--265,4

core $ CString :: ==
	redef fun ==(o) is intern do return is_same_instance(o)
lib/core/text/native.nit:115,2--56

poset $ POSet :: ==
	# Two posets are equal if they contain the same elements and edges.
	#
	# ~~~
	# var pos1 = new POSet[String]
	# pos1.add_chain(["A", "B", "C", "D", "E"])
	# pos1.add_chain(["A", "X", "C", "Y", "E"])
	#
	# var pos2 = new POSet[Object]
	# pos2.add_edge("Y", "E")
	# pos2.add_chain(["A", "X", "C", "D", "E"])
	# pos2.add_chain(["A", "B", "C", "Y"])
	#
	# assert pos1 == pos2
	#
	# pos1.add_edge("D", "Y")
	# assert pos1 != pos2
	#
	# pos2.add_edge("D", "Y")
	# assert pos1 == pos2
	#
	# pos1.add_node("Z")
	# assert pos1 != pos2
	# ~~~
	redef fun ==(other) do
		if not other isa POSet[nullable Object] then return false
		if not self.elements.keys.has_exactly(other.elements.keys) then return false
		for e, ee in elements do
			if ee.direct_greaters != other[e].direct_greaters then return false
		end
		assert hash == other.hash
		return true
	end
lib/poset/poset.nit:447,2--478,4

gmp $ Ratio :: ==
    redef fun ==(r) do return r isa Ratio and (self <=> r) == 0
lib/gmp/gmp.nit:314,5--63

core $ Char :: ==
	redef fun ==(o) is intern
lib/core/kernel.nit:911,2--26

core $ Byte :: ==
	redef fun ==(i) is intern
lib/core/kernel.nit:614,2--26

core $ Float :: ==
	redef fun ==(i) is intern
lib/core/kernel.nit:525,2--26

core $ Set :: ==
	# Equality is defined on set and means that each set contains the same elements
	redef fun ==(other)
	do
		if not other isa Set[nullable Object] then return false
		if other.length != length then return false
		return has_all(other)
	end
lib/core/collection/abstract_collection.nit:485,2--491,4

gmp $ BigInt :: ==
    redef fun ==(i) do return i isa BigInt and (self <=> i) == 0
lib/gmp/gmp.nit:146,5--64

core $ Int :: ==
	redef fun ==(i) is intern
lib/core/kernel.nit:715,2--26

core $ Text :: ==
	# Equality of text
	# Two pieces of text are equals if thez have the same characters in the same order.
	#
	# ~~~
	# assert "hello" == "hello"
	# assert "hello" != "HELLO"
	# assert "hello" == "hel"+"lo"
	# ~~~
	#
	# Things that are not Text are not equal.
	#
	# ~~~
	# assert "9" != '9'
	# assert "9" != ['9']
	# assert "9" != 9
	#
	# assert "9".chars.first == '9'   # equality of Char
	# assert "9".chars       == ['9'] # equality of Sequence
	# assert "9".to_i        == 9     # equality of Int
	# ~~~
	redef fun ==(o)
	do
		if o == null then return false
		if not o isa Text then return false
		if self.is_same_instance(o) then return true
		if self.length != o.length then return false
		return self.chars == o.chars
	end
lib/core/text/abstract_text.nit:1025,2--1052,4

core $ Array :: ==
	redef fun ==(o)
	do
		if not o isa Array[nullable Object] then return super
		# Efficient implementation
		var l = length
		if l != o.length then return false
		if l == 0 then return true
		var i = 0
		var it = _items.as(not null)
		var oit = o._items.as(not null)
		while i < l do
			if it[i] != oit[i] then return false
			i += 1
		end
		return true
	end
lib/core/collection/array.nit:471,2--486,4

pthreads :: redef_collections $ Array :: ==
	redef fun ==(o)
	do
		mutex.lock
		var r = super
		mutex.unlock
		return r
	end
lib/pthreads/redef_collections.nit:98,2--104,4

core $ FlatString :: ==
	redef fun ==(other)
	do
		if not other isa FlatText then return super

		if self.object_id == other.object_id then return true

		var my_length = _byte_length

		if other._byte_length != my_length then return false

		var my_index = _first_byte
		var its_index = other.first_byte

		var last_iteration = my_index + my_length

		var its_items = other._items
		var my_items = self._items

		while my_index < last_iteration do
			if my_items[my_index] != its_items[its_index] then return false
			my_index += 1
			its_index += 1
		end

		return true
	end
lib/core/text/flat.nit:543,2--568,4