core :: CString :: byte_to_char_index_cached
Gets the char index of byte at positionn in a UTF-8 String
			core :: CString :: char_to_byte_index
Gets the byte index of char at positionn in UTF-8 String
			core :: CString :: char_to_byte_index_cached
Gets the byte index of char at positionn in UTF-8 String
			core :: CString :: check_base64
Isself a well-formed Base64 entity ?
			core :: CString :: defaultinit
core :: CString :: fast_cstring
Get a char* starting atindex.
			core :: CString :: fetch_4_chars
Fetch 4 chars inself at pos
			core :: CString :: fetch_4_hchars
Fetch 4 chars inself at pos
			core :: CString :: find_beginning_of_char_at
Returns the beginning position of the char at positionpos
			core :: CString :: length_of_char_at
Gets the length of the character at positionpos (1 if invalid sequence)
			core :: CString :: to_bytes_with_copy
Creates a newBytes object from a copy of self with len as length
			core :: CString :: to_java_string
Get a Java string from this C stringcore :: CString :: to_nsstring
Get aNSString from self with the specified length
			core :: CString :: to_s_unsafe
Get aString from the data at self (with unsafe options)
			core :: CString :: to_s_with_length
Get aString from byte_length bytes at self copied into Nit memory
			core :: CString :: utf8_length
Number of UTF-8 characters inself starting at from, for a length of byte_length
			json :: serialization_write $ CString :: accept_json_serializer
Refinable service to customize the serialization of this class to JSONmsgpack :: serialization_write $ CString :: accept_msgpack_serializer
Hook to customize the serialization of this class to MessagePackcore :: flat $ CString :: to_s_unsafe
Get aString from the data at self (with unsafe options)
			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 :: Pointer :: address_is_null
Is the address behind this Object at NULL?core :: CString :: byte_to_char_index_cached
Gets the char index of byte at positionn in a UTF-8 String
			core :: CString :: char_to_byte_index
Gets the byte index of char at positionn in UTF-8 String
			core :: CString :: char_to_byte_index_cached
Gets the byte index of char at positionn in UTF-8 String
			core :: CString :: check_base64
Isself a well-formed Base64 entity ?
			core :: Object :: class_factory
Implementation used byget_class to create the specific class.
			serialization :: Serializable :: core_serialize_to
Actual serialization ofself to serializer
			core :: CString :: defaultinit
c :: NativeCArray :: defaultinit
core :: Pointer :: defaultinit
core :: Object :: defaultinit
core :: CString :: fast_cstring
Get a char* starting atindex.
			core :: CString :: fetch_4_chars
Fetch 4 chars inself at pos
			core :: CString :: fetch_4_hchars
Fetch 4 chars inself at pos
			core :: CString :: find_beginning_of_char_at
Returns the beginning position of the char at positionpos
			serialization :: Serializable :: from_deserializer
Create an instance of this class from thedeserializer
			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 :: CString :: length_of_char_at
Gets the length of the character at positionpos (1 if invalid sequence)
			serialization :: Serializable :: msgpack_extra_array_items
Hook to request a larger than usual metadata arraycore :: Object :: output_class_name
Display class name on stdout (debug only).serialization :: Serializable :: serialize_msgpack
Serializeself to MessagePack bytes
			serialization :: Serializable :: serialize_to
Serializeself to serializer
			serialization :: Serializable :: serialize_to_json
Serializeself to JSON
			core :: CString :: to_bytes_with_copy
Creates a newBytes object from a copy of self with len as length
			core :: CString :: to_java_string
Get a Java string from this C stringcore :: CString :: to_nsstring
Get aNSString from self with the specified length
			serialization :: Serializable :: to_pretty_json
Serializeself to plain pretty JSON
			core :: CString :: to_s_unsafe
Get aString from the data at self (with unsafe options)
			core :: CString :: to_s_with_length
Get aString from byte_length bytes at self copied into Nit memory
			core :: CString :: utf8_length
Number of UTF-8 characters inself starting at from, for a length of byte_length
			Serializer::serialize
			serialization :: DirectSerializable
