implement {Bytes,String}.mapi

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15058 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Gabriel Scherer 2014-08-06 15:57:38 +00:00
parent 97b302a1ce
commit b7dd6d2c91
4 changed files with 38 additions and 13 deletions

View File

@ -164,7 +164,15 @@ let map f s =
let l = length s in
if l = 0 then s else begin
let r = create l in
for i = 0 to l - 1 do unsafe_set r i (f(unsafe_get s i)) done;
for i = 0 to l - 1 do unsafe_set r i (f (unsafe_get s i)) done;
r
end
let mapi f s =
let l = length s in
if l = 0 then s else begin
let r = create l in
for i = 0 to l - 1 do unsafe_set r i (f i (unsafe_get s i)) done;
r
end

View File

@ -67,8 +67,9 @@ val make : int -> char -> bytes
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val init : int -> (int -> char) -> bytes
(** [Bytes.init n f] returns a fresh byte sequence of length [n],
with character [i] initialized to the result of [f i].
(** [Bytes.init n f] returns a fresh byte sequence of length [n], with
character [i] initialized to the result of [f i] (in increasing
index order).
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
@ -132,9 +133,14 @@ val iteri : (int -> char -> unit) -> bytes -> unit
argument. *)
val map : (char -> char) -> bytes -> bytes
(** [map f s] applies function [f] in turn to all the bytes of [s] and
stores the resulting bytes in a new sequence that is returned as
the result. *)
(** [map f s] applies function [f] in turn to all the bytes of [s]
(in increasing index order) and stores the resulting bytes in
a new sequence that is returned as the result. *)
val mapi : (int -> char -> char) -> bytes -> bytes
(** [mapi f s] calls [f] with each character of [s] and its
index (in increasing index order) and stores the resulting bytes
in a new sequence that is returned as the result. *)
val trim : bytes -> bytes
(** Return a copy of the argument, without leading and trailing

View File

@ -37,6 +37,7 @@ let concat = (Obj.magic B.concat : string -> string list -> string)
let iter = (Obj.magic B.iter : (char -> unit) -> string -> unit)
let iteri = (Obj.magic B.iteri : (int -> char -> unit) -> string -> unit)
let map = (Obj.magic B.map : (char -> char) -> string -> string)
let mapi = (Obj.magic B.mapi : (int -> char -> char) -> string -> string)
(* Beware: we cannot use B.trim or B.escape because they always make a
copy, but String.mli spells out some cases where we are not allowed

View File

@ -81,10 +81,14 @@ val make : int -> char -> string
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val init : int -> (int -> char) -> string
(** [String.init n f] returns a string of length [n],
with character [i] initialized to the result of [f i].
(** [String.init n f] returns a string of length [n], with character
[i] initialized to the result of [f i] (called in increasing
index order).
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}.
@since 4.02.0
*)
val copy : string -> string
(** Return a copy of the given string. *)
@ -131,10 +135,16 @@ val iteri : (int -> char -> unit) -> string -> unit
@since 4.00.0 *)
val map : (char -> char) -> string -> string
(** [String.map f s] applies function [f] in turn to all
the characters of [s] and stores the results in a new string that
is returned.
@since 4.00.0 *)
(** [String.map f s] applies function [f] in turn to all the
characters of [s] (in increasing index order) and stores the
results in a new string that is returned.
@since 4.00.0 *)
val mapi : (int -> char -> char) -> string -> string
(** [String.mapi f s] calls [f] with each character of [s] and its
index (in increasing index order) and stores the results in a new
string that is returned.
@since 4.02.0 *)
val trim : string -> string
(** Return a copy of the argument, without leading and trailing