]> matita.cs.unibo.it Git - helm.git/blob - helm/uwobo/src/ocaml/uwobo_common.ml
Initial revision
[helm.git] / helm / uwobo / src / ocaml / uwobo_common.ml
1
2 (* Copyright (C) 2002, HELM Team.
3  * 
4  * This file is part of HELM, an Hypertextual, Electronic
5  * Library of Mathematics, developed at the Computer Science
6  * Department, University of Bologna, Italy.
7  * 
8  * HELM is free software; you can redistribute it and/or
9  * modify it under the terms of the GNU General Public License
10  * as published by the Free Software Foundation; either version 2
11  * of the License, or (at your option) any later version.
12  * 
13  * HELM is distributed in the hope that it will be useful,
14  * but WITHOUT ANY WARRANTY; without even the implied warranty of
15  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16  * GNU General Public License for more details.
17  *
18  * You should have received a copy of the GNU General Public License
19  * along with HELM; if not, write to the Free Software
20  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
21  * MA  02111-1307, USA.
22  * 
23  * For details, see the HELM World-Wide-Web page,
24  * http://cs.unibo.it/helm/.
25  *)
26
27 let debug = false;;
28 let debug_print msg = if debug then prerr_endline msg;;
29
30 exception Uwobo_failure of string;;
31
32 let supported_properties = [
33   "cdata-section-elements";
34   "doctype-public";
35   "doctype-system";
36   "encoding";
37   "indent";
38   "media-type";
39   "method";
40   "omit-xml-declaration";
41   "standalone";
42   "version"
43 ]
44
45 let is_supported_property name = List.mem name supported_properties
46
47 class threadSafe =
48   object (self)
49
50     val mutex = Mutex.create ()
51
52       (** condition variable: 'no readers is currently reading' *)
53     val noReaders = Condition.create ()
54
55       (** readers count *)
56     val mutable readersCount = 0
57
58     method private incrReadersCount = (* internal, not exported *)
59       self#doCritical (lazy (
60         readersCount <- readersCount + 1
61       ))
62
63     method private decrReadersCount = (* internal, not exported *)
64       self#doCritical (lazy (
65         if readersCount > 0 then readersCount <- readersCount - 1;
66       ))
67
68     method private signalNoReaders =  (* internal, not exported *)
69       self#doCritical (lazy (
70         if readersCount = 0 then Condition.signal noReaders
71       ))
72
73     method private doCritical: 'a. 'a lazy_t -> 'a =
74       fun action ->
75         debug_print "<doCritical>";
76         (try
77           Mutex.lock mutex;
78           let res = Lazy.force action in
79           Mutex.unlock mutex;
80           debug_print "</doCritical>";
81           res
82         with e ->
83           Mutex.unlock mutex;
84           raise e);
85
86     method private doReader: 'a. 'a lazy_t -> 'a =
87       fun action ->
88         debug_print "<doReader>";
89         let cleanup () =
90           self#decrReadersCount;
91           self#signalNoReaders
92         in
93         self#incrReadersCount;
94         let res = (try Lazy.force action with e -> (cleanup (); raise e)) in
95         cleanup ();
96         debug_print "</doReader>";
97         res
98
99       (* TODO may starve!!!! is what we want or not? *)
100     method private doWriter: 'a. 'a lazy_t -> 'a =
101       fun action ->
102         debug_print "<doWriter>";
103         self#doCritical (lazy (
104           while readersCount > 0 do
105             Condition.wait noReaders mutex
106           done;
107           let res = Lazy.force action in
108           debug_print "</doWriter>";
109           res
110         ))
111
112   end
113