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