Correspond to C int.
core :: Int :: bcm2835_delay
core :: Int :: bcm2835_delay_micros
core :: Int :: code_point
The character which code point (unicode-wise) isself
core :: Int :: digit_count
Number of digits of an integer in baseb
(plus one if negative)
core :: Int :: highest_bit
Returns the position of the highest bit set to 1 inself
core :: Int :: is_undefined
Is this value undefined according to MPI? (may be returned byStatus::count
)
core :: Int :: is_valid_utf8_start
Isself
a valid UTF-8 sequence start ?
core :: Int :: number_bits
Returns the number of bits of specified value (0 or 1) inself
json :: serialization_write $ Int :: accept_json_serializer
Refinable service to customize the serialization of this class to JSONmsgpack :: serialization_write $ Int :: accept_msgpack_serializer
Hook to customize the serialization of this class to MessagePackandroid :: bundle $ Int :: add_to_bundle
Called by[]=
to dynamically choose the appropriate method according
noise :: noise $ Int :: core_serialize_to
Actual serialization ofself
to serializer
core :: bytes $ Int :: first_index_in_from
Return the first occurence ofself
in b
starting at from
, or -1 if not found
noise :: noise $ Int :: from_deserializer
Create an instance of this class from thedeserializer
core :: bytes $ Int :: last_index_in_from
Return the last occurence ofself
in b
, or -1 if not found
core :: bytes $ Int :: search_all_in
Returns the indexes of all the occurences ofself
in b
serialization :: Serializable :: accept_json_serializer
Refinable service to customize the serialization of this class to JSONserialization :: Serializable :: accept_msgpack_attribute_counter
Hook to customize the behavior of theAttributeCounter
serialization :: Serializable :: accept_msgpack_serializer
Hook to customize the serialization of this class to MessagePackserialization :: Serializable :: add_to_bundle
Called by[]=
to dynamically choose the appropriate method according
core :: Int :: bcm2835_delay
core :: Int :: bcm2835_delay_micros
core :: Object :: class_factory
Implementation used byget_class
to create the specific class.
core :: Int :: code_point
The character which code point (unicode-wise) isself
serialization :: Serializable :: core_serialize_to
Actual serialization ofself
to serializer
sqlite3 :: Sqlite3Data :: defaultinit
core :: Comparable :: defaultinit
core :: Object :: defaultinit
core :: Numeric :: defaultinit
core :: Discrete :: defaultinit
core :: BytePattern :: defaultinit
core :: Int :: digit_count
Number of digits of an integer in baseb
(plus one if negative)
core :: BytePattern :: first_index_in
Return the first occurence ofself
in b
, or -1 if not found
core :: BytePattern :: first_index_in_from
Return the first occurence ofself
in b
starting at from
, or -1 if not found
serialization :: Serializable :: from_deserializer
Create an instance of this class from thedeserializer
core :: Int :: highest_bit
Returns the position of the highest bit set to 1 inself
core :: BytePattern :: is_prefix
Isself
a prefix for b
?
core :: Object :: is_same_instance
Return true ifself
and other
are the same instance (i.e. same identity).
core :: Object :: is_same_serialized
Isself
the same as other
in a serialization context?
core :: Object :: is_same_type
Return true ifself
and other
have the same dynamic type.
core :: BytePattern :: is_suffix
Isself
a suffix for b
?
core :: Int :: is_undefined
Is this value undefined according to MPI? (may be returned byStatus::count
)
core :: Int :: is_valid_utf8_start
Isself
a valid UTF-8 sequence start ?
core :: BytePattern :: last_index_in
Return the last occurence ofself
in b
, or -1 if not found
core :: BytePattern :: last_index_in_from
Return the last occurence ofself
in b
, or -1 if not found
serialization :: Serializable :: msgpack_extra_array_items
Hook to request a larger than usual metadata arraycore :: Int :: number_bits
Returns the number of bits of specified value (0 or 1) inself
core :: Object :: output_class_name
Display class name on stdout (debug only).core :: BytePattern :: search_all_in
Returns the indexes of all the occurences ofself
in b
serialization :: Serializable :: serialize_msgpack
Serializeself
to MessagePack bytes
serialization :: Serializable :: serialize_to
Serializeself
to serializer
serialization :: Serializable :: serialize_to_json
Serializeself
to JSON
serialization :: Serializable :: to_pretty_json
Serializeself
to plain pretty JSON
Serializer::serialize
core :: BytePattern
Any kind of entity which can be searched for in a Sequence of Byteserialization :: DirectSerializable
Instances of this class are not delayed and instead serialized immediately
# Native integer numbers.
# Correspond to C int.
universal Int
super Discrete
super Numeric
redef type OTHER: Int
redef fun successor(i) do return self + i
redef fun predecessor(i) do return self - i
redef fun object_id is intern
redef fun hash do return self
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
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 5 % 2 == 1
# assert 10 % 2 == 0
fun %(i: Int): Int is intern
redef fun zero do return 0
redef fun value_of(val) do return val.to_i
# `i` bits shift fo the left
#
# assert 5 << 1 == 10
fun <<(i: Int): Int is intern `{ return self << i; `}
# `i` bits shift fo the right
#
# assert 5 >> 1 == 2
fun >>(i: Int): Int is intern `{ return self >> i; `}
redef fun to_i do return self
redef fun to_f is intern
redef fun to_b is intern
redef fun distance(i)
do
var d = self - i
if d >= 0 then
return d
else
return -d
end
end
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
# The character which code point (unicode-wise) is `self`
#
# assert 65.code_point == 'A'
# assert 10.code_point == '\n'
# assert 0x220B.code_point == '∋'
fun code_point: Char is intern `{ return (uint32_t)self; `}
# Number of digits of an integer in base `b` (plus one if negative)
#
# assert 123.digit_count(10) == 3
# assert 123.digit_count(2) == 7 # 1111011 in binary
fun digit_count(b: Int): Int
do
if b == 10 then return digit_count_base_10
var d: Int # number of digits
var n: Int # current number
# Sign
if self < 0 then
d = 1
n = - self
else if self == 0 then
return 1
else
d = 0
n = self
end
# count digits
while n > 0 do
d += 1
n = n / b # euclidian division /
end
return d
end
# Optimized version for base 10
fun digit_count_base_10: Int
do
var val: Int
var result: Int
if self < 0 then
result = 2
val = -self
else
result = 1
val = self
end
loop
if val < 10 then return result
if val < 100 then return result+1
if val < 1000 then return result+2
if val < 10000 then return result+3
val = val / 10000
result += 4
end
end
# Return the corresponding digit character
# If 0 <= `self` <= 9, return the corresponding character.
#
# assert 5.to_c == '5'
#
# If 10 <= `self` <= 36, return the corresponding letter [a..z].
#
# assert 15.to_c == 'f'
fun to_c: Char
do
assert self >= 0 and self <= 36 # TODO plan for this
if self < 10 then
return (self + '0'.code_point).code_point
else
return (self - 10 + 'a'.code_point).code_point
end
end
# The absolute value of self
#
# assert (-10).abs == 10
# assert 10.abs == 10
# assert 0.abs == 0
fun abs: Int do return if self >= 0 then self else -self
# Is `self` an ASCII whitespace ?
fun is_whitespace: Bool do return self == 0x7F or self <= 0x20
end
lib/core/kernel.nit:702,1--886,3
redef class Int
# Returns the range from 0 to `self-1`.
#
# assert 3.times == [0..3[
# assert 10.times == [0..10[
# assert ((-1).times).is_empty
#
# This can be usefull for loops:
#
# var s = new Array[String]
# for i in 3.times do s.add "cool"
# assert s.join(" ") == "cool cool cool"
fun times: Range[Int] do return [0 .. self[
end
lib/core/collection/range.nit:240,1--253,3
redef class Int
# Returns a random `Int` in `[0 .. self[`.
fun rand: Int `{
if (nit_rand_seeded) return (long)(((double)self)*nit_rand()/(NIT_RAND_MAX+1.0));
return (long)(((double)self)*rand()/(RAND_MAX+1.0));
`}
# Returns the result of a binary AND operation on `self` and `i`
#
# assert 0x10 & 0x01 == 0
fun &(i: Int): Int is intern `{ return self & i; `}
# Returns the result of a binary OR operation on `self` and `i`
#
# assert 0x10 | 0x01 == 0x11
fun |(i: Int): Int is intern `{ return self | i; `}
# Returns the result of a binary XOR operation on `self` and `i`
#
# assert 0x101 ^ 0x110 == 0x11
fun ^(i: Int): Int `{ return self ^ i; `}
# Returns the 1's complement of `self`
#
# assert ~0x2F == -48
fun ~: Int `{ return ~self; `}
# Returns the square root of `self`
#
# assert 16.sqrt == 4
fun sqrt: Int `{ return sqrt(self); `}
# Returns the greatest common divisor of `self` and `o`
#
# assert 54.gcd(24) == 6
# assert -54.gcd(-24) == 6
# assert 54.gcd(-24) == -6
# assert -54.gcd(24) == -6
# assert 12.gcd(6) == 6
fun gcd(o: Int): Int
do
if self < 0 then return -(-self).gcd(o)
if o < 0 then return -(self.gcd(-o))
if self == 0 or o == self then return o
if o == 0 then return self
if self & 1 == 0 then
if o & 1 == 1 then
return (self >> 1).gcd(o)
else
return (self >> 1).gcd(o >> 1) << 1
end
end
if o & 1 == 0 then return self.gcd(o >> 1)
if self > o then return ((self - o) >> 1).gcd(o)
return ((o - self) >> 1).gcd(self)
end
# Is `self` even ?
#
# assert 12.is_even
fun is_even: Bool do return self % 2 == 0
# Is `self` odd ?
#
# assert not 13.is_even
fun is_odd: Bool do return not is_even
# Is self a prime number ?
#
# assert 3.is_prime
# assert not 1.is_prime
# assert not 15.is_prime
fun is_prime: Bool
do
if self == 2 then
return true
else if self <= 1 or self.is_even then
return false
end
for i in [3..self.sqrt] do
if self % i == 0 then return false
end
return true
end
# Returns the `self` raised to the power of `e`.
#
# assert 2 ** 3 == 8
fun **(e: Int): Int
do
return self.to_f.pow(e.to_f).to_i
end
# The factorial of `self` (aka `self!`)
#
# Returns `1 * 2 * 3 * ... * self-1 * self`
#
# assert 0.factorial == 1 # by convention for an empty product
# assert 1.factorial == 1
# assert 4.factorial == 24
# assert 9.factorial == 362880
fun factorial: Int
do
assert self >= 0
var res = 1
var n = self
while n > 0 do
res = res * n
n -= 1
end
return res
end
# Is `self` a power of two ?
#
# ~~~nit
# assert not 3.is_pow2
# assert 2.is_pow2
# assert 1.is_pow2
# assert not 0.is_pow2
# ~~~
fun is_pow2: Bool do return self != 0 and (self & self - 1) == 0
end
lib/core/math.nit:60,1--182,3
# Add support of binary operations related to binary level of Integer
# For compatibility reasons, xor, and, or methods are still in the `math` module.
redef class Int
# Sets the i-bit of self to the given `value`
#
# assert 11.setbit(0, 0) == 10
# assert 10.setbit(0, 1) == 11
fun setbit(index: Int, value: Int): Int `{
assert(index >= 0 && index < 32);
if(value == 1)
return self | (1 << index);
else
return self & ~(1 << index);
`}
# Returns the i-bit value of `self`
#
# assert 10.getbit(0) == 0
# assert 10.getbit(3) == 1
fun getbit(index: Int): Int `{
assert(index >= 0 && index < 32);
int op = 1 << index;
if((self & op) == 0)
return 0;
else
return 1;
`}
# Give a binary representation of self Integer
fun bits: Array[Int]
do
var bits = new Array[Int].with_capacity(32)
for i in [0..32[
do
bits[i] = getbit(i)
end
return bits
end
# Returns the number of bits of specified value (0 or 1) in `self`
#
# assert 10.number_bits(1) == 2
# assert 10.number_bits(0) == 30
fun number_bits(value: Int): Int `{
assert(value == 0 || value == 1);
long int bound = 1L << 31;
int count = 0;
long int i;
if(value == 1)
{
for(i=bound; i>0; i/=2)
{
if(self & i)
count++;
}
}
else
{
for(i=bound; i>0; i/=2)
{
if(!(self & i))
count++;
}
}
return count;
`}
# Returns the position of the highest bit set to 1 in `self`
#
# The rightmost bit is at position 0.
#
# assert 10.highest_bit == 3
# assert 1.highest_bit == 0
fun highest_bit: Int `{
long int msb = 1L << 31;
int pos = 31;
while(msb > 0 && !(self & msb))
{
msb /= 2;
pos--;
}
return pos;
`}
end
lib/core/bitset.nit:27,1--120,3
redef class Int
# Gives the length of the UTF-8 char starting with `self`
fun u8len: Int do
if self & 0b1000_0000 == 0 then
return 1
else if self & 0b1110_0000 == 0b1100_0000 then
return 2
else if self & 0b1111_0000 == 0b1110_0000 then
return 3
else if self & 0b1111_1000 == 0b1111_0000 then
return 4
else
return 1
end
end
# Is `self` a valid UTF-8 sequence start ?
#
# ~~~nit
# assert 0.is_valid_utf8_start
# assert 0xC0.is_valid_utf8_start
# assert 0xE0.is_valid_utf8_start
# assert 0xF0.is_valid_utf8_start
# ~~~
fun is_valid_utf8_start: Bool do
if self & 0x80 == 0 then return true
if self & 0b1110_0000 == 0b1100_0000 then return true
if self & 0b1111_0000 == 0b1110_0000 then return true
if self & 0b1111_1000 == 0b1111_0000 then return true
return false
end
end
lib/core/text/native.nit:38,1--69,3
redef class Int
# Wrapper of strerror C function
private fun strerror_ext: CString `{ return strerror((int)self); `}
# Returns a string describing error number
fun strerror: String do return strerror_ext.to_s
# Fill `s` with the digits in base `base` of `self` (and with the '-' sign if negative).
# assume < to_c max const of char
private fun fill_buffer(s: Buffer, base: Int)
do
var n: Int
# Sign
if self < 0 then
n = - self
s.chars[0] = '-'
else if self == 0 then
s.chars[0] = '0'
return
else
n = self
end
# Fill digits
var pos = digit_count(base) - 1
while pos >= 0 and n > 0 do
s.chars[pos] = (n % base).to_c
n = n / base # /
pos -= 1
end
end
# C function to calculate the length of the `CString` to receive `self`
private fun int_to_s_len: Int `{
return snprintf(NULL, 0, "%ld", self);
`}
# C function to convert an nit Int to a CString (char*)
private fun native_int_to_s(nstr: CString, strlen: Int) `{
snprintf(nstr, strlen, "%ld", self);
`}
# String representation of `self` in the given `base`
#
# ~~~
# assert 15.to_base(10) == "15"
# assert 15.to_base(16) == "f"
# assert 15.to_base(2) == "1111"
# assert (-10).to_base(3) == "-101"
# ~~~
fun to_base(base: Int): String
do
var l = digit_count(base)
var s = new Buffer
s.enlarge(l)
for x in [0..l[ do s.add(' ')
fill_buffer(s, base)
return s.to_s
end
# return displayable int in hexadecimal
#
# ~~~
# assert 1.to_hex == "1"
# assert (-255).to_hex == "-ff"
# ~~~
fun to_hex: String do return to_base(16)
end
lib/core/text/abstract_text.nit:1956,1--2024,3
redef class Int
# return displayable int in base 10 and signed
#
# assert 1.to_s == "1"
# assert (-123).to_s == "-123"
redef fun to_s do
# Fast case for common numbers
if self == 0 then return "0"
if self == 1 then return "1"
var nslen = int_to_s_len
var ns = new CString(nslen + 1)
ns[nslen] = 0
native_int_to_s(ns, nslen + 1)
return new FlatString.full(ns, nslen, 0, nslen)
end
end
lib/core/text/flat.nit:1465,1--1481,3
redef class Int
super BytePattern
# Write self as a string into `ns` at position `pos`
private fun add_digest_at(ns: CString, pos: Int) do
var tmp = (0xF0 & self) >> 4
ns[pos] = if tmp >= 0x0A then tmp + 0x37 else tmp + 0x30
tmp = 0x0F & self
ns[pos + 1] = if tmp >= 0x0A then tmp + 0x37 else tmp + 0x30
end
# Is `self` a valid hexadecimal digit (in ASCII)
#
# ~~~nit
# intrude import core::bytes
# assert not u'/'.is_valid_hexdigit
# assert u'0'.is_valid_hexdigit
# assert u'9'.is_valid_hexdigit
# assert not u':'.is_valid_hexdigit
# assert not u'@'.is_valid_hexdigit
# assert u'A'.is_valid_hexdigit
# assert u'F'.is_valid_hexdigit
# assert not u'G'.is_valid_hexdigit
# assert not u'`'.is_valid_hexdigit
# assert u'a'.is_valid_hexdigit
# assert u'f'.is_valid_hexdigit
# assert not u'g'.is_valid_hexdigit
# ~~~
private fun is_valid_hexdigit: Bool do
return (self >= 0x30 and self <= 0x39) or
(self >= 0x41 and self <= 0x46) or
(self >= 0x61 and self <= 0x66)
end
# `self` as a hexdigit to its byte value
#
# ~~~nit
# intrude import core::bytes
# assert 0x39.hexdigit_to_byteval == 0x09
# assert 0x43.hexdigit_to_byteval == 0x0C
# ~~~
#
# REQUIRE: `self.is_valid_hexdigit`
private fun hexdigit_to_byteval: Int do
if self >= 0x30 and self <= 0x39 then
return self - 0x30
else if self >= 0x41 and self <= 0x46 then
return self - 0x37
else if self >= 0x61 and self <= 0x66 then
return self - 0x57
end
# Happens only if the requirement is not met.
# i.e. this abort is here to please the compiler
abort
end
redef fun first_index_in_from(b, from) do
for i in [from .. b.length[ do if b[i] == self then return i
return -1
end
redef fun last_index_in_from(b, from) do
for i in [0 .. from].step(-1) do if b[i] == self then return i
return -1
end
redef fun search_all_in(b) do
var ret = new Array[Int]
var pos = 0
loop
pos = first_index_in_from(b, pos)
if pos == -1 then return ret
ret.add pos
pos += 1
end
end
redef fun pattern_length do return 1
redef fun append_to(b) do b.push self
# assert u'b'.is_suffix("baqsdb".to_bytes)
# assert not u'b'.is_suffix("baqsd".to_bytes)
redef fun is_suffix(b) do return b.length != 0 and b.last == self
# assert u'b'.is_prefix("baqsdb".to_bytes)
# assert not u'b'.is_prefix("aqsdb".to_bytes)
redef fun is_prefix(b) do return b.length != 0 and b.first == self
# 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
end
lib/core/bytes.nit:52,1--233,3
redef universal Int
redef fun add(other)
do
if other isa Float then
return to_f + other
else
return self + other.as(Int)
end
end
redef fun sub(other)
do
if other isa Float then
return to_f - other
else
return self - other.as(Int)
end
end
redef fun mul(other)
do
if other isa Float then
return to_f * other
else
return self * other.as(Int)
end
end
redef fun div(other)
do
if other isa Float then
return to_f / other
else if other isa Int then
if other == 0 then return self.to_f / 0.0
return self / other
else abort
end
end
lib/core/numeric.nit:85,1--122,3
redef class Int
# Creates a file stream from a file descriptor `fd` using the file access `mode`.
#
# NOTE: The `mode` specified must be compatible with the one used in the file descriptor.
private fun fd_to_stream(mode: CString): NativeFile `{
return fdopen((int)self, mode);
`}
# Does the file descriptor `self` refer to a terminal?
fun isatty: Bool `{ return isatty(self); `}
end
lib/core/file.nit:302,1--312,3
redef class Int
# Is `self` a valid Base64 character ?
fun is_base64_char: Bool do
if self == u'+' then return true
if self == u'/' then return true
if self > u'Z' then
if self < u'a' then return false
if self <= u'z' then return true
return false
end
if self >= u'A' then return true
if self <= u'9' and self >= u'0' then return true
return false
end
# Returns the `base64` equivalent of `self`
#
# REQUIRE `self`.`is_base64_char`
fun to_base64_char: Int do
if self == u'+' then return 62
if self == u'/' then return 63
if self > u'Z' then
if self < u'a' then abort
if self <= u'z' then return self - 71
abort
end
if self >= u'A' then return self - 0x41
if self <= u'9' and self >= u'0' then return self + 4
abort
end
end
lib/base64/base64.nit:28,1--58,3
redef universal Int
fun bcm2835_delay `{ bcm2835_delay(self); `}
fun bcm2835_delay_micros `{ bcm2835_delayMicroseconds(self); `}
end
lib/bcm2835/bcm2835.nit:121,1--124,3
redef class Int
# Utility for `BinaryWriter`
private fun int64_byte_at(index: Int, big_endian: Bool): Int `{
union {
unsigned char bytes[8];
int64_t val;
uint64_t conv;
} u;
u.val = self;
if (big_endian)
u.conv = htobe64(u.conv);
else u.conv = htole64(u.conv);
return u.bytes[index];
`}
end
lib/binary/binary.nit:342,1--359,3
redef class Int
# Generates the paces for each depth.
#
# Each entry of the returned array is a couple of the first pace
# and the second one, they are alternated when deciphering a rail-encrypted string.
#
# Say we have the encrypted string "fgounbmtcieehkh" on 4 rails
#
# To find the distance between each character on the original railed
# string, we need to compute the extremes.
#
# The extremes always have a distance of `depth - 1`, multiplied by 2, no pairing.
#
# In the example, that would be : [(4 - 1) * 2, (4 - 1) * 2] => [6,6]
#
# For every rail in-between, the first distance is the largest absolute value
# of the difference between the current depth and the extremes, multiplied by 2.
#
# Its pair is the distance of maximum and the distance yielded by the previous
# calculation.
#
# In our example, that would be :
#
# Maximums : (4 - 1) * 2 = 3 * 2 => [6,6]
# In between : Distance for depth 2 : max(2 - 1, 4 - 2) => 2
# The calculation yields the couple [(2 * 2), 6 - 4] => [4, 2]
# The symmetric couple is reversed : [2, 4]
#
# In fine, the example yields the array : [[6,6], [4,2], [2,4], [6,6]]
#
# In the end, our string is read using the generated array
#
# SEE: `Text::unrail` for how the array is used
private fun unrail_paces: Array[Couple[Int, Int]] do
var ret = new Array[Couple[Int,Int]].with_capacity(self)
var extremes = new Couple[Int, Int]((self - 1) * 2, (self - 1) * 2)
for i in [0..self[ do
ret.add extremes
end
var mid = ((self.to_f)/2.0).floor.to_i
for i in [1 .. mid[ do
var rd = i + 1
var lodepth = self - rd
var hidepth = (rd - self).abs
var dd: Int
if hidepth > lodepth then
dd = hidepth * 2
else
dd = lodepth * 2
end
var cp = new Couple[Int, Int](dd, extremes.first-dd)
var ccp = new Couple[Int, Int](extremes.first - dd, dd)
ret[i] = cp
ret[self - rd] = ccp
end
if not self.is_even then
ret[mid] = new Couple[Int, Int](extremes.first/2, extremes.first/2)
end
return ret
end
end
lib/crypto/basic_ciphers.nit:228,1--289,3
redef class Int
# Returns a coloured square for a defined colour id
#
# Assume colours are:
#
# * Green -> 0
# * White (replaced with light gray) -> 1
# * Red -> 2
# * Yellow -> 3
# * Orange (replaced with purple) -> 4
# * Blue -> 5
#
private fun rubix_colour: String do
if self == 0 then return square.green
if self == 1 then return square.light_gray
if self == 2 then return square.red
if self == 3 then return square.yellow
if self == 4 then return square.purple
if self == 5 then return square.blue
abort
end
end
lib/rubix/rubix.nit:53,1--75,3
redef universal Int super Sqlite3Data end
lib/sqlite3/sqlite3.nit:317,1--41
redef class Int super DirectSerializable end
lib/serialization/serialization_core.nit:261,1--44
redef class Int
redef fun accept_msgpack_serializer(v) do v.stream.write_msgpack_int self
end
lib/msgpack/serialization_write.nit:248,1--250,3
redef universal Int
# `self`th MPI rank
fun rank: Rank `{ return self; `}
# Tag identified by `self`
fun tag: Tag `{ return self; `}
# Is this value undefined according to MPI? (may be returned by `Status::count`)
fun is_undefined: Bool `{ return self == MPI_UNDEFINED; `}
end
lib/mpi/mpi.nit:378,1--387,3