Native bytes.

Same as a C unsigned char

Introduced properties

intern fun %(i: Byte): Byte

core :: Byte :: %

Modulo of self with i.
intern fun &(i: Byte): Byte

core :: Byte :: &

Returns the result of a binary AND operation on self and i
intern fun <<(i: Int): Byte

core :: Byte :: <<

i bits shift fo the left
intern fun >>(i: Int): Byte

core :: Byte :: >>

i bits shift fo the right
fun ^(i: Byte): Byte

core :: Byte :: ^

Returns the result of a binary XOR operation on self and i
fun is_whitespace: Bool

core :: Byte :: is_whitespace

Is self an ASCII whitespace ?
fun unary ~: Byte

core :: Byte :: unary ~

Returns the 1's complement of self
fun |(i: Byte): Byte

core :: Byte :: |

Returns the result of a binary OR operation on self and i

Redefined properties

redef intern fun !=(i: nullable Object): Bool

core $ Byte :: !=

Have self and other different values?
redef intern fun *(i: OTHER): OTHER

core $ Byte :: *

Multiplication of self with i
redef intern fun +(i: OTHER): OTHER

core $ Byte :: +

Addition of self with i
redef intern fun -(i: OTHER): OTHER

core $ Byte :: -

Substraction of i from self
redef intern fun /(i: OTHER): OTHER

core $ Byte :: /

Division of self with i
redef intern fun <(i: OTHER): Bool

core $ Byte :: <

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

core $ Byte :: <=

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

core $ Byte :: <=>

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

core $ Byte :: ==

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

core $ Byte :: >

other < self
redef intern fun >=(i: OTHER): Bool

core $ Byte :: >=

not self < other
redef type OTHER: Byte

core $ Byte :: OTHER

What self can be compared to?
redef type SELF: Byte

core $ Byte :: SELF

Type of this instance, automatically specialized in every class
redef fun accept_json_serializer(v: JsonSerializer)

json :: serialization_write $ Byte :: accept_json_serializer

Refinable service to customize the serialization of this class to JSON
redef fun accept_msgpack_serializer(v: MsgPackSerializer)

msgpack :: serialization_write $ Byte :: accept_msgpack_serializer

Hook to customize the serialization of this class to MessagePack
redef fun distance(i: OTHER): Int

core $ Byte :: distance

The distance between self and d.
redef fun hash: Int

core $ Byte :: hash

The hash code of the object.
redef fun is_between(c: OTHER, d: OTHER): Bool

core $ Byte :: is_between

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

core $ Byte :: max

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

core $ Byte :: min

The minimum between self and c (prefer self if equals)
redef intern fun object_id: Int

core $ Byte :: object_id

An internal hash code for the object based on its identity.
redef intern fun output

core $ Byte :: output

Display self on stdout (debug only).
redef fun predecessor(i: Int): OTHER

core $ Byte :: predecessor

The previous element.
redef fun successor(i: Int): OTHER

core $ Byte :: successor

The next element.
redef fun to_b: Byte

core $ Byte :: to_b

The byte equivalent of self
redef intern fun to_f: Float

core $ Byte :: to_f

The float equivalent of self
redef intern fun to_i: Int

core $ Byte :: to_i

The integer part of self.
redef intern fun to_i16: Int16

core :: fixed_ints $ Byte :: to_i16

The Int16 equivalent of self
redef intern fun to_i32: Int32

core :: fixed_ints $ Byte :: to_i32

The Int32 equivalent of self
redef intern fun to_i8: Int8

core :: fixed_ints $ Byte :: to_i8

The Int8 equivalent of self
redef fun to_s: String

core :: abstract_text $ Byte :: to_s

Displayable byte in its hexadecimal form (0x..)
redef intern fun to_u16: UInt16

core :: fixed_ints $ Byte :: to_u16

The UInt16 equivalent of self
redef intern fun to_u32: UInt32

core :: fixed_ints $ Byte :: to_u32

The UInt32 equivalent of self
redef intern fun unary -: OTHER

core $ Byte :: unary -

On an Byte, unary minus will return (256 - self) % 256
redef fun value_of(val: Numeric): OTHER

core $ Byte :: value_of

The value of val in the domain of self
redef fun zero: OTHER

core $ Byte :: zero

The value of zero in the domain of self

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
intern fun %(i: Byte): Byte

core :: Byte :: %

Modulo of self with i.
intern fun &(i: Byte): Byte

core :: Byte :: &

Returns the result of a binary AND operation on self and i
abstract fun *(i: OTHER): OTHER

core :: Numeric :: *

Multiplication of self with i
abstract fun +(i: OTHER): OTHER

core :: Numeric :: +

Addition of self with i
abstract fun -(i: OTHER): OTHER

core :: Numeric :: -

Substraction of i from self
abstract fun /(i: OTHER): OTHER

