All kinds of array-based text representations.

Introduced properties

protected fun byte_length=(byte_length: Int)

core :: FlatText :: byte_length=

fun bytepos: Int

core :: FlatText :: bytepos

Cached position (bytes) in the CString underlying the String
protected fun bytepos=(bytepos: Int)

core :: FlatText :: bytepos=

Cached position (bytes) in the CString underlying the String
fun char_to_byte_index(index: Int): Int

core :: FlatText :: char_to_byte_index

Index of the character index in _items
fun chars_to_escape_to_c: Int

core :: FlatText :: chars_to_escape_to_c

By escaping self to C, how many more bytes will be needed ?
fun chars_to_html_escape: Int

core :: FlatText :: chars_to_html_escape

By escaping self to HTML, how many more bytes will be needed ?
abstract fun fast_cstring: CString

core :: FlatText :: fast_cstring

Returns a char* starting at position first_byte
fun fetch_char_at(index: Int): Char

core :: FlatText :: fetch_char_at

Gets a Char at index in self
protected fun first_byte: Int

core :: FlatText :: first_byte

First byte of the CString
fun items: CString

core :: FlatText :: items

Underlying CString (char*)
protected fun items=(items: CString)

core :: FlatText :: items=

Underlying CString (char*)
protected fun last_byte: Int

core :: FlatText :: last_byte

Last byte of the CString
protected fun length=(length: Int)

core :: FlatText :: length=

fun position: Int

core :: FlatText :: position

Cache of the latest position (char) explored in the string
protected fun position=(position: Int)

core :: FlatText :: position=

Cache of the latest position (char) explored in the string

Redefined properties

redef type SELF: FlatText

core $ FlatText :: SELF

Type of this instance, automatically specialized in every class
redef fun [](index: Int): Char

core :: flat $ FlatText :: []

Access a character at index in the string.
redef fun append_to_bytes(b: Bytes)

core :: bytes $ FlatText :: append_to_bytes

Appends self.bytes to b
redef fun byte_length: Int

core $ FlatText :: byte_length

Number of bytes in self
redef fun char_to_byte_index(index: Int): Int

text_stat :: text_stat $ FlatText :: char_to_byte_index

Index of the character index in _items
redef fun check_base64: nullable Error

base64 :: base64 $ FlatText :: check_base64

Is self a well-formed Base64 entity ?
redef fun copy_to_native(dst: CString, n: Int, src_off: Int, dst_off: Int)

core :: flat $ FlatText :: copy_to_native

Copies n bytes from self at src_offset into dest starting at dest_offset
redef fun copy_to_native(dest: CString, n: Int, src_offset: Int, dest_offset: Int)

core $ FlatText :: copy_to_native

Copies n bytes from self at src_offset into dest starting at dest_offset
redef fun decode_base64: Bytes

base64 :: base64 $ FlatText :: decode_base64

Decodes the receiver string to base64 using a custom padding character.
redef fun encode_base64: String

base64 :: base64 $ FlatText :: encode_base64

Encodes the receiver string to base64 using a custom padding character.
redef fun escape_to_c: String

core :: flat $ FlatText :: escape_to_c

Escape " \ ', trigraphs and non printable characters using the rules of literal C strings and characters
redef fun html_escape: String

core :: flat $ FlatText :: html_escape

Escape the characters <, >, &, ", ' and / as HTML/XML entity references.
redef fun is_base64: Bool

base64 :: base64 $ FlatText :: is_base64

Is self a well-formed Base64 entity ?
redef fun length: Int

core $ FlatText :: length

Number of characters contained in self.
redef fun output

core $ FlatText :: output

Display self on stdout (debug only).
redef fun to_hex(pos: nullable Int, ln: nullable Int): Int

core :: flat $ FlatText :: to_hex

If self contains only digits and alpha <= 'f', return the corresponding integer.

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
abstract fun *(i: Int): SELFTYPE

core :: Text :: *

Concatenates self i times
abstract fun +(o: Text): SELFTYPE

core :: Text :: +

Concatenates o to self
fun /(path: Text): String

core :: Text :: /

Alias for join_path
abstract fun <(other: OTHER): Bool

core :: Comparable :: <

Is self lesser than other?
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
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
type SELFTYPE: Text

core :: Text :: SELFTYPE

Type of self (used for factorization of several methods, ex : substring_from, empty...)
fun [](index: Int): Char

core :: Text :: []

Access a character at index in the string.
fun a_to(base: Int): Int

core :: Text :: a_to

If self contains only digits and letters, return the corresponding integer in a given base
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
protected fun add_to_bundle(bundle: NativeBundle, key: JavaString)

serialization :: Serializable :: add_to_bundle

Called by []= to dynamically choose the appropriate method according
fun alert

core :: Text :: alert

Raise a JavaScript alert
fun append_to_bytes(b: Bytes)

core :: Text :: append_to_bytes

Appends self.bytes to b
fun basename(extension: nullable String): String

core :: Text :: basename

Extract the basename of a path and strip the extension
fun binarydigest_to_bytes: Bytes

core :: Text :: binarydigest_to_bytes

Return a Bytes by reading 0 and 1.
fun blue: String

