summaryrefslogtreecommitdiffstats
path: root/otherlibs/labltk/browser/shell.ml
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/labltk/browser/shell.ml')
-rw-r--r--otherlibs/labltk/browser/shell.ml54
1 files changed, 27 insertions, 27 deletions
diff --git a/otherlibs/labltk/browser/shell.ml b/otherlibs/labltk/browser/shell.ml
index a8188b9f0..7e8b479bd 100644
--- a/otherlibs/labltk/browser/shell.ml
+++ b/otherlibs/labltk/browser/shell.ml
@@ -19,7 +19,7 @@ open Dummy
(* Here again, memoize regexps *)
-let (~) = Jg_memo.fast fun:Str.regexp
+let (~) = Jg_memo.fast f:Str.regexp
(* Nice history class. May reuse *)
@@ -29,13 +29,13 @@ class ['a] history () = object
method empty = history = []
method add s = count <- 0; history <- s :: history
method previous =
- let s = List.nth pos:count history in
+ let s = List.nth history count in
count <- (count + 1) mod List.length history;
s
method next =
let l = List.length history in
count <- (l + count - 1) mod l;
- List.nth history pos:((l + count - 1) mod l)
+ List.nth history ((l + count - 1) mod l)
end
let dump_mem ?(:pos = 0) ?:len obj =
@@ -44,7 +44,7 @@ let dump_mem ?(:pos = 0) ?:len obj =
match len with
| None -> Obj.size obj * Sys.word_size / 8 - pos
| Some x -> x in
- let buf = Buffer.create size:256 in
+ let buf = Buffer.create 256 in
for i = pos to len - 1 do
let c = String.unsafe_get (Obj.obj obj) i in
Buffer.add_string buf (Printf.sprintf "%02x" (Char.code c))
@@ -74,7 +74,7 @@ object (self)
val h = new history ()
val mutable alive = true
val mutable reading = false
- val ibuffer = Buffer.create size:1024
+ val ibuffer = Buffer.create 1024
val imutex = Mutex.create ()
val mutable ithreads = []
method alive = alive
@@ -86,9 +86,9 @@ object (self)
try
if Sys.os_type = "Win32" then begin
ignore (Unix.write sig1 buf:"T" pos:0 len:1);
- List.iter fun:(protect Unix.close) [sig1; sig2]
+ List.iter f:(protect Unix.close) [sig1; sig2]
end else begin
- List.iter fun:(protect Unix.close) [in1; err1; sig1; sig2];
+ List.iter f:(protect Unix.close) [in1; err1; sig1; sig2];
Fileevent.remove_fileinput fd:in1;
Fileevent.remove_fileinput fd:err1;
Unix.kill :pid signal:Sys.sigkill;
@@ -107,12 +107,12 @@ object (self)
with Unix.Unix_error _ -> ()
method send s =
if alive then try
- output_string s to:out;
+ output_string out s;
flush out
with Sys_error _ -> ()
method private read :fd :len =
begin try
- let buf = String.create :len in
+ let buf = String.create len in
let len = Unix.read fd :buf pos:0 :len in
if len > 0 then begin
self#insert (String.sub buf pos:0 :len);
@@ -183,16 +183,16 @@ object (self)
([`Control], `KeyPressDetail"c", [], fun _ -> self#interrupt);
([], `Destroy, [], fun _ -> self#kill) ]
in
- List.iter bindings fun:
+ List.iter bindings f:
begin fun (modif,event,fields,action) ->
bind textw events:[`Modified(modif,event)] :fields :action
end;
bind textw events:[`KeyPressDetail"Return"] breakable:true
action:(fun _ -> self#return; break());
- List.iter fun:Unix.close [in2;out2;err2];
+ List.iter f:Unix.close [in2;out2;err2];
if Sys.os_type = "Win32" then begin
let fileinput_thread fd =
- let buf = String.create len:1024 in
+ let buf = String.create 1024 in
let len = ref 0 in
try while len := ThreadUnix.read fd :buf pos:0 len:1024; !len > 0 do
Mutex.lock imutex;
@@ -200,11 +200,11 @@ object (self)
Mutex.unlock imutex
done with Unix.Unix_error _ -> ()
in
- ithreads <- List.map [in1; err1] fun:(Thread.create fileinput_thread);
+ ithreads <- List.map [in1; err1] f:(Thread.create fileinput_thread);
let rec read_buffer () =
Mutex.lock imutex;
if Buffer.length ibuffer > 0 then begin
- self#insert (Str.global_replace pat:~"\r\n" with:"\n"
+ self#insert (Str.global_replace pat:~"\r\n" templ:"\n"
(Buffer.contents ibuffer));
Buffer.reset ibuffer;
Text.mark_set textw mark:"input" index:(`Mark"insert",[`Char(-1)])
@@ -215,7 +215,7 @@ object (self)
read_buffer ()
end else begin
try
- List.iter [in1;err1] fun:
+ List.iter [in1;err1] f:
begin fun fd ->
Fileevent.add_fileinput :fd
callback:(fun () -> ignore (self#read :fd len:1024))
@@ -230,11 +230,11 @@ let shells : (string * shell) list ref = ref []
(* Called before exiting *)
let kill_all () =
- List.iter !shells fun:(fun (_,sh) -> if sh#alive then sh#kill);
+ List.iter !shells f:(fun (_,sh) -> if sh#alive then sh#kill);
shells := []
let get_all () =
- let all = List.filter !shells pred:(fun (_,sh) -> sh#alive) in
+ let all = List.filter !shells f:(fun (_,sh) -> sh#alive) in
shells := all;
all
@@ -243,7 +243,7 @@ let may_exec_unix prog =
with Unix.Unix_error _ -> false
let may_exec_win prog =
- List.exists pred:may_exec_unix [prog; prog^".exe"; prog^".cmo"; prog^".bat"]
+ List.exists f:may_exec_unix [prog; prog^".exe"; prog^".cmo"; prog^".bat"]
let may_exec =
if Sys.os_type = "Win32" then may_exec_win else may_exec_unix
@@ -254,7 +254,7 @@ let warnings = ref "A"
let f :prog :title =
let progargs =
- List.filter pred:((<>) "") (Str.split sep:~" " prog) in
+ List.filter f:((<>) "") (Str.split sep:~" " prog) in
if progargs = [] then () else
let prog = List.hd progargs in
let path =
@@ -263,7 +263,7 @@ let f :prog :title =
let exists =
if not (Filename.is_implicit prog) then may_exec prog else
List.exists exec_path
- pred:(fun dir -> may_exec (Filename.concat dir prog)) in
+ f:(fun dir -> may_exec (Filename.concat dir prog)) in
if not exists then () else
let tl = Jg_toplevel.titled title in
let menus = Frame.create tl name:"menubar" in
@@ -278,15 +278,15 @@ let f :prog :title =
pack [sb] fill:`Y side:`Right;
pack [tw] fill:`Both expand:true side:`Left;
pack [frame] fill:`Both expand:true;
- let env = Array.map (Unix.environment ()) fun:
+ let env = Array.map (Unix.environment ()) f:
begin fun s ->
if Str.string_match pat:~"TERM=" s pos:0 then "TERM=dumb" else s
end in
let load_path =
- List2.flat_map !Config.load_path fun:(fun dir -> ["-I"; dir]) in
+ List2.flat_map !Config.load_path f:(fun dir -> ["-I"; dir]) in
let modern = if !Clflags.classic then [] else ["-label"] in
let warnings =
- if List.mem item:"-w" progargs || !warnings = "A" then []
+ if List.mem "-w" progargs || !warnings = "A" then []
else ["-w"; !warnings]
in
let args = Array.of_list (progargs @ modern @ warnings @ load_path) in
@@ -299,7 +299,7 @@ let f :prog :title =
if l = [] then () else
let name = List.hd l in
current_dir := Filename.dirname name;
- if Filename.check_suffix name suff:".ml"
+ if Filename.check_suffix name ".ml"
then
let cmd = "#use \"" ^ name ^ "\";;\n" in
sh#insert cmd; sh#send cmd)
@@ -312,8 +312,8 @@ let f :prog :title =
if l = [] then () else
let name = List.hd l in
current_dir := Filename.dirname name;
- if Filename.check_suffix name suff:".cmo" or
- Filename.check_suffix name suff:".cma"
+ if Filename.check_suffix name ".cmo" or
+ Filename.check_suffix name ".cma"
then
let cmd = "#load \"" ^ name ^ "\";;\n" in
sh#insert cmd; sh#send cmd)
@@ -321,7 +321,7 @@ let f :prog :title =
file_menu#add_command "Import path" command:
begin fun () ->
List.iter (List.rev !Config.load_path)
- fun:(fun dir -> sh#send ("#directory \"" ^ dir ^ "\";;\n"))
+ f:(fun dir -> sh#send ("#directory \"" ^ dir ^ "\";;\n"))
end;
file_menu#add_command "Close" command:(fun () -> destroy tl);
history_menu#add_command "Previous " accelerator:"M-p"