summaryrefslogtreecommitdiffstats
path: root/stdlib/bytes.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/bytes.ml')
-rw-r--r--stdlib/bytes.ml31
1 files changed, 29 insertions, 2 deletions
diff --git a/stdlib/bytes.ml b/stdlib/bytes.ml
index cfcd1ec05..ece7c1ea5 100644
--- a/stdlib/bytes.ml
+++ b/stdlib/bytes.ml
@@ -14,18 +14,22 @@
(* Byte sequence operations *)
external length : bytes -> int = "%string_length"
+external string_length : string -> int = "%string_length"
external get : bytes -> int -> char = "%string_safe_get"
external set : bytes -> int -> char -> unit = "%string_safe_set"
external create : int -> bytes = "caml_create_string"
external unsafe_get : bytes -> int -> char = "%string_unsafe_get"
external unsafe_set : bytes -> int -> char -> unit = "%string_unsafe_set"
-external unsafe_blit : bytes -> int -> bytes -> int -> int -> unit
- = "caml_blit_string" "noalloc"
external unsafe_fill : bytes -> int -> int -> char -> unit
= "caml_fill_string" "noalloc"
external unsafe_to_string : bytes -> string = "%identity"
external unsafe_of_string : string -> bytes = "%identity"
+external unsafe_blit : bytes -> int -> bytes -> int -> int -> unit
+ = "caml_blit_string" "noalloc"
+external unsafe_blit_string : string -> int -> bytes -> int -> int -> unit
+ = "caml_blit_string" "noalloc"
+
let make n c =
let s = create n in
unsafe_fill s 0 n c;
@@ -60,6 +64,14 @@ let sub s ofs len =
let sub_string b ofs len = unsafe_to_string (sub b ofs len)
+let extend s left right =
+ let len = length s + left + right in
+ let r = create len in
+ let (srcoff, dstoff) = if left < 0 then -left, 0 else 0, left in
+ let cpylen = min (length s - srcoff) (len - dstoff) in
+ if cpylen > 0 then unsafe_blit s srcoff r dstoff cpylen;
+ r
+
let fill s ofs len c =
if ofs < 0 || len < 0 || ofs > length s - len
then invalid_arg "Bytes.fill"
@@ -71,6 +83,12 @@ let blit s1 ofs1 s2 ofs2 len =
then invalid_arg "Bytes.blit"
else unsafe_blit s1 ofs1 s2 ofs2 len
+let blit_string s1 ofs1 s2 ofs2 len =
+ if len < 0 || ofs1 < 0 || ofs1 > string_length s1 - len
+ || ofs2 < 0 || ofs2 > length s2 - len
+ then invalid_arg "Bytes.blit_string"
+ else unsafe_blit_string s1 ofs1 s2 ofs2 len
+
let iter f a =
for i = 0 to length a - 1 do f(unsafe_get a i) done
@@ -95,6 +113,15 @@ let concat sep l =
tl;
r
+let cat s1 s2 =
+ let l1 = length s1 in
+ let l2 = length s2 in
+ let r = create (l1 + l2) in
+ unsafe_blit s1 0 r 0 l1;
+ unsafe_blit s2 0 r l1 l2;
+ r
+;;
+
external is_printable: char -> bool = "caml_is_printable"
external char_code: char -> int = "%identity"
external char_chr: int -> char = "%identity"