Property definitions

core $ Text :: defaultinit
# High-level abstraction for all text representations
abstract class Text
	super Comparable
	super Cloneable

	redef type OTHER: Text

	# Type of self (used for factorization of several methods, ex : substring_from, empty...)
	type SELFTYPE: Text

	# Gets a view on the chars of the Text object
	#
	# ~~~
	# assert "hello".chars.to_a == ['h', 'e', 'l', 'l', 'o']
	# ~~~
	fun chars: SequenceRead[Char] is abstract

	# Gets a view on the bytes of the Text object
	#
	# ~~~
	# assert "hello".bytes.to_a == [104, 101, 108, 108, 111]
	# ~~~
	fun bytes: SequenceRead[Int] is abstract

	# Number of characters contained in self.
	#
	# ~~~
	# assert "12345".length == 5
	# assert "".length == 0
	# assert "あいうえお".length == 5
	# ~~~
	fun length: Int is abstract

	# Number of bytes in `self`
	#
	# ~~~
	# assert "12345".byte_length == 5
	# assert "あいうえお".byte_length == 15
	# ~~~
	fun byte_length: Int is abstract

	# Create a substring.
	#
	# ~~~
	# assert "abcd".substring(1, 2)      ==  "bc"
	# assert "abcd".substring(-1, 2)     ==  "a"
	# assert "abcd".substring(1, 0)      ==  ""
	# assert "abcd".substring(2, 5)      ==  "cd"
	# assert "あいうえお".substring(1,3) ==  "いうえ"
	# ~~~
	#
	# A `from` index < 0 will be replaced by 0.
	# Unless a `count` value is > 0 at the same time.
	# In this case, `from += count` and `count -= from`.
	fun substring(from: Int, count: Int): SELFTYPE is abstract

	# Iterates on the substrings of self if any
	private fun substrings: Iterator[FlatText] is abstract

	# Is the current Text empty (== "")
	#
	# ~~~
	# assert "".is_empty
	# assert not "foo".is_empty
	# ~~~
	fun is_empty: Bool do return self.length == 0

	# Returns an empty Text of the right type
	#
	# This method is used internally to get the right
	# implementation of an empty string.
	protected fun empty: SELFTYPE is abstract

	# Returns a copy of `self` as a Buffer
	fun to_buffer: Buffer is abstract

	# Gets the first char of the Text
	fun first: Char do return self.chars[0]

	# Access a character at `index` in the string.
	#
	# ~~~
	# assert "abcd"[2]         == 'c'
	# ~~~
	fun [](index: Int): Char do return self.chars[index]

	# Gets the index of the first occurence of 'c'
	#
	# Returns -1 if not found
	fun index_of(c: Char): Int
	do
		return index_of_from(c, 0)
	end

	# Gets the last char of self
	fun last: Char do return self.chars[length-1]

	# Gets the index of the first occurence of ´c´ starting from ´pos´
	#
	# Returns -1 if not found
	fun index_of_from(c: Char, pos: Int): Int
	do
		var iter = self.chars.iterator_from(pos)
		while iter.is_ok do
			if iter.item == c then return iter.index
			iter.next
		end
		return -1
	end

	# Gets the last index of char ´c´
	#
	# Returns -1 if not found
	fun last_index_of(c: Char): Int
	do
		return last_index_of_from(c, length - 1)
	end

	# Return a null terminated char *
	fun to_cstring: CString is abstract

	# The index of the last occurrence of an element starting from pos (in reverse order).
	#
	# ~~~
	# var s = "/etc/bin/test/test.nit"
	# assert s.last_index_of_from('/', s.length-1) == 13
	# assert s.last_index_of_from('/', 12)         == 8
	# ~~~
	#
	# Returns -1 if not found
	fun last_index_of_from(item: Char, pos: Int): Int do return chars.last_index_of_from(item, pos)

	# Concatenates `o` to `self`
	#
	# ~~~
	# assert "hello" + "world"  == "helloworld"
	# assert "" + "hello" + ""  == "hello"
	# ~~~
	fun +(o: Text): SELFTYPE is abstract

	# Gets an iterator on the chars of self
	fun iterator: Iterator[Char]
	do
		return self.chars.iterator
	end


	# Gets an Array containing the chars of self
	fun to_a: Array[Char] do return chars.to_a

	# Create a substring from `self` beginning at the `from` position
	#
	# ~~~
	# assert "abcd".substring_from(1)    ==  "bcd"
	# assert "abcd".substring_from(-1)   ==  "abcd"
	# assert "abcd".substring_from(2)    ==  "cd"
	# ~~~
	#
	# As with substring, a `from` index < 0 will be replaced by 0
	fun substring_from(from: Int): SELFTYPE
	do
		if from >= self.length then return empty
		if from < 0 then from = 0
		return substring(from, length - from)
	end

	# Does self have a substring `str` starting from position `pos`?
	#
	# ~~~
	# assert "abcd".has_substring("bc",1)	     ==  true
	# assert "abcd".has_substring("bc",2)	     ==  false
	# ~~~
	#
	# Returns true iff all characters of `str` are presents
	# at the expected index in `self.`
	# The first character of `str` being at `pos`, the second
	# character being at `pos+1` and so on...
	#
	# This means that all characters of `str` need to be inside `self`.
	#
	# ~~~
	# assert "abcd".has_substring("xab", -1)         == false
	# assert "abcd".has_substring("cdx", 2)          == false
	# ~~~
	#
	# And that the empty string is always a valid substring.
	#
	# ~~~
	# assert "abcd".has_substring("", 2)             == true
	# assert "abcd".has_substring("", 200)           == true
	# ~~~
	fun has_substring(str: String, pos: Int): Bool
	do
		if str.is_empty then return true
		if pos < 0 or pos + str.length > length then return false
		var myiter = self.chars.iterator_from(pos)
		var itsiter = str.chars.iterator
		while myiter.is_ok and itsiter.is_ok do
			if myiter.item != itsiter.item then return false
			myiter.next
			itsiter.next
		end
		if itsiter.is_ok then return false
		return true
	end

	# Is this string prefixed by `prefix`?
	#
	# ~~~
	# assert "abcd".has_prefix("ab")           ==  true
	# assert "abcbc".has_prefix("bc")          ==  false
	# assert "ab".has_prefix("abcd")           ==  false
	# ~~~
	fun has_prefix(prefix: String): Bool do return has_substring(prefix,0)

	# Is this string suffixed by `suffix`?
	#
	# ~~~
	# assert "abcd".has_suffix("abc")	     ==  false
	# assert "abcd".has_suffix("bcd")	     ==  true
	# ~~~
	fun has_suffix(suffix: String): Bool do return has_substring(suffix, length - suffix.length)

	# Returns `self` as the corresponding integer
	#
	# ~~~
	# assert "123".to_i        == 123
	# assert "-1".to_i         == -1
	# assert "0x64".to_i       == 100
	# assert "0b1100_0011".to_i== 195
	# assert "--12".to_i       == 12
	# assert "+45".to_i        == 45
	# ~~~
	#
	# REQUIRE: `self`.`is_int`
	fun to_i: Int is abstract

	# If `self` contains a float, return the corresponding float
	#
	# ~~~
	# assert "123".to_f        == 123.0
	# assert "-1".to_f         == -1.0
	# assert "-1.2e-3".to_f    == -0.0012
	# ~~~
	fun to_f: Float
	do
		# Shortcut
		return to_s.to_cstring.atof
	end

	# If `self` contains only digits and alpha <= 'f', return the corresponding integer.
	#
	# ~~~
	# assert "ff".to_hex == 255
	# ~~~
	fun to_hex(pos, ln: nullable Int): Int do
		var res = 0
		if pos == null then pos = 0
		if ln == null then ln = length - pos
		var max = pos + ln
		for i in [pos .. max[ do
			res <<= 4
			res += self[i].from_hex
		end
		return res
	end

	# If `self` contains only digits <= '7', return the corresponding integer.
	#
	# ~~~
	# assert "714".to_oct == 460
	# ~~~
	fun to_oct: Int do return a_to(8)

	# If `self` contains only '0' et '1', return the corresponding integer.
	#
	# ~~~
	# assert "101101".to_bin == 45
	# ~~~
	fun to_bin: Int do return a_to(2)

	# If `self` contains only digits '0' .. '9', return the corresponding integer.
	#
	# ~~~
	# assert "108".to_dec == 108
	# ~~~
	fun to_dec: Int do return a_to(10)

	# If `self` contains only digits and letters, return the corresponding integer in a given base
	#
	# ~~~
	# assert "120".a_to(3)     == 15
	# ~~~
	fun a_to(base: Int) : Int
	do
		var i = 0
		var neg = false

		for j in [0..length[ do
			var c = chars[j]
			var v = c.to_i
			if v > base then
				if neg then
					return -i
				else
					return i
				end
			else if v < 0 then
				neg = true
			else
				i = i * base + v
			end
		end
		if neg then
			return -i
		else
			return i
		end
	end

	# Is this string in a valid numeric format compatible with `to_f`?
	#
	# ~~~
	# assert "123".is_numeric  == true
	# assert "1.2".is_numeric  == true
	# assert "-1.2".is_numeric == true
	# assert "-1.23e-2".is_numeric == true
	# assert "1..2".is_numeric == false
	# assert "".is_numeric     == false
	# ~~~
	fun is_numeric: Bool
	do
		var has_point = false
		var e_index = -1
		for i in [0..length[ do
			var c = chars[i]
			if not c.is_numeric then
				if c == '.' and not has_point then
					has_point = true
				else if c == 'e' and e_index == -1 and i > 0 and i < length - 1 and chars[i-1] != '-' then
					e_index = i
				else if c == '-' and i == e_index + 1 and i < length - 1 then
				else
					return false
				end
			end
		end
		return not is_empty
	end

	# Returns `true` if the string contains only Hex chars
	#
	# ~~~
	# assert "048bf".is_hex  == true
	# assert "ABCDEF".is_hex  == true
	# assert "0G".is_hex == false
	# ~~~
	fun is_hex: Bool
	do
		for i in [0..length[ do
			var c = chars[i]
			if not (c >= 'a' and c <= 'f') and
			   not (c >= 'A' and c <= 'F') and
			   not (c >= '0' and c <= '9') then return false
		end
		return true
	end

	# Returns `true` if the string contains only Binary digits
	#
	# ~~~
	# assert "1101100".is_bin  == true
	# assert "1101020".is_bin  == false
	# ~~~
	fun is_bin: Bool do
		for i in chars do if i != '0' and i != '1' then return false
		return true
	end

	# Returns `true` if the string contains only Octal digits
	#
	# ~~~
	# assert "213453".is_oct  == true
	# assert "781".is_oct     == false
	# ~~~
	fun is_oct: Bool do
		for i in chars do if i < '0' or i > '7' then return false
		return true
	end

	# Returns `true` if the string contains only Decimal digits
	#
	# ~~~
	# assert "10839".is_dec == true
	# assert "164F".is_dec  == false
	# ~~~
	fun is_dec: Bool do
		for i in chars do if i < '0' or i > '9' then return false
		return true
	end

	# Are all letters in `self` upper-case ?
	#
	# ~~~
	# assert "HELLO WORLD".is_upper == true
	# assert "%$&%!".is_upper       == true
	# assert "hello world".is_upper == false
	# assert "Hello World".is_upper == false
	# ~~~
	fun is_upper: Bool
	do
		for i in [0..length[ do
			var char = chars[i]
			if char.is_lower then return false
		end
		return true
	end

	# Are all letters in `self` lower-case ?
	#
	# ~~~
	# assert "hello world".is_lower == true
	# assert "%$&%!".is_lower       == true
	# assert "Hello World".is_lower == false
	# ~~~
	fun is_lower: Bool
	do
		for i in [0..length[ do
			var char = chars[i]
			if char.is_upper then return false
		end
		return true
	end

	# Removes the whitespaces at the beginning of self
	#
	# ~~~
	# assert " \n\thello \n\t".l_trim == "hello \n\t"
	# ~~~
	#
	# `Char::is_whitespace` determines what is a whitespace.
	fun l_trim: SELFTYPE
	do
		var iter = self.chars.iterator
		while iter.is_ok do
			if not iter.item.is_whitespace then break
			iter.next
		end
		if iter.index == length then return self.empty
		return self.substring_from(iter.index)
	end

	# Removes the whitespaces at the end of self
	#
	# ~~~
	# assert " \n\thello \n\t".r_trim == " \n\thello"
	# ~~~
	#
	# `Char::is_whitespace` determines what is a whitespace.
	fun r_trim: SELFTYPE
	do
		var iter = self.chars.reverse_iterator
		while iter.is_ok do
			if not iter.item.is_whitespace then break
			iter.next
		end
		if iter.index < 0 then return self.empty
		return self.substring(0, iter.index + 1)
	end

	# Trims trailing and preceding white spaces
	#
	# ~~~
	# assert "  Hello  World !  ".trim   == "Hello  World !"
	# assert "\na\nb\tc\t".trim          == "a\nb\tc"
	# ~~~
	#
	# `Char::is_whitespace` determines what is a whitespace.
	fun trim: SELFTYPE do return (self.l_trim).r_trim

	# Is the string non-empty but only made of whitespaces?
	#
	# ~~~
	# assert " \n\t ".is_whitespace    == true
	# assert "  hello  ".is_whitespace == false
	# assert "".is_whitespace          == false
	# ~~~
	#
	# `Char::is_whitespace` determines what is a whitespace.
	fun is_whitespace: Bool
	do
		if is_empty then return false
		for c in self.chars do
			if not c.is_whitespace then return false
		end
		return true
	end

	# Returns `self` removed from its last line terminator (if any).
	#
	# ~~~
	# assert "Hello\n".chomp == "Hello"
	# assert "Hello".chomp   == "Hello"
	#
	# assert "\n".chomp == ""
	# assert "".chomp   == ""
	# ~~~
	#
	# Line terminators are `"\n"`, `"\r\n"` and `"\r"`.
	# A single line terminator, the last one, is removed.
	#
	# ~~~
	# assert "\r\n".chomp     == ""
	# assert "\r\n\n".chomp   == "\r\n"
	# assert "\r\n\r\n".chomp == "\r\n"
	# assert "\r\n\r".chomp   == "\r\n"
	# ~~~
	#
	# Note: unlike with most IO methods like `Reader::read_line`,
	# a single `\r` is considered here to be a line terminator and will be removed.
	fun chomp: SELFTYPE
	do
		var len = length
		if len == 0 then return self
		var l = self.chars.last
		if l == '\r' then
			return substring(0, len-1)
		else if l != '\n' then
			return self
		else if len > 1 and self.chars[len-2] == '\r' then
			return substring(0, len-2)
		else
			return substring(0, len-1)
		end
	end

	# Justify `self` in a space of `length`
	#
	# `left` is the space ratio on the left side.
	# * 0.0 for left-justified (no space at the left)
	# * 1.0 for right-justified (all spaces at the left)
	# * 0.5 for centered (half the spaces at the left)
	#
	# `char`, or `' '` by default, is repeated to pad the empty space.
	#
	# Examples
	#
	# ~~~
	# assert "hello".justify(10, 0.0)  == "hello     "
	# assert "hello".justify(10, 1.0)  == "     hello"
	# assert "hello".justify(10, 0.5)  == "  hello   "
	# assert "hello".justify(10, 0.5, '.') == "..hello..."
	# ~~~
	#
	# If `length` is not enough, `self` is returned as is.
	#
	# ~~~
	# assert "hello".justify(2, 0.0)   == "hello"
	# ~~~
	#
	# REQUIRE: `left >= 0.0 and left <= 1.0`
	# ENSURE: `self.length <= length implies result.length == length`
	# ENSURE: `self.length >= length implies result == self`
	fun justify(length: Int, left: Float, char: nullable Char): String
	do
		var pad = (char or else ' ').to_s
		var diff = length - self.length
		if diff <= 0 then return to_s
		assert left >= 0.0 and left <= 1.0
		var before = (diff.to_f * left).to_i
		return pad * before + self + pad * (diff-before)
	end

	# Mangle a string to be a unique string only made of alphanumeric characters and underscores.
	#
	# This method is injective (two different inputs never produce the same
	# output) and the returned string always respect the following rules:
	#
	# * Contains only US-ASCII letters, digits and underscores.
	# * Never starts with a digit.
	# * Never ends with an underscore.
	# * Never contains two contiguous underscores.
	#
	# Examples:
	#
	# ~~~
	# assert "42_is/The answer!".to_cmangle == "_52d2_is_47dThe_32danswer_33d"
	# assert "__".to_cmangle == "_95d_95d"
	# assert "__d".to_cmangle == "_95d_d"
	# assert "_d_".to_cmangle == "_d_95d"
	# assert "_42".to_cmangle == "_95d42"
	# assert "foo".to_cmangle == "foo"
	# assert "".to_cmangle == ""
	# ~~~
	fun to_cmangle: String
	do
		if is_empty then return ""
		var res = new Buffer
		var underscore = false
		var start = 0
		var c = self[0]

		if c >= '0' and c <= '9' then
			res.add('_')
			res.append(c.code_point.to_s)
			res.add('d')
			start = 1
		end
		for i in [start..length[ do
			c = self[i]
			if (c >= 'a' and c <= 'z') or (c >='A' and c <= 'Z') then
				res.add(c)
				underscore = false
				continue
			end
			if underscore then
				res.append('_'.code_point.to_s)
				res.add('d')
			end
			if c >= '0' and c <= '9' then
				res.add(c)
				underscore = false
			else if c == '_' then
				res.add(c)
				underscore = true
			else
				res.add('_')
				res.append(c.code_point.to_s)
				res.add('d')
				underscore = false
			end
		end
		if underscore then
			res.append('_'.code_point.to_s)
			res.add('d')
		end
		return res.to_s
	end

	# Escape `"` `\` `'`, trigraphs and non printable characters using the rules of literal C strings and characters
	#
	# ~~~
	# assert "abAB12<>&".escape_to_c       == "abAB12<>&"
	# assert "\n\"'\\".escape_to_c         == "\\n\\\"\\'\\\\"
	# assert "allo???!".escape_to_c        == "allo??\\?!"
	# assert "??=??/??'??(??)".escape_to_c == "?\\?=?\\?/??\\'?\\?(?\\?)"
	# assert "??!??<??>??-".escape_to_c    == "?\\?!?\\?<?\\?>?\\?-"
	# ~~~
	#
	# Most non-printable characters (bellow ASCII 32) are escaped to an octal form `\nnn`.
	# Three digits are always used to avoid following digits to be interpreted as an element
	# of the octal sequence.
	#
	# ~~~
	# assert "{0.code_point}{1.code_point}{8.code_point}{31.code_point}{32.code_point}".escape_to_c == "\\000\\001\\010\\037 "
	# ~~~
	#
	# The exceptions are the common `\t` and `\n`.
	fun escape_to_c: String
	do
		var b = new Buffer
		for i in [0..length[ do
			var c = chars[i]
			if c == '\n' then
				b.append("\\n")
			else if c == '\t' then
				b.append("\\t")
			else if c == '"' then
				b.append("\\\"")
			else if c == '\'' then
				b.append("\\\'")
			else if c == '\\' then
				b.append("\\\\")
			else if c == '?' then
				# Escape if it is the last question mark of a ANSI C trigraph.
				var j = i + 1
				if j < length then
					var next = chars[j]
					# We ignore `??'` because it will be escaped as `??\'`.
					if
						next == '!' or
						next == '(' or
						next == ')' or
						next == '-' or
						next == '/' or
						next == '<' or
						next == '=' or
						next == '>'
					then b.add('\\')
				end
				b.add('?')
			else if c.code_point < 32 then
				b.add('\\')
				var oct = c.code_point.to_base(8)
				# Force 3 octal digits since it is the
				# maximum allowed in the C specification
				if oct.length == 1 then
					b.add('0')
					b.add('0')
				else if oct.length == 2 then
					b.add('0')
				end
				b.append(oct)
			else
				b.add(c)
			end
		end
		return b.to_s
	end

	# Escape additionnal characters
	# The result might no be legal in C but be used in other languages
	#
	# ~~~
	# assert "ab|\{\}".escape_more_to_c("|\{\}") == "ab\\|\\\{\\\}"
	# assert "allo???!".escape_more_to_c("")     == "allo??\\?!"
	# ~~~
	fun escape_more_to_c(chars: String): String
	do
		var b = new Buffer
		for c in escape_to_c.chars do
			if chars.chars.has(c) then
				b.add('\\')
			end
			b.add(c)
		end
		return b.to_s
	end

	# Escape to C plus braces
	#
	# ~~~
	# assert "\n\"'\\\{\}".escape_to_nit      == "\\n\\\"\\'\\\\\\\{\\\}"
	# ~~~
	fun escape_to_nit: String do return escape_more_to_c("\{\}")

	# Escape to POSIX Shell (sh).
	#
	# Abort if the text contains a null byte.
	#
	# ~~~
	# assert "\n\"'\\\{\}0".escape_to_sh == "'\n\"'\\''\\\{\}0'"
	# ~~~
	fun escape_to_sh: String do
		var b = new Buffer
		b.chars.add '\''
		for i in [0..length[ do
			var c = chars[i]
			if c == '\'' then
				b.append("'\\''")
			else
				assert without_null_byte: c != '\0'
				b.add(c)
			end
		end
		b.chars.add '\''
		return b.to_s
	end

	# Escape to include in a Makefile
	#
	# Unfortunately, some characters are not escapable in Makefile.
	# These characters are `;`, `|`, `\`, and the non-printable ones.
	# They will be rendered as `"?{hex}"`.
	fun escape_to_mk: String do
		var b = new Buffer
		for i in [0..length[ do
			var c = chars[i]
			if c == '$' then
				b.append("$$")
			else if c == ':' or c == ' ' or c == '#' then
				b.add('\\')
				b.add(c)
			else if c.code_point < 32 or c == ';' or c == '|' or c == '\\' then
				b.append("?{c.code_point.to_base(16)}")
			else
				b.add(c)
			end
		end
		return b.to_s
	end

	# Return a string where Nit escape sequences are transformed.
	#
	# ~~~
	# var s = "\\n"
	# assert s.length        ==  2
	# var u = s.unescape_nit
	# assert u.length        ==  1
	# assert u.chars[0].code_point      ==  10 # (the ASCII value of the "new line" character)
	# ~~~
	fun unescape_nit: String
	do
		var res = new Buffer.with_cap(self.length)
		var was_slash = false
		for i in [0..length[ do
			var c = chars[i]
			if not was_slash then
				if c == '\\' then
					was_slash = true
				else
					res.add(c)
				end
				continue
			end
			was_slash = false
			if c == 'n' then
				res.add('\n')
			else if c == 'r' then
				res.add('\r')
			else if c == 't' then
				res.add('\t')
			else if c == '0' then
				res.add('\0')
			else
				res.add(c)
			end
		end
		return res.to_s
	end

	# Returns `self` with all characters escaped with their UTF-16 representation
	#
	# ~~~
	# assert "Aèあ𐏓".escape_to_utf16 == "\\u0041\\u00e8\\u3042\\ud800\\udfd3"
	# ~~~
	fun escape_to_utf16: String do
		var buf = new Buffer
		for i in chars do buf.append i.escape_to_utf16
		return buf.to_s
	end

	# Returns the Unicode char escaped by `self`
	#
	# ~~~
	# assert "\\u0041".from_utf16_escape == 'A'
	# assert "\\ud800\\udfd3".from_utf16_escape == '𐏓'
	# assert "\\u00e8".from_utf16_escape == 'è'
	# assert "\\u3042".from_utf16_escape == 'あ'
	# ~~~
	fun from_utf16_escape(pos, ln: nullable Int): Char do
		if pos == null then pos = 0
		if ln == null then ln = length - pos
		if ln < 6 then return 0xFFFD.code_point
		var cp = from_utf16_digit(pos + 2).to_u32
		if cp < 0xD800u32 then return cp.code_point
		if cp > 0xDFFFu32 then return cp.code_point
		if cp > 0xDBFFu32 then return 0xFFFD.code_point
		if ln == 6 then return 0xFFFD.code_point
		if ln < 12 then return 0xFFFD.code_point
		cp <<= 16
		cp += from_utf16_digit(pos + 8).to_u32
		var cplo = cp & 0xFFFFu32
		if cplo < 0xDC00u32 then return 0xFFFD.code_point
		if cplo > 0xDFFFu32 then return 0xFFFD.code_point
		return cp.from_utf16_surr.code_point
	end

	# Returns a UTF-16 escape value
	#
	# ~~~
	# var s = "\\ud800\\udfd3"
	# assert s.from_utf16_digit(2) == 0xD800
	# assert s.from_utf16_digit(8) == 0xDFD3
	# ~~~
	fun from_utf16_digit(pos: nullable Int): Int do
		if pos == null then pos = 0
		return to_hex(pos, 4)
	end

	# Encode `self` to percent (or URL) encoding
	#
	# ~~~
	# assert "aBc09-._~".to_percent_encoding == "aBc09-._~"
	# assert "%()< >".to_percent_encoding == "%25%28%29%3c%20%3e"
	# assert ".com/post?e=asdf&f=123".to_percent_encoding == ".com%2fpost%3fe%3dasdf%26f%3d123"
	# assert "éあいう".to_percent_encoding == "%c3%a9%e3%81%82%e3%81%84%e3%81%86"
	# ~~~
	fun to_percent_encoding: String
	do
		var buf = new Buffer

		for i in [0..length[ do
			var c = chars[i]
			if (c >= '0' and c <= '9') or
			   (c >= 'a' and c <= 'z') or
			   (c >= 'A' and c <= 'Z') or
			   c == '-' or c == '.' or
			   c == '_' or c == '~'
			then
				buf.add c
			else
				var bytes = c.to_s.bytes
				for b in bytes do buf.append "%{b.to_i.to_hex}"
			end
		end

		return buf.to_s
	end

	# Decode `self` from percent (or URL) encoding to a clear string
	#
	# Invalid '%' are not decoded.
	#
	# ~~~
	# assert "aBc09-._~".from_percent_encoding == "aBc09-._~"
	# assert "%25%28%29%3c%20%3e".from_percent_encoding == "%()< >"
	# assert ".com%2fpost%3fe%3dasdf%26f%3d123".from_percent_encoding == ".com/post?e=asdf&f=123"
	# assert "%25%28%29%3C%20%3E".from_percent_encoding == "%()< >"
	# assert "incomplete %".from_percent_encoding == "incomplete %"
	# assert "invalid % usage".from_percent_encoding == "invalid % usage"
	# assert "%c3%a9%e3%81%82%e3%81%84%e3%81%86".from_percent_encoding == "éあいう"
	# assert "%1 %A %C3%A9A9".from_percent_encoding == "%1 %A éA9"
	# ~~~
	fun from_percent_encoding: String
	do
		var len = byte_length
		var has_percent = false
		for c in chars do
			if c == '%' then
				len -= 2
				has_percent = true
			end
		end

		# If no transformation is needed, return self as a string
		if not has_percent then return to_s

		var buf = new CString(len)
		var i = 0
		var l = 0
		while i < length do
			var c = chars[i]
			if c == '%' then
				if i + 2 >= length then
					# What follows % has been cut off
					buf[l] = u'%'
				else
					i += 1
					var hex_s = substring(i, 2)
					if hex_s.is_hex then
						var hex_i = hex_s.to_hex
						buf[l] = hex_i
						i += 1
					else
						# What follows a % is not Hex
						buf[l] = u'%'
						i -= 1
					end
				end
			else buf[l] = c.code_point

			i += 1
			l += 1
		end

		return buf.to_s_unsafe(l, copy=false)
	end

	# Escape the characters `<`, `>`, `&`, `"`, `'` and `/` as HTML/XML entity references.
	#
	# ~~~
	# assert "a&b-<>\"x\"/'".html_escape      ==  "a&amp;b-&lt;&gt;&#34;x&#34;&#47;&#39;"
	# ~~~
	#
	# SEE: <https://www.owasp.org/index.php/XSS_%28Cross_Site_Scripting%29_Prevention_Cheat_Sheet#RULE_.231_-_HTML_Escape_Before_Inserting_Untrusted_Data_into_HTML_Element_Content>
	fun html_escape: String
	do
		var buf: nullable Buffer = null

		for i in [0..length[ do
			var c = chars[i]
			var sub = null
			if c == '&' then
				sub = "&amp;"
			else if c == '<' then
				sub = "&lt;"
			else if c == '>' then
				sub = "&gt;"
			else if c == '"' then
				sub = "&#34;"
			else if c == '\'' then
				sub = "&#39;"
			else if c == '/' then
				sub = "&#47;"
			else
				if buf != null then buf.add c
				continue
			end
			if buf == null then
				buf = new Buffer
				for j in [0..i[ do buf.add chars[j]
			end
			buf.append sub
		end

		if buf == null then return self.to_s
		return buf.to_s
	end

	# Equality of text
	# Two pieces of text are equals if thez have the same characters in the same order.
	#
	# ~~~
	# assert "hello" == "hello"
	# assert "hello" != "HELLO"
	# assert "hello" == "hel"+"lo"
	# ~~~
	#
	# Things that are not Text are not equal.
	#
	# ~~~
	# assert "9" != '9'
	# assert "9" != ['9']
	# assert "9" != 9
	#
	# assert "9".chars.first == '9'   # equality of Char
	# assert "9".chars       == ['9'] # equality of Sequence
	# assert "9".to_i        == 9     # equality of Int
	# ~~~
	redef fun ==(o)
	do
		if o == null then return false
		if not o isa Text then return false
		if self.is_same_instance(o) then return true
		if self.length != o.length then return false
		return self.chars == o.chars
	end

	# Lexicographical comparaison
	#
	# ~~~
	# assert "abc" < "xy"
	# assert "ABC" < "abc"
	# ~~~
	redef fun <(other)
	do
		var self_chars = self.chars.iterator
		var other_chars = other.chars.iterator

		while self_chars.is_ok and other_chars.is_ok do
			if self_chars.item < other_chars.item then return true
			if self_chars.item > other_chars.item then return false
			self_chars.next
			other_chars.next
		end

		if self_chars.is_ok then
			return false
		else
			return true
		end
	end

	# Escape string used in labels for graphviz
	#
	# ~~~
	# assert ">><<".escape_to_dot == "\\>\\>\\<\\<"
	# ~~~
	fun escape_to_dot: String
	do
		return escape_more_to_c("|\{\}<>")
	end

	private var hash_cache: nullable Int = null

	redef fun hash
	do
		if hash_cache == null then
			# djb2 hash algorithm
			var h = 5381

			for i in [0..length[ do
				var char = chars[i]
				h = (h << 5) + h + char.code_point
			end

			hash_cache = h
		end
		return hash_cache.as(not null)
	end

	# Format `self` by replacing each `%n` with the `n`th item of `args`
	#
	# The character `%` followed by something other than a number are left as is.
	# To represent a `%` followed by a number, double the `%`, as in `%%7`.
	#
	# ~~~
	# assert "This %0 is a %1.".format("String", "formatted String") == "This String is a formatted String."
	# assert "Do not escape % nor %%1".format("unused") == "Do not escape % nor %1"
	# ~~~
	fun format(args: Object...): String do
		var s = new Array[Text]
		var curr_st = 0
		var i = 0
		while i < length do
			if self[i] == '%' then
				var fmt_st = i
				i += 1
				var ciph_st = i
				while i < length and self[i].is_numeric do
					i += 1
				end

				var ciph_len = i - ciph_st
				if ciph_len == 0 then
					# What follows '%' is not a number.
					s.push substring(curr_st, i - curr_st)
					if i < length and self[i] == '%' then
						# Skip the next `%`
						i += 1
					end
					curr_st = i
					continue
				end

				var arg_index = substring(ciph_st, ciph_len).to_i
				if arg_index >= args.length then continue

				s.push substring(curr_st, fmt_st - curr_st)
				s.push args[arg_index].to_s

				curr_st = i
				i -= 1
			end
			i += 1
		end
		s.push substring(curr_st, length - curr_st)
		return s.plain_to_s
	end

	# Return the Levenshtein distance between two strings
	#
	# ~~~
	# assert "abcd".levenshtein_distance("abcd") == 0
	# assert "".levenshtein_distance("abcd")     == 4
	# assert "abcd".levenshtein_distance("")     == 4
	# assert "abcd".levenshtein_distance("xyz")  == 4
	# assert "abcd".levenshtein_distance("xbdy") == 3
	# ~~~
	fun levenshtein_distance(other: String): Int
	do
		var slen = self.length
		var olen = other.length

		# fast cases
		if slen == 0 then return olen
		if olen == 0 then return slen
		if self == other then return 0

		# previous row of distances
		var v0 = new Array[Int].with_capacity(olen+1)

		# current row of distances
		var v1 = new Array[Int].with_capacity(olen+1)

		for j in [0..olen] do
			# prefix insert cost
			v0[j] = j
		end

		for i in [0..slen[ do

			# prefix delete cost
			v1[0] = i + 1

			for j in [0..olen[ do
				# delete cost
				var cost1 = v1[j] + 1
				# insert cost
				var cost2 = v0[j + 1] + 1
				# same char cost (+0)
				var cost3 = v0[j]
				# change cost
				if self[i] != other[j] then cost3 += 1
				# keep the min
				v1[j+1] = cost1.min(cost2).min(cost3)
			end

			# Switch columns:
			# * v1 become v0 in the next iteration
			# * old v0 is reused as the new v1
			var tmp = v1
			v1 = v0
			v0 = tmp
		end

		return v0[olen]
	end

	# Copies `n` bytes from `self` at `src_offset` into `dest` starting at `dest_offset`
	#
	# Basically a high-level synonym of CString::copy_to
	#
	# REQUIRE: `n` must be large enough to contain `len` bytes
	#
	# ~~~
	# var ns = new CString(8)
	# "Text is String".copy_to_native(ns, 8, 2, 0)
	# assert ns.to_s_with_length(8) == "xt is St"
	# ~~~
	fun copy_to_native(dest: CString, n, src_offset, dest_offset: Int) do
		var mypos = src_offset
		var itspos = dest_offset
		while n > 0 do
			dest[itspos] = self.bytes[mypos]
			itspos += 1
			mypos += 1
			n -= 1
		end
	end

	# Packs the content of a string in packs of `ln` chars.
	# This variant ensures that only the last element might be smaller than `ln`
	#
	# ~~~
	# var s = "abcdefghijklmnopqrstuvwxyz"
	# assert s.pack_l(4) == ["abcd","efgh","ijkl","mnop","qrst","uvwx","yz"]
	# ~~~
	fun pack_l(ln: Int): Array[Text] do
		var st = 0
		var retarr = new Array[Text].with_capacity(length / ln + length % ln)
		while st < length do
			retarr.add(substring(st, ln))
			st += ln
		end
		return retarr
	end

	# Packs the content of a string in packs of `ln` chars.
	# This variant ensures that only the first element might be smaller than `ln`
	#
	# ~~~
	# var s = "abcdefghijklmnopqrstuvwxyz"
	# assert s.pack_r(4) == ["ab","cdef","ghij","klmn","opqr","stuv","wxyz"]
	# ~~~
	fun pack_r(ln: Int): Array[Text] do
		var st = length
		var retarr = new Array[Text].with_capacity(length / ln + length % ln)
		while st >= 0 do
			retarr.add(substring(st - ln, ln))
			st -= ln
		end
		return retarr.reversed
	end

	# Concatenates self `i` times
	#
	# ~~~
	# assert "abc" * 4 == "abcabcabcabc"
	# assert "abc" * 1 == "abc"
	# assert "abc" * 0 == ""
	# var b = new Buffer
	# b.append("天地")
	# b = b * 4
	# assert b == "天地天地天地天地"
	# ~~~
	fun *(i: Int): SELFTYPE is abstract

	# Insert `s` at `pos`.
	#
	# ~~~
	# assert "helloworld".insert_at(" ", 5)	== "hello world"
	# var b = new Buffer
	# b.append("Hello世界")
	# b = b.insert_at(" beautiful ", 5)
	# assert b == "Hello beautiful 世界"
	# ~~~
	fun insert_at(s: String, pos: Int): SELFTYPE is abstract

	# Returns a reversed version of self
	#
	# ~~~
	# assert "hello".reversed  == "olleh"
	# assert "bob".reversed    == "bob"
	# assert "".reversed       == ""
	# ~~~
	fun reversed: SELFTYPE is abstract

	# A upper case version of `self`
	#
	# ~~~
	# assert "Hello World!".to_upper     == "HELLO WORLD!"
	# ~~~
	fun to_upper: SELFTYPE is abstract

	# A lower case version of `self`
	#
	# ~~~
	# assert "Hello World!".to_lower     == "hello world!"
	# ~~~
	fun to_lower : SELFTYPE is abstract

	# Takes a camel case `self` and converts it to snake case
	#
	# ~~~
	# assert "randomMethodId".to_snake_case == "random_method_id"
	# ~~~
	#
	# The rules are the following:
	#
	# An uppercase is always converted to a lowercase
	#
	# ~~~
	# assert "HELLO_WORLD".to_snake_case == "hello_world"
	# ~~~
	#
	# An uppercase that follows a lowercase is prefixed with an underscore
	#
	# ~~~
	# assert "HelloTheWORLD".to_snake_case == "hello_the_world"
	# ~~~
	#
	# An uppercase that follows an uppercase and is followed by a lowercase, is prefixed with an underscore
	#
	# ~~~
	# assert "HelloTHEWorld".to_snake_case == "hello_the_world"
	# ~~~
	#
	# All other characters are kept as is; `self` does not need to be a proper CamelCased string.
	#
	# ~~~
	# assert "=-_H3ll0Th3W0rld_-=".to_snake_case == "=-_h3ll0th3w0rld_-="
	# ~~~
	fun to_snake_case: SELFTYPE is abstract

	# Takes a snake case `self` and converts it to camel case
	#
	# ~~~
	# assert "random_method_id".to_camel_case == "randomMethodId"
	# ~~~
	#
	# If the identifier is prefixed by an underscore, the underscore is ignored
	#
	# ~~~
	# assert "_private_field".to_camel_case == "_privateField"
	# ~~~
	#
	# If `self` is upper, it is returned unchanged
	#
	# ~~~
	# assert "RANDOM_ID".to_camel_case == "RANDOM_ID"
	# ~~~
	#
	# If there are several consecutive underscores, they are considered as a single one
	#
	# ~~~
	# assert "random__method_id".to_camel_case == "randomMethodId"
	# ~~~
	fun to_camel_case: SELFTYPE is abstract

	# Returns a capitalized `self`
	#
	# Letters that follow a letter are lowercased
	# Letters that follow a non-letter are upcased.
	#
	# If `keep_upper = true`, already uppercase letters are not lowercased.
	#
	# SEE : `Char::is_letter` for the definition of letter.
	#
	# ~~~
	# assert "jAVASCRIPT".capitalized == "Javascript"
	# assert "i am root".capitalized == "I Am Root"
	# assert "ab_c -ab0c ab\nc".capitalized == "Ab_C -Ab0C Ab\nC"
	# assert "preserve my ACRONYMS".capitalized(keep_upper=true) == "Preserve My ACRONYMS"
	# ~~~
	fun capitalized(keep_upper: nullable Bool): SELFTYPE do
		if length == 0 then return self

		var buf = new Buffer.with_cap(length)
		buf.capitalize(keep_upper=keep_upper, src=self)
		return buf.to_s
	end
end
lib/core/text/abstract_text.nit:25,1--1398,3