#6500: add String.init, Bytes.init, Labels couterparts, Stream.of_byte. (Cherry-picked from 15029 on 4.02.)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15030 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2014-07-28 13:29:50 +00:00
parent cf6714ead2
commit aeead32662
8 changed files with 44 additions and 0 deletions

View File

@ -31,6 +31,13 @@ let make n c =
unsafe_fill s 0 n c;
s
let init n f =
let s = create n in
for i = 0 to n - 1 do
unsafe_set s i (f i)
done;
s
let empty = create 0;;
let copy s =

View File

@ -66,6 +66,12 @@ 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].
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val empty : bytes
(** A byte sequence of size 0. *)

View File

@ -40,6 +40,12 @@ val make : int -> char -> bytes
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val init : int -> (int -> char) -> bytes
(** [init n f] returns a fresh byte sequence of length [n],
with character [i] initialized to the result of [f i].
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val empty : bytes
(** A byte sequence of size 0. *)

View File

@ -159,6 +159,15 @@ let of_string s =
else None)
;;
let of_bytes s =
let count = ref 0 in
from (fun _ ->
let c = !count in
if c < Bytes.length s
then (incr count; Some (Bytes.get s c))
else None)
;;
let of_channel ic =
{count = 0;
data = Sbuffio {ic = ic; buff = Bytes.create 4096; len = 0; ind = 0}}

View File

@ -46,6 +46,9 @@ val of_list : 'a list -> 'a t
val of_string : string -> char t
(** Return the stream of the characters of the string parameter. *)
val of_bytes : bytes -> char t
(** Return the stream of the characters of the bytes parameter. *)
val of_channel : in_channel -> char t
(** Return the stream of the characters read from the input channel. *)

View File

@ -27,6 +27,7 @@ external unsafe_fill : bytes -> int -> int -> char -> unit
module B = Bytes
let make = (Obj.magic B.make : int -> char -> string)
let init = (Obj.magic B.init : int -> (int -> char) -> string)
let copy = (Obj.magic B.copy : string -> string)
let sub = (Obj.magic B.sub : string -> int -> int -> string)
let fill = B.fill

View File

@ -80,6 +80,12 @@ 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].
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val copy : string -> string
(** Return a copy of the given string. *)

View File

@ -46,6 +46,12 @@ val make : int -> char -> string
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val init : int -> (int -> char) -> string
(** [init n f] returns a string of length [n],
with character [i] initialized to the result of [f i].
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}. *)
val copy : string -> string
(** Return a copy of the given string. *)