core :: Text :: blue

Make the text appear in blue in a ANSI/VT100 terminal.
fun bold: String

core :: Text :: bold

Make the text appear in bold in a ANSI/VT100 terminal.
abstract fun byte_length: Int

core :: Text :: byte_length

Number of bytes in self
protected fun byte_length=(byte_length: Int)

core :: FlatText :: byte_length=

fun bytepos: Int

core :: FlatText :: bytepos

Cached position (bytes) in the CString underlying the String
protected fun bytepos=(bytepos: Int)

core :: FlatText :: bytepos=

Cached position (bytes) in the CString underlying the String
abstract fun bytes: SequenceRead[Int]

core :: Text :: bytes

Gets a view on the bytes of the Text object
fun capitalized(keep_upper: nullable Bool): SELFTYPE

core :: Text :: capitalized

Returns a capitalized self
fun char_to_byte_index(index: Int): Int

core :: FlatText :: char_to_byte_index

Index of the character index in _items
abstract fun chars: SequenceRead[Char]

core :: Text :: chars

Gets a view on the chars of the Text object
fun chars_to_escape_to_c: Int

core :: FlatText :: chars_to_escape_to_c

By escaping self to C, how many more bytes will be needed ?
fun chars_to_html_escape: Int

core :: FlatText :: chars_to_html_escape

By escaping self to HTML, how many more bytes will be needed ?
fun chdir: nullable Error

core :: Text :: chdir

Change the current working directory
fun check_base64: nullable Error

core :: Text :: check_base64

Is self a well-formed Base64 entity ?
fun chomp: SELFTYPE

core :: Text :: chomp

Returns self removed from its last line terminator (if any).
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.
abstract fun clone: SELF

core :: Cloneable :: clone

Duplicate self
fun copy_to_native(dest: CString, n: Int, src_offset: Int, dest_offset: Int)

core :: Text :: copy_to_native

Copies n bytes from self at src_offset into dest starting at dest_offset
fun core_serialize_to(serializer: Serializer)

serialization :: Serializable :: core_serialize_to

Actual serialization of self to serializer
fun cyan: String

core :: Text :: cyan

Make the text appear in cyan in a ANSI/VT100 terminal.
fun decode_base64: Bytes

core :: Text :: decode_base64

Decodes the receiver string to base64 using a custom padding character.
fun deserialize_json(static_type: nullable String): nullable Object

core :: Text :: deserialize_json

Deserialize a nullable Object from this JSON formatted string
fun dirname: String

core :: Text :: dirname

Extract the dirname of a path
protected abstract fun empty: SELFTYPE

core :: Text :: empty

Returns an empty Text of the right type
fun encode_base64: String

core :: Text :: encode_base64

Encodes the receiver string to base64 using a custom padding character.
fun english_scoring: Float

core :: Text :: english_scoring

Score self according to english's letter frequency.
fun escape_more_to_c(chars: String): String

core :: Text :: escape_more_to_c

Escape additionnal characters
fun escape_to_c: String

core :: Text :: escape_to_c

Escape " \ ', trigraphs and non printable characters using the rules of literal C strings and characters
fun escape_to_dot: String

core :: Text :: escape_to_dot

Escape string used in labels for graphviz
fun escape_to_js: Text

core :: Text :: escape_to_js

Escape the content of self to pass to JavaScript code
fun escape_to_mk: String

core :: Text :: escape_to_mk

Escape to include in a Makefile
fun escape_to_nit: String

core :: Text :: escape_to_nit

Escape to C plus braces
fun escape_to_sh: String

core :: Text :: escape_to_sh

Escape to POSIX Shell (sh).
fun escape_to_utf16: String

core :: Text :: escape_to_utf16

Returns self with all characters escaped with their UTF-16 representation
abstract fun fast_cstring: CString

core :: FlatText :: fast_cstring

Returns a char* starting at position first_byte
fun fetch_char_at(index: Int): Char

core :: FlatText :: fetch_char_at

Gets a Char at index in self
fun file_copy_to(dest: String)

core :: Text :: file_copy_to

Copy content of file at self to dest
fun file_delete: Bool

core :: Text :: file_delete

Remove a file, return true if success
fun file_exists: Bool

core :: Text :: file_exists

return true if a file with this names exists
fun file_extension: nullable String

core :: Text :: file_extension

Return right-most extension (without the dot)
fun file_lstat: nullable FileStat

core :: Text :: file_lstat

The status of a file or of a symlink. see POSIX lstat(2).
fun file_stat: nullable FileStat

core :: Text :: file_stat

The status of a file. see POSIX stat(2).
fun files: Array[String]

core :: Text :: files

Returns entries contained within the directory represented by self.
fun first: Char

core :: Text :: first

Gets the first char of the Text
protected fun first_byte: Int

core :: FlatText :: first_byte

First byte of the CString
fun format(args: Object...): String

core :: Text :: format

Format self by replacing each %n with the nth item of args
init from_deserializer(deserializer: Deserializer)

serialization :: Serializable :: from_deserializer

Create an instance of this class from the deserializer
fun from_percent_encoding: String

core :: Text :: from_percent_encoding

