diff options
author | Jacques Garrigue <garrigue at math.nagoya-u.ac.jp> | 1999-12-01 09:31:59 +0000 |
---|---|---|
committer | Jacques Garrigue <garrigue at math.nagoya-u.ac.jp> | 1999-12-01 09:31:59 +0000 |
commit | 905267fe2cec4625651507db7539493504789d05 (patch) | |
tree | ff1267bc4ee35ed4f6b8cc5bd01f6e1d2340c45a /otherlibs | |
parent | b9926a88bab922f6f095b838444e29094aef9b34 (diff) |
changed some labels
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2659 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs')
-rw-r--r-- | otherlibs/graph/graphics.mli | 24 | ||||
-rw-r--r-- | otherlibs/labltk/browser/editor.ml | 10 | ||||
-rw-r--r-- | otherlibs/labltk/browser/fileselect.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/browser/list2.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/browser/searchid.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/browser/setpath.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/browser/shell.ml | 7 | ||||
-rw-r--r-- | otherlibs/labltk/browser/useunix.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/browser/viewer.ml | 6 | ||||
-rw-r--r-- | otherlibs/labltk/builtin/builtini_index.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/compile.ml | 8 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/intf.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/maincompile.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/compiler/tables.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/jpf/fileselect.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/widget.ml | 4 | ||||
-rw-r--r-- | otherlibs/unix/unix.mli | 12 |
17 files changed, 48 insertions, 53 deletions
diff --git a/otherlibs/graph/graphics.mli b/otherlibs/graph/graphics.mli index fe13764a0..047bf0cc0 100644 --- a/otherlibs/graph/graphics.mli +++ b/otherlibs/graph/graphics.mli @@ -75,28 +75,28 @@ val foreground: color (*** Point and line drawing *) -external plot : int -> int -> unit = "gr_plot" +external plot : x:int -> y:int -> unit = "gr_plot" (* Plot the given point with the current drawing color. *) -external point_color : int -> int -> color = "gr_point_color" +external point_color : x:int -> y:int -> color = "gr_point_color" (* Return the color of the given point. *) -external moveto : int -> int -> unit = "gr_moveto" +external moveto : x:int -> y:int -> unit = "gr_moveto" (* Position the current point. *) external current_point : unit -> int * int = "gr_current_point" (* Return the position of the current point. *) -external lineto : int -> int -> unit = "gr_lineto" +external lineto : x:int -> y:int -> unit = "gr_lineto" (* Draw a line with endpoints the current point and the given point, and move the current point to the given point. *) external draw_arc : - int -> int -> rx:int -> ry:int -> start:int -> stop:int -> unit + x:int -> y:int -> rx:int -> ry:int -> start:int -> stop:int -> unit = "gr_draw_arc" "gr_draw_arc_nat" (* [draw_arc x y rx ry a1 a2] draws an elliptical arc with center [x,y], horizontal radius [rx], vertical radius [ry], from angle [a1] to angle [a2] (in degrees). The current point is unchanged. *) -val draw_ellipse : int -> int -> rx:int -> ry:int -> unit +val draw_ellipse : x:int -> y:int -> rx:int -> ry:int -> unit (* [draw_ellipse x y rx ry] draws an ellipse with center [x,y], horizontal radius [rx] and vertical radius [ry]. The current point is unchanged. *) -val draw_circle : int -> int -> r:int -> unit +val draw_circle : x:int -> y:int -> r:int -> unit (* [draw_circle x y r] draws a circle with center [x,y] and radius [r]. The current point is unchanged. *) external set_line_width : int -> unit = "gr_set_line_width" @@ -123,21 +123,21 @@ external text_size : string -> int * int = "gr_text_size" (*** Filling *) -external fill_rect : int -> int -> w:int -> h:int -> unit = "gr_fill_rect" +external fill_rect : x:int -> y:int -> w:int -> h:int -> unit = "gr_fill_rect" (* [fill_rect x y w h] fills the rectangle with lower left corner at [x,y], width [w] and height [h], with the current color. *) external fill_poly : (int * int) array -> unit = "gr_fill_poly" (* Fill the given polygon with the current color. The array contains the coordinates of the vertices of the polygon. *) external fill_arc : - int -> int -> rx:int -> ry:int -> start:int -> stop:int -> unit + x:int -> y:int -> rx:int -> ry:int -> start:int -> stop:int -> unit = "gr_fill_arc" "gr_fill_arc_nat" (* Fill an elliptical pie slice with the current color. The parameters are the same as for [draw_arc]. *) -val fill_ellipse : int -> int -> rx:int -> ry:int -> unit +val fill_ellipse : x:int -> y:int -> rx:int -> ry:int -> unit (* Fill an ellipse with the current color. The parameters are the same as for [draw_ellipse]. *) -val fill_circle : int -> int -> r:int -> unit +val fill_circle : x:int -> y:int -> r:int -> unit (* Fill a circle with the current color. The parameters are the same as for [draw_circle]. *) @@ -164,7 +164,7 @@ external dump_image : image -> color array array = "gr_dump_image" (* Convert an image to a color matrix. *) external draw_image : image -> x:int -> y:int -> unit = "gr_draw_image" (* Draw the given image with lower left corner at the given point. *) -val get_image : int -> int -> w:int -> h:int -> image +val get_image : x:int -> y:int -> w:int -> h:int -> image (* Capture the contents of a rectangle on the screen as an image. The parameters are the same as for [fill_rect]. *) external create_image : w:int -> h:int -> image = "gr_create_image" diff --git a/otherlibs/labltk/browser/editor.ml b/otherlibs/labltk/browser/editor.ml index 57354a22c..9a8f3328e 100644 --- a/otherlibs/labltk/browser/editor.ml +++ b/otherlibs/labltk/browser/editor.ml @@ -38,9 +38,9 @@ let compiler_preferences () = pack [ok;cancel] side:`Left fill:`X expand:true; pack [buttons] side:`Bottom fill:`X -let rec exclude elt:txt = function +let rec exclude item:txt = function [] -> [] - | x :: l -> if txt.number = x.number then l else x :: exclude elt:txt l + | x :: l -> if txt.number = x.number then l else x :: exclude item:txt l let goto_line tw = let tl = Jg_toplevel.titled "Go to" in @@ -228,7 +228,7 @@ class editor :top :menus = object (self) method set_edit txt = if windows <> [] then Pack.forget [(List.hd windows).frame]; - windows <- txt :: exclude elt:txt windows; + windows <- txt :: exclude item:txt windows; self#reset_window_menu; current_tw <- txt.tw; Checkbutton.configure label text:(Filename.basename txt.name) @@ -255,7 +255,7 @@ class editor :top :menus = object (self) action:(`Set ([`Char], fun ev -> if ev.ev_Char <> "" & (ev.ev_Char.[0] >= ' ' or - List.mem elt: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"] @@ -386,7 +386,7 @@ class editor :top :menus = object (self) | `no -> () | `cancel -> raise Exit end; - windows <- exclude elt:txt windows; + windows <- exclude item:txt windows; if windows = [] then self#new_window (current_dir ^ "/untitled") else self#set_edit (List.hd windows); diff --git a/otherlibs/labltk/browser/fileselect.ml b/otherlibs/labltk/browser/fileselect.ml index f59140b2e..82adbb7b8 100644 --- a/otherlibs/labltk/browser/fileselect.ml +++ b/otherlibs/labltk/browser/fileselect.ml @@ -119,11 +119,11 @@ let f :title action:proc ?:dir{=Unix.getcwd ()} let files = ls :dir :pattern in Sort.merge order:(<) files (List.fold_left files :acc - fun:(fun :acc name -> List2.exclude elt:name acc)) + fun:(fun :acc name -> List2.exclude item:name acc)) end else List.fold_left directories acc:(ls :dir :pattern) - fun:(fun :acc dir -> List2.exclude elt:dir acc) + fun:(fun :acc dir -> List2.exclude item:dir acc) in Textvariable.set filter_var to:filter; Textvariable.set selection_var to:(dir ^ deffile); diff --git a/otherlibs/labltk/browser/list2.ml b/otherlibs/labltk/browser/list2.ml index 6ab8b7863..8092f6ff1 100644 --- a/otherlibs/labltk/browser/list2.ml +++ b/otherlibs/labltk/browser/list2.ml @@ -1,6 +1,6 @@ (* $Id$ *) -let exclude elt:x l = List.filter l pred:((<>) x) +let exclude item:x l = List.filter l pred:((<>) x) let rec flat_map fun:f = function [] -> [] diff --git a/otherlibs/labltk/browser/searchid.ml b/otherlibs/labltk/browser/searchid.ml index c5871cc93..fe8cb2e2c 100644 --- a/otherlibs/labltk/browser/searchid.ml +++ b/otherlibs/labltk/browser/searchid.ml @@ -154,7 +154,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 elt: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: @@ -416,7 +416,7 @@ let search_structure str :name :kind :prefix = Pstr_value (_, l) when kind = Pvalue -> List.iter l fun: begin fun (pat,_) -> - if List.mem elt: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/setpath.ml b/otherlibs/labltk/browser/setpath.ml index 1c6ad22ef..cd255af19 100644 --- a/otherlibs/labltk/browser/setpath.ml +++ b/otherlibs/labltk/browser/setpath.ml @@ -47,12 +47,12 @@ let add_to_path :dirs ?:base{=""} box = in set_load_path (dirs @ List.fold_left dirs acc:(get_load_path ()) - fun:(fun :acc x -> List2.exclude elt:x acc)) + fun:(fun :acc x -> List2.exclude item:x acc)) let remove_path box :dirs = set_load_path (List.fold_left dirs acc:(get_load_path ()) - fun:(fun :acc x -> List2.exclude elt:x acc)) + fun:(fun :acc x -> List2.exclude item:x acc)) (* main function *) diff --git a/otherlibs/labltk/browser/shell.ml b/otherlibs/labltk/browser/shell.ml index 8f91c6a4f..039dc3f7b 100644 --- a/otherlibs/labltk/browser/shell.ml +++ b/otherlibs/labltk/browser/shell.ml @@ -152,12 +152,7 @@ let get_all () = all let may_exec prog = - try - let stats = Unix.stat prog in - stats.Unix.st_perm land 1 <> 0 or - stats.Unix.st_perm land 8 <> 0 - & List.mem elt:stats.Unix.st_gid (Array.to_list (Unix.getgroups ())) or - stats.Unix.st_perm land 64 <> 0 & stats.Unix.st_uid = Unix.getuid () + try Unix.access file:prog perm:[Unix.X_OK]; true with Unix.Unix_error _ -> false let f :prog :title = diff --git a/otherlibs/labltk/browser/useunix.ml b/otherlibs/labltk/browser/useunix.ml index 33dd20f2b..660d552d7 100644 --- a/otherlibs/labltk/browser/useunix.ml +++ b/otherlibs/labltk/browser/useunix.ml @@ -17,7 +17,7 @@ let get_files_in_directory dir = let is_directory name = try - (stat name).st_kind = S_DIR + (stat file:name).st_kind = S_DIR with _ -> false let get_directories_in_files :path = diff --git a/otherlibs/labltk/browser/viewer.ml b/otherlibs/labltk/browser/viewer.ml index 6ca0a0a81..9af6f76d2 100644 --- a/otherlibs/labltk/browser/viewer.ml +++ b/otherlibs/labltk/browser/viewer.ml @@ -21,7 +21,7 @@ let list_modules :path = String.capitalize (Filename.chop_suffix x suff:".cmi") end in List.fold_left l :acc - fun:(fun :acc elt -> if List.mem acc :elt then acc else elt :: acc) + fun:(fun :acc item -> if List.mem acc :item then acc else item :: acc) end let reset_modules box = @@ -227,12 +227,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 elt:("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 elt:(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/builtin/builtini_index.ml b/otherlibs/labltk/builtin/builtini_index.ml index cd2dc9c0b..30f6a4f34 100644 --- a/otherlibs/labltk/builtin/builtini_index.ml +++ b/otherlibs/labltk/builtin/builtini_index.ml @@ -29,7 +29,7 @@ let cCAMLtoTKtext_index = (cCAMLtoTKindex : text_index -> tkArgs) let cTKtoCAMLindex s = try - let p = String.index elt:'.' s in + let p = String.index char:'.' s in `Linechar (int_of_string (String.sub s pos:0 len:p), int_of_string (String.sub s pos:(p+1) len:(String.length s - p - 1))) @@ -40,7 +40,7 @@ let cTKtoCAMLindex s = let cTKtoCAMLtext_index s = try - let p = String.index elt:'.' s in + let p = String.index char:'.' s in `Linechar (int_of_string (String.sub s pos:0 len:p), int_of_string (String.sub s pos:(p+1) len:(String.length s - p - 1))) diff --git a/otherlibs/labltk/compiler/compile.ml b/otherlibs/labltk/compiler/compile.ml index 88a83fdfc..66c5fb569 100644 --- a/otherlibs/labltk/compiler/compile.ml +++ b/otherlibs/labltk/compiler/compile.ml @@ -42,7 +42,7 @@ let small_ident s = let idents = ["to"; "raise"; "in"; "class"; "new"] in let s = small s in - if List.mem elt: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 = @@ -54,7 +54,7 @@ let gettklabel fc = if s = "" then small fc.ml_name else small s | _ -> raise (Failure "gettklabel") -let count elt: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 elt: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 @@ -761,7 +761,7 @@ let write_catch_optionals :w clas def:typdef = (* used as names of variants *) fc.var_name, begin let p = gettklabel fc in - if count elt:p tklabels > 1 then small fc.ml_name else p + if count item:p tklabels > 1 then small fc.ml_name else p end, small_ident fc.ml_name (* used as labels *) end in diff --git a/otherlibs/labltk/compiler/intf.ml b/otherlibs/labltk/compiler/intf.ml index 2affef4b6..93126b467 100644 --- a/otherlibs/labltk/compiler/intf.ml +++ b/otherlibs/labltk/compiler/intf.ml @@ -15,7 +15,7 @@ let write_create_p :w wname = let l = List.map classdefs fun: begin fun fc -> begin let p = gettklabel fc in - if count elt: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 (catenate_sep sep:" ->\n" diff --git a/otherlibs/labltk/compiler/maincompile.ml b/otherlibs/labltk/compiler/maincompile.ml index 8f4d29ae8..ffa4aa49c 100644 --- a/otherlibs/labltk/compiler/maincompile.ml +++ b/otherlibs/labltk/compiler/maincompile.ml @@ -106,7 +106,7 @@ verbose_string "type "; verbose_string "C2T "; write_CAMLtoTK w:(output_string to:oc') typname def:typdef; verbose_string "T2C "; - if List.mem elt: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 e4e0c5e7d..bd650463e 100644 --- a/otherlibs/labltk/compiler/tables.ml +++ b/otherlibs/labltk/compiler/tables.ml @@ -235,7 +235,7 @@ let rec has_callback = function (*** Returned types ***) let really_add ty = - if List.mem elt: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 e7af7fc2c..728a0245d 100644 --- a/otherlibs/labltk/jpf/fileselect.ml +++ b/otherlibs/labltk/jpf/fileselect.ml @@ -96,7 +96,7 @@ let get_files_in_directory dir = let rec get_directories_in_files path = function [] -> [] | x::xs -> - if try (stat (path ^ x)).st_kind = S_DIR with _ -> false then + if try (stat file:(path ^ x)).st_kind = S_DIR with _ -> false then x::(get_directories_in_files path xs) else get_directories_in_files path xs @@ -104,7 +104,7 @@ let remove_directories dirname = let rec remove = function [] -> [] | x :: xs -> - if try (stat (dirname ^ x)).st_kind = S_DIR with _ -> true then + if try (stat file:(dirname ^ x)).st_kind = S_DIR with _ -> true then remove xs else x :: (remove xs) diff --git a/otherlibs/labltk/support/widget.ml b/otherlibs/labltk/support/widget.ml index 7f6436c9b..8c86e4448 100644 --- a/otherlibs/labltk/support/widget.ml +++ b/otherlibs/labltk/support/widget.ml @@ -150,11 +150,11 @@ let check_class w clas = match w with Untyped _ -> () (* assume run-time check by tk*) | Typed(_,c) -> - if List.mem clas elt: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 elt:c then () + if List.mem table item:c then () else raise (Invalid_argument errname) diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli index 2f6ee69fa..b96c0cb4b 100644 --- a/otherlibs/unix/unix.mli +++ b/otherlibs/unix/unix.mli @@ -292,9 +292,9 @@ type stats = (* The informations returned by the [stat] calls. *) -val stat : string -> stats +val stat : file:string -> stats (* Return the information for the named file. *) -val lstat : string -> stats +val lstat : file: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 : string -> unit +val unlink : file: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 : string -> as:string -> unit +val link : source:string -> dest:string -> unit (* [link source dest] creates a hard link named [dest] to the file named [new]. *) @@ -399,7 +399,7 @@ val pipe : unit -> file_descr * file_descr for reading, that's the exit to the pipe. The second component is opened for writing, that's the entrance to the pipe. *) -val mkfifo : string -> file_perm -> unit +val mkfifo : string -> perm:file_perm -> unit (* Create a named pipe with the given permissions. *) @@ -458,7 +458,7 @@ val close_process_full: in_channel * out_channel * in_channel -> process_status (*** Symbolic links *) -val symlink : string -> as:string -> unit +val symlink : source:string -> dest:string -> unit (* [symlink source dest] creates the file [dest] as a symbolic link to the file [source]. *) val readlink : string -> string |