Instances of this class are not delayed and instead serialized immediatelyc :: NativeCArray
A native C array, as in a pointer to the first element of the array
# C string `char *`
#
# Used as underlying implementation for `String` and some other `Text`.
extern class CString `{ char* `}
	# Create a new `CString` with the capacity for `length` characters
	new(length: Int) is intern
	# Get a char* starting at `index`.
	#
	# WARNING: Unsafe for extern code, use only for temporary
	# pointer manipulation purposes (e.g. write to file or such)
	fun fast_cstring(index: Int): CString is intern
	# Get char at `index`.
	fun [](index: Int): Int is intern
	# Set char `item` at index.
	fun []=(index: Int, item: Int) is intern
	# Copy `self` to `dest`.
	fun copy_to(dest: CString, length: Int, from: Int, to: Int) is intern
	redef fun ==(o) is intern do return is_same_instance(o)
	redef fun !=(o) is intern do return not is_same_instance(o)
	# Position of the first nul character.
	fun cstring_length: Int
	do
		var l = 0
		while self[l] != 0 do l += 1
		return l
	end
	# Parse `self` as an Int.
	fun atoi: Int is intern
	# Parse `self` as a Float.
	fun atof: Float `{ return atof(self); `}
	# Gets the UTF-8 char at index `pos`
	#
	# Index is expressed in Unicode chars
	#
	# ~~~raw
	#     assert "かきく".as(FlatString).items.char_at(0) == 'か'
	# ~~~
	#
	# If the char at position pos is an invalid Unicode char,
	# the Unicode replacement character � (0xFFFD) will be used.
	#
	# ~~~raw
	#     assert "かきく".as(FlatString).items.char_at(1) == '�'
	# ~~~
	fun char_at(pos: Int): Char do
		var c = self[pos]
		if c & 0x80 == 0 then return c.code_point
		var b = fetch_4_hchars(pos)
		var ret = 0u32
		if b & 0xC00000u32 != 0x800000u32 then return 0xFFFD.code_point
		if b & 0xE0000000u32 == 0xC0000000u32 then
			ret |= (b & 0x1F000000u32) >> 18
			ret |= (b & 0x3F0000u32) >> 16
			return ret.code_point
		end
		if not b & 0xC000u32 == 0x8000u32 then return 0xFFFD.code_point
		if b & 0xF0000000u32 == 0xE0000000u32 then
			ret |= (b & 0xF000000u32) >> 12
			ret |= (b & 0x3F0000u32) >> 10
			ret |= (b & 0x3F00u32) >> 8
			return ret.code_point
		end
		if not b & 0xC0u32 == 0x80u32 then return 0xFFFD.code_point
		if b & 0xF8000000u32 == 0xF0000000u32 then
			ret |= (b & 0x7000000u32) >> 6
			ret |= (b & 0x3F0000u32) >> 4
			ret |= (b & 0x3F00u32) >> 2
			ret |= b & 0x3Fu32
			return ret.code_point
		end
		return 0xFFFD.code_point
	end
	# Gets the byte index of char at position `n` in UTF-8 String
	fun char_to_byte_index(n: Int): Int do return char_to_byte_index_cached(n, 0, 0)
	# Gets the length of the character at position `pos` (1 if invalid sequence)
	fun length_of_char_at(pos: Int): Int do
		var c = self[pos]
		if c & 0x80 == 0x00 then
			return 1
		else if c & 0xE0 == 0xC0 and self[pos + 1] & 0xC0 == 0x80 then
			return 2
		else if c & 0xF0 == 0xE0 and self[pos + 1] & 0xC0 == 0x80 and self[pos + 2] & 0xC0 == 0x80 then
			return 3
		else if c & 0xF8 == 0xF0 and self[pos + 1] & 0xC0 == 0x80 and self[pos + 2] & 0xC0 == 0x80 and self[pos + 3] & 0xC0 == 0x80 then
			return 4
		else
			return 1
		end
	end
	# Gets the byte index of char at position `n` in UTF-8 String
	#
	# `char_from` and `byte_from` are cached values to seek from.
	#
	# NOTE: char_from and byte_from are not guaranteed to be valid cache values
	# It it up to the client to ensure the validity of the information
	fun char_to_byte_index_cached(n, char_from, byte_from: Int): Int do
		var ns_i = byte_from
		var my_i = char_from
		var dist = n - my_i
		while dist > 0 do
			while dist >= 4 do
				var i = fetch_4_chars(ns_i)
				if i & 0x80808080u32 != 0u32 then break
				ns_i += 4
				my_i += 4
				dist -= 4
			end
			if dist == 0 then break
			ns_i += length_of_char_at(ns_i)
			my_i += 1
			dist -= 1
		end
		while dist < 0 do
			while dist <= -4 do
				var i = fetch_4_chars(ns_i - 4)
				if i & 0x80808080u32 != 0u32 then break
				ns_i -= 4
				my_i -= 4
				dist += 4
			end
			if dist == 0 then break
			ns_i = find_beginning_of_char_at(ns_i - 1)
			my_i -= 1
			dist += 1
		end
		return ns_i
	end
	# Gets the char index of byte at position `n` in a UTF-8 String
	#
	# `char_from` and `byte_from` are cached values to seek from.
	#
	# NOTE: char_from and byte_from are not guaranteed to be valid cache values
	# It it up to the client to ensure the validity of the information
	fun byte_to_char_index_cached(n, char_from, byte_from: Int): Int do
		var ns_i = byte_from
		var my_i = char_from
		while ns_i < n do
			ns_i += length_of_char_at(ns_i)
			my_i += 1
		end
		while ns_i > n do
			ns_i = find_beginning_of_char_at(ns_i - 1)
			my_i -= 1
		end
		return my_i
	end
	# Returns the beginning position of the char at position `pos`
	#
	# If the char is invalid UTF-8, `pos` is returned as-is
	#
	# ~~~raw
	#	assert "abc".items.find_beginning_of_char_at(2) == 2
	#	assert "か".items.find_beginning_of_char_at(1) == 0
	#	assert [0x41, 233].to_s.items.find_beginning_of_char_at(1) == 1
	# ~~~
	fun find_beginning_of_char_at(pos: Int): Int do
		var endpos = pos
		var c = self[pos]
		if c & 0x80 == 0x00 then return pos
		while c & 0xC0 == 0x80 do
			pos -= 1
			c = self[pos]
		end
		var stpos = pos
		if length_of_char_at(stpos) >= (endpos - stpos + 1) then return pos
		return endpos
	end
	# Number of UTF-8 characters in `self` starting at `from`, for a length of `byte_length`
	fun utf8_length(from, byte_length: Int): Int is intern do
		var st = from
		var ln = 0
		while byte_length > 0 do
			while byte_length >= 4 do
				var i = fetch_4_chars(st)
				if i & 0x80808080u32 != 0u32 then break
				byte_length -= 4
				st += 4
				ln += 4
			end
			if byte_length == 0 then break
			var cln = length_of_char_at(st)
			st += cln
			ln += 1
			byte_length -= cln
		end
		return ln
	end
	# Fetch 4 chars in `self` at `pos`
	fun fetch_4_chars(pos: Int): UInt32 is intern `{ return *((uint32_t*)(self+pos)); `}
	# Fetch 4 chars in `self` at `pos`
	fun fetch_4_hchars(pos: Int): UInt32 is intern `{ return (uint32_t)be32toh(*((uint32_t*)(self+pos))); `}
	# Right shifts `len` bytes of `self` from `sh` bytes starting at position `pos`
	fun rshift(sh, len, pos: Int) do
		copy_to(self, len, pos, pos + sh)
	end
	# Left shifts `len` bytes of `self` from `sh` bytes starting at position `pos`
	fun lshift(sh, len, pos: Int) do
		copy_to(self, len, pos, pos - sh)
	end
	# Sets the contents of `self` to `value` for `len` bytes
	fun memset(value, len: Int) `{
		assert(len >= 0);
		memset(self, value, len);
	`}
