summaryrefslogtreecommitdiffstats
path: root/otherlibs/labltk/browser/shell.ml
blob: 88492cc9ec587319c1366edccac1d3cc85d88128 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
(*************************************************************************)
(*                                                                       *)
(*                Objective Caml LablTk library                          *)
(*                                                                       *)
(*            Jacques Garrigue, Kyoto University RIMS                    *)
(*                                                                       *)
(*   Copyright 1999 Institut National de Recherche en Informatique et    *)
(*   en Automatique and Kyoto University.  All rights reserved.          *)
(*   This file is distributed under the terms of the GNU Library         *)
(*   General Public License.                                             *)
(*                                                                       *)
(*************************************************************************)

(* $Id$ *)

open Tk
open Jg_tk
open Dummy

(* Here again, memoize regexps *)

let (~) = Jg_memo.fast fun:Str.regexp

(* Nice history class. May reuse *)

class ['a] history () = object
  val mutable history = ([] : 'a list)
  val mutable count = 0
  method empty = history = []
  method add s = count <- 0; history <- s :: history
  method previous =
    let s = List.nth pos:count history 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)
end

let dump_mem ?(:pos = 0) ?:len obj =
  if not (Obj.is_block obj) then invalid_arg "Shell.dump_mem";
  let len =
    match len with
    | None -> Obj.size obj * Sys.word_size / 8 - pos
    | Some x -> x in
  let buf = Buffer.create size: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))
  done;
  Buffer.contents buf

(* The shell class. Now encapsulated *)

let protect f x = try f x with _ -> ()

class shell :textw :prog :args :env =
  let (in2,out1) = Unix.pipe ()
  and (in1,out2) = Unix.pipe ()
  and (err1,err2) = Unix.pipe ()
  and (sig2,sig1) = Unix.pipe () in
