]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql/avsUtil.ml
an optimization was inserted
[helm.git] / helm / ocaml / mathql / avsUtil.ml
1 (* Copyright (C) 2000, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 (*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
27  *)
28
29 module I = MathQL.I
30
31 (* strings ******************************************************************)
32
33 let avs_of_string s = I.make s I.grp_empty 
34
35 let string_of_avs r =
36    match I.peek r with 
37       | I.Single (s, _) -> Some s
38       | _               -> None
39
40 (* boolean constants  *******************************************************)
41
42 let bool_of_avs r = r <> I.empty
43
44 let avs_of_bool = function
45    | true  -> I.make "" I.grp_empty
46    | false -> I.empty
47
48 let val_false = avs_of_bool false
49
50 let val_true = avs_of_bool true
51
52 (* iterators ****************************************************************)
53
54 let grp_iter f al =
55    List.fold_left (fun s a -> I.grp_union s (f a)) I.grp_empty (List.rev al)
56
57 let grp_iter2 f al bl = 
58    List.fold_left2 (fun s a b -> I.grp_union s (f a b)) 
59                    I.grp_empty (List.rev al) (List.rev bl)
60
61 let iter f al = List.fold_left (fun s a -> I.union s (f a)) 
62                                I.empty (List.rev al)
63
64 (* other ********************************************************************)
65
66 let grp_make_x p vl = grp_iter (I.grp_make p) vl
67
68 let x_grp_make_x p rs = 
69    let aux g s _ = I.grp_union g (I.grp_make p s) in
70    I.iter aux I.grp_empty rs
71
72 let make_x s gl = 
73    if gl = [] then avs_of_string s else iter (I.make s) gl
74
75 let count v = I.iter (fun n _ _ -> succ n) 0 v
76
77 let subj v = iter (fun s -> I.make s I.grp_empty) v
78
79 (* numeric operations *******************************************************)
80
81 exception NumberError of MathQL.result
82
83 let avs_of_int i = I.make (string_of_int i) I.grp_empty
84
85 let int_of_avs r =
86    try match (I.peek r) with 
87       | I.Empty
88       | I.Many _        -> raise (Failure "int_of_string")
89       | I.Single (s, _) -> MQueryUtil.int_of_string s
90    with Failure "int_of_string" -> raise (NumberError r)