end
					lib/core/text/native.nit:93,1--325,3
				
redef class CString
	# Get a `String` from the data at `self` (with unsafe options)
	#
	# The default behavior is the safest and equivalent to `to_s`.
	#
	# Options:
	#
	# * Set `byte_length` to the number of bytes to use as data.
	#   Otherwise, this method searches for a terminating null byte.
	#
	# * Set `char_length` to the number of Unicode character in the string.
	#   Otherwise, the data is read to count the characters.
	#   Ignored if `clean == true`.
	#
	# * If `copy == true`, the default, copies the data at `self` in the
	#   Nit GC allocated memory. Otherwise, the return may still point to
	#   the data at `self`.
	#
	# * If `clean == true`, the default, the string is cleaned of invalid UTF-8
	#   characters. If cleaning is necessary, the data is copied into Nit GC
	#   managed memory, whether or not `copy == true`.
	#   Don't clean only when the data has already been verified as valid UTF-8,
	#   other library services rely on UTF-8 compliant characters.
	fun to_s_unsafe(byte_length, char_length: nullable Int, copy, clean: nullable Bool): String is abstract
	# Retro-compatibility service use by execution engines
	#
	# TODO remove this method at the next c_src regen.
	private fun to_s_full(byte_length, char_length: Int): String do return to_s_unsafe(byte_length, char_length, false, false)
	# Copies the content of `src` to `self`
	#
	# NOTE: `self` must be large enough to contain `self.byte_length` bytes
	fun fill_from(src: Text) do src.copy_to_native(self, src.byte_length, 0, 0)