Decode self from percent (or URL) encoding to a clear string
fun from_utf16_digit(pos: nullable Int): Int

core :: Text :: from_utf16_digit

Returns a UTF-16 escape value
fun from_utf16_escape(pos: nullable Int, ln: nullable Int): Char

core :: Text :: from_utf16_escape

Returns the Unicode char escaped by self
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun gray: String

core :: Text :: gray

Make the text appear in dark gray (or black) in a ANSI/VT100 terminal.
fun green: String

core :: Text :: green

Make the text appear in green in a ANSI/VT100 terminal.
fun group_exists: Bool

core :: Text :: group_exists

Does the operating system know the group named self?
fun has(pattern: Pattern): Bool

core :: Text :: has

Does self contains at least one instance of pattern?
fun has_prefix(prefix: String): Bool

core :: Text :: has_prefix

Is this string prefixed by prefix?
fun has_substring(str: String, pos: Int): Bool

core :: Text :: has_substring

Does self have a substring str starting from position pos?
fun has_suffix(suffix: String): Bool

core :: Text :: has_suffix

Is this string suffixed by suffix?
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun hexdigest: String

core :: Text :: hexdigest

Gets the hexdigest of the bytes of self
fun hexdigest_to_bytes: Bytes

core :: Text :: hexdigest_to_bytes

Returns a new Bytes instance with the digest as content
fun html_escape: String

core :: Text :: html_escape

Escape the characters <, >, &, ", ' and / as HTML/XML entity references.
fun http_download(output_path: nullable Text, accept_status_code: nullable Int): nullable String

core :: Text :: http_download

Download the file at URL self to output_path with a simple HTTP request
fun http_get(accept_status_code: nullable Int): nullable String

core :: Text :: http_get

Execute a simple HTTP GET request to the URL self
fun index_of(c: Char): Int

core :: Text :: index_of

Gets the index of the first occurence of 'c'
fun index_of_from(c: Char, pos: Int): Int

core :: Text :: index_of_from

Gets the index of the first occurence of ´c´ starting from ´pos´
init init

core :: Object :: init

abstract fun insert_at(s: String, pos: Int): SELFTYPE

core :: Text :: insert_at

Insert s at pos.
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_base64: Bool

core :: Text :: is_base64

Is self a well-formed Base64 entity ?
fun is_between(c: OTHER, d: OTHER): Bool

core :: Comparable :: is_between

c <= self <= d
fun is_bi: Bool

core :: Text :: is_bi

Is self a well-formed BigInt (i.e. parsable via to_bi)
fun is_bin: Bool

core :: Text :: is_bin

Returns true if the string contains only Binary digits
fun is_dec: Bool

core :: Text :: is_dec

Returns true if the string contains only Decimal digits
fun is_empty: Bool

core :: Text :: is_empty

Is the current Text empty (== "")
fun is_hex: Bool

core :: Text :: is_hex

Returns true if the string contains only Hex chars
protected fun is_in(s: Text): Bool

core :: Pattern :: is_in

Is self in s?
fun is_int: Bool

core :: Text :: is_int

Is self a well-formed Integer (i.e. parsable via to_i)
fun is_lower: Bool

core :: Text :: is_lower

Are all letters in self lower-case ?
fun is_num: Bool

core :: Text :: is_num

Is self a valid integer ?
fun is_numeric: Bool

core :: Text :: is_numeric

Is this string in a valid numeric format compatible with to_f?
fun is_oct: Bool

core :: Text :: is_oct

Returns true if the string contains only Octal digits
fun is_r: Bool

core :: Text :: is_r

Is self a well-formed Ratio (i.e. parsable via to_r)
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_sha1_digest: Bool

core :: Text :: is_sha1_digest

Is self a SHA-1 hexdigest?
fun is_upper: Bool

core :: Text :: is_upper

Are all letters in self upper-case ?
fun is_valid_hexdigest: Bool

core :: Text :: is_valid_hexdigest

Is self a valid hexdigest ?
fun is_whitespace: Bool

core :: Text :: is_whitespace

Is the string non-empty but only made of whitespaces?
fun items: CString

core :: FlatText :: items

Underlying CString (char*)
protected fun items=(items: CString)

core :: FlatText :: items=

Underlying CString (char*)
fun iterator: Iterator[Char]

core :: Text :: iterator

Gets an iterator on the chars of self
fun join_path(path: Text): String

core :: Text :: join_path

Correctly join two path using the directory separator.
fun justify(length: Int, left: Float, char: nullable Char): String

core :: Text :: justify

Justify self in a space of length
fun l_trim: SELFTYPE

core :: Text :: l_trim

Removes the whitespaces at the beginning of self
fun last: Char

core :: Text :: last

Gets the last char of self
protected fun last_byte: Int

core :: FlatText :: last_byte

Last byte of the CString
fun last_index_of(c: Char): Int

core :: Text :: last_index_of

Gets the last index of char ´c´
fun last_index_of_from(item: Char, pos: Int): Int

core :: Text :: last_index_of_from

The index of the last occurrence of an element starting from pos (in reverse order).
abstract fun length: Int

core :: Text :: length

