Switch to OCaml version 4.04.0.

This commit is contained in:
Benjamin Canou 2017-03-17 14:39:31 +01:00
parent ed6e91a47d
commit 31bc331063
12 changed files with 292 additions and 205 deletions

View File

@ -1,4 +1,4 @@
#! /bin/sh
alpine_version=3.5
ocaml_version=4.03.0
ocaml_version=4.04.0

View File

@ -167,6 +167,7 @@ module Make (T: QTY) : S = struct
| Ok res -> Ok res
| Error ([ Addition_overflow _ ] as errs) ->
Error (Multiplication_overflow (t, m) :: errs)
| Error errs -> Error errs
let ( /? ) t d =
if d <= 0L then

View File

@ -13,6 +13,14 @@
(* *)
(**************************************************************************)
(* TEZOS CHANGES
* Import version 4.04.0
* Remove unsafe functions
* Remove deprecated functions
*)
(** Array operations. *)
external length : 'a array -> int = "%array_length"
@ -48,19 +56,11 @@ external make : int -> 'a -> 'a array = "caml_make_vect"
If the value of [x] is a floating-point number, then the maximum
size is only [Sys.max_array_length / 2].*)
external create : int -> 'a -> 'a array = "caml_make_vect"
[@@ocaml.deprecated "Use Array.make instead."]
(** @deprecated [Array.create] is an alias for {!Array.make}. *)
external create_float: int -> float array = "caml_make_float_vect"
(** [Array.create_float n] returns a fresh float array of length [n],
with uninitialized data.
@since 4.03 *)
val make_float: int -> float array
[@@ocaml.deprecated "Use Array.create_float instead."]
(** @deprecated [Array.make_float] is an alias for {!Array.create_float}. *)
val init : int -> (int -> 'a) -> 'a array
(** [Array.init n f] returns a fresh array of length [n],
with element number [i] initialized to the result of [f i].
@ -84,10 +84,6 @@ val make_matrix : int -> int -> 'a -> 'a array array
If the value of [e] is a floating-point number, then the maximum
size is only [Sys.max_array_length / 2]. *)
val create_matrix : int -> int -> 'a -> 'a array array
[@@ocaml.deprecated "Use Array.make_matrix instead."]
(** @deprecated [Array.create_matrix] is an alias for {!Array.make_matrix}. *)
val append : 'a array -> 'a array -> 'a array
(** [Array.append v1 v2] returns a fresh array containing the
concatenation of the arrays [v1] and [v2]. *)
@ -174,13 +170,15 @@ val fold_right : ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a
val iter2 : ('a -> 'b -> unit) -> 'a array -> 'b array -> unit
(** [Array.iter2 f a b] applies function [f] to all the elements of [a]
and [b].
Raise [Invalid_argument] if the arrays are not the same size. *)
Raise [Invalid_argument] if the arrays are not the same size.
@since 4.03.0 *)
val map2 : ('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
(** [Array.map2 f a b] applies function [f] to all the elements of [a]
and [b], and builds an array with the results returned by [f]:
[[| f a.(0) b.(0); ...; f a.(Array.length a - 1) b.(Array.length b - 1)|]].
Raise [Invalid_argument] if the arrays are not the same size. *)
Raise [Invalid_argument] if the arrays are not the same size.
@since 4.03.0 *)
(** {6 Array scanning} *)
@ -189,20 +187,24 @@ val map2 : ('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
val for_all : ('a -> bool) -> 'a array -> bool
(** [Array.for_all p [|a1; ...; an|]] checks if all elements of the array
satisfy the predicate [p]. That is, it returns
[(p a1) && (p a2) && ... && (p an)]. *)
[(p a1) && (p a2) && ... && (p an)].
@since 4.03.0 *)
val exists : ('a -> bool) -> 'a array -> bool
(** [Array.exists p [|a1; ...; an|]] checks if at least one element of
the array satisfies the predicate [p]. That is, it returns
[(p a1) || (p a2) || ... || (p an)]. *)
[(p a1) || (p a2) || ... || (p an)].
@since 4.03.0 *)
val mem : 'a -> 'a array -> bool
(** [mem a l] is true if and only if [a] is equal
to an element of [l]. *)
to an element of [l].
@since 4.03.0 *)
val memq : 'a -> 'a array -> bool
(** Same as {!Array.mem}, but uses physical equality instead of structural
equality to compare array elements. *)
equality to compare array elements.
@since 4.03.0 *)
(** {6 Sorting} *)
@ -249,11 +251,3 @@ val fast_sort : ('a -> 'a -> int) -> 'a array -> unit
on typical input.
*)
(**/**)
(** {6 Undocumented functions} *)
(* The following is for system use only. Do not call directly. *)
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"

View File

@ -1,20 +1,22 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Pierre Weis and Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1999 Institut National de Recherche en Informatique et *)
(* en Automatique. All rights reserved. This file is distributed *)
(* under the terms of the GNU Library General Public License, with *)
(* the special exception on linking described in file ../LICENSE. *)
(* *)
(***********************************************************************)
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Pierre Weis and Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1999 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* TEZOS CHANGES
* import version 4.02.1
* Removed channel functions
* Import version 4.04.0
* Remove channel functions
*)
@ -45,17 +47,19 @@ val create : int -> t
val contents : t -> string
(** Return a copy of the current contents of the buffer.
The buffer itself is unchanged. *)
The buffer itself is unchanged. *)
val to_bytes : t -> bytes
(** Return a copy of the current contents of the buffer.
The buffer itself is unchanged. *)
The buffer itself is unchanged.
@since 4.02 *)
val sub : t -> int -> int -> string
(** [Buffer.sub b off len] returns (a copy of) the bytes from the
current contents of the buffer [b] starting at offset [off] of
length [len] bytes. May raise [Invalid_argument] if out of bounds
request. The buffer itself is unaffected. *)
(** [Buffer.sub b off len] returns a copy of [len] bytes from the
current contents of the buffer [b], starting at offset [off].
Raise [Invalid_argument] if [srcoff] and [len] do not designate a valid
range of [b]. *)
val blit : t -> int -> bytes -> int -> int -> unit
(** [Buffer.blit src srcoff dst dstoff len] copies [len] characters from
@ -69,7 +73,7 @@ val blit : t -> int -> bytes -> int -> int -> unit
*)
val nth : t -> int -> char
(** get the n-th character of the buffer. Raise [Invalid_argument] if
(** Get the n-th character of the buffer. Raise [Invalid_argument] if
index out of bounds *)
val length : t -> int
@ -86,25 +90,27 @@ val reset : t -> unit
faster reclamation of the space used by the buffer. *)
val add_char : t -> char -> unit
(** [add_char b c] appends the character [c] at the end of the buffer [b]. *)
(** [add_char b c] appends the character [c] at the end of buffer [b]. *)
val add_string : t -> string -> unit
(** [add_string b s] appends the string [s] at the end of the buffer [b]. *)
(** [add_string b s] appends the string [s] at the end of buffer [b]. *)
val add_bytes : t -> bytes -> unit
(** [add_string b s] appends the string [s] at the end of the buffer [b]. *)
(** [add_bytes b s] appends the byte sequence [s] at the end of buffer [b].
@since 4.02 *)
val add_substring : t -> string -> int -> int -> unit
(** [add_substring b s ofs len] takes [len] characters from offset
[ofs] in string [s] and appends them at the end of the buffer [b]. *)
[ofs] in string [s] and appends them at the end of buffer [b]. *)
val add_subbytes : t -> bytes -> int -> int -> unit
(** [add_substring b s ofs len] takes [len] characters from offset
[ofs] in byte sequence [s] and appends them at the end of the buffer [b]. *)
(** [add_subbytes b s ofs len] takes [len] characters from offset
[ofs] in byte sequence [s] and appends them at the end of buffer [b].
@since 4.02 *)
val add_substitute : t -> (string -> string) -> string -> unit
(** [add_substitute b f s] appends the string pattern [s] at the end
of the buffer [b] with substitution.
of buffer [b] with substitution.
The substitution process looks for variables into
the pattern and substitutes each variable name by its value, as
obtained by applying the mapping [f] to the variable name. Inside the

View File

@ -13,6 +13,15 @@
(* *)
(**************************************************************************)
(* TEZOS CHANGES
* Import version 4.04.0
* Remove unsafe functions
* Remove deprecated functions
* Add binary data insertion / extraction functions
*)
(** Byte sequence operations.
A byte sequence is a mutable data structure that contains a
@ -42,21 +51,21 @@
@since 4.02.0
*)
external length : bytes -> int = "%string_length"
external length : bytes -> int = "%bytes_length"
(** Return the length (number of bytes) of the argument. *)
external get : bytes -> int -> char = "%string_safe_get"
external get : bytes -> int -> char = "%bytes_safe_get"
(** [get s n] returns the byte at index [n] in argument [s].
Raise [Invalid_argument] if [n] not a valid index in [s]. *)
external set : bytes -> int -> char -> unit = "%string_safe_set"
external set : bytes -> int -> char -> unit = "%bytes_safe_set"
(** [set s n c] modifies [s] in place, replacing the byte at index [n]
with [c].
Raise [Invalid_argument] if [n] is not a valid index in [s]. *)
external create : int -> bytes = "caml_create_string"
external create : int -> bytes = "caml_create_bytes"
(** [create n] returns a new byte sequence of length [n]. The
sequence is uninitialized and contains arbitrary bytes.
@ -232,32 +241,6 @@ val rcontains_from : bytes -> int -> char -> bool
Raise [Invalid_argument] if [stop < 0] or [stop+1] is not a valid
position in [s]. *)
val uppercase : bytes -> bytes
[@@ocaml.deprecated "Use Bytes.uppercase_ascii instead."]
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO
Latin-1 (8859-1) character set.
@deprecated Functions operating on Latin-1 character set are deprecated. *)
val lowercase : bytes -> bytes
[@@ocaml.deprecated "Use Bytes.lowercase_ascii instead."]
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, including accented letters of the ISO
Latin-1 (8859-1) character set.
@deprecated Functions operating on Latin-1 character set are deprecated. *)
val capitalize : bytes -> bytes
[@@ocaml.deprecated "Use Bytes.capitalize_ascii instead."]
(** Return a copy of the argument, with the first character set to uppercase,
using the ISO Latin-1 (8859-1) character set..
@deprecated Functions operating on Latin-1 character set are deprecated. *)
val uncapitalize : bytes -> bytes
[@@ocaml.deprecated "Use Bytes.uncapitalize_ascii instead."]
(** Return a copy of the argument, with the first character set to lowercase,
using the ISO Latin-1 (8859-1) character set..
@deprecated Functions operating on Latin-1 character set are deprecated. *)
val uppercase_ascii : bytes -> bytes
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, using the US-ASCII character set.

View File

@ -15,10 +15,10 @@
(* TEZOS CHANGES
* import version 4.03.0
* Removed channel functions
* Removed toplevel effect based functions
* Removed deprecated functions
* Import version 4.04.0
* Remove channel functions
* Remove toplevel effect based functions
* Remove deprecated functions
*)
@ -83,15 +83,48 @@
the evaluation order of printing commands.
*)
(** {6:tags Semantic Tags} *)
type tag = string
(** {6:meaning Changing the meaning of standard formatter pretty printing} *)
(** The [Format] module is versatile enough to let you completely redefine
the meaning of pretty printing: you may provide your own functions to define
how to handle indentation, line splitting, and even printing of all the
characters that have to be printed! *)
type formatter_out_functions = {
out_string : string -> int -> int -> unit;
out_flush : unit -> unit;
out_newline : unit -> unit;
out_spaces : int -> unit;
}
(** {6:tagsmeaning Changing the meaning of printing semantic tags} *)
type formatter_tag_functions = {
mark_open_tag : tag -> string;
mark_close_tag : tag -> string;
print_open_tag : tag -> unit;
print_close_tag : tag -> unit;
}
(** The tag handling functions specific to a formatter:
[mark] versions are the 'tag marking' functions that associate a string
marker to a tag in order for the pretty-printing engine to flush
those markers as 0 length tokens in the output device of the formatter.
[print] versions are the 'tag printing' functions that can perform
regular printing when a tag is closed or opened. *)
(** {6 Multiple formatted output} *)
type formatter;;
type formatter
(** Abstract data corresponding to a pretty-printer (also called a
formatter) and all its machinery.
Defining new pretty-printers permits unrelated output of material in
parallel on several output channels.
All the parameters of a pretty-printer are local to this pretty-printer:
All the parameters of a pretty-printer are local to a formatter:
margin, maximum indentation limit, maximum number of boxes
simultaneously opened, ellipsis, and so on, are specific to
each pretty-printer and may be fixed independently.
@ -154,6 +187,36 @@ val pp_over_max_boxes : formatter -> unit -> bool
val pp_set_ellipsis_text : formatter -> string -> unit
val pp_get_ellipsis_text : formatter -> unit -> string
val pp_set_formatter_output_functions :
formatter -> (string -> int -> int -> unit) -> (unit -> unit) -> unit
val pp_get_formatter_output_functions :
formatter -> unit -> (string -> int -> int -> unit) * (unit -> unit)
val pp_set_formatter_tag_functions :
formatter -> formatter_tag_functions -> unit
val pp_get_formatter_tag_functions :
formatter -> unit -> formatter_tag_functions
val pp_set_formatter_out_functions :
formatter -> formatter_out_functions -> unit
val pp_get_formatter_out_functions :
formatter -> unit -> formatter_out_functions
(** These functions are the basic ones: usual functions
operating on the standard formatter are defined via partial
evaluation of these primitives. For instance,
[print_string] is equal to [pp_print_string std_formatter]. *)
val pp_flush_formatter : formatter -> unit
(** [pp_flush_formatter fmt] flushes [fmt]'s internal queue, ensuring that all
the printing and flushing actions have been performed. In addition, this
operation will close all boxes and reset the state of the formatter.
This will not flush [fmt]'s output. In most cases, the user may want to use
{!pp_print_flush} instead. *)
(** {6 Convenience formatting functions.} *)
val pp_print_list:

View File

@ -13,6 +13,13 @@
(* *)
(**************************************************************************)
(* TEZOS CHANGES
* Import version 4.04.0
* Remove deprecated functions
*)
(** 32-bit integers.
This module provides operations on the type [int32]
@ -167,10 +174,3 @@ val equal: t -> t -> bool
(** The equal function for int32s.
@since 4.03.0 *)
(**/**)
(** {6 Deprecated functions} *)
external format : string -> int32 -> string = "caml_int32_format"
(** Do not use this deprecated function. Instead,
used {!Printf.sprintf} with a [%l...] format. *)

