]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/thread/extThread.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / thread / extThread.ml
1 (*
2  * Copyright (C) 2003-2004:
3  *    Stefano Zacchiroli <zack@cs.unibo.it>
4  *    for the HELM Team http://helm.cs.unibo.it/
5  *
6  *  This file is part of HELM, an Hypertextual, Electronic
7  *  Library of Mathematics, developed at the Computer Science
8  *  Department, University of Bologna, Italy.
9  *
10  *  HELM is free software; you can redistribute it and/or
11  *  modify it under the terms of the GNU General Public License
12  *  as published by the Free Software Foundation; either version 2
13  *  of the License, or (at your option) any later version.
14  *
15  *  HELM is distributed in the hope that it will be useful,
16  *  but WITHOUT ANY WARRANTY; without even the implied warranty of
17  *  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  *  GNU General Public License for more details.
19  *
20  *  You should have received a copy of the GNU General Public License
21  *  along with HELM; if not, write to the Free Software
22  *  Foundation, Inc., 59 Temple Place - Suite 330, Boston,
23  *  MA  02111-1307, USA.
24  *
25  *  For details, see the HELM World-Wide-Web page,
26  *  http://helm.cs.unibo.it/
27  *)
28
29 let debug = true
30 let debug_print s = if debug then prerr_endline (Lazy.force s)
31
32 exception Can_t_kill of Thread.t * string (* thread, reason *)
33 exception Thread_not_found of Thread.t
34
35 module OrderedPid =
36   struct
37     type t = int
38     let compare = Pervasives.compare
39   end
40 module PidSet = Set.Make (OrderedPid)
41
42  (* perform an action inside a critical section controlled by given mutex *)
43 let do_critical mutex =
44   fun action ->
45     try
46       Mutex.lock mutex;
47       let res = Lazy.force action in
48       Mutex.unlock mutex;
49       res 
50     with e -> Mutex.unlock mutex; raise e
51
52 let kill_signal = Sys.sigusr2   (* signal used to kill children *)
53 let chan = Event.new_channel () (* communication channel between threads *)
54 let creation_mutex = Mutex.create ()
55 let dead_threads_walking = ref PidSet.empty
56 let pids: (Thread.t, int) Hashtbl.t = Hashtbl.create 17
57
58   (* given a thread body (i.e. first argument of a Thread.create invocation)
59   return a new thread body which unblock the kill signal and send its pid to
60   parent over "chan" *)
61 let wrap_thread body =
62   fun arg ->
63     ignore (Unix.sigprocmask Unix.SIG_UNBLOCK [ kill_signal ]);
64     Event.sync (Event.send chan (Unix.getpid ()));
65     body arg
66
67 (*
68 (* FAKE IMPLEMENTATION *)
69 let create = Thread.create
70 let kill _ = ()
71 *)
72
73 let create body arg =
74   do_critical creation_mutex (lazy (
75     let thread_t = Thread.create (wrap_thread body) arg in
76     let pid = Event.sync (Event.receive chan) in
77     Hashtbl.add pids thread_t pid;
78     thread_t
79   ))
80
81 let kill thread_t =
82   try
83     let pid =
84       try
85         Hashtbl.find pids thread_t
86       with Not_found -> raise (Thread_not_found thread_t)
87     in
88     dead_threads_walking := PidSet.add pid !dead_threads_walking;
89     Unix.kill pid kill_signal
90   with e -> raise (Can_t_kill (thread_t, Printexc.to_string e))
91
92   (* "kill_signal" handler, check if current process must die, if this is the
93   case exits with Thread.exit *)
94 let _ =
95   ignore (Sys.signal kill_signal (Sys.Signal_handle
96     (fun signal ->
97       let myself = Unix.getpid () in
98       match signal with
99       | sg when (sg = kill_signal) &&
100                 (PidSet.mem myself !dead_threads_walking) ->
101           dead_threads_walking := PidSet.remove myself !dead_threads_walking;
102           debug_print (lazy "AYEEEEH!");
103           Thread.exit ()
104       | _ -> ())))
105
106   (* block kill signal in main process *)
107 let _ = ignore (Unix.sigprocmask Unix.SIG_BLOCK [ kill_signal ])
108