summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2014-07-28 13:29:50 +0000
committerAlain Frisch <alain@frisch.fr>2014-07-28 13:29:50 +0000
commitaeead3266235b9aadaf492dc8247b0fc84bff61c (patch)
tree231cde8a63c39a3f8a5849d0bb9c33552a801d45 /stdlib
parentcf6714ead24163382ab73426a8206421e0d7c706 (diff)
#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
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/bytes.ml7
-rw-r--r--stdlib/bytes.mli6
-rw-r--r--stdlib/bytesLabels.mli6
-rw-r--r--stdlib/stream.ml9
-rw-r--r--stdlib/stream.mli3
-rw-r--r--stdlib/string.ml1
-rw-r--r--stdlib/string.mli6
-rw-r--r--stdlib/stringLabels.mli6
8 files changed, 44 insertions, 0 deletions
diff --git a/stdlib/bytes.ml b/stdlib/bytes.ml
index e405f1727..092f8c8f0 100644
--- a/stdlib/bytes.ml
+++ b/stdlib/bytes.ml
@@ -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 =
diff --git a/stdlib/bytes.mli b/stdlib/bytes.mli
index 0367d52bb..99c2af033 100644
--- a/stdlib/bytes.mli
+++ b/stdlib/bytes.mli
@@ -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. *)
diff --git a/stdlib/bytesLabels.mli b/stdlib/bytesLabels.mli
index e8eaaa9fe..eb1a46070 100644
--- a/stdlib/bytesLabels.mli
+++ b/stdlib/bytesLabels.mli
@@ -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. *)
diff --git a/stdlib/stream.ml b/stdlib/stream.ml
index 076b6733e..751c741a8 100644
--- a/stdlib/stream.ml
+++ b/stdlib/stream.ml
@@ -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}}
diff --git a/stdlib/stream.mli b/stdlib/stream.mli
index aeb0da1e8..85a846102 100644
--- a/stdlib/stream.mli
+++ b/stdlib/stream.mli
@@ -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. *)
diff --git a/stdlib/string.ml b/stdlib/string.ml
index 064c3fdbe..741ca2af1 100644
--- a/stdlib/string.ml
+++ b/stdlib/string.ml
@@ -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
diff --git a/stdlib/string.mli b/stdlib/string.mli
index 45ef65756..3cfccd1f2 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -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. *)
diff --git a/stdlib/stringLabels.mli b/stdlib/stringLabels.mli
index 4ae8a72e1..6ff413e37 100644
--- a/stdlib/stringLabels.mli
+++ b/stdlib/stringLabels.mli
@@ -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. *)