Skip to content

Commit 946de5a

Browse files
committed
Remove references to safe-string in the stdlib
1 parent c256a92 commit 946de5a

File tree

6 files changed

+14
-15
lines changed

6 files changed

+14
-15
lines changed

stdlib/.depend

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -475,14 +475,12 @@ stdlib__Lazy.cmi : lazy.mli \
475475
camlinternalLazy.cmi
476476
stdlib__Lexing.cmo : lexing.ml \
477477
stdlib__Sys.cmi \
478-
stdlib__String.cmi \
479478
stdlib__Int.cmi \
480479
stdlib__Bytes.cmi \
481480
stdlib__Array.cmi \
482481
stdlib__Lexing.cmi
483482
stdlib__Lexing.cmx : lexing.ml \
484483
stdlib__Sys.cmx \
485-
stdlib__String.cmx \
486484
stdlib__Int.cmx \
487485
stdlib__Bytes.cmx \
488486
stdlib__Array.cmx \

stdlib/bytes.mli

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -332,9 +332,9 @@ val ends_with :
332332
This section describes unsafe, low-level conversion functions
333333
between [bytes] and [string]. They do not copy the internal data;
334334
used improperly, they can break the immutability invariant on
335-
strings provided by the [-safe-string] option. They are available for
336-
expert library authors, but for most purposes you should use the
337-
always-correct {!to_string} and {!of_string} instead.
335+
strings. They are available for expert library authors, but for
336+
most purposes you should use the always-correct {!to_string} and
337+
{!of_string} instead.
338338
*)
339339

340340
val unsafe_to_string : bytes -> string

stdlib/bytesLabels.mli

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -332,9 +332,9 @@ val ends_with :
332332
This section describes unsafe, low-level conversion functions
333333
between [bytes] and [string]. They do not copy the internal data;
334334
used improperly, they can break the immutability invariant on
335-
strings provided by the [-safe-string] option. They are available for
336-
expert library authors, but for most purposes you should use the
337-
always-correct {!to_string} and {!of_string} instead.
335+
strings. They are available for expert library authors, but for
336+
most purposes you should use the always-correct {!to_string} and
337+
{!of_string} instead.
338338
*)
339339

340340
val unsafe_to_string : bytes -> string

stdlib/lexing.ml

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -163,10 +163,13 @@ let from_channel ?with_positions ic =
163163
from_function ?with_positions (fun buf n -> input ic buf 0 n)
164164

165165
let from_string ?(with_positions = true) s =
166+
(* We can't use [Bytes.unsafe_of_string] here,
167+
[lex_buffer] is exported in the mli, one can mutate
168+
it outside this module. *)
169+
let lex_buffer = Bytes.of_string s in
166170
{ refill_buff = (fun lexbuf -> lexbuf.lex_eof_reached <- true);
167-
lex_buffer = Bytes.of_string s; (* have to make a copy for compatibility
168-
with unsafe-string mode *)
169-
lex_buffer_len = String.length s;
171+
lex_buffer;
172+
lex_buffer_len = Bytes.length lex_buffer;
170173
lex_abs_pos = 0;
171174
lex_start_pos = 0;
172175
lex_curr_pos = 0;

stdlib/string.mli

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -347,8 +347,7 @@ val rindex_opt : string -> char -> int option
347347

348348
val to_seq : t -> char Seq.t
349349
(** [to_seq s] is a sequence made of the string's characters in
350-
increasing order. In ["unsafe-string"] mode, modifications of the string
351-
during iteration will be reflected in the sequence.
350+
increasing order.
352351
353352
@since 4.07 *)
354353

stdlib/stringLabels.mli

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -347,8 +347,7 @@ val rindex_opt : string -> char -> int option
347347

348348
val to_seq : t -> char Seq.t
349349
(** [to_seq s] is a sequence made of the string's characters in
350-
increasing order. In ["unsafe-string"] mode, modifications of the string
351-
during iteration will be reflected in the sequence.
350+
increasing order.
352351
353352
@since 4.07 *)
354353

0 commit comments

Comments
 (0)