core :: Numeric :: /

Division of self with i
abstract fun <(other: OTHER): Bool

core :: Comparable :: <

Is self lesser than other?
intern fun <<(i: Int): Byte

core :: Byte :: <<

i bits shift fo the left
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
intern fun >>(i: Int): Byte

core :: Byte :: >>

i bits shift fo the right
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 ^(i: Byte): Byte

core :: Byte :: ^

Returns the result of a binary XOR operation on self and i
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
abstract fun add(other: Numeric): Numeric

core :: Numeric :: add

Universal + with any Numeric
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
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 core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
fun distance(d: OTHER): Int

core :: Discrete :: distance

The distance between self and d.
abstract fun div(other: Numeric): Numeric

core :: Numeric :: div

Universal / with any Numeric
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 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 is_whitespace: Bool

core :: Byte :: is_whitespace

Is self an ASCII whitespace ?
fun is_zero: Bool

core :: Numeric :: is_zero

Is this the value of zero in its domain?
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)
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
abstract fun mul(other: Numeric): Numeric

core :: Numeric :: mul

Universal * with any Numeric
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).
abstract fun predecessor(i: Int): OTHER

core :: Discrete :: predecessor

The previous element.
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
abstract fun sub(other: Numeric): Numeric

core :: Numeric :: sub

Universal - with any Numeric
abstract fun successor(i: Int): OTHER

core :: Discrete :: successor

The next element.
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_b: Byte

core :: Numeric :: to_b

The byte equivalent of self
fun to_bi: BigInt

core :: Numeric :: to_bi

The BigInt equivalent of self
abstract fun to_f: Float

core :: Numeric :: to_f

The float equivalent of self
abstract fun to_i: Int

core :: Numeric :: to_i

The integer part of self.
fun to_i16: Int16

core :: Numeric :: to_i16

The Int16 equivalent of self
fun to_i32: Int32

core :: Numeric :: to_i32

The Int32 equivalent of self
fun to_i8: Int8

core :: Numeric :: to_i8

The Int8 equivalent of self
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_pretty_json: String

serialization :: Serializable :: to_pretty_json

Serialize self to plain pretty JSON
fun to_r: Ratio

core :: Numeric :: to_r

The Ratio equivalent of self
fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun to_u16: UInt16

core :: Numeric :: to_u16

The UInt16 equivalent of self
fun to_u32: UInt32

core :: Numeric :: to_u32

The UInt32 equivalent of self
abstract fun unary -: OTHER

core :: Numeric :: unary -

Inverse of self
fun unary ~: Byte

core :: Byte :: unary ~

Returns the 1's complement of self
abstract fun value_of(val: Numeric): OTHER

core :: Numeric :: value_of

The value of val in the domain of self
abstract fun zero: OTHER

core :: Numeric :: zero

The value of zero in the domain of self
fun |(i: Byte): Byte

core :: Byte :: |

Returns the result of a binary OR operation on self and i
package_diagram core::Byte Byte serialization::DirectSerializable DirectSerializable core::Byte->serialization::DirectSerializable core::Discrete Discrete core::Byte->core::Discrete core::Numeric Numeric core::Byte->core::Numeric serialization::Serializable Serializable serialization::DirectSerializable->serialization::Serializable core::Comparable Comparable core::Discrete->core::Comparable core::Numeric->core::Comparable ...serialization::Serializable ... ...serialization::Serializable->serialization::Serializable ...core::Comparable ... ...core::Comparable->core::Comparable

Ancestors

interface Comparable

core :: Comparable

The ancestor of class where objects are in a total order.
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 DirectSerializable

serialization :: DirectSerializable

Instances of this class are not delayed and instead serialized immediately
interface Discrete

core :: Discrete

Discrete total orders.
interface Numeric

core :: Numeric

A numeric value supporting mathematical operations

Class definitions

