diff options
Diffstat (limited to 'stdlib/buffer.ml')
-rw-r--r-- | stdlib/buffer.ml | 46 |
1 files changed, 25 insertions, 21 deletions
diff --git a/stdlib/buffer.ml b/stdlib/buffer.ml index 78a9e2611..986fe6f33 100644 --- a/stdlib/buffer.ml +++ b/stdlib/buffer.ml @@ -14,41 +14,38 @@ (* Extensible buffers *) type t = - {mutable buffer : string; + {mutable buffer : bytes; mutable position : int; mutable length : int; - initial_buffer : string} + initial_buffer : bytes} let create n = let n = if n < 1 then 1 else n in let n = if n > Sys.max_string_length then Sys.max_string_length else n in - let s = String.create n in + let s = Bytes.create n in {buffer = s; position = 0; length = n; initial_buffer = s} -let contents b = String.sub b.buffer 0 b.position +let contents b = Bytes.sub_string b.buffer 0 b.position +let to_bytes b = Bytes.sub b.buffer 0 b.position let sub b ofs len = if ofs < 0 || len < 0 || ofs > b.position - len then invalid_arg "Buffer.sub" - else begin - let r = String.create len in - String.unsafe_blit b.buffer ofs r 0 len; - r - end + else Bytes.sub_string b.buffer ofs len ;; let blit src srcoff dst dstoff len = if len < 0 || srcoff < 0 || srcoff > src.position - len - || dstoff < 0 || dstoff > (String.length dst) - len + || dstoff < 0 || dstoff > (Bytes.length dst) - len then invalid_arg "Buffer.blit" else - String.blit src.buffer srcoff dst dstoff len + Bytes.unsafe_blit src.buffer srcoff dst dstoff len ;; let nth b ofs = if ofs < 0 || ofs >= b.position then invalid_arg "Buffer.nth" - else String.unsafe_get b.buffer ofs + else Bytes.unsafe_get b.buffer ofs ;; let length b = b.position @@ -57,7 +54,7 @@ let clear b = b.position <- 0 let reset b = b.position <- 0; b.buffer <- b.initial_buffer; - b.length <- String.length b.buffer + b.length <- Bytes.length b.buffer let resize b more = let len = b.length in @@ -68,34 +65,41 @@ let resize b more = then new_len := Sys.max_string_length else failwith "Buffer.add: cannot grow buffer" end; - let new_buffer = String.create !new_len in - String.blit b.buffer 0 new_buffer 0 b.position; + let new_buffer = Bytes.create !new_len in + (* PR#6148: let's keep using [blit] rather than [unsafe_blit] in + this tricky function that is slow anyway. *) + Bytes.blit b.buffer 0 new_buffer 0 b.position; b.buffer <- new_buffer; b.length <- !new_len let add_char b c = let pos = b.position in if pos >= b.length then resize b 1; - String.unsafe_set b.buffer pos c; + Bytes.unsafe_set b.buffer pos c; b.position <- pos + 1 let add_substring b s offset len = - if offset < 0 || len < 0 || offset > String.length s - len - then invalid_arg "Buffer.add_substring"; + 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; - String.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_subbytes b s offset len = + add_substring b (Bytes.unsafe_to_string s) offset len + 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; - String.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_bytes b s = add_string b (Bytes.unsafe_to_string s) + let add_buffer b bs = - add_substring b bs.buffer 0 bs.position + add_subbytes b bs.buffer 0 bs.position let add_channel b ic len = if len < 0 || len > Sys.max_string_length then (* PR#5004 *) |