summaryrefslogtreecommitdiffstats
path: root/stdlib/bytes.ml
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/bytes.ml
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/bytes.ml')
-rw-r--r--stdlib/bytes.ml7
1 files changed, 7 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 =