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

Introduced properties

protected fun is_in(s: Text): Bool

core :: Pattern :: is_in

Is self in s?
protected fun search_all_in(s: Text): Array[Match]

core :: Pattern :: search_all_in

Search all self occurrences into s.
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.
protected fun split_in(s: Text): Array[Match]

core :: Pattern :: split_in

Split s using self is separator.

Redefined properties

redef type SELF: Pattern

core $ Pattern :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
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.
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
protected fun is_in(s: Text): Bool

core :: Pattern :: is_in

Is self in s?
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.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
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).
protected fun search_all_in(s: Text): Array[Match]

core :: Pattern :: search_all_in

Search all self occurrences into s.
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 serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
protected fun split_in(s: Text): Array[Match]

core :: Pattern :: split_in

Split s using self is separator.
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram core::Pattern Pattern core::Object Object core::Pattern->core::Object core::BM_Pattern BM_Pattern core::BM_Pattern->core::Pattern core::Char Char core::Char->core::Pattern core::Text Text core::Text->core::Pattern core::Regex Regex core::Regex->core::Pattern core::FlatText FlatText core::FlatText->core::Text core::String String core::String->core::Text core::Buffer Buffer core::Buffer->core::Text core::U16String U16String core::U16String->core::Text core::FlatText... ... core::FlatText...->core::FlatText core::String... ... core::String...->core::String core::Buffer... ... core::Buffer...->core::Buffer core::U16String... ... core::U16String...->core::U16String

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class BM_Pattern

core :: BM_Pattern

BM_Pattern are pre-compiled string motif for the Boyer-Moore algorithm.
enum Char

core :: Char

Native characters.
class Regex

core :: Regex

A regular expression pattern
abstract class Text

core :: Text

High-level abstraction for all text representations

Descendants

abstract class Buffer

core :: Buffer

A mutable sequence of characters.
class FlatBuffer

core :: FlatBuffer

Mutable strings of characters.
abstract class FlatString

core :: FlatString

Immutable strings of characters.
abstract class FlatText

core :: FlatText

All kinds of array-based text representations.
abstract class String

core :: String

Immutable sequence of characters.
class U16String

core :: U16String

UTF-16 encoded string

Class definitions

core $ Pattern
# Patterns are abstract string motifs (include `String` and `Char`).
interface Pattern
	# Search `self` into `s` from a certain position.
	# Return the position of the first character of the matching section.
	# Return -1 if not found.
	#
	#     assert 'l'.search_index_in("hello world", 0)  == 2
	#     assert 'l'.search_index_in("hello world", 3)  == 3
	#     assert 'z'.search_index_in("hello world", 0)  == -1
	#
	# This method is usually faster than `search_in` if what is
	# required is only the index.
	# Note: in most implementation, `search_in` is implemented with this method.
	protected fun search_index_in(s: Text, from: Int): Int is abstract

	# Search `self` into `s` from a certain position.
	# Return null if not found.
	#
	#     assert 'l'.search_in("hello world", 0).from  == 2
	#     assert 'l'.search_in("hello world", 3).from  == 3
	#     assert 'z'.search_in("hello world", 0)       == null
	#
	# If only the index of the first character if required, see `search_index_in`.
	#
	# Note: Is used by `String::search`, `String::search_from`, and others.
	protected fun search_in(s: Text, from: Int): nullable Match is abstract

	# Search all `self` occurrences into `s`.
	#
	#     assert 'l'.search_all_in("hello world").length  == 3
	#     assert 'z'.search_all_in("hello world").length  == 0
	#
	# Note: Is used by `String::search_all`.
	protected fun search_all_in(s: Text): Array[Match]
	do
		var res = new Array[Match] # Result
		var match = search_in(s, 0)
		while match != null do
			res.add(match)
			match = search_in(s, match.after)
		end
		return res
	end

	# Split `s` using `self` is separator.
	#
	# Returns an array of matches that are between each occurence of `self`.
	# If self is not present, an array with a single match on `s` is retunred.
	#
	#     assert 'l'.split_in("hello world").join("|")  == "he||o wor|d"
	#     assert 'z'.split_in("hello world").join("|")  == "hello world"
	#
	# Note: is used by `String::split`
	protected fun split_in(s: Text): Array[Match]
	do
		var res = new Array[Match] # Result
		var i = 0 # Cursor
		var match = search_in(s, 0)
		while match != null do
			# Compute the splited part length
			var len = match.from - i
			res.add(new Match(s.to_s, i, len))
			i = match.after
			match = search_in(s, i)
		end
		# Add the last part
		res.add(new Match(s.to_s, i, s.length - i))
		return res
	end

	# Is `self` in `s`?
	protected fun is_in(s: Text): Bool do return search_index_in(s, 0) != -1
end
lib/core/text/string_search.nit:18,1--90,3