summaryrefslogtreecommitdiffstats
path: root/otherlibs/str/str.mli
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-04 16:16:05 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-04 16:16:05 +0000
commit4d5679c9ba6a8ce0093a4f54f6d5d089ddcda491 (patch)
tree76db38b2e3b94817bda2dba77acbfff1aa043109 /otherlibs/str/str.mli
parenta97296fe48058c6f2e36504cb16140c94e8387cb (diff)
commentaires après
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4098 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs/str/str.mli')
-rw-r--r--otherlibs/str/str.mli73
1 files changed, 36 insertions, 37 deletions
diff --git a/otherlibs/str/str.mli b/otherlibs/str/str.mli
index ba1c44fb6..da3b5b2ef 100644
--- a/otherlibs/str/str.mli
+++ b/otherlibs/str/str.mli
@@ -18,10 +18,11 @@
(** {2 Regular expressions} *)
-(** The type of compiled regular expressions. *)
type regexp
+(** The type of compiled regular expressions. *)
+val regexp : string -> regexp
(** Compile a regular expression. The syntax for regular expressions
is the same as in Gnu Emacs. The special characters are
[$^.*+?[]]. The following constructs are recognized:
@@ -42,71 +43,70 @@ type regexp
([\2] for the second expression, etc)
- [\b ] matches word boundaries
- [\ ] quotes special characters. *)
-val regexp: string -> regexp
+val regexp_case_fold : string -> regexp
(** Same as [regexp], but the compiled expression will match text
in a case-insensitive way: uppercase and lowercase letters will
be considered equivalent. *)
-val regexp_case_fold: string -> regexp
+val quote : string -> string
(** [Str.quote s] returns a regexp string that matches exactly
[s] and nothing else. *)
-val quote: string -> string
+val regexp_string : string -> regexp
(** [Str.regexp_string s] returns a regular expression
that matches exactly [s] and nothing else.*)
-val regexp_string: string -> regexp
+val regexp_string_case_fold : string -> regexp
(** [Str.regexp_string_case_fold] is similar to {!Str.regexp_string},
but the regexp matches in a case-insensitive way. *)
-val regexp_string_case_fold: string -> regexp
(** {2 String matching and searching} *)
+external string_match : regexp -> string -> int -> bool = "str_string_match"
(** [string_match r s start] tests whether the characters in [s]
starting at position [start] match the regular expression [r].
The first character of a string has position [0], as usual. *)
-external string_match: regexp -> string -> int -> bool
- = "str_string_match"
+external search_forward :
+ regexp -> string -> int -> int = "str_search_forward"
(** [search_forward r s start] searchs the string [s] for a substring
matching the regular expression [r]. The search starts at position
[start] and proceeds towards the end of the string.
Return the position of the first character of the matched
substring, or raise [Not_found] if no substring matches. *)
-external search_forward: regexp -> string -> int -> int
- = "str_search_forward"
+external search_backward :
+ regexp -> string -> int -> int = "str_search_backward"
(** Same as {!Str.search_forward}, but the search proceeds towards the
beginning of the string. *)
-external search_backward: regexp -> string -> int -> int
- = "str_search_backward"
+external string_partial_match :
+ regexp -> string -> int -> bool = "str_string_partial_match"
(** Similar to {!Str.string_match}, but succeeds whenever the argument
string is a prefix of a string that matches. This includes
the case of a true complete match. *)
-external string_partial_match: regexp -> string -> int -> bool
- = "str_string_partial_match"
+val matched_string : string -> string
(** [matched_string s] returns the substring of [s] that was matched
by the latest {!Str.string_match}, {!Str.search_forward} or
{!Str.search_backward}.
The user must make sure that the parameter [s] is the same string
that was passed to the matching or searching function. *)
-val matched_string: string -> string
+val match_beginning : unit -> int
(** [match_beginning()] returns the position of the first character
of the substring that was matched by {!Str.string_match},
{!Str.search_forward} or {!Str.search_backward}. *)
-val match_beginning: unit -> int
+val match_end : unit -> int
(** [match_end()] returns the position of the character following the
last character of the substring that was matched by [string_match],
[search_forward] or [search_backward]. *)
-val match_end: unit -> int
+val matched_group : int -> string -> string
(** [matched_group n s] returns the substring of [s] that was matched
by the [n]th group [\(...\)] of the regular expression during
the latest {!Str.string_match}, {!Str.search_forward} or
@@ -119,50 +119,47 @@ val match_end: unit -> int
or repetitions [*]. For instance, the empty string will match
[\(a\)*], but [matched_group 1 ""] will raise [Not_found]
because the first group itself was not matched. *)
-val matched_group: int -> string -> string
+val group_beginning : int -> int
(** [group_beginning n] returns the position of the first character
of the substring that was matched by the [n]th group of
the regular expression.
@raise Not_found if the [n]th group of the regular expression
was not matched. *)
-val group_beginning: int -> int
+val group_end : int -> int
(** [group_end n] returns
the position of the character following the last character of
substring that was matched by the [n]th group of the regular expression.
@raise Not_found if the [n]th group of the regular expression
was not matched. *)
-val group_end: int -> int
(** {2 Replacement} *)
+val global_replace : regexp -> string -> string -> string
(** [global_replace regexp templ s] returns a string identical to [s],
except that all substrings of [s] that match [regexp] have been
replaced by [templ]. The replacement template [templ] can contain
[\1], [\2], etc; these sequences will be replaced by the text
matched by the corresponding group in the regular expression.
[\0] stands for the text matched by the whole regular expression. *)
-val global_replace: regexp -> string -> string -> string
+val replace_first : regexp -> string -> string -> string
(** Same as {!Str.global_replace}, except that only the first substring
matching the regular expression is replaced. *)
-val replace_first: regexp -> string -> string -> string
+val global_substitute : regexp -> (string -> string) -> string -> string
(** [global_substitute regexp subst s] returns a string identical
to [s], except that all substrings of [s] that match [regexp]
have been replaced by the result of function [subst]. The
function [subst] is called once for each matching substring,
and receives [s] (the whole text) as argument. *)
-val global_substitute:
- regexp -> (string -> string) -> string -> string
+val substitute_first : regexp -> (string -> string) -> string -> string
(** Same as {!Str.global_substitute}, except that only the first substring
matching the regular expression is replaced. *)
-val substitute_first:
- regexp -> (string -> string) -> string -> string
(** [replace_matched repl s] returns the replacement text [repl]
in which [\1], [\2], etc. have been replaced by the text
@@ -175,69 +172,71 @@ val replace_matched : string -> string -> string
(** {2 Splitting} *)
+val split : regexp -> string -> string list
(** [split r s] splits [s] into substrings, taking as delimiters
the substrings that match [r], and returns the list of substrings.
For instance, [split (regexp "[ \t]+") s] splits [s] into
blank-separated words. An occurrence of the delimiter at the
beginning and at the end of the string is ignored. *)
-val split: regexp -> string -> string list
+val bounded_split : regexp -> string -> int -> string list
(** Same as {!Str.split}, but splits into at most [n] substrings,
where [n] is the extra integer parameter. *)
-val bounded_split: regexp -> string -> int -> string list
+val split_delim : regexp -> string -> string list
(** Same as {!Str.split} but occurrences of the
delimiter at the beginning and at the end of the string are
recognized and returned as empty strings in the result.
For instance, [split_delim (regexp " ") " abc "]
returns [[""; "abc"; ""]], while [split] with the same
arguments returns [["abc"]]. *)
-val split_delim: regexp -> string -> string list
+val bounded_split_delim : regexp -> string -> int -> string list
(** Same as {!Str.bounded_split}, but occurrences of the
delimiter at the beginning and at the end of the string are
recognized and returned as empty strings in the result.
For instance, [split_delim (regexp " ") " abc "]
returns [[""; "abc"; ""]], while [split] with the same
arguments returns [["abc"]]. *)
-val bounded_split_delim: regexp -> string -> int -> string list
-type split_result = Text of string | Delim of string
+type split_result =
+ Text of string
+ | Delim of string
+val full_split : regexp -> string -> split_result list
(** Same as {!Str.split_delim}, but returns
the delimiters as well as the substrings contained between
delimiters. The former are tagged [Delim] in the result list;
the latter are tagged [Text]. For instance,
[full_split (regexp "[{}]") "{ab}"] returns
[[Delim "{"; Text "ab"; Delim "}"]]. *)
-val full_split: regexp -> string -> split_result list
+val bounded_full_split : regexp -> string -> int -> split_result list
(** Same as {!Str.bounded_split_delim}, but returns
the delimiters as well as the substrings contained between
delimiters. The former are tagged [Delim] in the result list;
the latter are tagged [Text]. For instance,
[full_split (regexp "[{}]") "{ab}"] returns
[[Delim "{"; Text "ab"; Delim "}"]]. *)
-val bounded_full_split: regexp -> string -> int -> split_result list
(** {2 Extracting substrings} *)
+val string_before : string -> int -> string
(** [string_before s n] returns the substring of all characters of [s]
that precede position [n] (excluding the character at
position [n]). *)
-val string_before: string -> int -> string
+val string_after : string -> int -> string
(** [string_after s n] returns the substring of all characters of [s]
that follow position [n] (including the character at
position [n]). *)
-val string_after: string -> int -> string
+val first_chars : string -> int -> string
(** [first_chars s n] returns the first [n] characters of [s].
This is the same function as {!Str.string_before}. *)
-val first_chars: string -> int -> string
+val last_chars : string -> int -> string
(** [last_chars s n] returns the last [n] characters of [s]. *)
-val last_chars: string -> int -> string