]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/mqint.ml
mathQL and mqint updated
[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 open Mathql_semantics;;
42
43 let prop_pool = ref None;;
44
45 let fi_to_string fi =
46  match fi with
47     (None, _)   ->
48      ""
49  |  (Some i, y) ->
50      "#xpointer(1/"       ^
51      string_of_int i      ^
52      (
53       match y with
54          None   ->
55           ""
56       |  Some j ->
57           "/" ^ (string_of_int j)
58      )                    ^
59      ")"
60 ;;
61
62 let see_prop_pool () =
63  let _ = print_endline "eccomi" in
64  List.iter
65   (fun elem -> print_endline (fst elem ^ ": " ^ snd elem))
66   (match !prop_pool with Some l -> l | _ -> print_endline "ciao"; assert false)
67 ;;
68
69 (*
70  * inizializzazione della connessione al database
71  *)
72 let init () =
73  let _ = Dbconn.init () in
74   let c = pgc () in
75    let res = 
76     c#exec "select name,id from property where ns_id in (select id from namespace where url='http://www.cs.unibo.it/helm/schemas/mattone.rdf#')"
77    in
78     prop_pool := Some
79      (
80       List.map
81        (function
82            a::b::_ -> (a, b)
83          | _       -> print_endline "no"; assert false
84        )
85        res#get_list
86      )
87 ;;
88
89 let get_prop_id prop =
90  if prop="refObj" then "F"
91  else if prop="backPointer" then "B"
92  else List.assoc prop (match !prop_pool with Some l -> l | _ -> assert false)
93 ;;
94
95 (* automatically performes the union of a given list of patterns *)
96 let rec pattern_list_ex = function
97    | [] -> []
98    | [(apreamble, apattern, afragid)] -> pattern_ex (apreamble, apattern, afragid)
99    | (apreamble, apattern, afragid) :: tail -> 
100       union_ex (pattern_ex (apreamble, apattern, afragid)) (pattern_list_ex tail)
101
102 (* execute_ex env q                                                   *)
103 (*  [env] is the attributed uri environment in which the query [q]    *)
104 (*        must be evaluated                                           *)
105 (*  [q]   is the query to evaluate                                    *)
106 (*  It returns a [Mathql_semantics.result]                            *)
107 let rec execute_ex env =
108  function
109     MQSelect (apvar, alist, abool) ->
110      select_ex env apvar (execute_ex env alist) abool
111  |  MQUsedBy (alist, asvar) ->
112      use_ex (execute_ex env alist) asvar (get_prop_id "refObj")      (* "F" (*"refObj"*) *)
113  |  MQUse (alist, asvar) ->
114      use_ex (execute_ex env alist) asvar (get_prop_id "backPointer") (* "B" (*"backPointer"*) *)
115  |  MQPattern l ->
116      pattern_list_ex l
117  |  MQUnion (l1, l2) ->
118      union_ex (execute_ex env l1) (execute_ex env l2)
119  |  MQDiff (l1, l2) ->
120      diff_ex (execute_ex env l1) (execute_ex env l2)
121  |  MQSortedBy (l, o, f) ->
122      sortedby_ex (execute_ex env l) o f
123  |  MQIntersect (l1, l2) ->
124      intersect_ex (execute_ex env l1) (execute_ex env l2)
125  |  MQListRVar rvar -> [List.assoc rvar env]
126  |  MQLetIn (lvar, l1, l2) ->
127      let t = Unix.time () in
128       let res =
129        (*CSC: The interesting code *)
130        let _ = letin_ex lvar (execute_ex env l1) in
131         execute_ex env l2
132        (*CSC: end of the interesting code *)
133       in
134        letdispose ();
135        print_string ("LETIN = " ^ string_of_int (List.length res) ^ ": ") ;
136        print_endline (string_of_float (Unix.time () -. t) ^ "s") ;
137        flush stdout ;
138        res
139  |  MQListLVar lvar ->
140      letref_ex lvar
141  |  MQReference l -> (* FG: *)
142      let rec build_result = function
143        | [] -> []
144        | s :: tail -> 
145          {uri = s ; attributes = [] ; extra = ""} :: build_result tail
146      in build_result l
147  | MQMinimize l ->     (* FG: sostituire con l'implementazione vera *)
148      execute_ex env l 
149 ;;
150
151 (* Let's initialize the execute in Select, creating a cyclical recursion *)
152 Select.execute := execute_ex;;
153
154 (*
155  * converte il risultato interno di una query (uri + contesto)
156  * in un risultato di sole uri
157  *
158  * parametri:
159  * l: string list list;
160  *
161  * output: mqresult;
162  *
163  * note:
164  * il tipo del risultato mantenuto internamente e' diverso dal tipo di risultato
165  * restituito in output poiche', mentre chi effettua le query vuole come risultato
166  * solo le eventuali uri che soddisfano le query stesse, internamente ad una uri
167  * sono associati anche i valori delle variabili che ancora non sono state valutate
168  * perche', ad esempio, si trovano in altri rami dell'albero.
169  *
170  * Esempio:
171  * SELECT x IN USE PATTERN "cic:/**.con" POSITION $a WHERE $a IS MainConclusion
172  * L'albero corrispondente a questa query e':
173  *
174  *                  SELECT
175  *                /   |    \
176  *               x   USE    IS
177  *                  /   \    /\
178  *           PATTERN    $a  $a MainConclusion
179  *
180  * Nel momento in cui si esegue il ramo USE non sono noti i vincoli sullla variabile $a
181  * percui e' necessario considerare, oltre alle uri, i valori della variabile per i quali
182  * la uri puo' far parte del risultato.
183  *)
184 let xres_to_res l =
185  MQRefs (List.map (function {Mathql_semantics.uri = uri} -> uri) l)
186 (*
187  let tmp = List.map (function {Mathql_semantics.uri = uri} -> uri) l in
188   MQRefs
189    (List.map
190     (function l ->
191       (*let _ = print_endline ("DEBUG: (mqint.ml: xres_to_res)" ^ l) in*)
192       match Str.split (Str.regexp ":\|#\|/\|(\|)") l with
193          hd::""::tl -> (
194           match List.rev tl with
195              n::"1"::"xpointer"::tail    ->
196               (
197                Some hd,
198                List.fold_left
199                 (fun par t ->
200                  match par with
201                     [] -> [MQBC t] 
202                  |  _  -> (MQBC t) :: MQBD :: par
203                 )
204                 []
205                 tail, 
206                [MQFC (int_of_string n)]
207               )
208           |  n::m::"1"::"xpointer"::tail ->
209               (
210                Some hd,
211                List.fold_left
212                 (fun par t ->
213                  match par with
214                     [] -> [MQBC t] 
215                  |  _  -> (MQBC t) :: MQBD :: par
216                 )
217                 []
218                 tail,
219                [MQFC (int_of_string m); MQFC (int_of_string n)]
220               )
221           |  tail                          ->
222               (
223                Some hd,
224                List.fold_left
225                 (fun par t ->
226                  match par with
227                     [] -> [MQBC t] 
228                  |  _  -> (MQBC t) :: MQBD :: par
229                 )
230                 []
231                 tail, 
232                []
233               )
234       )  
235        | _ -> assert false
236     )
237     tmp
238    )
239 *)
240 ;;
241
242
243 (*
244  * 
245  *)
246 let execute q =
247  match q with
248     MQList qq -> xres_to_res (execute_ex [] qq)
249 ;;
250
251 (*
252  * chiusura della connessione al database
253  *)
254 let close () = Dbconn.close ();;
255