Number of characters contained in self.
protected fun length=(length: Int)

core :: FlatText :: length=

fun levenshtein_distance(other: String): Int

core :: Text :: levenshtein_distance

Return the Levenshtein distance between two strings
fun light_gray: String

core :: Text :: light_gray

Make the text appear in light gray (or white) in a ANSI/VT100 terminal.
fun max(other: OTHER): OTHER

core :: Comparable :: max

The maximum between self and other (prefers self if equals).
fun md5: String

core :: Text :: md5

MD5 digest of self
fun min(c: OTHER): OTHER

core :: Comparable :: min

The minimum between self and c (prefer self if equals)
fun mkdir(mode: nullable Int): nullable Error

core :: Text :: mkdir

Create a directory (and all intermediate directories if needed)
protected fun msgpack_extra_array_items: Int

serialization :: Serializable :: msgpack_extra_array_items

Hook to request a larger than usual metadata array
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun open_in_browser

core :: Text :: open_in_browser

Open the URL self with the default browser
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).
fun pack_l(ln: Int): Array[Text]

core :: Text :: pack_l

Packs the content of a string in packs of ln chars.
fun pack_r(ln: Int): Array[Text]

core :: Text :: pack_r

Packs the content of a string in packs of ln chars.
fun parse_bmfont(dir: String): MaybeError[BMFont, Error]

core :: Text :: parse_bmfont

Parse self as an XML BMFont description file
fun parse_json: nullable Serializable

core :: Text :: parse_json

Parse self as JSON.
fun position: Int

core :: FlatText :: position

Cache of the latest position (char) explored in the string
protected fun position=(position: Int)

core :: FlatText :: position=

Cache of the latest position (char) explored in the string
fun prefix(t: Text): nullable Match

core :: Text :: prefix

Extract a given prefix, if any.
fun purple: String

core :: Text :: purple

Make the text appear in magenta in a ANSI/VT100 terminal.
fun r_trim: SELFTYPE

core :: Text :: r_trim

Removes the whitespaces at the end of self
fun railfence(depth: Int): Text

core :: Text :: railfence

Returns a rail-fence cipher from self with depth rails
fun realpath: String

core :: Text :: realpath

Return the canonicalized absolute pathname (see POSIX function realpath)
fun red: String

core :: Text :: red

Make the text appear in red in a ANSI/VT100 terminal.
fun relpath(dest: String): String

core :: Text :: relpath

Returns the relative path needed to go from self to dest.
fun remove_all(pattern: Pattern): String

core :: Text :: remove_all

Returns a copy of self minus all occurences of pattern
fun replace(pattern: Pattern, string: Text): String

core :: Text :: replace

Replace all occurrences of pattern with string
fun replace_first(pattern: Pattern, string: Text): String

core :: Text :: replace_first

Replace the first occurrence of pattern with string
abstract fun reversed: SELFTYPE

core :: Text :: reversed

Returns a reversed version of self
fun rmdir: nullable Error

core :: Text :: rmdir

Delete a directory and all of its content, return true on success
fun rot(x: Int): Text

core :: Text :: rot

Performs a Rotation of x on each letter of self
fun run_js

core :: Text :: run_js

Run self as JavaScript code
fun search(pattern: Pattern): nullable Match

core :: Text :: search

Search the first occurence of pattern.
fun search_all(pattern: Pattern): Array[Match]

core :: Text :: search_all

Search all occurrences of pattern into self.
protected fun search_all_in(s: Text): Array[Match]

core :: Pattern :: search_all_in

Search all self occurrences into s.
fun search_from(pattern: Pattern, from: Int): nullable Match

core :: Text :: search_from

Search the first occurence of pattern after from.
protected abstract fun search_in(s: Text, from: Int): nullable Match

core :: Pattern :: search_in

Search self into s from a certain position.
protected abstract fun search_index_in(s: Text, from: Int): Int

core :: Pattern :: search_index_in

Search self into s from a certain position.
fun search_last(t: Text): nullable Match

core :: Text :: search_last

Search the last occurence of the text t.
fun search_last_up_to(t: Text, up_to: Int): nullable Match

core :: Text :: search_last_up_to

Search the last occurence of the text t before up_to.
protected abstract fun send(mpi: MPI, at: Int, count: Int, dest: Rank, tag: Tag, comm: Comm)

mpi :: Sendable :: send

Type specific send over MPI
protected abstract fun send_all(mpi: MPI, dest: Rank, tag: Tag, comm: Comm)

mpi :: Sendable :: send_all

Type specific send full buffer over MPI
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
fun sha1: Bytes

core :: Text :: sha1

Computes the SHA1 of the receiver
fun sha1_hexdigest: String

core :: Text :: sha1_hexdigest

Computes the SHA1 of the receiver.
fun simplify_path: String

core :: Text :: simplify_path

Simplify a file path by remove useless ., removing //, and resolving ..
fun split(pattern: Pattern): Array[String]

core :: Text :: split

Split self using pattern as separator.
protected fun split_in(s: Text): Array[Match]

core :: Pattern :: split_in

Split s using self is separator.
fun split_once_on(pattern: Pattern): Array[SELFTYPE]

