Merge pull request #972 from dra27/string-primitive-compatibility

Make %string_safe_set and %string_unsafe_set deprecated aliases for bytes versions
master
Gabriel Scherer 2017-03-08 20:49:17 -05:00 committed by GitHub
commit 40ad626cc3
5 changed files with 18 additions and 12 deletions

View File

@ -1264,6 +1264,10 @@ OCaml 4.03.0 (25 Apr 2016):
caml_fill_bytes and caml_create_bytes for migration
(Hongbo Zhang, review by Damien Doligez, Alain Frisch, and Hugo Heuzard)
- GPR#772 %string_safe_set and %string_unsafe_set are deprecated aliases
for %bytes_safe_set and %bytes_unsafe_set.
(Hongbo Zhang and Damien Doligez)
- PR#3612, PR#92: allow allocating custom block with finalizers
in the minor heap.
(Pierre Chambart)

View File

@ -231,7 +231,9 @@ let primitives_table = create_hashtable 57 [
"%gefloat", Pfloatcomp Cge;
"%string_length", Pstringlength;
"%string_safe_get", Pstringrefs;
"%string_safe_set", Pbytessets;
"%string_unsafe_get", Pstringrefu;
"%string_unsafe_set", Pbytessetu;
"%bytes_length", Pbyteslength;
"%bytes_safe_get", Pbytesrefs;
"%bytes_safe_set", Pbytessets;

View File

@ -23,14 +23,14 @@
external length : string -> int = "%string_length"
external get : string -> int -> char = "%string_safe_get"
external set : bytes -> int -> char -> unit = "%bytes_safe_set"
external create : int -> bytes = "caml_create_bytes"
external set : bytes -> int -> char -> unit = "%string_safe_set"
external create : int -> bytes = "caml_create_string"
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : bytes -> int -> char -> unit = "%bytes_unsafe_set"
external unsafe_set : bytes -> int -> char -> unit = "%string_unsafe_set"
external unsafe_blit : string -> int -> bytes -> int -> int -> unit
= "caml_blit_string" [@@noalloc]
external unsafe_fill : bytes -> int -> int -> char -> unit
= "caml_fill_bytes" [@@noalloc]
= "caml_fill_string" [@@noalloc]
module B = Bytes

View File

@ -58,7 +58,7 @@ external get : string -> int -> char = "%string_safe_get"
Raise [Invalid_argument] if [n] not a valid index in [s]. *)
external set : bytes -> int -> char -> unit = "%bytes_safe_set"
external set : bytes -> int -> char -> unit = "%string_safe_set"
[@@ocaml.deprecated "Use Bytes.set instead."]
(** [String.set s n c] modifies byte sequence [s] in place,
replacing the byte at index [n] with [c].
@ -68,7 +68,7 @@ external set : bytes -> int -> char -> unit = "%bytes_safe_set"
@deprecated This is a deprecated alias of {!Bytes.set}.[ ] *)
external create : int -> bytes = "caml_create_bytes"
external create : int -> bytes = "caml_create_string"
[@@ocaml.deprecated "Use Bytes.create instead."]
(** [String.create n] returns a fresh byte sequence of length [n].
The sequence is uninitialized and contains arbitrary bytes.
@ -338,11 +338,11 @@ val split_on_char: char -> string -> string list
(* The following is for system use only. Do not call directly. *)
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : bytes -> int -> char -> unit = "%bytes_unsafe_set"
external unsafe_set : bytes -> int -> char -> unit = "%string_unsafe_set"
[@@ocaml.deprecated]
external unsafe_blit :
string -> int -> bytes -> int -> int -> unit
= "caml_blit_string" [@@noalloc]
external unsafe_fill :
bytes -> int -> int -> char -> unit = "caml_fill_bytes" [@@noalloc]
bytes -> int -> int -> char -> unit = "caml_fill_string" [@@noalloc]
[@@ocaml.deprecated]

View File

@ -24,7 +24,7 @@ external get : string -> int -> char = "%string_safe_get"
Raise [Invalid_argument] if [n] not a valid index in [s]. *)
external set : bytes -> int -> char -> unit = "%bytes_safe_set"
external set : bytes -> int -> char -> unit = "%string_safe_set"
[@@ocaml.deprecated "Use BytesLabels.set instead."]
(** [String.set s n c] modifies byte sequence [s] in place,
replacing the byte at index [n] with [c].
@ -34,7 +34,7 @@ external set : bytes -> int -> char -> unit = "%bytes_safe_set"
@deprecated This is a deprecated alias of {!BytesLabels.set}. *)
external create : int -> bytes = "caml_create_bytes"
external create : int -> bytes = "caml_create_string"
[@@ocaml.deprecated "Use BytesLabels.create instead."]
(** [String.create n] returns a fresh byte sequence of length [n].
The sequence is uninitialized and contains arbitrary bytes.
@ -293,11 +293,11 @@ val split_on_char: sep:char -> string -> string list
(* The following is for system use only. Do not call directly. *)
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : bytes -> int -> char -> unit = "%bytes_unsafe_set"
external unsafe_set : bytes -> int -> char -> unit = "%string_unsafe_set"
[@@ocaml.deprecated]
external unsafe_blit :
src:string -> src_pos:int -> dst:bytes -> dst_pos:int -> len:int ->
unit = "caml_blit_string" [@@noalloc]
external unsafe_fill :
bytes -> pos:int -> len:int -> char -> unit = "caml_fill_bytes" [@@noalloc]
bytes -> pos:int -> len:int -> char -> unit = "caml_fill_string" [@@noalloc]
[@@ocaml.deprecated]