diff options
Diffstat (limited to 'stdlib')
-rw-r--r-- | stdlib/array.mli | 3 | ||||
-rw-r--r-- | stdlib/buffer.mli | 2 | ||||
-rw-r--r-- | stdlib/format.mli | 18 | ||||
-rw-r--r-- | stdlib/list.mli | 4 | ||||
-rw-r--r-- | stdlib/pervasives.mli | 6 | ||||
-rw-r--r-- | stdlib/set.mli | 6 | ||||
-rw-r--r-- | stdlib/string.mli | 6 | ||||
-rw-r--r-- | stdlib/weak.mli | 3 |
8 files changed, 26 insertions, 22 deletions
diff --git a/stdlib/array.mli b/stdlib/array.mli index 9beb68082..e98b80cec 100644 --- a/stdlib/array.mli +++ b/stdlib/array.mli @@ -81,7 +81,8 @@ val fill: 'a array -> pos:int -> len:int -> 'a -> unit storing [x] in elements number [ofs] to [ofs + len - 1]. Raise [Invalid_argument "Array.fill"] if [ofs] and [len] do not designate a valid subarray of [a]. *) -val blit: 'a array -> pos:int -> to:'a array -> to_pos:int -> len:int -> unit +val blit: src:'a array -> src_pos:int -> + dst:'a array -> dst_pos:int -> len:int -> unit (* [Array.blit v1 o1 v2 o2 len] copies [len] elements from array [v1], starting at element number [o1], to array [v2], starting at element number [o2]. It works correctly even if diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index 8d205cca8..1f9728d94 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -55,7 +55,7 @@ val add_string : t -> string -> unit val add_substring : t -> string -> pos:int -> len: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]. *) -val add_buffer : t -> t -> unit +val add_buffer : t -> src:t -> unit (* [add_buffer b1 b2] appends the current contents of buffer [b2] at the end of buffer [b1]. [b2] is not modified. *) val add_channel : t -> in_channel -> len:int -> unit diff --git a/stdlib/format.mli b/stdlib/format.mli index 244af7a29..08e6dc314 100644 --- a/stdlib/format.mli +++ b/stdlib/format.mli @@ -224,7 +224,7 @@ val set_formatter_out_channel : out_channel -> unit;; (* Redirect the pretty-printer output to the given channel. *) val set_formatter_output_functions : - out:(buffer:string -> pos:int -> len:int -> unit) -> + out:(buf:string -> pos:int -> len:int -> unit) -> flush:(unit -> unit) -> unit;; (* [set_formatter_output_functions out flush] redirects the pretty-printer output to the functions [out] and [flush]. @@ -235,12 +235,12 @@ val set_formatter_output_functions : called whenever the pretty-printer is flushed using [print_flush] or [print_newline]. *) val get_formatter_output_functions : - unit -> (buffer:string -> pos:int -> len:int -> unit) * (unit -> unit);; + unit -> (buf:string -> pos:int -> len:int -> unit) * (unit -> unit);; (* Return the current output functions of the pretty-printer. *) (*** Changing the meaning of indentation and line breaking *) val set_all_formatter_output_functions : - out:(buffer:string -> pos:int -> len:int -> unit) -> + out:(buf:string -> pos:int -> len:int -> unit) -> flush:(unit -> unit) -> newline:(unit -> unit) -> space:(int -> unit) -> unit;; (* [set_all_formatter_output_functions out flush outnewline outspace] @@ -259,7 +259,7 @@ val set_all_formatter_output_functions : [outspace] and [outnewline] are [out (String.make n ' ') 0 n] and [out "\n" 0 1]. *) val get_all_formatter_output_functions : unit -> - (buffer:string -> pos:int -> len:int -> unit) * (unit -> unit) * + (buf:string -> pos:int -> len:int -> unit) * (unit -> unit) * (unit -> unit) * (int -> unit);; (* Return the current output functions of the pretty-printer, including line breaking and indentation functions. *) @@ -313,7 +313,7 @@ val flush_str_formatter : unit -> string;; [str_formatter] is defined as [formatter_of_buffer stdbuf]. *) val make_formatter : - out:(buffer:string -> pos:int -> len:int -> unit) -> + out:(buf:string -> pos:int -> len:int -> unit) -> flush:(unit -> unit) -> formatter;; (* [make_formatter out flush] returns a new formatter that writes according to the output function [out], and the flushing @@ -355,16 +355,16 @@ val pp_set_ellipsis_text : formatter -> string -> unit;; val pp_get_ellipsis_text : formatter -> unit -> string;; val pp_set_formatter_out_channel : formatter -> out_channel -> unit;; val pp_set_formatter_output_functions : formatter -> - out:(buffer:string -> pos:int -> len:int -> unit) -> + out:(buf:string -> pos:int -> len:int -> unit) -> flush:(unit -> unit) -> unit;; val pp_get_formatter_output_functions : formatter -> unit -> - (buffer:string -> pos:int -> len:int -> unit) * (unit -> unit);; + (buf:string -> pos:int -> len:int -> unit) * (unit -> unit);; val pp_set_all_formatter_output_functions : formatter -> - out:(buffer:string -> pos:int -> len:int -> unit) -> + out:(buf:string -> pos:int -> len:int -> unit) -> flush:(unit -> unit) -> newline:(unit -> unit) -> space:(int -> unit) -> unit;; val pp_get_all_formatter_output_functions : formatter -> unit -> - (buffer:string -> pos:int -> len:int -> unit) * (unit -> unit) * + (buf:string -> pos:int -> len:int -> unit) * (unit -> unit) * (unit -> unit) * (int -> unit);; (* The basic functions to use with formatters. These functions are the basic ones: usual functions diff --git a/stdlib/list.mli b/stdlib/list.mli index 6667526d0..90d224db1 100644 --- a/stdlib/list.mli +++ b/stdlib/list.mli @@ -117,10 +117,10 @@ val exists2 : pred:('a -> 'b -> bool) -> 'a list -> 'b list -> bool (* Same as [for_all] and [exists], but for a two-argument predicate. Raise [Invalid_argument] if the two lists have different lengths. *) -val mem : item:'a -> 'a list -> bool +val mem : key:'a -> 'a list -> bool (* [mem a l] is true if and only if [a] is equal to an element of [l]. *) -val memq : item:'a -> 'a list -> bool +val memq : key:'a -> 'a list -> bool (* Same as [mem], but uses physical equality instead of structural equality to compare list elements. *) diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index 73108775f..e4bb280cf 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -455,7 +455,7 @@ val output_char : to:out_channel -> char -> unit (* Write the character on the given output channel. *) val output_string : to:out_channel -> string -> unit (* Write the string on the given output channel. *) -val output : out_channel -> buffer:string -> pos:int -> len:int -> unit +val output : out_channel -> buf:string -> pos:int -> len:int -> unit (* [output chan buff ofs len] writes [len] characters from string [buff], starting at offset [ofs], to the output channel [chan]. Raise [Invalid_argument "output"] if [ofs] and [len] do not @@ -526,7 +526,7 @@ val input_line : in_channel -> string all characters read, without the newline character at the end. Raise [End_of_file] if the end of the file is reached at the beginning of line. *) -val input : in_channel -> buffer:string -> pos:int -> len:int -> int +val input : in_channel -> buf:string -> pos:int -> len:int -> int (* [input chan buff ofs len] attempts to read [len] characters from channel [chan], storing them in string [buff], starting at character number [ofs]. It returns the actual number of characters @@ -537,7 +537,7 @@ val input : in_channel -> buffer:string -> pos:int -> len:int -> int called again to read the remaining characters, if desired. Exception [Invalid_argument "input"] is raised if [ofs] and [len] do not designate a valid substring of [buff]. *) -val really_input : in_channel -> buffer:string -> pos:int -> len:int -> unit +val really_input : in_channel -> buf:string -> pos:int -> len:int -> unit (* [really_input chan buff ofs len] reads [len] characters from channel [chan], storing them in string [buff], starting at character number [ofs]. Raise [End_of_file] if diff --git a/stdlib/set.mli b/stdlib/set.mli index 058a91146..7317915a6 100644 --- a/stdlib/set.mli +++ b/stdlib/set.mli @@ -46,14 +46,14 @@ module type S = (* The empty set. *) val is_empty: t -> bool (* Test whether a set is empty or not. *) - val mem: elt:elt -> t -> bool + val mem: key:elt -> t -> bool (* [mem x s] tests whether [x] belongs to the set [s]. *) - val add: elt:elt -> t -> t + val add: key:elt -> t -> t (* [add x s] returns a set containing all elements of [s], plus [x]. If [x] was already in [s], [s] is returned unchanged. *) val singleton: elt -> t (* [singleton x] returns the one-element set containing only [x]. *) - val remove: elt:elt -> t -> t + val remove: key:elt -> t -> t (* [remove x s] returns a set containing all elements of [s], except [x]. If [x] was not in [s], [s] is returned unchanged. *) val union: t -> t -> t diff --git a/stdlib/string.mli b/stdlib/string.mli index 7add92843..270667782 100644 --- a/stdlib/string.mli +++ b/stdlib/string.mli @@ -56,7 +56,8 @@ val fill : string -> pos:int -> len:int -> char -> unit by [c]. Raise [Invalid_argument] if [start] and [len] do not designate a valid substring of [s]. *) -val blit : string -> pos:int -> to:string -> to_pos:int -> len:int -> unit +val blit : src:string -> src_pos:int -> + dst:string -> dst_pos:int -> len:int -> unit (* [String.blit src srcoff dst dstoff len] copies [len] characters from string [src], starting at character number [srcoff], to string [dst], starting at character number [dstoff]. It works @@ -125,7 +126,8 @@ val uncapitalize: string -> string external unsafe_get : string -> int -> char = "%string_unsafe_get" external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set" external unsafe_blit : - string -> pos:int -> to:string -> to_pos:int -> len:int -> unit + src:string -> src_pos:int -> + dst:string -> dst_pos:int -> len:int -> unit = "blit_string" "noalloc" external unsafe_fill : string -> pos:int -> len:int -> char -> unit = "fill_string" "noalloc" diff --git a/stdlib/weak.mli b/stdlib/weak.mli index 8b8b6b331..5e671fdbd 100644 --- a/stdlib/weak.mli +++ b/stdlib/weak.mli @@ -53,7 +53,8 @@ val fill: 'a t -> pos:int -> len:int -> 'a option -> unit;; [ofs] to [ofs + len - 1]. Raise [Invalid_argument "Weak.fill"] if [ofs] and [len] do not designate a valid subarray of [a]. *) -val blit : 'a t -> pos:int -> to:'a t -> to_pos:int -> len:int -> unit;; +val blit : src:'a t -> src_pos:int -> + dst:'a t -> dst_pos:int -> len:int -> unit;; (* [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers from [ar1] (starting at [off1]) to [ar2] (starting at [off2]). It works correctly even if [ar1] and [ar2] are the same. |