core :: Text :: split_once_on

Split self on the first occurence of pattern
fun split_with(pattern: Pattern): Array[String]

core :: Text :: split_with

@deprecated alias for split
fun strip_extension(extension: nullable String): String

core :: Text :: strip_extension

Remove the trailing extension.
fun strip_nullable: Text

core :: Text :: strip_nullable

Strip the nullable prefix from the type name self
fun strip_nullable_and_params: Text

core :: Text :: strip_nullable_and_params

Strip the nullable prefix and the params from the type name self
abstract fun substring(from: Int, count: Int): SELFTYPE

core :: Text :: substring

Create a substring.
fun substring_from(from: Int): SELFTYPE

core :: Text :: substring_from

Create a substring from self beginning at the from position
fun suffix(t: Text): nullable Match

core :: Text :: suffix

Extract a given suffix, if any.
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun to_a: Array[Char]

core :: Text :: to_a

Gets an Array containing the chars of self
fun to_bi: BigInt

core :: Text :: to_bi

If self contains a BigInt, return the corresponding BigInt
fun to_bin: Int

core :: Text :: to_bin

If self contains only '0' et '1', return the corresponding integer.
abstract fun to_buffer: Buffer

core :: Text :: to_buffer

Returns a copy of self as a Buffer
fun to_bytes: Bytes

core :: Text :: to_bytes

Returns a mutable copy of self's bytes
abstract fun to_camel_case: SELFTYPE

core :: Text :: to_camel_case

Takes a snake case self and converts it to camel case
fun to_cmangle: String

core :: Text :: to_cmangle

Mangle a string to be a unique string only made of alphanumeric characters and underscores.
fun to_cpp_string: CppString

core :: Text :: to_cpp_string

Get self as a CppString
abstract fun to_cstring: CString

core :: Text :: to_cstring

Return a null terminated char *
fun to_dec: Int

core :: Text :: to_dec

If self contains only digits '0' .. '9', return the corresponding integer.
fun to_dot: String

core :: Text :: to_dot

Returns the graphviz-formatted content of self
fun to_f: Float

core :: Text :: to_f

If self contains a float, return the corresponding float
fun to_hex(pos: nullable Int, ln: nullable Int): Int

core :: Text :: to_hex

If self contains only digits and alpha <= 'f', return the corresponding integer.
abstract fun to_i: Int

core :: Text :: to_i

Returns self as the corresponding integer
fun to_java_string: JavaString

core :: Text :: to_java_string

Get self as a JavaString
fun to_json: String

serialization :: Serializable :: to_json

Serialize self to plain JSON
fun to_json_value: JsonValue

core :: Text :: to_json_value

Parse self to a JsonValue
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

abstract fun to_lower: SELFTYPE

core :: Text :: to_lower

A lower case version of self
fun to_n: Numeric

core :: Text :: to_n

Get the numeric version of self
fun to_nsstring: NSString

core :: Text :: to_nsstring

Get a NSString from self
fun to_num: nullable Numeric

core :: Text :: to_num

If self is a properly formatted integer, returns the corresponding value
fun to_oct: Int

core :: Text :: to_oct

If self contains only digits <= '7', return the corresponding integer.
fun to_path: Path

core :: Text :: to_path

Access file system related services on the path at self
fun to_percent_encoding: String

core :: Text :: to_percent_encoding

Encode self to percent (or URL) encoding
fun to_pretty_json: String

serialization :: Serializable :: to_pretty_json

Serialize self to plain pretty JSON
fun to_program_name: String

core :: Text :: to_program_name

Convert the path (self) to a program name.
fun to_r: Ratio

core :: Text :: to_r

If self contains a Ratio, return the corresponding Ratio
fun to_re: Regex

core :: Text :: to_re

Get a Regex instance from self
fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun to_sexp: SExpEntity

core :: Text :: to_sexp

Tries to parse self as an S-Expression
abstract fun to_snake_case: SELFTYPE

core :: Text :: to_snake_case

Takes a camel case self and converts it to snake case
fun to_sql_date_string: String

core :: Text :: to_sql_date_string

Format the date represented by self into an escaped string for SQLite
fun to_sql_string: String

core :: Text :: to_sql_string

Return self between 's, escaping \ and '
abstract fun to_upper: SELFTYPE

core :: Text :: to_upper

A upper case version of self
fun to_xml: XMLEntity

core :: Text :: to_xml

Tries to parse the current string to XML
fun trim: SELFTYPE

core :: Text :: trim

Trims trailing and preceding white spaces
fun underline: String

core :: Text :: underline

Make the text underlined in a ANSI/VT100 terminal.
fun unescape_json: Text

core :: Text :: unescape_json

Removes JSON-escaping if necessary in a JSON string
fun unescape_nit: String

core :: Text :: unescape_nit

Return a string where Nit escape sequences are transformed.
fun unescape_to_bytes: Bytes

core :: Text :: unescape_to_bytes

Return a Bytes instance where Nit escape sequences are transformed.
fun unrail(depth: Int): Text

core :: Text :: unrail

Transforms a rail-fence-encrypted Text to its original
fun user_exists: Bool

core :: Text :: user_exists

