summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--otherlibs/labltk/browser/editor.ml2
-rw-r--r--otherlibs/labltk/browser/searchid.ml4
-rw-r--r--otherlibs/labltk/browser/shell.ml4
-rw-r--r--otherlibs/labltk/browser/viewer.ml6
-rw-r--r--otherlibs/labltk/compiler/compile.ml8
-rw-r--r--otherlibs/labltk/compiler/intf.ml2
-rw-r--r--otherlibs/labltk/compiler/maincompile.ml2
-rw-r--r--otherlibs/labltk/compiler/tables.ml2
-rw-r--r--otherlibs/labltk/jpf/fileselect.ml2
-rw-r--r--otherlibs/labltk/support/textvariable.ml8
-rw-r--r--otherlibs/labltk/support/widget.ml4
-rw-r--r--otherlibs/systhreads/threadUnix.mli29
-rw-r--r--otherlibs/threads/threadUnix.mli2
-rw-r--r--otherlibs/unix/unix.mli22
-rw-r--r--stdlib/list.mli4
-rw-r--r--stdlib/set.mli6
-rw-r--r--utils/config.mlp2
17 files changed, 54 insertions, 55 deletions
diff --git a/otherlibs/labltk/browser/editor.ml b/otherlibs/labltk/browser/editor.ml
index 5a5f5f821..e7ee627ac 100644
--- a/otherlibs/labltk/browser/editor.ml
+++ b/otherlibs/labltk/browser/editor.ml
@@ -327,7 +327,7 @@ class editor :top :menus = object (self)
action:(fun ev ->
if ev.ev_Char <> "" &
(ev.ev_Char.[0] >= ' ' or
- List.mem key:ev.ev_Char.[0]
+ List.mem item:ev.ev_Char.[0]
(List.map fun:control ['d'; 'h'; 'i'; 'k'; 'o'; 't'; 'w'; 'y']))
then Textvariable.set txt.modified to:"modified");
bind tw events:[`KeyPressDetail"Tab"] breakable:true
diff --git a/otherlibs/labltk/browser/searchid.ml b/otherlibs/labltk/browser/searchid.ml
index e0d538350..ade14981e 100644
--- a/otherlibs/labltk/browser/searchid.ml
+++ b/otherlibs/labltk/browser/searchid.ml
@@ -167,7 +167,7 @@ let rec included :prefix t1 t2 =
let l2 = if arr len1 in:len2 < 100 then l2 else
let ll1 = get_options (fst (List.split l1)) in
List.filter l2
- pred:(fun (l,_) -> not (is_opt l) or List.mem key:l ll1)
+ pred:(fun (l,_) -> not (is_opt l) or List.mem item:l ll1)
in
len1 <= len2 &
List.exists (List2.flat_map fun:permutations (choose len1 in:l2)) pred:
@@ -432,7 +432,7 @@ let search_structure str :name :kind :prefix =
Pstr_value (_, l) when kind = Pvalue ->
List.iter l fun:
begin fun (pat,_) ->
- if List.mem key:name (bound_variables pat)
+ if List.mem item:name (bound_variables pat)
then loc := pat.ppat_loc.loc_start
end;
false
diff --git a/otherlibs/labltk/browser/shell.ml b/otherlibs/labltk/browser/shell.ml
index f2fbd3a7e..3a5958806 100644
--- a/otherlibs/labltk/browser/shell.ml
+++ b/otherlibs/labltk/browser/shell.ml
@@ -68,7 +68,7 @@ object (self)
Array.append env [|sigdef|]
else env
in
- Unix.create_process_env name:prog :args :env
+ Unix.create_process_env :prog :args :env
stdin:in2 stdout:out2 stderr:err2
val out = Unix.out_channel_of_descr out1
val h = new history ()
@@ -239,7 +239,7 @@ let get_all () =
all
let may_exec_unix prog =
- try Unix.access name:prog perm:[Unix.X_OK]; true
+ try Unix.access file:prog perm:[Unix.X_OK]; true
with Unix.Unix_error _ -> false
let may_exec_win prog =
diff --git a/otherlibs/labltk/browser/viewer.ml b/otherlibs/labltk/browser/viewer.ml
index 11f3b2925..84099c2c8 100644
--- a/otherlibs/labltk/browser/viewer.ml
+++ b/otherlibs/labltk/browser/viewer.ml
@@ -34,7 +34,7 @@ let list_modules :path =
String.capitalize (Filename.chop_suffix x suff:".cmi")
end in
List.fold_left l :acc
- fun:(fun :acc key -> if List.mem acc :key then acc else key :: acc)
+ fun:(fun :acc item -> if List.mem acc :item then acc else item :: acc)
end
let reset_modules box =
@@ -242,12 +242,12 @@ let start_shell () =
Jg_entry.create entries command:(fun _ -> Button.invoke ok)
and names = List.map fun:fst (Shell.get_all ()) in
Entry.insert e1 index:`End text:!default_shell;
- while List.mem names key:("Shell #" ^ string_of_int !shell_counter) do
+ while List.mem names item:("Shell #" ^ string_of_int !shell_counter) do
incr shell_counter
done;
Entry.insert e2 index:`End text:("Shell #" ^ string_of_int !shell_counter);
Button.configure ok command:(fun () ->
- if not (List.mem names key:(Entry.get e2)) then begin
+ if not (List.mem names item:(Entry.get e2)) then begin
default_shell := Entry.get e1;
Shell.f prog:!default_shell title:(Entry.get e2);
destroy tl
diff --git a/otherlibs/labltk/compiler/compile.ml b/otherlibs/labltk/compiler/compile.ml
index a7c12ab12..1a743b9f5 100644
--- a/otherlibs/labltk/compiler/compile.ml
+++ b/otherlibs/labltk/compiler/compile.ml
@@ -47,7 +47,7 @@ let small_ident s =
let idents = ["to"; "raise"; "in"; "class"; "new"]
in
let s = small s in
- if List.mem key:s idents then (String.make len:1 s.[0])^s
+ if List.mem item:s idents then (String.make len:1 s.[0])^s
else s
let gettklabel fc =
@@ -59,7 +59,7 @@ let gettklabel fc =
if s = "" then small fc.ml_name else small s
| _ -> raise (Failure "gettklabel")
-let count key:x l =
+let count item:x l =
let count = ref 0 in
List.iter fun:(fun y -> if x = y then incr count) l;
!count
@@ -103,7 +103,7 @@ let ppMLtype ?(:any=false) ?(:return=false) ?(:def=false) ?(:counter=ref 0) =
let l = List.map fcl fun:
begin fun fc ->
"?" ^ begin let p = gettklabel fc in
- if count key:p tklabels > 1 then small fc.ml_name else p
+ if count item:p tklabels > 1 then small fc.ml_name else p
end
^ ":" ^
let l = types_of_template fc.template in
@@ -724,7 +724,7 @@ let write_catch_optionals :w clas def:typdef =
if co <> "" then fatal_error "optionals in optionals";
*)
let p = gettklabel fc in
- (if count key:p tklabels > 1 then small fc.ml_name else p),
+ (if count item:p tklabels > 1 then small fc.ml_name else p),
small_ident fc.ml_name (* used as labels *),
small fc.ml_name
end in
diff --git a/otherlibs/labltk/compiler/intf.ml b/otherlibs/labltk/compiler/intf.ml
index a46a6b250..42225ed5b 100644
--- a/otherlibs/labltk/compiler/intf.ml
+++ b/otherlibs/labltk/compiler/intf.ml
@@ -30,7 +30,7 @@ let write_create_p :w wname =
let l = List.map classdefs fun:
begin fun fc ->
begin let p = gettklabel fc in
- if count key:p tklabels > 1 then small fc.ml_name else p
+ if count item:p tklabels > 1 then small fc.ml_name else p
end, fc.template
end in
w (String.concat sep:" ->\n"
diff --git a/otherlibs/labltk/compiler/maincompile.ml b/otherlibs/labltk/compiler/maincompile.ml
index ff646226b..503416482 100644
--- a/otherlibs/labltk/compiler/maincompile.ml
+++ b/otherlibs/labltk/compiler/maincompile.ml
@@ -121,7 +121,7 @@ verbose_string "type ";
verbose_string "C2T ";
write_CAMLtoTK w:(output_string to:oc') typname def:typdef;
verbose_string "T2C ";
- if List.mem key:typname !types_returned then
+ if List.mem item:typname !types_returned then
write_TKtoCAML w:(output_string to:oc') typname def:typdef;
verbose_string "CO ";
write_catch_optionals w:(output_string to:oc') typname def:typdef;
diff --git a/otherlibs/labltk/compiler/tables.ml b/otherlibs/labltk/compiler/tables.ml
index eea78ab59..30a7b954b 100644
--- a/otherlibs/labltk/compiler/tables.ml
+++ b/otherlibs/labltk/compiler/tables.ml
@@ -250,7 +250,7 @@ let rec has_callback = function
(*** Returned types ***)
let really_add ty =
- if List.mem key:ty !types_returned then ()
+ if List.mem item:ty !types_returned then ()
else types_returned := ty :: !types_returned
let rec add_return_type = function
diff --git a/otherlibs/labltk/jpf/fileselect.ml b/otherlibs/labltk/jpf/fileselect.ml
index bf981eea6..e3b08e051 100644
--- a/otherlibs/labltk/jpf/fileselect.ml
+++ b/otherlibs/labltk/jpf/fileselect.ml
@@ -49,7 +49,7 @@ let subshell cmd =
let r,w = pipe () in
match fork () with
0 -> close r; dup2 src:w dst:stdout;
- execv name:"/bin/sh" args:[| "/bin/sh"; "-c"; cmd |];
+ execv prog:"/bin/sh" args:[| "/bin/sh"; "-c"; cmd |];
exit 127
| id ->
close w;
diff --git a/otherlibs/labltk/support/textvariable.ml b/otherlibs/labltk/support/textvariable.ml
index c6f3e637a..f467a7150 100644
--- a/otherlibs/labltk/support/textvariable.ml
+++ b/otherlibs/labltk/support/textvariable.ml
@@ -97,12 +97,12 @@ let add w v =
let r = ref StringSet.empty in
Hashtbl.add memo key:w data:r;
r in
- r := StringSet.add !r key:v
+ r := StringSet.add !r item:v
(* to be used with care ! *)
let free v =
rem_all_handles v;
- freelist := StringSet.add key:v !freelist
+ freelist := StringSet.add item:v !freelist
(* Free variables associated with a widget *)
let freew w =
@@ -125,7 +125,7 @@ let getv () =
end
else
let v = StringSet.choose !freelist in
- freelist := StringSet.remove key:v !freelist;
+ freelist := StringSet.remove item:v !freelist;
v in
set v to:"";
v
@@ -141,7 +141,7 @@ let create ?on: w () =
(* to be used with care ! *)
let free v =
- freelist := StringSet.add key:v !freelist
+ freelist := StringSet.add item:v !freelist
let cCAMLtoTKtextVariable s = TkToken s
diff --git a/otherlibs/labltk/support/widget.ml b/otherlibs/labltk/support/widget.ml
index 1da823ce8..2174fc3cb 100644
--- a/otherlibs/labltk/support/widget.ml
+++ b/otherlibs/labltk/support/widget.ml
@@ -165,11 +165,11 @@ let check_class w clas =
match w with
Untyped _ -> () (* assume run-time check by tk*)
| Typed(_,c) ->
- if List.mem clas key:c then ()
+ if List.mem clas item:c then ()
else raise (IllegalWidgetType c)
(* Checking membership of constructor in subtype table *)
let chk_sub errname table c =
- if List.mem table key:c then ()
+ if List.mem table item:c then ()
else raise (Invalid_argument errname)
diff --git a/otherlibs/systhreads/threadUnix.mli b/otherlibs/systhreads/threadUnix.mli
index fa120c068..23693e6c8 100644
--- a/otherlibs/systhreads/threadUnix.mli
+++ b/otherlibs/systhreads/threadUnix.mli
@@ -22,10 +22,9 @@
(*** Process handling *)
-external execv : prog:string -> args:string array -> unit = "unix_execv"
-external execve : prog:string -> args:string array -> env:string array -> unit
- = "unix_execve"
-external execvp : prog:string -> args:string array -> unit = "unix_execvp"
+val execv : prog:string -> args:string array -> unit
+val execve : prog:string -> args:string array -> env:string array -> unit
+val execvp : prog:string -> args:string array -> unit
val wait : unit -> int * Unix.process_status
val waitpid : flags:Unix.wait_flag list -> int -> int * Unix.process_status
val system : string -> Unix.process_status
@@ -35,13 +34,6 @@ val system : string -> Unix.process_status
val read : Unix.file_descr -> buf:string -> pos:int -> len:int -> int
val write : Unix.file_descr -> buf:string -> pos:int -> len:int -> int
-(*** Polling *)
-
-val select :
- read:Unix.file_descr list -> write:Unix.file_descr list ->
- exn:Unix.file_descr list -> timeout:float ->
- Unix.file_descr list * Unix.file_descr list * Unix.file_descr list
-
(*** Input/output with timeout *)
val timed_read :
@@ -50,11 +42,18 @@ val timed_read :
val timed_write :
Unix.file_descr ->
buf:string -> pos:int -> len:int -> timeout:float -> int
- (* Behave as [read] and [write], except that
+ (* Behave as [read] and [write], except that
[Unix_error(ETIMEDOUT,_,_)] is raised if no data is
available for reading or ready for writing after [d] seconds.
The delay [d] is given in the fifth argument, in seconds. *)
+(*** Polling *)
+
+val select :
+ read:Unix.file_descr list -> write:Unix.file_descr list ->
+ except:Unix.file_descr list -> timeout:float ->
+ Unix.file_descr list * Unix.file_descr list * Unix.file_descr list
+
(*** Pipes and redirections *)
val pipe : unit -> Unix.file_descr * Unix.file_descr
@@ -64,16 +63,16 @@ val open_process: string -> in_channel * out_channel
(*** Time *)
-external sleep : int -> unit = "unix_sleep"
+val sleep : int -> unit
(*** Sockets *)
val socket : domain:Unix.socket_domain ->
type:Unix.socket_type -> proto:int -> Unix.file_descr
val accept : Unix.file_descr -> Unix.file_descr * Unix.sockaddr
-external connect : Unix.file_descr -> Unix.sockaddr -> unit = "unix_connect"
+val connect : Unix.file_descr -> Unix.sockaddr -> unit
val recv : Unix.file_descr -> buf:string ->
- pos:int -> len:int -> flags:Unix.msg_flag list -> int
+ pos:int -> len:int -> flags:Unix.msg_flag list -> int
val recvfrom : Unix.file_descr -> buf:string -> pos:int -> len:int ->
flags:Unix.msg_flag list -> int * Unix.sockaddr
val send : Unix.file_descr -> buf:string -> pos:int -> len:int ->
diff --git a/otherlibs/threads/threadUnix.mli b/otherlibs/threads/threadUnix.mli
index 82148e142..2383c35c4 100644
--- a/otherlibs/threads/threadUnix.mli
+++ b/otherlibs/threads/threadUnix.mli
@@ -51,7 +51,7 @@ val timed_write :
val select :
read:Unix.file_descr list -> write:Unix.file_descr list ->
- exn:Unix.file_descr list -> timeout:float ->
+ except:Unix.file_descr list -> timeout:float ->
Unix.file_descr list * Unix.file_descr list * Unix.file_descr list
(*** Pipes and redirections *)
diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli
index ebe6eb701..eeb6aedcf 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 : name:string -> args:string array -> unit
+val execv : prog: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 : name:string -> args:string array -> env:string array -> unit
+val execve : prog: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 : name:string -> args:string array -> unit
-val execvpe : name:string -> args:string array -> env:string array -> unit
+val execvp : prog:string -> args:string array -> unit
+val execvpe : prog: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
@@ -323,17 +323,17 @@ type access_permission =
(* Flags for the [access] call. *)
-val chmod : name:string -> perm:file_perm -> unit
+val chmod : file: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 : name:string -> uid:int -> gid:int -> unit
+val chown : file: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 : name:string -> perm:access_permission list -> unit
+val access : file:string -> perm:access_permission list -> unit
(* Check that the process has the given permissions over the named
file. Raise [Unix_error] otherwise. *)
@@ -406,7 +406,7 @@ val mkfifo : string -> perm:file_perm -> unit
(*** High-level process and redirection management *)
val create_process :
- name:string -> args:string array ->
+ prog: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
@@ -425,7 +425,7 @@ val create_process :
outputs. *)
val create_process_env :
- name:string -> args:string array -> env:string array ->
+ prog: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
@@ -468,7 +468,7 @@ val readlink : string -> string
(*** Polling *)
val select :
- read:file_descr list -> write:file_descr list -> exn:file_descr list ->
+ read:file_descr list -> write:file_descr list -> except:file_descr list ->
timeout:float ->
file_descr list * file_descr list * file_descr list
(* Wait until some input/output operations become possible on
@@ -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 : name:string -> access:float -> modif:float -> unit
+val utimes : file: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. *)
diff --git a/stdlib/list.mli b/stdlib/list.mli
index 80e3b62bd..e39795887 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 : key:'a -> 'a list -> bool
+val mem : item:'a -> 'a list -> bool
(* [mem a l] is true if and only if [a] is equal
to an element of [l]. *)
-val memq : key:'a -> 'a list -> bool
+val memq : item:'a -> 'a list -> bool
(* Same as [mem], but uses physical equality instead of structural
equality to compare list elements. *)
diff --git a/stdlib/set.mli b/stdlib/set.mli
index 7317915a6..e48cbd4c5 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: key:elt -> t -> bool
+ val mem: item:elt -> t -> bool
(* [mem x s] tests whether [x] belongs to the set [s]. *)
- val add: key:elt -> t -> t
+ val add: item: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: key:elt -> t -> t
+ val remove: item: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/utils/config.mlp b/utils/config.mlp
index dc127dc2e..14639ccf4 100644
--- a/utils/config.mlp
+++ b/utils/config.mlp
@@ -12,7 +12,7 @@
(* $Id$ *)
-let version = "2.99+2"
+let version = "2.99+3 (2000/02/01)"
let standard_library =
try