View File

@ -13,6 +13,12 @@
(* *)
(**************************************************************************)
(* TEZOS CHANGES
* Import version 4.04.0
* Remove deprecated functions
*)
(** 64-bit integers.
This module provides operations on the type [int64] of
@ -188,11 +194,3 @@ val compare: t -> t -> int
val equal: t -> t -> bool
(** The equal function for int64s.
@since 4.03.0 *)
(**/**)
(** {6 Deprecated functions} *)
external format : string -> int64 -> string = "caml_int64_format"
(** Do not use this deprecated function. Instead,
used {!Printf.sprintf} with a [%L...] format. *)

View File

@ -67,8 +67,7 @@ val concat : 'a list list -> 'a list
(length of the argument + length of the longest sub-list). *)
val flatten : 'a list list -> 'a list
(** Same as [concat]. Not tail-recursive
(length of the argument + length of the longest sub-list). *)
(** An alias for [concat]. *)
(** {6 Iterators} *)

View File

@ -15,9 +15,12 @@
(* TEZOS CHANGES
* import version 4.02.1
* Removed [channel], [exit], ...
* Removed polymorphic comparisons
* Import version 4.04.0
* Remove [channel], [exit], ...
* Remove polymorphic comparisons
* Remove non IEEE754-standardized functions on floats
* Remove deprecated functions
*)
@ -38,7 +41,7 @@
external raise : exn -> 'a = "%raise"
(** Raise the given exception value *)
(* external raise_notrace : exn -> 'a = "%raise_notrace" *)
external raise_notrace : exn -> 'a = "%raise_notrace"
(** A faster version [raise] which does not record the backtrace.
@since 4.02.0
*)
@ -46,7 +49,7 @@ external raise : exn -> 'a = "%raise"
val invalid_arg : string -> 'a
(** Raise exception [Invalid_argument] with the given string. *)
(* val failwith : string -> 'a *)
val failwith : string -> 'a
(** Raise exception [Failure] with the given string. *)
exception Exit
@ -64,56 +67,72 @@ external ( && ) : bool -> bool -> bool = "%sequand"
in [e1 && e2], [e1] is evaluated first, and if it returns [false],
[e2] is not evaluated at all. *)
external ( & ) : bool -> bool -> bool = "%sequand"
(** @deprecated {!Pervasives.( && )} should be used instead. *)
external ( || ) : bool -> bool -> bool = "%sequor"
(** The boolean 'or'. Evaluation is sequential, left-to-right:
in [e1 || e2], [e1] is evaluated first, and if it returns [true],
[e2] is not evaluated at all. *)
external ( or ) : bool -> bool -> bool = "%sequor"
[@@ocaml.deprecated "Use (||) instead."]
(** @deprecated {!Pervasives.( || )} should be used instead.*)
(** {6 Debugging} *)
external __LOC__ : string = "%loc_LOC"
(** [__LOC__] returns the location at which this expression appears in
the file currently being parsed by the compiler, with the standard
error format of OCaml: "File %S, line %d, characters %d-%d" *)
error format of OCaml: "File %S, line %d, characters %d-%d".
@since 4.02.0
*)
external __FILE__ : string = "%loc_FILE"
(** [__FILE__] returns the name of the file currently being
parsed by the compiler. *)
parsed by the compiler.
@since 4.02.0
*)
external __LINE__ : int = "%loc_LINE"
(** [__LINE__] returns the line number at which this expression
appears in the file currently being parsed by the compiler. *)
appears in the file currently being parsed by the compiler.
@since 4.02.0
*)
external __MODULE__ : string = "%loc_MODULE"
(** [__MODULE__] returns the module name of the file being
parsed by the compiler. *)
parsed by the compiler.
@since 4.02.0
*)
external __POS__ : string * int * int * int = "%loc_POS"
(** [__POS__] returns a tuple [(file,lnum,cnum,enum)], corresponding
to the location at which this expression appears in the file
currently being parsed by the compiler. [file] is the current
filename, [lnum] the line number, [cnum] the character position in
the line and [enum] the last character position in the line. *)
the line and [enum] the last character position in the line.
@since 4.02.0
*)
external __LOC_OF__ : 'a -> string * 'a = "%loc_LOC"
(** [__LOC_OF__ expr] returns a pair [(loc, expr)] where [loc] is the
location of [expr] in the file currently being parsed by the
compiler, with the standard error format of OCaml: "File %S, line
%d, characters %d-%d" *)
%d, characters %d-%d".
@since 4.02.0
*)
external __LINE_OF__ : 'a -> int * 'a = "%loc_LINE"
(** [__LINE__ expr] returns a pair [(line, expr)], where [line] is the
line number at which the expression [expr] appears in the file
currently being parsed by the compiler. *)
currently being parsed by the compiler.
@since 4.02.0
*)
external __POS_OF__ : 'a -> (string * int * int * int) * 'a = "%loc_POS"
(** [__POS_OF__ expr] returns a pair [(expr,loc)], where [loc] is a
(** [__POS_OF__ expr] returns a pair [(loc,expr)], where [loc] is a
tuple [(file,lnum,cnum,enum)] corresponding to the location at
which the expression [expr] appears in the file currently being
parsed by the compiler. [file] is the current filename, [lnum] the
line number, [cnum] the character position in the line and [enum]
the last character position in the line. *)
the last character position in the line.
@since 4.02.0
*)
(** {6 Composition operators} *)
@ -556,5 +575,27 @@ type ('a, 'b, 'c, 'd) format4 = ('a, 'b, 'c, 'c, 'c, 'd) format6
type ('a, 'b, 'c) format = ('a, 'b, 'c, 'c) format4
val string_of_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
(** Converts a format string into a string. *)
external format_of_string :
('a, 'b, 'c, 'd, 'e, 'f) format6 ->
('a, 'b, 'c, 'd, 'e, 'f) format6 = "%identity"
(** [format_of_string s] returns a format string read from the string
literal [s].
Note: [format_of_string] can not convert a string argument that is not a
literal. If you need this functionality, use the more general
{!Scanf.format_from_string} function.
*)
val ( ^^ ) :
('a, 'b, 'c, 'd, 'e, 'f) format6 ->
('f, 'b, 'c, 'e, 'g, 'h) format6 ->
('a, 'b, 'c, 'd, 'g, 'h) format6
(** [f1 ^^ f2] catenates format strings [f1] and [f2]. The result is a
format string that behaves as the concatenation of format strings [f1] and
[f2]: in case of formatted output, it accepts arguments from [f1], then
arguments from [f2]; in case of formatted input, it returns results from
[f1], then results from [f2].
*)

View File

@ -118,6 +118,17 @@ module type S =
The elements of [s] are presented to [f] in increasing order
with respect to the ordering over the type of the elements. *)
val map: (elt -> elt) -> t -> t
(** [map f s] is the set whose elements are [f a0],[f a1]... [f
aN], where [a0],[a1]...[aN] are the elements of [s].
The elements are passed to [f] in increasing order
with respect to the ordering over the type of the elements.
If no element of [s] is changed by [f], [s] is returned
unchanged. (If each output of [f] is physically equal to its
input, the returned set is physically equal to [s].) *)
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
(** [fold f s a] computes [(f xN ... (f x2 (f x1 a))...)],
where [x1 ... xN] are the elements of [s], in increasing order. *)

View File

@ -1,15 +1,26 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. All rights reserved. This file is distributed *)
(* under the terms of the GNU Library General Public License, with *)
(* the special exception on linking described in file ../LICENSE. *)
(* *)
(***********************************************************************)
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* TEZOS CHANGES
* Import version 4.04.0
* Remove unsafe functions
* Remove deprecated functions (enforcing string immutability)
* Add binary data extraction functions
*)
(** String operations.
@ -30,20 +41,6 @@
substring of [s] if [len >= 0] and [start] and [start+len] are
valid positions in [s].
OCaml strings used to be modifiable in place, for instance via the
{!String.set} and {!String.blit} functions described below. This
usage is deprecated and only possible when the compiler is put in
"unsafe-string" mode by giving the [-unsafe-string] command-line
option (which is currently the default for reasons of backward
compatibility). This is done by making the types [string] and
[bytes] (see module {!Bytes}) interchangeable so that functions
expecting byte sequences can also accept strings as arguments and
modify them.
All new code should avoid this feature and be compiled with the
[-safe-string] command-line option to enforce the separation between
the types [string] and [bytes].
*)
external length : string -> int = "%string_length"
@ -56,25 +53,6 @@ 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 = "%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].
You can also write [s.[n] <- c] instead of [String.set s n c].
Raise [Invalid_argument] if [n] is not a valid index in [s].
@deprecated This is a deprecated alias of {!Bytes.set}.[ ] *)
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.
Raise [Invalid_argument] if [n < 0] or [n > ]{!Sys.max_string_length}.
@deprecated This is a deprecated alias of {!Bytes.create}.[ ] *)
val make : int -> char -> string
(** [String.make n c] returns a fresh string of length [n],
filled with the character [c].
@ -91,12 +69,6 @@ val init : int -> (int -> char) -> string
@since 4.02.0
*)
val copy : string -> string [@@ocaml.deprecated]
(** Return a copy of the given string.
@deprecated Because strings are immutable, it doesn't make much
sense to make identical copies of them. *)
val sub : string -> int -> int -> string
(** [String.sub s start len] returns a fresh string of length [len],
containing the substring of [s] that starts at position [start] and
@ -105,16 +77,6 @@ val sub : string -> int -> int -> string
Raise [Invalid_argument] if [start] and [len] do not
designate a valid substring of [s]. *)
val fill : bytes -> int -> int -> char -> unit
[@@ocaml.deprecated "Use Bytes.fill instead."]
(** [String.fill s start len c] modifies byte sequence [s] in place,
replacing [len] bytes with [c], starting at [start].
Raise [Invalid_argument] if [start] and [len] do not
designate a valid range of [s].
@deprecated This is a deprecated alias of {!Bytes.fill}.[ ] *)
val blit : string -> int -> bytes -> int -> int -> unit
(** Same as {!Bytes.blit_string}. *)
@ -158,13 +120,20 @@ val trim : string -> string
val escaped : string -> string
(** Return a copy of the argument, with special characters
represented by escape sequences, following the lexical
conventions of OCaml. If there is no special
character in the argument, return the original string itself,
not a copy. Its inverse function is Scanf.unescaped.
represented by escape sequences, following the lexical
conventions of OCaml.
All characters outside the ASCII printable range (32..126) are
escaped, as well as backslash and double-quote.
Raise [Invalid_argument] if the result is longer than
{!Sys.max_string_length} bytes. *)
If there is no special character in the argument that needs
escaping, return the original string itself, not a copy.
Raise [Invalid_argument] if the result is longer than
{!Sys.max_string_length} bytes.
The function {!Scanf.unescaped} is a left inverse of [escaped],
i.e. [Scanf.unescaped (escaped s) = s] for any string [s] (unless
[escape s] fails). *)
val index : string -> char -> int
(** [String.index s c] returns the index of the first
@ -214,21 +183,25 @@ val rcontains_from : string -> int -> char -> bool
Raise [Invalid_argument] if [stop < 0] or [stop+1] is not a valid
position in [s]. *)
val uppercase : string -> string
val uppercase_ascii : string -> string
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO
Latin-1 (8859-1) character set. *)
translated to uppercase, using the US-ASCII character set.
@since 4.03.0 *)
val lowercase : string -> string
val lowercase_ascii : string -> string
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, including accented letters of the ISO
Latin-1 (8859-1) character set. *)
translated to lowercase, using the US-ASCII character set.
@since 4.03.0 *)
val capitalize : string -> string
(** Return a copy of the argument, with the first character set to uppercase. *)
val capitalize_ascii : string -> string
(** Return a copy of the argument, with the first character set to uppercase,
using the US-ASCII character set.
@since 4.03.0 *)
val uncapitalize : string -> string
(** Return a copy of the argument, with the first character set to lowercase. *)
val uncapitalize_ascii : string -> string
(** Return a copy of the argument, with the first character set to lowercase,
using the US-ASCII character set.
@since 4.03.0 *)
type t = string
(** An alias for the type of strings. *)
@ -239,6 +212,24 @@ val compare: t -> t -> int
allows the module [String] to be passed as argument to the functors
{!Set.Make} and {!Map.Make}. *)
val equal: t -> t -> bool
(** The equal function for strings.
@since 4.03.0 *)
val split_on_char: char -> string -> string list
(** [String.split_on_char sep s] returns the list of all (possibly empty)
substrings of [s] that are delimited by the [sep] character.
The function's output is specified by the following invariants:
- The list is not empty.
- Concatenating its elements using [sep] as a separator returns a
string equal to the input ([String.concat (String.make 1 sep)
(String.split_on_char sep s) = s]).
- No string in the result contains the [sep] character.
@since 4.04.0
*)
(** Functions reading bytes *)