Does the operating system know the user named self?
fun uvigenere(key: String): String

core :: Text :: uvigenere

Vigenere decoder on ASCII letters.
fun vigenere(key: String): String

core :: Text :: vigenere

Vigenere encoder on ASCII letters.
abstract fun write_to(stream: Writer)

core :: Writable :: write_to

Write itself to a stream
fun write_to_bytes: Bytes

core :: Writable :: write_to_bytes

Like write_to but return a new Bytes (may be quite large)
fun write_to_file(filepath: String)

core :: Writable :: write_to_file

Like write_to but take care of creating the file
fun write_to_string: String

core :: Writable :: write_to_string

Like write_to but return a new String (may be quite large).
fun yellow: String

core :: Text :: yellow

Make the text appear in yellow in a ANSI/VT100 terminal.
package_diagram core::FlatText FlatText core::Text Text core::FlatText->core::Text serialization::DirectSerializable DirectSerializable core::Text->serialization::DirectSerializable core::Comparable Comparable core::Text->core::Comparable core::Cloneable Cloneable core::Text->core::Cloneable core::Pattern Pattern core::Text->core::Pattern core::Writable Writable core::Text->core::Writable mpi::Sendable Sendable core::Text->mpi::Sendable ...serialization::DirectSerializable ... ...serialization::DirectSerializable->serialization::DirectSerializable ...core::Comparable ... ...core::Comparable->core::Comparable ...core::Cloneable ... ...core::Cloneable->core::Cloneable ...core::Pattern ... ...core::Pattern->core::Pattern ...core::Writable ... ...core::Writable->core::Writable ...mpi::Sendable ... ...mpi::Sendable->mpi::Sendable core::FlatString FlatString core::FlatString->core::FlatText core::FlatBuffer FlatBuffer core::FlatBuffer->core::FlatText

Ancestors

interface Cloneable

core :: Cloneable

Something that can be cloned
interface Comparable

core :: Comparable

The ancestor of class where objects are in a total order.
interface DirectSerializable

serialization :: DirectSerializable

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

core :: Object

The root of the class hierarchy.
interface Pattern

core :: Pattern

Patterns are abstract string motifs (include String and Char).
interface Sendable

mpi :: Sendable

Something sendable directly and efficiently over MPI
interface Serializable

serialization :: Serializable

Instances of this class can be passed to Serializer::serialize
interface Writable

core :: Writable

Things that can be efficienlty written to a Writer

Parents

abstract class Text

core :: Text

High-level abstraction for all text representations

Children

class FlatBuffer

core :: FlatBuffer

Mutable strings of characters.
abstract class FlatString

core :: FlatString

Immutable strings of characters.

Class definitions

core $ FlatText
# All kinds of array-based text representations.
abstract class FlatText
	super Text

	# Underlying CString (`char*`)
	#
	# Warning: Might be void in some subclasses, be sure to check
	# if set before using it.
	var items: CString is noinit

	# Returns a char* starting at position `first_byte`
	#
	# WARNING: If you choose to use this service, be careful of the following.
	#
	# Strings and CString are *ideally* always allocated through a Garbage Collector.
	# Since the GC tracks the use of the pointer for the beginning of the char*, it may be
	# deallocated at any moment, rendering the pointer returned by this function invalid.
	# Any access to freed memory may very likely cause undefined behaviour or a crash.
	# (Failure to do so will most certainly result in long and painful debugging hours)
	#
	# The only safe use of this pointer is if it is ephemeral (e.g. read in a C function
	# then immediately return).
	#
	# As always, do not modify the content of the String in C code, if this is what you want
	# copy locally the char* as Nit Strings are immutable.
	fun fast_cstring: CString is abstract

	redef var length = 0

	redef var byte_length = 0

	redef fun output
	do
		var i = 0
		while i < length do
			items[i].output
			i += 1
		end
	end

	redef fun copy_to_native(dest, n, src_offset, dest_offset) do
		items.copy_to(dest, n, src_offset, dest_offset)
	end
end
lib/core/text/abstract_text.nit:1400,1--1443,3

