The ancestor of class where objects are in a total order.

In order to work, the method '<' has to be redefined.

Introduced properties

abstract fun <(other: OTHER): Bool

core :: Comparable :: <

Is self lesser than other?
fun <=(other: OTHER): Bool

core :: Comparable :: <=

not other < self
fun <=>(other: OTHER): Int

core :: Comparable :: <=>

-1 if <, +1 if > and 0 otherwise
fun >(other: OTHER): Bool

core :: Comparable :: >

other < self
fun >=(other: OTHER): Bool

core :: Comparable :: >=

not self < other
type OTHER: Comparable

core :: Comparable :: OTHER

What self can be compared to?
fun clamp(min: OTHER, max: OTHER): OTHER

core :: Comparable :: clamp

Constraint self within [min..max]
fun is_between(c: OTHER, d: OTHER): Bool

core :: Comparable :: is_between

c <= self <= d
fun max(other: OTHER): OTHER

core :: Comparable :: max

The maximum between self and other (prefers self if equals).
fun min(c: OTHER): OTHER

core :: Comparable :: min

The minimum between self and c (prefer self if equals)

Redefined properties

redef type SELF: Comparable

core $ Comparable :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
abstract fun <(other: OTHER): Bool

core :: Comparable :: <

Is self lesser than other?
fun <=(other: OTHER): Bool

core :: Comparable :: <=

not other < self
fun <=>(other: OTHER): Int

core :: Comparable :: <=>

-1 if <, +1 if > and 0 otherwise
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
fun >(other: OTHER): Bool

core :: Comparable :: >

other < self
fun >=(other: OTHER): Bool

core :: Comparable :: >=

not self < other
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type OTHER: Comparable

core :: Comparable :: OTHER

What self can be compared to?
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun clamp(min: OTHER, max: OTHER): OTHER

core :: Comparable :: clamp

Constraint self within [min..max]
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 get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
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".
fun is_between(c: OTHER, d: OTHER): Bool

core :: Comparable :: is_between

c <= self <= d
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.
fun max(other: OTHER): OTHER

core :: Comparable :: max

The maximum between self and other (prefers self if equals).
fun min(c: OTHER): OTHER

core :: Comparable :: min

The minimum between self and c (prefer self if equals)
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 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_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram core::Comparable Comparable core::Object Object core::Comparable->core::Object core::Comparable... ... core::Comparable...->core::Comparable

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class ArrayCmp[E: nullable Comparable]

core :: ArrayCmp

Comparable array for comparable elements.
class BKMatch

trees :: BKMatch

A match in a BKTree
class Date

date :: Date

A date, composed by a year, a month and a day
interface Discrete

core :: Discrete

Discrete total orders.
class ISODate

core :: ISODate

Date using the international format defined by ISO 8601.
class IndexMatch[DOC: Document]

vsm :: IndexMatch

A match to a request in an Index
interface Numeric

core :: Numeric

A numeric value supporting mathematical operations
abstract class Text

core :: Text

High-level abstraction for all text representations
class Tile

ai :: Tile

A movable tile
class Time

date :: Time

A time of the day, composed of an hour, a minute and a second count
abstract class TreeNode[K: Comparable, E: nullable Object]

trees :: TreeNode

Abstract node structure used in Tree implementation

Descendants

class BigInt

gmp :: BigInt

Multi precision Integer numbers.
class BinTreeNode[K: Comparable, E: nullable Object]

trees :: BinTreeNode

TreeNode used by BinTree
abstract class Buffer

core :: Buffer

A mutable sequence of characters.
enum Byte

core :: Byte

Native bytes.
enum Char

core :: Char

Native characters.
class DateTime

date :: DateTime

A Time in a Date
class FlatBuffer

core :: FlatBuffer

Mutable strings of characters.
abstract class FlatString

core :: FlatString

Immutable strings of characters.
abstract class FlatText

core :: FlatText

All kinds of array-based text representations.
enum Float

core :: Float

Native floating point numbers.
enum Int

core :: Int

Native integer numbers.
enum Int16

core :: Int16

Native 16-bit signed integer.
enum Int32

core :: Int32

Native 32-bit signed integer.
enum Int8

core :: Int8

Native 8-bit signed integer.
class RBTreeNode[K: Comparable, E: nullable Object]

trees :: RBTreeNode

RedBlackTree node (can be red or black)
class Ratio

gmp :: Ratio

Multi precision Rational numbers.
abstract class String

core :: String

Immutable sequence of characters.
class U16String

core :: U16String

UTF-16 encoded string
enum UInt16

core :: UInt16

Native 16-bit unsigned integer.
enum UInt32

core :: UInt32

Native 32-bit unsigned integer.

Class definitions

core $ Comparable
# The ancestor of class where objects are in a total order.
# In order to work, the method '<' has to be redefined.
interface Comparable
	# What `self` can be compared to?
	type OTHER: Comparable

	# Is `self` lesser than `other`?
	fun <(other: OTHER): Bool is abstract

	# not `other` < `self`
	# Note, the implementation must ensure that: `(x<=y) == (x<y or x==y)`
	fun <=(other: OTHER): Bool do return not other < self

	# not `self` < `other`
	# Note, the implementation must ensure that: `(x>=y) == (x>y or x==y)`
	fun >=(other: OTHER): Bool do return not self < other

	# `other` < `self`
	fun >(other: OTHER): Bool do return other < self

	# -1 if <, +1 if > and 0 otherwise
	# Note, the implementation must ensure that: (x<=>y == 0) == (x==y)
	fun <=>(other: OTHER): Int
	do
		if self < other then
			return -1
		else if other < self then
			return 1
		else
			return 0
		end
	end

	# c <= self <= d
	fun is_between(c: OTHER, d: OTHER): Bool
	do
		return c <= self and self <= d
	end

	# The maximum between `self` and `other` (prefers `self` if equals).
	fun max(other: OTHER): OTHER
	do
		if self < other then
			return other
		else
			return self
		end
	end

	# The minimum between `self` and `c` (prefer `self` if equals)
	fun min(c: OTHER): OTHER
	do
		if c < self then
			return c
		else
			return self
		end
	end
end
lib/core/kernel.nit:313,1--371,3

core :: math $ Comparable
redef class Comparable
	# Constraint `self` within `[min..max]`
	#
	#     assert 1.clamp(5, 10) == 5
	#     assert 7.clamp(5, 10) == 7
	#     assert 15.clamp(5, 10) == 10
	#     assert 1.5.clamp(1.0, 2.0) == 1.5
	#     assert "a".clamp("b", "c") == "b"
	fun clamp(min, max: OTHER): OTHER do return self.max(min).min(max)
end
lib/core/math.nit:423,1--432,3