]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/mQueryIO.ml
14199e513136d396f88380fe130346200d430395
[helm.git] / helm / ocaml / mathql_interpreter / mQueryIO.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 M = MathQL
30 module I = M.I
31 module P = MQueryUtil
32 module L = MQILib
33
34 (* text linearization and parsing *******************************************)
35
36 let txt_quote s =
37    let rec aux r i l s = 
38       let commit c =
39          let l = pred (l - i) in
40          aux (r ^ String.sub s 0 i ^ c) 0 l (String.sub s (succ i) l) 
41       in
42       if i = l then r ^ s else
43       match s.[i] with
44          | '\\' -> commit "\\\\^"
45          | '^'  -> commit "\\^^"
46          | '\"' -> commit "\\\"^"
47          | _    -> aux r (succ i) l s
48    in
49    aux "" 0 (String.length s) s
50
51 let txt_str out s = out ("\"" ^ txt_quote s ^ "\"")
52
53 let txt_path out p = out "/"; P.flat_list out (txt_str out) "/" p 
54
55 let text_of_result out sep x =
56    let txt_attr _ p l b = 
57       txt_path out p;
58       if l <> [] then begin 
59          out " = "; P.flat_list out (txt_str out) ", " l
60       end; 
61       if b then out ("; " ^ sep)
62    in
63    let txt_group l = out "{"; I.x_grp_iter txt_attr () l; out "}" in 
64    let txt_res _ s l b = 
65       txt_str out s; 
66       if l <> [] then begin 
67          out " = "; P.flat_list out txt_group ", " l
68       end;
69       if b then out "; "
70    in
71    I.x_iter txt_res () x; out sep
72
73 let rec xtext_of_groups out l = 
74    let txt_attr (p, x) = txt_path out p; out " = "; text_of_query out "" x in
75    let txt_group l = out "{"; P.flat_list out txt_attr "; " l; out "}" in
76    P.flat_list out txt_group ", " l
77
78 and xtext_of_result out x =
79    let txt_res = function
80       | (s, []) -> txt_str out s 
81       | (s, l)  -> txt_str out s; out " attr "; xtext_of_groups out l
82    in   
83    P.flat_list out txt_res "; " x
84
85 and text_of_query out sep x = 
86    let txt_svar sv = out ("$" ^ sv) in 
87    let txt_avar av = out ("@" ^ av) in
88    let txt_inv i = if i then out "inverse " in
89    let txt_ref = function
90       | M.RefineExact -> ()
91       | M.RefineSub   -> out "sub "
92       | M.RefineSuper -> out "super "
93    in
94    let txt_qualif i r p = txt_inv i; txt_ref r; txt_path out p in
95    let main = function
96       | [] -> ()
97       | p  -> out " main "; txt_path out p
98    in
99    let txt_exp = function
100       | (pl, None)    -> txt_path out pl 
101       | (pl, Some pr) -> txt_path out pl; out " as "; txt_path out pr
102    in
103    let txt_exp_list = function
104       | [] -> ()
105       | l  -> out " attr "; P.flat_list out txt_exp ", " l 
106    in
107    let pattern b = if b then out "pattern " in
108    let txt_distr d = if d then out "distr " in
109    let txt_gen = function
110       | M.GenFJoin -> out " sup "
111       | M.GenFMeet -> out " inf "
112    in
113    let rec txt_con (pat, p, x) = 
114       txt_path out p; 
115       if pat then out " match " else out " in ";
116       txt_set x
117    and txt_con_list s = function
118       | [] -> ()
119       | l  -> out s; P.flat_list out txt_con ", " l 
120    and txt_istrue lt = txt_con_list " istrue " lt 
121    and txt_isfalse lf = txt_con_list " isfalse " lf
122    and txt_grp = function
123       | M.Attr g  -> xtext_of_groups out g
124       | M.From av -> txt_avar av
125    and txt_set = function
126       | M.Fun (p, pl, xl)      -> 
127          let o = {L.out = out; L.path = txt_path; 
128                   L.query = text_of_query; L.result = text_of_result
129                  } 
130          in
131          L.fun_txt_out o p pl xl 
132       | M.Const [s, []]       -> txt_str out s
133       | M.Const r             -> xtext_of_result out r
134       | M.Dot (av, p)         -> txt_avar av; out "."; txt_path out p
135       | M.Ex (b, x)           -> out "ex "; txt_set x
136 (*    | M.Ex b x              -> out "ex ["; P.flat_list out txt_avar "," b; 
137                                  out "] "; txt_set x
138 *)    | M.SVar sv             -> txt_svar sv
139       | M.AVar av             -> txt_avar av
140       | M.Property (q0, q1, q2, mc, ct, cfl, xl, b, x) -> 
141          out "property "; txt_qualif q0 q1 q2; main mc;
142          txt_istrue ct; P.flat_list out txt_isfalse "" cfl; txt_exp_list xl;
143          out " of "; pattern b; txt_set x
144       | M.Let (Some sv, x, y) -> out "let "; txt_svar sv; out " = "; 
145                                  txt_set x; out " in "; txt_set y
146       | M.Let (None, x, y)    -> txt_set x; out " ;; "; txt_set y
147       | M.Select (av, x, y)   -> out "select "; txt_avar av; out " from ";
148                                  txt_set x; out " where "; txt_set y
149       | M.For (k, av, x, y)   -> out "for "; txt_avar av; out " in ";
150                                  txt_set x; txt_gen k; txt_set y
151       | M.While (k, x, y)     -> out "while "; txt_set x; txt_gen k; txt_set y
152       | M.Add (d, g, x)       -> out "add "; txt_distr d; txt_grp g; 
153                                  out " in "; txt_set x
154       | M.Gen (p, [x])        -> out "gen "; txt_path out p; out " in "; txt_set x
155       | M.Gen (p, l)          -> out "gen "; txt_path out p; out " {";
156                                  P.flat_list out txt_set ", " l; out "}"
157    in 
158    txt_set x; out sep
159
160 let text_out_spec out sep =
161    {L.out = out; L.path = txt_path; 
162     L.query = text_of_query; L.result = text_of_result
163    }
164
165 let query_of_text lexbuf =
166    MQueryTParser.query MQueryTLexer.query_token lexbuf 
167
168 let result_of_text lexbuf =
169    MQueryTParser.result MQueryTLexer.result_token lexbuf 
170
171 let text_in_spec = {L.result_in = result_of_text}