core :: flat $ FlatText
redef class FlatText

	# First byte of the CString
	protected fun first_byte: Int do return 0

	# Last byte of the CString
	protected fun last_byte: Int do return first_byte + _byte_length - 1

	# Cache of the latest position (char) explored in the string
	var position: Int = 0

	# Cached position (bytes) in the CString underlying the String
	var bytepos: Int = 0

	# Index of the character `index` in `_items`
	fun char_to_byte_index(index: Int): Int do
		var dpos = index - _position
		var b = _bytepos
		var its = _items

		if dpos == 1 then
			if its[b] & 0x80 == 0x00 then
				b += 1
			else
				b += its.length_of_char_at(b)
			end
			_bytepos = b
			_position = index
			return b
		end
		if dpos == -1 then
			b = its.find_beginning_of_char_at(b - 1)
			_bytepos = b
			_position = index
			return b
		end
		if dpos == 0 then return b

		var ln = _length
		var pos = _position
		# Find best insertion point
		var delta_begin = index
		var delta_end = (ln - 1) - index
		var delta_cache = (pos - index).abs
		var min = delta_begin

		if delta_cache < min then min = delta_cache
		if delta_end < min then min = delta_end

		var ns_i: Int
		var my_i: Int

		if min == delta_cache then
			ns_i = _bytepos
			my_i = pos
		else if min == delta_begin then
			ns_i = first_byte
			my_i = 0
		else
			ns_i = its.find_beginning_of_char_at(last_byte)
			my_i = _length - 1
		end

		ns_i = its.char_to_byte_index_cached(index, my_i, ns_i)

		_position = index
		_bytepos = ns_i

		return ns_i
	end

	# By escaping `self` to HTML, how many more bytes will be needed ?
	fun chars_to_html_escape: Int do
		var its = _items
		var max = last_byte
		var pos = first_byte
		var endlen = 0
		while pos <= max do
			var c = its[pos]
			if c == u'<' then
				endlen += 3
			else if c == u'>' then
				endlen += 3
			else if c == u'&' then
				endlen += 4
			else if c == u'"' then
				endlen += 4
			else if c == u'\'' then
				endlen += 4
			else if c == 0x2F then
				endlen += 4
			end
			pos += 1
		end
		return endlen
	end

	redef fun html_escape
	do
		var extra = chars_to_html_escape
		if extra == 0 then return to_s
		var its = _items
		var max = last_byte
		var pos = first_byte
		var nlen = extra + _byte_length
		var nits = new CString(nlen)
		var outpos = 0
		while pos <= max do
			var c = its[pos]
			# Special codes:
			# Some HTML characters are used as meta-data, they need
			# to be replaced by an HTML-Escaped equivalent
			if c == u'<' then
				nits[outpos] = u'&'
				nits[outpos + 1] = u'l'
				nits[outpos + 2] = u't'
				nits[outpos + 3] = u';'
				outpos += 4
			else if c == u'>' then
				nits[outpos] = u'&'
				nits[outpos + 1] = u'g'
				nits[outpos + 2] = u't'
				nits[outpos + 3] = u';'
				outpos += 4
			else if c == u'&' then
				nits[outpos] = u'&'
				nits[outpos + 1] = u'a'
				nits[outpos + 2] = u'm'
				nits[outpos + 3] = u'p'
				nits[outpos + 4] = u';'
				outpos += 5
			else if c == u'"' then
				nits[outpos] = u'&'
				nits[outpos + 1] = u'#'
				nits[outpos + 2] = u'3'
				nits[outpos + 3] = u'4'
				nits[outpos + 4] = u';'
				outpos += 5
			else if c == u'\'' then
				nits[outpos] = u'&'
				nits[outpos + 1] = u'#'
				nits[outpos + 2] = u'3'
				nits[outpos + 3] = u'9'
				nits[outpos + 4] = u';'
				outpos += 5
			else if c == u'/' then
				nits[outpos] = u'&'
				nits[outpos + 1] = u'#'
				nits[outpos + 2] = u'4'
				nits[outpos + 3] = u'7'
				nits[outpos + 4] = u';'
				outpos += 5
			else
				nits[outpos] = c
				outpos += 1
			end
			pos += 1
		end
		var s = new FlatString.with_infos(nits, nlen, 0)
		return s
	end

	# By escaping `self` to C, how many more bytes will be needed ?
	#
	# This enables a double-optimization in `escape_to_c` since if this
	# method returns 0, then `self` does not need escaping and can be
	# returned as-is
	fun chars_to_escape_to_c: Int do
		var its = _items
		var max = last_byte
		var pos = first_byte
		var req_esc = 0
		while pos <= max do
			var c = its[pos]
			if c == u'\n' then
				req_esc += 1
			else if c == u'\t' then
				req_esc += 1
			else if c == u'"' then
				req_esc += 1
			else if c == u'\'' then
				req_esc += 1
			else if c == u'\\' then
				req_esc += 1
			else if c == u'?' then
				var j = pos + 1
				if j < length then
					var next = its[j]
					# We ignore `??'` because it will be escaped as `??\'`.
					if
						next == 0x21 or
						next == 0x28 or
						next == 0x29 or
						next == 0x2D or
						next == 0x2F or
						next == 0x3C or
						next == 0x3D or
						next == 0x3E
					then req_esc += 1
				end
			else if c < 32 then
				req_esc += 3
			end
			pos += 1
		end
		return req_esc
	end

	redef fun escape_to_c do
		var ln_extra = chars_to_escape_to_c
		if ln_extra == 0 then return self.to_s
		var its = _items
		var max = last_byte
		var nlen = _byte_length + ln_extra
		var nns = new CString(nlen)
		var pos = first_byte
		var opos = 0
		while pos <= max do
			var c = its[pos]
			# Special codes:
			#
			# Any byte with value < 32 is a control character
			# All their uses will be replaced by their octal
			# value in C.
			#
			# There are two exceptions however:
			#
			# * 0x09 => \t
			# * 0x0A => \n
			#
			# Aside from the code points above, the following are:
			#
			# * 0x22 => \"
			# * 0x27 => \'
			# * 0x5C => \\
			if c == u'\t' then
				nns[opos] = u'\\'
				nns[opos + 1] = u't'
				opos += 2
			else if c == u'\n' then
				nns[opos] = u'\\'
				nns[opos + 1] = u'n'
				opos += 2
			else if c == u'"' then
				nns[opos] = u'\\'
				nns[opos + 1] = u'"'
				opos += 2
			else if c == u'\'' then
				nns[opos] = u'\\'
				nns[opos + 1] = u'\''
				opos += 2
			else if c == u'\\' then
				nns[opos] = u'\\'
				nns[opos + 1] = u'\\'
				opos += 2
			else if c == u'?' then
				var j = pos + 1
				if j < length then
					var next = its[j]
					# We ignore `??'` because it will be escaped as `??\'`.
					if
						next == 0x21 or
						next == 0x28 or
						next == 0x29 or
						next == 0x2D or
						next == 0x2F or
						next == 0x3C or
						next == 0x3D or
						next == 0x3E
					then
						nns[opos] = 0x5C
						opos += 1
					end
				end
				nns[opos] = 0x3F
				opos += 1
			else if c < 32 then
				nns[opos] = u'\\'
				nns[opos + 1] = u'0'
				nns[opos + 2] = ((c & 0x38) >> 3) + u'0'
				nns[opos + 3] = (c & 0x07) + u'0'
				opos += 4
			else
				nns[opos] = c
				opos += 1
			end
			pos += 1
		end
		return nns.to_s_unsafe(nlen, copy=false, clean=false)
	end

	redef fun [](index) do
		var len = _length

		# Statistically:
		# * ~70% want the next char
		# * ~23% want the previous
		# * ~7% want the same char
		#
		# So it makes sense to shortcut early. And early is here.
		var dpos = index - _position
		var b = _bytepos
		if dpos == 1 and index < len - 1 then
			var its = _items
			var c = its[b]
			if c & 0x80 == 0x00 then
				# We want the next, and current is easy.
				# So next is easy to find!
				b += 1
				_position = index
				_bytepos = b
				# The rest will be done by `dpos==0` bellow.
				dpos = 0
			end
		else if dpos == -1 and index > 1 then
			var its = _items
			var c = its[b-1]
			if c & 0x80 == 0x00 then
				# We want the previous, and it is easy.
				b -= 1
				dpos = 0
				_position = index
				_bytepos = b
				return c.code_point
			end
		end
		if dpos == 0 then
			# We know what we want (+0 or +1) just get it now!
			var its = _items
			var c = its[b]
			if c & 0x80 == 0x00 then return c.code_point
			return items.char_at(b)
		end

		assert index >= 0 and index < len
		return fetch_char_at(index)
	end

	# Gets a `Char` at `index` in `self`
	#
	# WARNING: Use at your own risks as no bound-checking is done
	fun fetch_char_at(index: Int): Char do
		var i = char_to_byte_index(index)
		var items = _items
		var b = items[i]
		if b & 0x80 == 0x00 then return b.code_point
		return items.char_at(i)
	end

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

	redef fun copy_to_native(dst, n, src_off, dst_off) do
		_items.copy_to(dst, n, first_byte + src_off, dst_off)
	end
