]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/mqint.ml
56fa38ad928d0b9017ac58f0ebaad8b26d57f9f4
[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 (*
64  * esecuzione di una query
65  *
66  * parametri:
67  * q
68  *
69  * output: string list list; risultato internto formato da uri + contesto.
70  *)
71 let rec execute_ex q =
72    match q with
73       MQSelect (apvar, alist, abool) ->
74        select_ex apvar (execute_ex alist) abool
75    |  MQUsedBy (alist, asvar) ->
76        use_ex (execute_ex alist) asvar "refObj"
77    |  MQUse (alist, asvar) ->
78        use_ex (execute_ex alist) asvar "backPointer"
79    |  MQPattern (apreamble, apattern, afragid) ->
80        let _ = print_endline ("*********" ^ (fi_to_string afragid)); flush stdout in
81        pattern_ex apreamble apattern afragid
82    |  MQUnion (l1, l2) ->
83        union_ex (execute_ex l1) (execute_ex l2)
84    |  MQDiff (l1, l2) ->
85        diff_ex (execute_ex l1) (execute_ex l2)
86    |  MQSortedBy (l, o, f) ->
87        sortedby_ex (execute_ex l) o f
88    |  MQIntersect (l1, l2) ->
89        intersect_ex (execute_ex l1) (execute_ex l2)
90 ;;
91
92 (*
93  * converte il risultato interno di una query (uri + contesto)
94  * in un risultato di sole uri
95  *
96  * parametri:
97  * l: string list list;
98  *
99  * output: mqresult;
100  *
101  * note:
102  * il tipo del risultato mantenuto internamente e' diverso dal tipo di risultato
103  * restituito in output poiche', mentre chi effettua le query vuole come risultato
104  * solo le eventuali uri che soddisfano le query stesse, internamente ad una uri
105  * sono associati anche i valori delle variabili che ancora non sono state valutate
106  * perche', ad esempio, si trovano in altri rami dell'albero.
107  *
108  * Esempio:
109  * SELECT x IN USE PATTERN "cic:/**.con" POSITION $a WHERE $a IS MainConclusion
110  * L'albero corrispondente a questa query e':
111  *
112  *                  SELECT
113  *                /   |    \
114  *               x   USE    IS
115  *                  /   \    /\
116  *           PATTERN    $a  $a MainConclusion
117  *
118  * Nel momento in cui si esegue il ramo USE non sono noti i vincoli sullla variabile $a
119  * percui e' necessario considerare, oltre alle uri, i valori della variabile per i quali
120  * la uri puo' far parte del risultato.
121  *)
122 let xres_to_res l =
123  let tmp = List.map List.hd (List.tl l) in
124   MQRefs
125    (List.map
126     (function l ->
127       match Str.split (Str.regexp ":\|#\|/") l with
128          hd::tl -> (
129           match List.rev tl with
130              ")"::n::"xpointer(1"::tail    ->
131               (
132                hd,
133                List.fold_left
134                 (fun par t ->
135                  match par with
136                     [] -> [MQString t] 
137                  |  _  -> (MQString t) :: MQSlash :: par
138                 )
139                 []
140                 tail, 
141                (Some (int_of_string n), None)
142               )
143           |  ")"::n::m::"xpointer(1"::tail ->
144               (
145                hd,
146                List.fold_left
147                 (fun par t ->
148                  match par with
149                     [] -> [MQString t] 
150                  |  _  -> (MQString t) :: MQSlash :: par
151                 )
152                 []
153                 tail,
154                (Some (int_of_string m), Some (int_of_string n))
155               )
156           |  tail                          ->
157               (
158                hd,
159                List.fold_left
160                 (fun par t ->
161                  match par with
162                     [] -> [MQString t] 
163                  |  _  -> (MQString t) :: MQSlash :: par
164                 )
165                 []
166                 tail, 
167                (None, None)
168               )
169       )  
170       |  [] -> assert false
171     )
172     tmp
173    )
174 ;;
175
176
177 (*
178  * 
179  *)
180 let execute q =
181  match q with
182     MQList qq -> xres_to_res (execute_ex qq)
183 ;;
184
185 (*
186  * chiusura della connessione al database
187  *)
188 let close () = Dbconn.close ();;
189