]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/stdlib/string.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / stdlib / string.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the GNU Library General Public License, with    *)
10 (*  the special exception on linking described in file ../LICENSE.     *)
11 (*                                                                     *)
12 (***********************************************************************)
13
14 (* $Id: string.mli 9079 2008-10-08 13:09:39Z doligez $ *)
15
16 (** String operations.
17   Given a string [s] of length [l], we call character number in [s]
18   the index of a character in [s].  Indexes start at [0], and we will
19   call a character number valid in [s] if it falls within the range
20   [[0...l-1]]. A position is the point between two characters or at
21   the beginning or end of the string.  We call a position valid
22   in [s] if it falls within the range [[0...l]]. Note that character
23   number [n] is between positions [n] and [n+1].
24
25   Two parameters [start] and [len] are said to designate a valid
26   substring of [s] if [len >= 0] and [start] and [start+len] are
27   valid positions in [s].
28  *)
29
30 external length : string -> int = "%string_length"
31 (** Return the length (number of characters) of the given string. *)
32
33 external get : string -> int -> char = "%string_safe_get"
34 (** [String.get s n] returns character number [n] in string [s].
35    You can also write [s.[n]] instead of [String.get s n].
36
37    Raise [Invalid_argument] if [n] not a valid character number in [s]. *)
38
39
40 external set : string -> int -> char -> unit = "%string_safe_set"
41 (** [String.set s n c] modifies string [s] in place,
42    replacing the character number [n] by [c].
43    You can also write [s.[n] <- c] instead of [String.set s n c].
44
45    Raise [Invalid_argument] if [n] is not a valid character number in [s]. *)
46
47 external create : int -> string = "caml_create_string"
48 (** [String.create n] returns a fresh string of length [n].
49    The string initially contains arbitrary characters.
50
51    Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
52
53 val make : int -> char -> string
54 (** [String.make n c] returns a fresh string of length [n],
55    filled with the character [c].
56
57    Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}.*)
58
59 val copy : string -> string
60 (** Return a copy of the given string. *)
61
62 val sub : string -> int -> int -> string
63 (** [String.sub s start len] returns a fresh string of length [len],
64    containing the substring of [s] that starts at position [start] and
65    has length [len].
66
67    Raise [Invalid_argument] if [start] and [len] do not
68    designate a valid substring of [s]. *)
69
70 val fill : string -> int -> int -> char -> unit
71 (** [String.fill s start len c] modifies string [s] in place,
72    replacing [len] characters by [c], starting at [start].
73
74    Raise [Invalid_argument] if [start] and [len] do not
75    designate a valid substring of [s]. *)
76
77 val blit : string -> int -> string -> int -> int -> unit
78 (** [String.blit src srcoff dst dstoff len] copies [len] characters
79    from string [src], starting at character number [srcoff], to
80    string [dst], starting at character number [dstoff]. It works
81    correctly even if [src] and [dst] are the same string,
82    and the source and destination intervals overlap.
83
84    Raise [Invalid_argument] if [srcoff] and [len] do not
85    designate a valid substring of [src], or if [dstoff] and [len]
86    do not designate a valid substring of [dst]. *)
87
88 val concat : string -> string list -> string
89 (** [String.concat sep sl] concatenates the list of strings [sl],
90    inserting the separator string [sep] between each. *)
91
92 val iter : (char -> unit) -> string -> unit
93 (** [String.iter f s] applies function [f] in turn to all
94    the characters of [s].  It is equivalent to
95    [f s.[0]; f s.[1]; ...; f s.[String.length s - 1]; ()]. *)
96
97 val escaped : string -> string
98 (** Return a copy of the argument, with special characters
99    represented by escape sequences, following the lexical
100    conventions of Objective Caml.  If there is no special
101    character in the argument, return the original string itself,
102    not a copy. *)
103
104 val index : string -> char -> int
105 (** [String.index s c] returns the character number of the first
106    occurrence of character [c] in string [s].
107
108    Raise [Not_found] if [c] does not occur in [s]. *)
109
110 val rindex : string -> char -> int
111 (** [String.rindex s c] returns the character number of the last
112    occurrence of character [c] in string [s].
113
114    Raise [Not_found] if [c] does not occur in [s]. *)
115
116 val index_from : string -> int -> char -> int
117 (** [String.index_from s i c] returns the character number of the
118    first occurrence of character [c] in string [s] after position [i].
119    [String.index s c] is equivalent to [String.index_from s 0 c].
120
121    Raise [Invalid_argument] if [i] is not a valid position in [s].
122    Raise [Not_found] if [c] does not occur in [s] after position [i]. *)
123
124 val rindex_from : string -> int -> char -> int
125 (** [String.rindex_from s i c] returns the character number of the
126    last occurrence of character [c] in string [s] before position [i+1].
127    [String.rindex s c] is equivalent to
128    [String.rindex_from s (String.length s - 1) c].
129
130    Raise [Invalid_argument] if [i+1] is not a valid position in [s].
131    Raise [Not_found] if [c] does not occur in [s] before position [i+1]. *)
132
133 val contains : string -> char -> bool
134 (** [String.contains s c] tests if character [c]
135    appears in the string [s]. *)
136
137 val contains_from : string -> int -> char -> bool
138 (** [String.contains_from s start c] tests if character [c]
139    appears in [s] after position [start].
140    [String.contains s c] is equivalent to
141    [String.contains_from s 0 c].
142
143    Raise [Invalid_argument] if [start] is not a valid position in [s]. *)
144
145 val rcontains_from : string -> int -> char -> bool
146 (** [String.rcontains_from s stop c] tests if character [c]
147    appears in [s] before position [stop+1].
148
149    Raise [Invalid_argument] if [stop < 0] or [stop+1] is not a valid
150    position in [s]. *)
151
152 val uppercase : string -> string
153 (** Return a copy of the argument, with all lowercase letters
154    translated to uppercase, including accented letters of the ISO
155    Latin-1 (8859-1) character set. *)
156
157 val lowercase : string -> string
158 (** Return a copy of the argument, with all uppercase letters
159    translated to lowercase, including accented letters of the ISO
160    Latin-1 (8859-1) character set. *)
161
162 val capitalize : string -> string
163 (** Return a copy of the argument, with the first character set to uppercase. *)
164
165 val uncapitalize : string -> string
166 (** Return a copy of the argument, with the first character set to lowercase. *)
167
168 type t = string
169 (** An alias for the type of strings. *)
170
171 val compare: t -> t -> int
172 (** The comparison function for strings, with the same specification as
173     {!Pervasives.compare}.  Along with the type [t], this function [compare]
174     allows the module [String] to be passed as argument to the functors
175     {!Set.Make} and {!Map.Make}. *)
176
177 (**/**)
178
179 external unsafe_get : string -> int -> char = "%string_unsafe_get"
180 external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
181 external unsafe_blit :
182   string -> int -> string -> int -> int -> unit = "caml_blit_string" "noalloc"
183 external unsafe_fill :
184   string -> int -> int -> char -> unit = "caml_fill_string" "noalloc"