A signed big-endian representation of self

assert     1.to_bytes.hexdigest ==     "01"
assert   255.to_bytes.hexdigest ==     "FF"
assert   256.to_bytes.hexdigest ==   "0100"
assert 65535.to_bytes.hexdigest ==   "FFFF"
assert 65536.to_bytes.hexdigest == "010000"

Negative values are converted to their two's complement. Be careful as the result can be ambiguous.

assert     (-1).to_bytes.hexdigest ==     "FF"
assert    (-32).to_bytes.hexdigest ==     "E0"
assert   (-512).to_bytes.hexdigest ==   "FE00"
assert (-65794).to_bytes.hexdigest == "FEFEFE"

Optionally, set n_bytes to the desired number of bytes in the output. This setting can disambiguate the result between positive and negative integers. Be careful with this parameter as the result may overflow.

assert        1.to_bytes(2).hexdigest ==     "0001"
assert    65535.to_bytes(2).hexdigest ==     "FFFF"
assert     (-1).to_bytes(2).hexdigest ==     "FFFF"
assert   (-512).to_bytes(4).hexdigest == "FFFFFE00"
assert 0x123456.to_bytes(2).hexdigest ==     "3456"

For 0, a Bytes object with single nul byte is returned (instead of an empty Bytes object).

assert 0.to_bytes.hexdigest == "00"

For positive integers, Bytes::to_i can reverse the operation.

assert 1234.to_bytes.to_i == 1234

Require self >= 0

Property definitions

core :: bytes $ Int :: to_bytes
	# A signed big-endian representation of `self`
	#
	# ~~~
	# assert     1.to_bytes.hexdigest ==     "01"
	# assert   255.to_bytes.hexdigest ==     "FF"
	# assert   256.to_bytes.hexdigest ==   "0100"
	# assert 65535.to_bytes.hexdigest ==   "FFFF"
	# assert 65536.to_bytes.hexdigest == "010000"
	# ~~~
	#
	# Negative values are converted to their two's complement.
	# Be careful as the result can be ambiguous.
	#
	# ~~~
	# assert     (-1).to_bytes.hexdigest ==     "FF"
	# assert    (-32).to_bytes.hexdigest ==     "E0"
	# assert   (-512).to_bytes.hexdigest ==   "FE00"
	# assert (-65794).to_bytes.hexdigest == "FEFEFE"
	# ~~~
	#
	# Optionally, set `n_bytes` to the desired number of bytes in the output.
	# This setting can disambiguate the result between positive and negative
	# integers. Be careful with this parameter as the result may overflow.
	#
	# ~~~
	# assert        1.to_bytes(2).hexdigest ==     "0001"
	# assert    65535.to_bytes(2).hexdigest ==     "FFFF"
	# assert     (-1).to_bytes(2).hexdigest ==     "FFFF"
	# assert   (-512).to_bytes(4).hexdigest == "FFFFFE00"
	# assert 0x123456.to_bytes(2).hexdigest ==     "3456"
	# ~~~
	#
	# For 0, a Bytes object with single nul byte is returned (instead of an empty Bytes object).
	#
	# ~~~
	# assert 0.to_bytes.hexdigest == "00"
	# ~~~
	#
	# For positive integers, `Bytes::to_i` can reverse the operation.
	#
	# ~~~
	# assert 1234.to_bytes.to_i == 1234
	# ~~~
	#
	# Require self >= 0
	fun to_bytes(n_bytes: nullable Int): Bytes do

		# If 0, force using at least one byte
		if self == 0 and n_bytes == null then n_bytes = 1

		# Compute the len (log256)
		var len = 1
		var max = 256
		var s = self.abs
		while s >= max do
			len += 1
			max *= 256
		end

		# Two's complement
		s = self
		if self < 0 then
			var ff = 0
			for j in [0..len[ do
				ff *= 0x100
				ff += 0xFF
			end

			s = ((-self) ^ ff) + 1
		end

		# Cut long values
		if n_bytes != null and len > n_bytes then len = n_bytes

		# Allocate the buffer
		var cap = n_bytes or else len
		var res = new Bytes.with_capacity(cap)

		var filler = if self < 0 then 0xFF else 0
		for i in [0..cap[ do res[i] = filler

		# Fill it starting with the end
		var i = cap
		var sum = s
		while i > cap - len do
			i -= 1
			res[i] = sum % 256
			sum /= 256
		end

		return res
	end
lib/core/bytes.nit:141,2--232,4