end
					lib/core/text/abstract_text.nit:2525,1--2560,3
				
redef class CString
	# Get a `String` from the data at `self` copied into Nit memory
	#
	# Require: `self` is a null-terminated string.
	redef fun to_s do return to_s_unsafe
	# Get a `String` from `byte_length` bytes at `self` copied into Nit memory
	#
	# The string is cleaned.
	fun to_s_with_length(byte_length: Int): String do return to_s_unsafe(byte_length)
	redef fun to_s_unsafe(byte_length, char_length, copy, clean)
	do
		byte_length = byte_length or else cstring_length
		clean = clean or else true
		copy = copy or else true
		# Clean?
		var str = null
		if clean then
			str = clean_utf8(byte_length)
			char_length = str.length
		else
			char_length = char_length or else utf8_length(0, byte_length)
		end
		# Copy? (if not already copied by `clean_utf8`)
		if copy and (str == null or str.items == self) then
			var new_cstr = new CString(byte_length + 1)
			copy_to(new_cstr, byte_length, 0, 0)
			new_cstr[byte_length] = 0
			str = new FlatString.full(new_cstr, byte_length, 0, char_length)
		end
		if str == null then
			str = new FlatString.full(self, byte_length, 0, char_length)
		end
		return str
	end
	# Cleans a CString if necessary
	fun clean_utf8(len: Int): FlatString do
		var replacements: nullable Array[Int] = null
		var end_length = len
		var pos = 0
		var chr_ln = 0
		var rem = len
		while rem > 0 do
			while rem >= 4 do
				var i = fetch_4_chars(pos)
				if i & 0x80808080u32 != 0u32 then break
				pos += 4
				chr_ln += 4
				rem -= 4
			end
			if rem == 0 then break
			var b = self[pos]
			if b & 0x80 == 0x00 then
				pos += 1
				chr_ln += 1
				rem -= 1
				continue
			end
			var nxst = length_of_char_at(pos)
			var ok_st: Bool
			if nxst == 1 then
				ok_st = b & 0x80 == 0
			else if nxst == 2 then
				ok_st = b & 0xE0 == 0xC0
			else if nxst == 3 then
				ok_st = b & 0xF0 == 0xE0
			else
				ok_st = b & 0xF8 == 0xF0
			end
			if not ok_st then
				if replacements == null then replacements = new Array[Int]
				replacements.add pos
				end_length += 2
				pos += 1
				rem -= 1
				chr_ln += 1
				continue
			end
			var ok_c: Bool
			var c = char_at(pos)
			var cp = c.code_point
			if nxst == 1 then
				ok_c = cp >= 0 and cp <= 0x7F
			else if nxst == 2 then
				ok_c = cp >= 0x80 and cp <= 0x7FF
			else if nxst == 3 then
				ok_c = cp >= 0x800 and cp <= 0xFFFF
				ok_c = ok_c and not (cp >= 0xD800 and cp <= 0xDFFF) and cp != 0xFFFE and cp != 0xFFFF
			else
				ok_c = cp >= 0x10000 and cp <= 0x10FFFF
			end
			if not ok_c then
				if replacements == null then replacements = new Array[Int]
				replacements.add pos
				end_length += 2
				pos += 1
				chr_ln += 1
				rem -= 1
				continue
			end
			var clen = c.u8char_len
			pos += clen
			rem -= clen
			chr_ln += 1
		end
		var ret = self
		if end_length != len then
			ret = new CString(end_length)
			var old_repl = 0
			var off = 0
			var repls = replacements.as(not null)
			var r = repls.items.as(not null)
			var imax = repls.length
			for i in [0 .. imax[ do
				var repl_pos = r[i]
				var chkln = repl_pos - old_repl
				copy_to(ret, chkln, old_repl, off)
				off += chkln
				ret[off] = 0xEF
				ret[off + 1] = 0xBF
				ret[off + 2] = 0xBD
				old_repl = repl_pos + 1
				off += 3
			end
			copy_to(ret, len - old_repl, old_repl, off)
		end
		return new FlatString.full(ret, end_length, 0, chr_ln)
	end
	# Sets the next bytes at position `pos` to the value of `c`, encoded in UTF-8
	#
	# Very unsafe, make sure to have room for this char prior to calling this function.
	private fun set_char_at(pos: Int, c: Char) do
		var cp = c.code_point
		if cp < 128 then
			self[pos] = cp
			return
		end
		var ln = c.u8char_len
		if ln == 2 then
			self[pos] = 0xC0 | ((cp & 0x7C0) >> 6)
			self[pos + 1] = 0x80 | (cp & 0x3F)
		else if ln == 3 then
			self[pos] = 0xE0 | ((cp & 0xF000) >> 12)
			self[pos + 1] = 0x80 | ((cp & 0xFC0) >> 6)
			self[pos + 2] = 0x80 | (cp & 0x3F)
		else if ln == 4 then
			self[pos] = 0xF0 | ((cp & 0x1C0000) >> 18)
			self[pos + 1] = 0x80 | ((cp & 0x3F000) >> 12)
			self[pos + 2] = 0x80 | ((cp & 0xFC0) >> 6)
			self[pos + 3] = 0x80 | (cp & 0x3F)
		end
	end
end
					lib/core/text/flat.nit:1303,1--1463,3
				
redef class CString
	# Creates a new `Bytes` object from `self` with `len` as length
	#
	# If `len` is null, strlen will determine the length of the Bytes
	fun to_bytes(len: nullable Int): Bytes do
		if len == null then len = cstring_length
		return new Bytes(self, len, len)
	end
	# Creates a new `Bytes` object from a copy of `self` with `len` as length
	#
	# If `len` is null, strlen will determine the length of the Bytes
	fun to_bytes_with_copy(len: nullable Int): Bytes do
		if len == null then len = cstring_length
		var nns = new CString(len)
		copy_to(nns, len, 0, 0)
		return new Bytes(nns, len, len)
	end
end
					lib/core/bytes.nit:1022,1--1040,3
				
redef class CString
	private fun file_exists: Bool `{
#ifdef _WIN32
		DWORD attribs = GetFileAttributesA(self);
		return attribs != INVALID_FILE_ATTRIBUTES;
#else
		FILE *hdl = fopen(self,"r");
		if(hdl != NULL){
			fclose(hdl);
		}
		return hdl != NULL;
#endif
	`}
	private fun file_stat: NativeFileStat `{
		struct stat buff;
		if(stat(self, &buff) != -1) {
			struct stat* stat_element;
			stat_element = malloc(sizeof(struct stat));
			return memcpy(stat_element, &buff, sizeof(struct stat));
		}
		return 0;
	`}
	private fun file_lstat: NativeFileStat `{
#ifdef _WIN32
		// FIXME use a higher level abstraction to support WIN32
		return NULL;
#else
		struct stat* stat_element;
		int res;
		stat_element = malloc(sizeof(struct stat));
		res = lstat(self, stat_element);
		if (res == -1) return NULL;
		return stat_element;
#endif
	`}
	private fun file_mkdir(mode: Int): Bool `{
#ifdef _WIN32
		return !mkdir(self);
#else
		return !mkdir(self, mode);
#endif
	`}
	private fun rmdir: Bool `{ return !rmdir(self); `}
	private fun file_delete: Bool `{
		return remove(self) == 0;
	`}
	private fun file_chdir: Bool `{ return !chdir(self); `}
	private fun file_realpath: CString `{
#ifdef _WIN32
		DWORD len = GetFullPathName(self, 0, NULL, NULL);
		char *buf = malloc(len+1); // FIXME don't leak memory
		len = GetFullPathName(self, len+1, buf, NULL);
		return buf;
#else
		return realpath(self, NULL);
#endif
	`}
