summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorJacques Garrigue <garrigue at math.nagoya-u.ac.jp>1999-12-07 15:01:27 +0000
committerJacques Garrigue <garrigue at math.nagoya-u.ac.jp>1999-12-07 15:01:27 +0000
commitc7168d234652e28f6da580b6f03efecf7d19ccb7 (patch)
treeec555bfa2186c74b161eac541d69d47266ad12c5
parentaa78984afcb46226cbc35922af41ff79278a237a (diff)
changed some labels
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2675 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--otherlibs/db/db.mli10
-rw-r--r--otherlibs/dbm/dbm.mli2
-rw-r--r--otherlibs/str/str.mli21
-rw-r--r--otherlibs/unix/unix.mli96
-rw-r--r--stdlib/array.mli3
-rw-r--r--stdlib/buffer.mli2
-rw-r--r--stdlib/format.mli18
-rw-r--r--stdlib/list.mli4
-rw-r--r--stdlib/pervasives.mli6
-rw-r--r--stdlib/set.mli6
-rw-r--r--stdlib/string.mli6
-rw-r--r--stdlib/weak.mli3
12 files changed, 91 insertions, 86 deletions
diff --git a/otherlibs/db/db.mli b/otherlibs/db/db.mli
index 904e63647..520f5db8f 100644
--- a/otherlibs/db/db.mli
+++ b/otherlibs/db/db.mli
@@ -48,7 +48,7 @@ type t
(* Raw access *)
external dbopen :
- string -> flags:open_flag list -> perm:file_perm -> btree_flag list -> t
+ string -> mode:open_flag list -> perm:file_perm -> btree_flag list -> t
= "caml_db_open"
(* [dbopen file flags mode] *)
@@ -56,18 +56,18 @@ external dbopen :
external close : t -> unit
= "caml_db_close"
-external del : t -> key:key -> cmd:routine_flag list -> unit
+external del : t -> key:key -> mode:routine_flag list -> unit
= "caml_db_del"
(* raise Not_found if the key was not in the file *)
-external get : t -> key:key -> cmd:routine_flag list -> data
+external get : t -> key:key -> mode:routine_flag list -> data
= "caml_db_get"
(* raise Not_found if the key was not in the file *)
-external put : t -> key:key -> data:data -> cmd:routine_flag list -> unit
+external put : t -> key:key -> data:data -> mode:routine_flag list -> unit
= "caml_db_put"
-external seq : t -> key:key -> cmd:routine_flag list -> (key * data)
+external seq : t -> key:key -> mode:routine_flag list -> (key * data)
= "caml_db_seq"
external sync : t -> unit
diff --git a/otherlibs/dbm/dbm.mli b/otherlibs/dbm/dbm.mli
index 06600cc05..32ff149c7 100644
--- a/otherlibs/dbm/dbm.mli
+++ b/otherlibs/dbm/dbm.mli
@@ -24,7 +24,7 @@ type open_flag =
exception Dbm_error of string
(* Raised by the following functions when an error is encountered. *)
-val opendbm : string -> flags:open_flag list -> perm:int -> t
+val opendbm : string -> mode:open_flag list -> perm:int -> t
(* Open a descriptor on an NDBM database. The first argument is
the name of the database (without the [.dir] and [.pag] suffixes).
The second argument is a list of flags: [Dbm_rdonly] opens
diff --git a/otherlibs/str/str.mli b/otherlibs/str/str.mli
index dff91ed48..cd9aab1d5 100644
--- a/otherlibs/str/str.mli
+++ b/otherlibs/str/str.mli
@@ -56,23 +56,23 @@ val regexp_string_case_fold: string -> regexp
(*** String matching and searching *)
-external string_match: regexp -> string -> pos:int -> bool
+external string_match: pat:regexp -> string -> pos:int -> bool
= "str_string_match"
(* [string_match r s start] tests whether the characters in [s]
starting at position [start] match the regular expression [r].
The first character of a string has position [0], as usual. *)
-external search_forward: regexp -> string -> pos:int -> int
+external search_forward: pat:regexp -> string -> pos:int -> int
= "str_search_forward"
(* [search_forward r s start] searchs the string [s] for a substring
matching the regular expression [r]. The search starts at position
[start] and proceeds towards the end of the string.
Return the position of the first character of the matched
substring, or raise [Not_found] if no substring matches. *)
-external search_backward: regexp -> string -> pos:int -> int
+external search_backward: pat:regexp -> string -> pos:int -> int
= "str_search_backward"
(* Same as [search_forward], but the search proceeds towards the
beginning of the string. *)
-external string_partial_match: regexp -> string -> pos:int -> bool
+external string_partial_match: pat:regexp -> string -> pos:int -> bool
= "str_string_partial_match"
(* Similar to [string_match], but succeeds whenever the argument
string is a prefix of a string that matches. This includes
@@ -106,23 +106,24 @@ val group_end: int -> int
(*** Replacement *)
-val global_replace: regexp -> with:string -> string -> string
+val global_replace: pat:regexp -> with:string -> string -> string
(* [global_replace regexp repl s] returns a string identical to [s],
except that all substrings of [s] that match [regexp] have been
replaced by [repl]. The replacement text [repl] can contain
[\1], [\2], etc; these sequences will be replaced by the text
matched by the corresponding group in the regular expression.
[\0] stands for the text matched by the whole regular expression. *)
-val replace_first: regexp -> with:string -> string -> string
+val replace_first: pat:regexp -> with:string -> string -> string
(* Same as [global_replace], except that only the first substring
matching the regular expression is replaced. *)
-val global_substitute: regexp -> with:(string -> string) -> string -> string
+val global_substitute:
+ pat:regexp -> with:(string -> string) -> string -> string
(* [global_substitute regexp subst s] returns a string identical
to [s], except that all substrings of [s] that match [regexp]
have been replaced by the result of function [subst]. The
function [subst] is called once for each matching substring,
and receives [s] (the whole text) as argument. *)
-val substitute_first: regexp -> with:(string -> string) -> string -> string
+val substitute_first: pat:regexp -> with:(string -> string) -> string -> string
(* Same as [global_substitute], except that only the first substring
matching the regular expression is replaced. *)
val replace_matched : string -> string -> string
@@ -140,12 +141,12 @@ val split: sep:regexp -> string -> string list
For instance, [split (regexp "[ \t]+") s] splits [s] into
blank-separated words. An occurrence of the delimiter at the
beginning and at the end of the string is ignored. *)
-val bounded_split: sep:regexp -> string -> int -> string list
+val bounded_split: sep:regexp -> string -> max:int -> string list
(* Same as [split], but splits into at most [n] substrings,
where [n] is the extra integer parameter. *)
val split_delim: sep:regexp -> string -> string list
-val bounded_split_delim: sep:regexp -> string -> int -> string list
+val bounded_split_delim: sep:regexp -> string -> max:int -> string list
(* Same as [split] and [bounded_split], but occurrences of the
delimiter at the beginning and at the end of the string are
recognized and returned as empty strings in the result.
diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli
index b96c0cb4b..705cc8128 100644
--- a/otherlibs/unix/unix.mli
+++ b/otherlibs/unix/unix.mli
@@ -145,14 +145,14 @@ type wait_flag =
[WUNTRACED] means report also the children that receive stop
signals. *)
-val execv : prog:string -> args:string array -> unit
+val execv : name:string -> args:string array -> unit
(* [execv prog args] execute the program in file [prog], with
the arguments [args], and the current process environment. *)
-val execve : prog:string -> args:string array -> env:string array -> unit
+val execve : name:string -> args:string array -> env:string array -> unit
(* Same as [execv], except that the third argument provides the
environment to the program executed. *)
-val execvp : prog:string -> args:string array -> unit
-val execvpe : prog:string -> args:string array -> env:string array -> unit
+val execvp : name:string -> args:string array -> unit
+val execvpe : name:string -> args:string array -> env:string array -> unit
(* Same as [execv] and [execvp] respectively, except that
the program is searched in the path. *)
val fork : unit -> int
@@ -161,7 +161,7 @@ val fork : unit -> int
val wait : unit -> int * process_status
(* Wait until one of the children processes die, and return its pid
and termination status. *)
-val waitpid : flags:wait_flag list -> int -> int * process_status
+val waitpid : mode:wait_flag list -> int -> int * process_status
(* Same as [wait], but waits for the process whose pid is given.
A pid of [-1] means wait for any child.
A pid of [0] means wait for any child in the same process group
@@ -211,17 +211,17 @@ type open_flag =
type file_perm = int
(* The type of file access rights. *)
-val openfile : string -> flags:open_flag list -> perm:file_perm -> file_descr
+val openfile : string -> mode:open_flag list -> perm:file_perm -> file_descr
(* Open the named file with the given flags. Third argument is
the permissions to give to the file if it is created. Return
a file descriptor on the named file. *)
val close : file_descr -> unit
(* Close a file descriptor. *)
-val read : file_descr -> buffer:string -> pos:int -> len:int -> int
+val read : file_descr -> buf:string -> pos:int -> len:int -> int
(* [read fd buff ofs len] reads [len] characters from descriptor
[fd], storing them in string [buff], starting at position [ofs]
in string [buff]. Return the number of characters actually read. *)
-val write : file_descr -> buffer:string -> pos:int -> len:int -> int
+val write : file_descr -> buf:string -> pos:int -> len:int -> int
(* [write fd buff ofs len] writes [len] characters to descriptor
[fd], taking them from string [buff], starting at position [ofs]
in string [buff]. Return the number of characters actually
@@ -256,9 +256,9 @@ type seek_command =
the current position, [SEEK_END] relative to the end of the
file. *)
-val lseek : file_descr -> pos:int -> cmd:seek_command -> int
+val lseek : file_descr -> pos:int -> mode:seek_command -> int
(* Set the current position for a file descriptor *)
-val truncate : file:string -> len:int -> unit
+val truncate : name:string -> len:int -> unit
(* Truncates the named file to the given size. *)
val ftruncate : file_descr -> len:int -> unit
(* Truncates the file corresponding to the given descriptor
@@ -292,9 +292,9 @@ type stats =
(* The informations returned by the [stat] calls. *)
-val stat : file:string -> stats
+val stat : name:string -> stats
(* Return the information for the named file. *)
-val lstat : file:string -> stats
+val lstat : name:string -> stats
(* Same as [stat], but in case the file is a symbolic link,
return the information for the link itself. *)
val fstat : file_descr -> stats
@@ -304,11 +304,11 @@ val fstat : file_descr -> stats
(*** Operations on file names *)
-val unlink : file:string -> unit
+val unlink : name:string -> unit
(* Removes the named file *)
val rename : old:string -> new:string -> unit
(* [rename old new] changes the name of a file from [old] to [new]. *)
-val link : source:string -> dest:string -> unit
+val link : src:string -> dst:string -> unit
(* [link source dest] creates a hard link named [dest] to the file
named [new]. *)
@@ -323,17 +323,17 @@ type access_permission =
(* Flags for the [access] call. *)
-val chmod : file:string -> perm:file_perm -> unit
+val chmod : name:string -> perm:file_perm -> unit
(* Change the permissions of the named file. *)
val fchmod : file_descr -> perm:file_perm -> unit
(* Change the permissions of an opened file. *)
-val chown : file:string -> uid:int -> gid:int -> unit
+val chown : name:string -> uid:int -> gid:int -> unit
(* Change the owner uid and owner gid of the named file. *)
val fchown : file_descr -> uid:int -> gid:int -> unit
(* Change the owner uid and owner gid of an opened file. *)
val umask : int -> int
(* Set the process creation mask, and return the previous mask. *)
-val access : file:string -> perm:access_permission list -> unit
+val access : name:string -> perm:access_permission list -> unit
(* Check that the process has the given permissions over the named
file. Raise [Unix_error] otherwise. *)
@@ -343,7 +343,7 @@ val access : file:string -> perm:access_permission list -> unit
val dup : file_descr -> file_descr
(* Return a new file descriptor referencing the same file as
the given descriptor. *)
-val dup2 : file_descr -> file_descr -> unit
+val dup2 : src:file_descr -> dst:file_descr -> unit
(* [dup2 fd1 fd2] duplicates [fd1] to [fd2], closing [fd2] if already
opened. *)
val set_nonblock : file_descr -> unit
@@ -406,8 +406,8 @@ val mkfifo : string -> perm:file_perm -> unit
(*** High-level process and redirection management *)
val create_process :
- prog:string -> args:string array ->
- in:file_descr -> out:file_descr -> err:file_descr -> int
+ name:string -> args:string array ->
+ stdin:file_descr -> stdout:file_descr -> stderr:file_descr -> int
(* [create_process prog args new_stdin new_stdout new_stderr]
forks a new process that executes the program
in file [prog], with arguments [args]. The pid of the new
@@ -425,8 +425,8 @@ val create_process :
outputs. *)
val create_process_env :
- prog:string -> args:string array -> env:string array ->
- in:file_descr -> out:file_descr -> err:file_descr -> int
+ name:string -> args:string array -> env:string array ->
+ stdin:file_descr -> stdout:file_descr -> stderr:file_descr -> int
(* [create_process_env prog args env new_stdin new_stdout new_stderr]
works as [create_process], except that the extra argument
[env] specifies the environment passed to the program. *)
@@ -458,10 +458,10 @@ val close_process_full: in_channel * out_channel * in_channel -> process_status
(*** Symbolic links *)
-val symlink : source:string -> dest:string -> unit
+val symlink : src:string -> dst:string -> unit
(* [symlink source dest] creates the file [dest] as a symbolic link
to the file [source]. *)
-val readlink : string -> string
+val readlink : name:string -> string
(* Read the contents of a link. *)
@@ -494,7 +494,7 @@ type lock_command =
(* Commands for [lockf]. *)
-val lockf : file_descr -> cmd:lock_command -> len:int -> unit
+val lockf : file_descr -> mode:lock_command -> len:int -> unit
(* [lockf fd cmd size] puts a lock on a region of the file opened
as [fd]. The region starts at the current read/write position for
@@ -515,7 +515,7 @@ val kill : pid:int -> signal:int -> unit
type sigprocmask_command = SIG_SETMASK | SIG_BLOCK | SIG_UNBLOCK
-val sigprocmask: sigprocmask_command -> int list -> int list
+val sigprocmask: mode:sigprocmask_command -> int list -> int list
(* [sigprocmask cmd sigs] changes the set of blocked signals.
If [cmd] is [SIG_SETMASK], blocked signals are set to those in
the list [sigs].
@@ -582,7 +582,7 @@ val sleep : int -> unit
(* Stop execution for the given number of seconds. *)
val times : unit -> process_times
(* Return the execution times of the process. *)
-val utimes : file:string -> access:float -> modif:float -> unit
+val utimes : name:string -> access:float -> modif:float -> unit
(* Set the last access time (second arg) and last modification time
(third arg) for a file. Times are expressed in seconds from
00:00:00 GMT, Jan. 1, 1970. *)
@@ -713,21 +713,21 @@ type sockaddr =
[port] is the port number. *)
val socket :
- domain:socket_domain -> type:socket_type -> proto:int -> file_descr
+ domain:socket_domain -> type:socket_type -> protocol:int -> file_descr
(* Create a new socket in the given domain, and with the
given kind. The third argument is the protocol type; 0 selects
the default protocol for that kind of sockets. *)
val socketpair :
- domain:socket_domain -> type:socket_type -> proto:int ->
+ domain:socket_domain -> type:socket_type -> protocol:int ->
file_descr * file_descr
(* Create a pair of unnamed sockets, connected together. *)
val accept : file_descr -> file_descr * sockaddr
(* Accept connections on the given socket. The returned descriptor
is a socket connected to the client; the returned address is
the address of the connecting client. *)
-val bind : file_descr -> sockaddr -> unit
+val bind : file_descr -> addr:sockaddr -> unit
(* Bind a socket to an address. *)
-val connect : file_descr -> sockaddr -> unit
+val connect : file_descr -> addr:sockaddr -> unit
(* Connect a socket to an address. *)
val listen : file_descr -> max:int -> unit
(* Set up a socket for receiving connection requests. The integer
@@ -739,7 +739,7 @@ type shutdown_command =
| SHUTDOWN_ALL (* Close both *)
(* The type of commands for [shutdown]. *)
-val shutdown : file_descr -> cmd:shutdown_command -> unit
+val shutdown : file_descr -> mode:shutdown_command -> unit
(* Shutdown a socket connection. [SHUTDOWN_SEND] as second argument
causes reads on the other end of the connection to return
an end-of-file condition.
@@ -758,17 +758,17 @@ type msg_flag =
(* The flags for [recv], [recvfrom], [send] and [sendto]. *)
val recv :
- file_descr -> buffer:string -> pos:int -> len:int
- -> flags:msg_flag list -> int
+ file_descr -> buf:string -> pos:int -> len:int
+ -> mode:msg_flag list -> int
val recvfrom :
- file_descr -> buffer:string -> pos:int -> len:int
- -> flags:msg_flag list -> int * sockaddr
+ file_descr -> buf:string -> pos:int -> len:int
+ -> mode:msg_flag list -> int * sockaddr
(* Receive data from an unconnected socket. *)
-val send : file_descr -> buffer:string -> pos:int -> len:int
- -> flags:msg_flag list -> int
+val send : file_descr -> buf:string -> pos:int -> len:int
+ -> mode:msg_flag list -> int
val sendto :
- file_descr -> buffer:string -> pos:int -> len:int
- -> flags:msg_flag list -> addr:sockaddr -> int
+ file_descr -> buf:string -> pos:int -> len:int
+ -> mode:msg_flag list -> addr:sockaddr -> int
(* Send data over an unconnected socket. *)
type socket_option =
@@ -780,9 +780,9 @@ type socket_option =
| SO_OOBINLINE (* Leave out-of-band data in line *)
(* The socket options settable with [setsockopt]. *)
-val getsockopt : file_descr -> opt:socket_option -> bool
+val getsockopt : file_descr -> key:socket_option -> bool
(* Return the current status of an option in the given socket. *)
-val setsockopt : file_descr -> opt:socket_option -> bool -> unit
+val setsockopt : file_descr -> key:socket_option -> bool -> unit
(* Set or clear an option in the given socket. *)
(*** High-level network connection functions *)
@@ -796,7 +796,7 @@ val shutdown_connection : in_channel -> unit
(* ``Shut down'' a connection established with [open_connection];
that is, transmit an end-of-file condition to the server reading
on the other side of the connection. *)
-val establish_server : fun:(in:in_channel -> out:out_channel -> 'a) ->
+val establish_server : fun:(in:in_channel -> out:out_channel -> unit) ->
addr:sockaddr -> unit
(* Establish a server on the given address.
The function given as first argument is called for each connection
@@ -841,10 +841,10 @@ val getprotobyname : string -> protocol_entry
val getprotobynumber : int -> protocol_entry
(* Find an entry in [protocols] with the given protocol number,
or raise [Not_found]. *)
-val getservbyname : string -> proto:string -> service_entry
+val getservbyname : string -> protocol:string -> service_entry
(* Find an entry in [services] with the given name, or raise
[Not_found]. *)
-val getservbyport : int -> proto:string -> service_entry
+val getservbyport : int -> protocol:string -> service_entry
(* Find an entry in [services] with the given service number,
or raise [Not_found]. *)
@@ -910,7 +910,7 @@ val tcgetattr: file_descr -> terminal_io
type setattr_when = TCSANOW | TCSADRAIN | TCSAFLUSH
-val tcsetattr: file_descr -> when:setattr_when -> terminal_io -> unit
+val tcsetattr: file_descr -> mode:setattr_when -> terminal_io -> unit
(* Set the status of the terminal referred to by the given
file descriptor. The second argument indicates when the
status change takes place: immediately ([TCSANOW]),
@@ -931,7 +931,7 @@ val tcdrain: file_descr -> unit
type flush_queue = TCIFLUSH | TCOFLUSH | TCIOFLUSH
-val tcflush: file_descr -> cmd:flush_queue -> unit
+val tcflush: file_descr -> mode:flush_queue -> unit
(* Discard data written on the given file descriptor but not yet
transmitted, or data received but not yet read, depending on the
second argument: [TCIFLUSH] flushes data received but not read,
@@ -940,7 +940,7 @@ val tcflush: file_descr -> cmd:flush_queue -> unit
type flow_action = TCOOFF | TCOON | TCIOFF | TCION
-val tcflow: file_descr -> cmd:flow_action -> unit
+val tcflow: file_descr -> mode:flow_action -> unit
(* Suspend or restart reception or transmission of data on
the given file descriptor, depending on the second argument:
[TCOOFF] suspends output, [TCOON] restarts output,
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.