summaryrefslogtreecommitdiffstats
path: root/stdlib/buffer.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/buffer.ml')
-rw-r--r--stdlib/buffer.ml20
1 files changed, 10 insertions, 10 deletions
diff --git a/stdlib/buffer.ml b/stdlib/buffer.ml
index 659729d3c..986fe6f33 100644
--- a/stdlib/buffer.ml
+++ b/stdlib/buffer.ml
@@ -78,25 +78,25 @@ let add_char b c =
Bytes.unsafe_set b.buffer pos c;
b.position <- pos + 1
-let add_subbytes b s offset len =
- if offset < 0 || len < 0 || offset > Bytes.length s - len
- then invalid_arg "Buffer.add_subbytes";
+let add_substring b s offset len =
+ if offset < 0 || len < 0 || offset + len > String.length s
+ then invalid_arg "Buffer.add_substring/add_subbytes";
let new_position = b.position + len in
if new_position > b.length then resize b len;
- Bytes.unsafe_blit s offset b.buffer b.position len;
+ Bytes.blit_string s offset b.buffer b.position len;
b.position <- new_position
-let add_substring b s offset len =
- add_subbytes b (Bytes.unsafe_of_string s) offset len
+let add_subbytes b s offset len =
+ add_substring b (Bytes.unsafe_to_string s) offset len
-let add_bytes b s =
- let len = Bytes.length s in
+let add_string b s =
+ let len = String.length s in
let new_position = b.position + len in
if new_position > b.length then resize b len;
- Bytes.unsafe_blit s 0 b.buffer b.position len;
+ Bytes.blit_string s 0 b.buffer b.position len;
b.position <- new_position
-let add_string b s = add_bytes b (Bytes.unsafe_of_string s)
+let add_bytes b s = add_string b (Bytes.unsafe_to_string s)
let add_buffer b bs =
add_subbytes b bs.buffer 0 bs.position