end
					lib/core/file.nit:1396,1--1460,3
				
redef class CString
	# Execute self as a shell command.
	#
	# See the posix function system(3).
	fun system: Int `{
		int status = system(self);
#ifndef _WIN32
		if (WIFSIGNALED(status) && WTERMSIG(status) == SIGINT) {
			// system exited on SIGINT: in my opinion the user wants the main to be discontinued
			kill(getpid(), SIGINT);
		}
#endif
		return status;
	`}
end
					lib/core/exec.nit:461,1--475,3
				
redef class CString
	# Alphabet used by the base64 algorithm
	private fun base64_chars : Bytes
	do
		return b"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"
	end
	# Encodes `self` to base64.
	#
	# By default, uses "=" for padding.
	#
	#     assert "string".encode_base64 == "c3RyaW5n"
	private fun encode_base64(length: Int): Bytes do
		var base64_bytes = once base64_chars
		var steps = length / 3
		var bytes_in_last_step = length % 3
		var result_length = steps * 4
		if bytes_in_last_step > 0 then result_length += 4
		var result = new Bytes.with_capacity(result_length)
		var in_off = 0
		for s in [0 .. steps[ do
			var ind = (self[in_off] & 0b1111_1100) >> 2
			result.add base64_bytes[ind]
			ind = ((self[in_off] & 0b0000_0011) << 4) | ((self[in_off + 1] & 0b1111_0000) >> 4)
			result.add base64_bytes[ind]
			ind = ((self[in_off + 1] & 0b0000_1111) << 2) | ((self[in_off + 2] & 0b1100_0000) >> 6)
			result.add base64_bytes[ind]
			ind = (self[in_off + 2] & 0b0011_1111)
			result.add base64_bytes[ind]
			in_off += 3
		end
		if bytes_in_last_step == 1 then
			result.add base64_bytes[(self[in_off] & 0b1111_1100) >> 2]
			result.add base64_bytes[(self[in_off] & 0b0000_0011) << 4]
		else if bytes_in_last_step == 2 then
			result.add base64_bytes[(self[in_off] & 0b1111_1100) >> 2]
			result.add base64_bytes[((self[in_off] & 0b0000_0011) << 4) | ((self[in_off + 1] & 0b1111_0000) >> 4)]
			result.add base64_bytes[(self[in_off + 1] & 0b0000_1111) << 2]
		end
		var rempad = if bytes_in_last_step > 0 then 3 - bytes_in_last_step else 0
		for i in [0 .. rempad[ do result.add u'='
		return result
	end
	# Decodes `self` from base64
	#
	#      assert "c3RyaW5n".decode_base64.to_s == "string"
	#      assert "c3Rya\nW5n".decode_base64.to_s == "string"
	#      assert "c3RyaW5nCg==".decode_base64.to_s == "string\n"
	#      assert "c3RyaW5nCg".decode_base64.to_s == "string\n"
	#      assert "c3RyaW5neQo=".decode_base64.to_s == "stringy\n"
	#      assert "c3RyaW5neQo".decode_base64.to_s == "stringy\n"
	#
	private fun decode_base64(length: Int): Bytes do
		if length == 0 then return new Bytes.empty
		# Avoids constant unboxing
		var pad = '='
		var result = new Bytes.with_capacity((length / 4 + 1) * 3)
		var curr = 0
		var cnt = 0
		var endpos = -1
		for i in [0 .. length[ do
			var b = self[i]
			if b == pad then
				endpos = i
				break
			end
			# Ignore whitespaces
			if b <= 0x20 then continue
			if not b.is_base64_char then continue
			curr <<= 6
			curr += b.to_base64_char.to_i
			cnt += 1
			if cnt == 4 then
				result.add ((curr & 0xFF0000) >> 16)
				result.add ((curr & 0xFF00) >> 8)
				result.add (curr & 0xFF)
				curr = 0
				cnt = 0
			end
		end
		if endpos != -1 or cnt != 0 then
			var pads = 0
			for i in [endpos .. length[ do
				var b = self[i]
				if b <= 0x20 then continue
				pads += 1
			end
			if cnt == 2 then
				curr >>= 4
				result.add(curr)
			else if cnt == 3 then
				curr >>= 2
				result.add ((curr & 0xFF00) >> 8)
				result.add (curr & 0xFF)
			end
		end
		return result
	end
	# Is `self` a well-formed Base64 entity ?
	#
	# ~~~nit
	#	assert "Qn03".is_base64
	#	assert not "#sd=".is_base64
	# ~~~
	fun is_base64(length: Int): Bool do return check_base64(length) == null
	# Is `self` a well-formed Base64 entity ?
	#
	# Will return an Error otherwise with info on which part is erroneous.
	fun check_base64(length: Int): nullable Error do
		var rlen = 0
		var opos = length
		for i in [0 .. length[ do
			if self[i] == u'=' then
				opos = i
				break
			end
			if self[i].is_whitespace then continue
			if not self[i].is_base64_char then return new Error("Invalid Base64 character at position {i}: {self[i].code_point}")
			rlen += 1
			if rlen > 4 then rlen -= 4
		end
		var pad = 0
		for i in [opos .. length[ do
			if self[i].is_whitespace then continue
			if self[i] != u'=' then return new Error("Invalid padding character {self[i].code_point} at position {i}")
			pad += 1
		end
		if rlen + pad != 4 then return new Error("Invalid padding length")
		return null
	end
end
					lib/base64/base64.nit:60,1--198,3
				
redef class CString
	# Get a `NSString` from `self` with the specified `length`
	fun to_nsstring(length: Int): NSString in "ObjC" `{
		return [[NSString alloc] initWithBytes:self
			length:length
			encoding:NSUTF8StringEncoding];
	`}
end
					lib/cocoa/foundation.nit:43,1--50,3
				
redef class CString
	# In-place XOR `self` with `key`
	fun xor(key: CString, len: Int, key_length: Int, key_offset: nullable Int) do
		if key_offset == null then key_offset = 0
		var key_pos = key_offset % key_length
		for i in [0 .. len[ do
			self[i] = key[key_pos] ^ self[i]
			key_pos += 1
			if key_pos >= key_length then key_pos = 0
		end
	end
end
					lib/crypto/xor_ciphers.nit:35,1--48,3
				
redef extern class CString
	private fun native_callback_header(size, count: Int, target: NativeCurlCallbacks): Int
	do
		target.header_callback to_s_with_length(size*count)
		# FIXME we probably should return a value from the user
		return count
	end
	private fun native_callback_body(size, count: Int, target: NativeCurlCallbacks): Int
	do
		target.body_callback to_s_with_length(size*count)
		return count
	end
	private fun native_callback_stream(size, count: Int, target: NativeCurlCallbacks): Int
	do
		target.stream_callback to_s_with_length(size*count)
		return count
	end
end
					lib/curl/native_curl.nit:48,1--70,3
				
redef class CString
	# Sets the locale of the program running
	#
	# This can be set at different times in the program,
	# if used with an empty string, the locale will
	# be set to the user's environment locale.
	#
	# For more info, SEE setlocale manual
	fun set_locale `{
		setlocale(LC_ALL, self);
	`}
end
					lib/gettext/gettext.nit:32,1--43,3
				
redef class CString
	private fun native_md5: CString `{
		md5_state_t state;
		md5_byte_t digest[16]; /* result */
		char *hex_output = malloc(33*sizeof(char));
		int di;
		md5_init(&state);
		md5_append(&state, (const md5_byte_t *)self, (int)strlen(self));
		md5_finish(&state, digest);
		for (di = 0; di < 16; ++di)
			sprintf(hex_output + di * 2, "%02x", digest[di]);
		hex_output[32] = '\0';
		return hex_output;
	`}
end
					lib/md5/md5.nit:503,1--520,3
				
redef class CString
	private fun sha1_intern(len: Int): CString `{
		sha1nfo s;
		sha1_init(&s);
		sha1_write(&s, self, len);
		uint8_t* digest = sha1_result(&s);
		char* digested = malloc(21);
		memcpy(digested, digest, 20);
		digested[20] = '\0';
		return digested;
	`}
end
					lib/sha1/sha1.nit:220,1--236,3
				
redef class CString
	# Get a Java string from this C string
	#
	# This instance is only valid until the next execution of Java code.
	# You can use `new_local_ref` to keep it longer.
	fun to_java_string: JavaString import sys, Sys.jni_env `{
		Sys sys = JavaString_sys(self);
		JNIEnv *env = Sys_jni_env(sys);
		return (*env)->NewStringUTF(env, self);
	`}
end
					lib/java/ffi_support.nit:122,1--132,3
				
redef class CString super DirectSerializable end
					lib/serialization/serialization_core.nit:263,1--48
				
redef class CString
	redef fun accept_json_serializer(v) do to_s.accept_json_serializer(v)
end
					lib/json/serialization_write.nit:302,1--304,3
				
redef class CString
	redef fun accept_msgpack_serializer(v) do to_s.accept_msgpack_serializer(v)
end
					lib/msgpack/serialization_write.nit:293,1--295,3