core $ Byte
# Native bytes.
# Same as a C `unsigned char`
universal Byte
	super Discrete
	super Numeric

	redef type OTHER: Byte

	redef fun successor(i) do return self + i.to_b
	redef fun predecessor(i) do return self - i.to_b

	redef fun object_id is intern
	redef fun hash do return self.to_i
	redef fun ==(i) is intern
	redef fun !=(i) is intern
	redef fun output is intern

	redef fun <=(i) is intern
	redef fun <(i) is intern
	redef fun >=(i) is intern
	redef fun >(i) is intern
	redef fun +(i) is intern

	# On an Byte, unary minus will return `(256 - self) % 256`
	#
	#     assert -1u8 == 0xFFu8
	#     assert -0u8 == 0x00u8
	redef fun - is intern
	redef fun -(i) is intern
	redef fun *(i) is intern
	redef fun /(i) is intern

	# Modulo of `self` with `i`.
	#
	# Finds the remainder of division of `self` by `i`.
	#
	#     assert 5u8 % 2u8		== 1u8
	#     assert 10u8 % 2u8		== 0u8
	fun %(i: Byte): Byte is intern

	redef fun zero do return 0.to_b
	redef fun value_of(val) do return val.to_b

	# `i` bits shift fo the left
	#
	#     assert 5u8 << 1    == 10u8
	fun <<(i: Int): Byte is intern `{ return self << i; `}

	# `i` bits shift fo the right
	#
	#     assert 5u8 >> 1    == 2u8
	fun >>(i: Int): Byte is intern `{ return self >> i; `}

	redef fun to_i is intern
	redef fun to_f is intern
	redef fun to_b do return self

	redef fun distance(i) do return (self - i).to_i

	redef fun <=>(other)
	do
		if self < other then
			return -1
		else if other < self then
			return 1
		else
			return 0
		end
	end

	redef fun is_between(c, d)
	do
		if self < c or d < self then
			return false
		else
			return true
		end
	end

	redef fun max(other)
	do
		if self < other then
			return other
		else
			return self
		end
	end

	redef fun min(c)
	do
		if c < self then
			return c
		else
			return self
		end
	end

	# Is `self` an ASCII whitespace ?
	fun is_whitespace: Bool do return self == 0x7Fu8 or self <= 0x20u8
end
lib/core/kernel.nit:601,1--700,3

core :: fixed_ints $ Byte
redef class Byte
	redef fun to_i8 is intern
	redef fun to_i16 is intern
	redef fun to_u16 is intern
	redef fun to_i32 is intern
	redef fun to_u32 is intern
end
lib/core/fixed_ints.nit:85,1--91,3

core :: math $ Byte
redef class Byte
	# Returns the result of a binary AND operation on `self` and `i`
	#
	#     assert 0x10u8 & 0x01u8 == 0u8
	fun &(i: Byte): Byte is intern `{ return self & i; `}

	# Returns the result of a binary OR operation on `self` and `i`
	#
	#     assert 0x10u8 | 0x01u8 == 0x11u8
	fun |(i: Byte): Byte `{ return self | i; `}

	# Returns the result of a binary XOR operation on `self` and `i`
	#
	#     assert 0x101u8 ^ 0x110u8 == 0x11u8
	fun ^(i: Byte): Byte `{ return self ^ i; `}

	# Returns the 1's complement of `self`
	#
	#     assert ~0x2Fu8 == 0xD0u8
	fun ~: Byte `{ return ~self; `}
end
lib/core/math.nit:184,1--204,3

core :: abstract_text $ Byte
redef class Byte
	# C function to calculate the length of the `CString` to receive `self`
	private fun byte_to_s_len: Int `{
		return snprintf(NULL, 0, "0x%02x", self);
	`}

	# C function to convert an nit Int to a CString (char*)
	private fun native_byte_to_s(nstr: CString, strlen: Int) `{
		snprintf(nstr, strlen, "0x%02x", self);
	`}

	# Displayable byte in its hexadecimal form (0x..)
	#
	# ~~~
	# assert 1.to_b.to_s       == "0x01"
	# assert (-123).to_b.to_s  == "0x85"
	# ~~~
	redef fun to_s do
		var nslen = byte_to_s_len
		var ns = new CString(nslen + 1)
		ns[nslen] = 0
		native_byte_to_s(ns, nslen + 1)
		return ns.to_s_unsafe(nslen, copy=false, clean=false)
	end
end
lib/core/text/abstract_text.nit:1930,1--1954,3

serialization :: serialization_core $ Byte
redef class Byte super DirectSerializable end
lib/serialization/serialization_core.nit:260,1--45

json :: serialization_write $ Byte
redef class Byte
	redef fun accept_json_serializer(v)
	do
		if v.plain_json then
			to_i.accept_json_serializer v
		else
			v.stream.write "\{\"__kind\": \"byte\", \"__val\": "
			to_i.accept_json_serializer v
			v.stream.write "\}"
		end
	end
end
lib/json/serialization_write.nit:289,1--300,3

serialization :: inspect $ Byte
redef class Byte
	redef fun accept_inspect_serializer(v)
	do
		v.stream.write to_s
		v.stream.write "u8"
	end
end
lib/serialization/inspect.nit:212,1--218,3

msgpack :: serialization_write $ Byte
redef class Byte
	redef fun accept_msgpack_serializer(v)
	do
		if v.plain_msgpack then
			# Write as a string
			v.stream.write_msgpack_int to_i
		else
			# Write as ext
			var bytes = new Bytes.with_capacity(1)
			bytes.add self.to_i
			v.stream.write_msgpack_ext(v.ext_typ_byte, bytes)
		end
	end
end
lib/msgpack/serialization_write.nit:260,1--273,3