end
lib/core/text/flat.nit:37,1--406,3

core :: bytes $ FlatText
redef class FlatText
	redef fun append_to_bytes(b) do
		var from = if self isa FlatString then first_byte else 0
		if isset _items then b.append_ns_from(items, byte_length, from)
	end
end
lib/core/bytes.nit:1015,1--1020,3

base64 :: base64 $ FlatText
redef class FlatText
	redef fun encode_base64 do return fast_cstring.encode_base64(byte_length).to_s

	redef fun decode_base64 do return fast_cstring.decode_base64(byte_length)

	redef fun is_base64 do return fast_cstring.is_base64(byte_length)

	redef fun check_base64 do return fast_cstring.check_base64(byte_length)
end
lib/base64/base64.nit:242,1--250,3

text_stat :: text_stat $ FlatText
redef class FlatText
	redef fun char_to_byte_index(index) do
		var ln = length
		assert index >= 0
		assert index < ln

		# Find best insertion point
		var delta_begin = index
		var delta_end = (ln - 1) - index
		var delta_cache = (position - index).abs
		var min = delta_begin
		var its = items

		if delta_cache < min then min = delta_cache
		if delta_end < min then min = delta_end

		var ns_i: Int
		var my_i: Int

		if min == delta_begin then
			ns_i = first_byte
			my_i = 0
		else if min == delta_cache then
			ns_i = bytepos
			my_i = position
		else
			ns_i = its.find_beginning_of_char_at(last_byte)
			my_i = length - 1
		end

		var from = ns_i

		ns_i = its.char_to_byte_index_cached(index, my_i, ns_i)

		var after = ns_i

		sys.index_len.inc((after - from).abs)

		position = index
		bytepos = ns_i

		return ns_i
	end
end
lib/text_stat/text_stat.nit:170,1--213,3

json :: static $ FlatText
redef class FlatText
	redef fun json_need_escape do
		var its = items
		for i in [first_byte .. last_byte] do
			if its[i] == 0x5C then return true
		end
		return false
	end
end
lib/json/static.nit:127,1--135,3