object (self)
  val pid =
    let env =
      if Sys.os_type = "Win32" then
        let sigdef = "CAMLSIGPIPE=" ^ dump_mem (Obj.repr sig2) in
        Array.append env [|sigdef|]
      else env
    in
    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 ()
  val mutable alive = true
  val mutable reading = false
  val ibuffer = Buffer.create size:1024
  val imutex = Mutex.create ()
  val mutable ithreads = []
  method alive = alive
  method kill =
    if Winfo.exists textw then Text.configure textw state:`Disabled;
    if alive then begin
      alive <- false;
      protect close_out out;
      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]
        end else begin
          List.iter fun:(protect Unix.close) [in1; err1; sig1; sig2];
          Fileevent.remove_fileinput fd:in1;
          Fileevent.remove_fileinput fd:err1;
          Unix.kill :pid signal:Sys.sigkill;
          ignore (Unix.waitpid mode:[] pid)
        end
      with _ -> ()
    end
  method interrupt =
    if alive then try
      reading <- false;
      if Sys.os_type = "Win32" then begin
        ignore (Unix.write sig1 buf:"C" pos:0 len:1);
        self#send " "
      end else
        Unix.kill :pid signal:Sys.sigint
    with Unix.Unix_error _ -> ()
  method send s =
    if alive then try
      output_string s to:out;
      flush out
    with Sys_error _ -> ()
  method private read :fd :len =
    begin try
      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);
	Text.mark_set textw mark:"input" index:(`Mark"insert",[`Char(-1)])
      end;
      len
    with Unix.Unix_error _ -> 0
    end;
  method history (dir : [`next|`previous]) =
    if not h#empty then begin
      if reading then begin
        Text.delete textw start:(`Mark"input",[`Char 1])
          end:(`Mark"insert",[])
      end else begin
        reading <- true;
        Text.mark_set textw mark:"input"
          index:(`Mark"insert",[`Char(-1)])
      end;
      self#insert (if dir = `previous then h#previous else h#next)
    end
  method private lex ?(:start = `Mark"insert",[`Linestart])
      ?(:end = `Mark"insert",[`Lineend]) () =
    Lexical.tag textw :start :end
  method insert text =
    let idx = Text.index textw
        index:(`Mark"insert",[`Char(-1);`Linestart]) in
    Text.insert textw :text index:(`Mark"insert",[]);
    self#lex start:(idx,[`Linestart]) ();
    Text.see textw index:(`Mark"insert",[])
  method private keypress c =
    if not reading & c > " " then begin
      reading <- true;
      Text.mark_set textw mark:"input" index:(`Mark"insert",[`Char(-1)])
    end
  method private keyrelease c = if c <> "" then self#lex ()
  method private return =
    if reading then reading <- false
    else Text.mark_set textw mark:"input"
        index:(`Mark"insert",[`Linestart;`Char 1]);
    Text.mark_set textw mark:"insert"index:(`Mark"insert",[`Line 1]);
    self#lex start:(`Mark"input",[`Linestart]) ();
    let s =
      (* input is one character before real input *)
      Text.get textw start:(`Mark"input",[`Char 1])
        end:(`Mark"insert",[]) in
    h#add s;
    Text.insert textw index:(`Mark"insert",[]) text:"\n";
    Text.yview_index textw index:(`Mark"insert",[]);
    self#send s;
    self#send "\n"
  method private paste ev =
    if not reading then begin
      reading <- true;
      Text.mark_set textw mark:"input"
        index:(`Atxy(ev.ev_MouseX, ev.ev_MouseY),[`Char(-1)])
    end
  initializer
    Lexical.init_tags textw;
    let rec bindings =
      [ ([], `KeyPress, [`Char], fun ev -> self#keypress ev.ev_Char);
        ([], `KeyRelease, [`Char], fun ev -> self#keyrelease ev.ev_Char);
        (* [], `KeyPressDetail"Return", [], fun _ -> self#return; *)
        ([], `ButtonPressDetail 2, [`MouseX; `MouseY],  self#paste);
        ([`Alt], `KeyPressDetail"p", [], fun _ -> self#history `previous);
        ([`Alt], `KeyPressDetail"n", [], fun _ -> self#history `next);
        ([`Meta], `KeyPressDetail"p", [], fun _ -> self#history `previous);
        ([`Meta], `KeyPressDetail"n", [], fun _ -> self#history `next);
        ([`Control], `KeyPressDetail"c", [], fun _ -> self#interrupt);
        ([], `Destroy, [], fun _ -> self#kill) ]
    in
    List.iter bindings fun:
      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];
    if Sys.os_type = "Win32" then begin
      let fileinput_thread fd =
        let buf = String.create len:1024 in
        let len = ref 0 in
        try while len := ThreadUnix.read fd :buf pos:0 len:1024; !len > 0 do
          Mutex.lock imutex;
          Buffer.add_substring ibuffer buf pos:0 len:!len;
          Mutex.unlock imutex
        done with Unix.Unix_error _ -> ()
      in
      ithreads <- List.map [in1; err1] fun:(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"
                         (Buffer.contents ibuffer));
          Buffer.reset ibuffer;
	  Text.mark_set textw mark:"input" index:(`Mark"insert",[`Char(-1)])
        end;
        Mutex.unlock imutex;
        Timer.set ms:100 callback:read_buffer
      in
      read_buffer ()
    end else begin
      try
	List.iter [in1;err1] fun:
          begin fun fd ->
            Fileevent.add_fileinput :fd
              callback:(fun () -> ignore (self#read :fd len:1024))
          end
      with _ -> ()
    end
end

(* Specific use of shell, for OCamlBrowser *)

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);
  shells := []

let get_all () =
  let all = List.filter !shells pred:(fun (_,sh) -> sh#alive) in
  shells := all;
  all

let may_exec_unix prog =
  try Unix.access file:prog perm:[Unix.X_OK]; true
  with Unix.Unix_error _ -> false

let may_exec_win prog =
  List.exists pred: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

let path_sep = if Sys.os_type = "Win32" then ";" else ":"

let f :prog :title =
  let progargs =
    List.filter pred:((<>) "") (Str.split sep:~" " prog) in
  if progargs = [] then () else
  let prog = List.hd progargs in
  let path =
    try Sys.getenv "PATH" with Not_found -> "/bin" ^ path_sep ^ "/usr/bin" in
  let exec_path = Str.split sep:~path_sep path in
  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
  if not exists then () else
  let tl = Jg_toplevel.titled title in
  let menus = Frame.create tl name:"menubar" in
  let file_menu = new Jg_menu.c "File" parent:menus
  and history_menu = new Jg_menu.c "History" parent:menus
  and signal_menu = new Jg_menu.c "Signal" parent:menus in
  pack [menus] side:`Top fill:`X;
  pack [file_menu#button; history_menu#button; signal_menu#button]
    side:`Left ipadx:5 anchor:`W;
  let frame, tw, sb = Jg_text.create_with_scrollbar tl in
  Text.configure tw background:`White;
  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:
      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
  let args = Array.of_list (progargs @ load_path) in
  let sh = new shell textw:tw :prog :env :args in
  let current_dir = ref (Unix.getcwd ()) in
  file_menu#add_command "Use..." command:
    begin fun () ->
      Fileselect.f title:"Use File" filter:"*.ml" sync:true dir:!current_dir ()
        action:(fun l ->
          if l = [] then () else
          let name = List.hd l in
          current_dir := Filename.dirname name;
          if Filename.check_suffix name suff:".ml"
          then
            let cmd = "#use \"" ^ name ^ "\";;\n" in
            sh#insert cmd; sh#send cmd)
    end;
  file_menu#add_command "Load..." command:
    begin fun () ->
      Fileselect.f title:"Load File" filter:"*.cm[oa]" sync:true ()
        dir:!current_dir
        action:(fun l ->
          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"
          then
            let cmd = "#load \"" ^ name ^ "\";;\n" in
            sh#insert cmd; sh#send cmd)
    end;
  file_menu#add_command "Import path" command:
    begin fun () ->
      List.iter (List.rev !Config.load_path)
        fun:(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"
    command:(fun () -> sh#history `previous);
  history_menu#add_command "Next" accelerator:"M-n"
    command:(fun () -> sh#history `next);
  signal_menu#add_command "Interrupt  " accelerator:"C-c"
    command:(fun () -> sh#interrupt);
  signal_menu#add_command "Kill" command:(fun () -> sh#kill);
  shells := (title, sh) :: !shells