]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/mQueryUtil.ml
test branch
[helm.git] / helm / ocaml / mathql_interpreter / mQueryUtil.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 (* $Id$ *)
30
31 (* text linearization and parsing *******************************************)
32
33 let rec txt_list out f s = function
34    | []        -> ()
35    | [a]       -> f a
36    | a :: tail -> f a; out s; txt_list out f s tail
37    
38 let txt_str out s = out ("\"" ^ s ^ "\"")
39
40 let txt_path out p = out "/"; txt_list out (txt_str out) "/" p 
41
42 let text_of_query out sep x =
43    let module M = MathQL in 
44    let txt_path_list l = txt_list out (txt_path out) ", " l in 
45    let txt_svar sv = out ("%" ^ sv) in 
46    let txt_avar av = out ("@" ^ av) in
47    let txt_vvar vv = out ("$" ^ vv) in
48    let txt_inv i = if i then out "inverse " in
49    let txt_ref = function
50       | M.RefineExact -> ()
51       | M.RefineSub   -> out "sub "
52       | M.RefineSuper -> out "super "
53    in
54    let txt_qualif i r p = txt_inv i; txt_ref r; txt_path out p in
55    let main = function
56       | [] -> ()
57       | p  -> out " main "; txt_path out p
58    in
59    let txt_exp = function
60       | (pl, None)    -> txt_path out pl 
61       | (pl, Some pr) -> txt_path out pl; out " as "; txt_path out pr
62    in
63    let txt_exp_list = function
64       | [] -> ()
65       | l  -> out " attr "; txt_list out txt_exp ", " l 
66    in
67    let pattern b = if b then out "pattern " in
68    let txt_opt_path = function
69       | None   -> ()
70       | Some p -> txt_path out p; out " "
71    in
72    let txt_distr d = if d then out "distr " in
73    let txt_bin = function
74       | M.BinFJoin -> out " union "
75       | M.BinFMeet -> out " intersect "
76       | M.BinFDiff -> out " diff "
77    in
78    let txt_gen = function
79       | M.GenFJoin -> out " sup "
80       | M.GenFMeet -> out " inf "
81    in
82    let txt_test = function
83       | M.Xor  -> out " xor "
84       | M.Or   -> out " or "
85       | M.And  -> out " and "
86       | M.Sub  -> out " sub "
87       | M.Meet -> out " meet "
88       | M.Eq   -> out " eq "
89       | M.Le   -> out " le "
90       | M.Lt   -> out " lt "
91    in
92    let txt_log a b = 
93       if a then out "xml ";
94       if b then out "source "
95    in
96    let txt_allbut b = if b then out "allbut " in   
97    let rec txt_con (pat, p, x) = 
98       txt_path out p; 
99       if pat then out " match " else out " in ";
100       txt_val x
101    and txt_con_list s = function
102       | [] -> ()
103       | l  -> out s; txt_list out txt_con ", " l 
104    and txt_istrue lt = txt_con_list " istrue " lt 
105    and txt_isfalse lf = txt_con_list " isfalse " lf
106    and txt_ass (p, x) = txt_val x; out " as "; txt_path out p
107    and txt_ass_list l = txt_list out txt_ass ", " l
108    and txt_assg_list g = txt_list out txt_ass_list "; " g
109    and txt_val_list = function
110       | [v] -> txt_val v
111       | l   -> out "{"; txt_list out txt_val ", " l; out "}" 
112    and txt_grp = function
113       | M.Attr g  -> txt_assg_list g
114       | M.From av -> txt_avar av
115    and txt_val = function
116       | M.True       -> out "true"
117       | M.False      -> out "false"
118       | M.Const s    -> txt_str out s
119       | M.Set l      -> txt_val_list l
120       | M.VVar vv    -> txt_vvar vv
121       | M.Dot (av,p)   -> txt_avar av; out "."; txt_path out p
122       | M.Proj (op,x)  -> out "proj "; txt_opt_path op; txt_set x
123       | M.Ex (b,x)     -> out "ex "; txt_val x
124 (*    | M.Ex b x     -> out "ex ["; txt_list out txt_avar "," b; out "] "; txt_val x
125 *)    | M.Not x      -> out "not "; txt_val x
126       | M.Test (k,x,y) -> out "("; txt_val x; txt_test k; txt_val y; out ")"
127       | M.StatVal x  -> out "stat "; txt_val x
128       | M.Count x    -> out "count "; txt_val x
129       | M.Align (s,x)  -> out "align "; txt_str out s; out " in "; txt_val x
130    and txt_set = function
131       | M.Empty              -> out "empty"
132       | M.SVar sv            -> txt_svar sv
133       | M.AVar av            -> txt_avar av
134       | M.Property (q0,q1,q2,mc,ct,cfl,xl,b,x) -> 
135          out "property "; txt_qualif q0 q1 q2; main mc;
136          txt_istrue ct; txt_list out txt_isfalse "" cfl; txt_exp_list xl;
137          out " of "; pattern b; txt_val x
138       | M.Bin (k,x,y)          -> out "("; txt_set x; txt_bin k; txt_set y;
139                                 out ")"
140       | M.LetSVar (sv,x,y)     -> out "let "; txt_svar sv; out " be "; 
141                                 txt_set x; out " in "; txt_set y
142       | M.LetVVar (vv,x,y)     -> out "let "; txt_vvar vv; out " be "; 
143                                 txt_val x; out " in "; txt_set y
144       | M.Select (av,x,y)      -> out "select "; txt_avar av; out " from ";
145                                 txt_set x; out " where "; txt_val y
146       | M.Subj x             -> out "subj "; txt_val x
147       | M.For (k,av,x,y)       -> out "for "; txt_avar av; out " in ";
148                                 txt_set x; txt_gen k; txt_set y
149       | M.If (x,y,z)           -> out "if "; txt_val x; out " then ";
150                                 txt_set y; out " else "; txt_set z
151       | M.Add (d,g,x)          -> out "add "; txt_distr d; txt_grp g; 
152                                 out " in "; txt_set x
153       | M.Log (a,b,x)          -> out "log "; txt_log a b; txt_set x
154       | M.StatQuery x        -> out "stat "; txt_set x
155       | M.Keep (b,l,x)         -> out "keep "; txt_allbut b; txt_path_list l;
156                                 txt_set x
157    in 
158    txt_set x; out sep
159
160 let text_of_result out sep x = 
161    let txt_attr = function
162       | (p, []) -> txt_path out p
163       | (p, l)  -> txt_path out p; out " = "; txt_list out (txt_str out) ", " l
164    in
165    let txt_group l = out "{"; txt_list out txt_attr "; " l; out "}" in
166    let txt_res = function
167       | (s, []) -> txt_str out s 
168       | (s, l)  -> txt_str out s; out " attr "; txt_list out txt_group ", " l
169    in   
170    let txt_set l = txt_list out txt_res ("; " ^ sep) l; out sep in
171    txt_set x
172
173 let query_of_text lexbuf =
174    MQueryTParser.query MQueryTLexer.query_token lexbuf 
175
176 let result_of_text lexbuf =
177    MQueryTParser.result MQueryTLexer.result_token lexbuf 
178
179 (* time handling  ***********************************************************)
180
181 type time = float * float 
182
183 let start_time () =
184    (Sys.time (), Unix.time ())
185    
186 let stop_time (s0, u0) =
187    let s1 = Sys.time () in
188    let u1 = Unix.time () in
189    Printf.sprintf "%.2fs,%.2fs" (s1 -. s0) (u1 -. u0)
190
191 (* operations on lists  *****************************************************)
192
193 type 'a comparison = Lt 
194                    | Gt
195                    | Eq of 'a
196
197 let list_join f l1 l2 =
198    let rec aux = function
199       | [], v
200       | v, []                                  -> v 
201       | ((h1 :: t1) as v1), ((h2 :: t2) as v2) -> begin
202          match f h1 h2 with
203             | Lt   -> h1 :: aux (t1, v2)
204             | Gt   -> h2 :: aux (v1, t2)
205             | Eq h -> h  :: aux (t1, t2)
206          end
207    in aux (l1, l2)
208
209 let list_meet f l1 l2 =
210    let rec aux = function
211       | [], v
212       | v, []                                  -> [] 
213       | ((h1 :: t1) as v1), ((h2 :: t2) as v2) -> begin
214          match f h1 h2 with
215             | Lt   -> aux (t1, v2)
216             | Gt   -> aux (v1, t2)
217             | Eq h -> h :: aux (t1, t2)
218          end
219    in aux (l1, l2)
220