]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/mqint.ml
new MathQL syntax
[helm.git] / helm / ocaml / mathql_interpreter / mqint.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 (*
27  * implementazione del'interprete MathQL
28  *)
29 open MathQL;;
30 open Eval;;
31 open Utility;;
32 open Dbconn;;
33 open Pattern;;
34 open Union;;
35 open Intersect;;
36 open Diff;;
37 open Sortedby;;
38 open Use;;
39 open Select;;
40
41 let fi_to_string fi =
42  match fi with
43     (None, _)   ->
44      ""
45  |  (Some i, y) ->
46      "#xpointer(1/"       ^
47      string_of_int i      ^
48      (
49       match y with
50          None   ->
51           ""
52       |  Some j ->
53           "/" ^ (string_of_int j)
54      )                    ^
55      ")"
56 ;;
57
58 (*
59  * inizializzazione della connessione al database
60  *)
61 let init () = Dbconn.init ();;
62
63 (* execute_ex env q                                                   *)
64 (*  [env] is the attributed uri environment in which the query [q]    *)
65 (*        must be evaluated                                           *)
66 (*  [q]   is the query to evaluate                                    *)
67 (*  It returns a [Mathql_semantics.result]                            *)
68 let rec execute_ex env =
69  function
70     MQSelect (apvar, alist, abool) ->
71      select_ex env apvar (execute_ex env alist) abool
72  |  MQUsedBy (alist, asvar) ->
73      use_ex (execute_ex env alist) asvar "F" (*"refObj"*)
74  |  MQUse (alist, asvar) ->
75      use_ex (execute_ex env alist) asvar "B" (*"backPointer"*)
76  |  MQPattern (apreamble, apattern, afragid) ->
77      pattern_ex (apreamble, apattern, afragid)
78  |  MQUnion (l1, l2) ->
79      union_ex (execute_ex env l1) (execute_ex env l2)
80 (*
81  |  MQDiff (l1, l2) ->
82      diff_ex (execute_ex env l1) (execute_ex env l2)
83  |  MQSortedBy (l, o, f) ->
84      sortedby_ex (execute_ex env l) o f
85 *)
86  |  MQIntersect (l1, l2) ->
87      intersect_ex (execute_ex env l1) (execute_ex env l2)
88  |  MQRVarOccur rvar -> [List.assoc rvar env]
89 ;;
90
91 (* Let's initialize the execute in Select, creating a cyclical recursion *)
92 Select.execute := execute_ex;;
93
94 (*
95  * converte il risultato interno di una query (uri + contesto)
96  * in un risultato di sole uri
97  *
98  * parametri:
99  * l: string list list;
100  *
101  * output: mqresult;
102  *
103  * note:
104  * il tipo del risultato mantenuto internamente e' diverso dal tipo di risultato
105  * restituito in output poiche', mentre chi effettua le query vuole come risultato
106  * solo le eventuali uri che soddisfano le query stesse, internamente ad una uri
107  * sono associati anche i valori delle variabili che ancora non sono state valutate
108  * perche', ad esempio, si trovano in altri rami dell'albero.
109  *
110  * Esempio:
111  * SELECT x IN USE PATTERN "cic:/**.con" POSITION $a WHERE $a IS MainConclusion
112  * L'albero corrispondente a questa query e':
113  *
114  *                  SELECT
115  *                /   |    \
116  *               x   USE    IS
117  *                  /   \    /\
118  *           PATTERN    $a  $a MainConclusion
119  *
120  * Nel momento in cui si esegue il ramo USE non sono noti i vincoli sullla variabile $a
121  * percui e' necessario considerare, oltre alle uri, i valori della variabile per i quali
122  * la uri puo' far parte del risultato.
123  *)
124 let xres_to_res l =
125  MQRefs (List.map (function {Mathql_semantics.uri = uri} -> uri) l)
126 (*
127  let tmp = List.map (function {Mathql_semantics.uri = uri} -> uri) l in
128   MQRefs
129    (List.map
130     (function l ->
131       match Str.split (Str.regexp ":\|#\|/") l with
132          hd::tl -> (
133           match List.rev tl with
134              ")"::n::"xpointer(1"::tail    ->
135               (
136                Some hd,
137                List.fold_left
138                 (fun par t ->
139                  match par with
140                     [] -> [MQBC t] 
141                  |  _  -> (MQBC t) :: MQBD :: par
142                 )
143                 []
144                 tail, 
145                [MQFC (int_of_string n)]
146               )
147           |  ")"::n::m::"xpointer(1"::tail ->
148               (
149                Some hd,
150                List.fold_left
151                 (fun par t ->
152                  match par with
153                     [] -> [MQBC t] 
154                  |  _  -> (MQBC t) :: MQBD :: par
155                 )
156                 []
157                 tail,
158                [MQFC (int_of_string m); MQFC (int_of_string n)]
159               )
160           |  tail                          ->
161               (
162                Some hd,
163                List.fold_left
164                 (fun par t ->
165                  match par with
166                     [] -> [MQBC t] 
167                  |  _  -> (MQBC t) :: MQBD :: par
168                 )
169                 []
170                 tail, 
171                []
172               )
173       )  
174       |  [] -> assert false
175     )
176     tmp
177    )
178 *)
179 ;;
180
181
182 (*
183  * 
184  *)
185 let execute q =
186  match q with
187     MQList qq -> xres_to_res (execute_ex [] qq)
188 ;;
189
190 (*
191  * chiusura della connessione al database
192  *)
193 let close () = Dbconn.close ();;
194