(* Copyright (C) 2000, HELM Team. * * This file is part of HELM, an Hypertextual, Electronic * Library of Mathematics, developed at the Computer Science * Department, University of Bologna, Italy. * * HELM is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * HELM is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with HELM; if not, write to the Free Software * Foundation, Inc., 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * * For details, see the HELM World-Wide-Web page, * http://cs.unibo.it/helm/. *) (* * implementazione del'interprete MathQL *) open MathQL;; open Eval;; open Utility;; open Dbconn;; open Pattern;; open Union;; open Intersect;; open Diff;; open Sortedby;; open Use;; open Select;; open Letin;; open Mathql_semantics;; let prop_pool = ref None;; let fi_to_string fi = match fi with (None, _) -> "" | (Some i, y) -> "#xpointer(1/" ^ string_of_int i ^ ( match y with None -> "" | Some j -> "/" ^ (string_of_int j) ) ^ ")" ;; let see_prop_pool () = let _ = print_endline "eccomi" in List.iter (fun elem -> print_endline (fst elem ^ ": " ^ snd elem)) (match !prop_pool with Some l -> l | _ -> print_endline "ciao"; assert false) ;; (* * inizializzazione della connessione al database *) let init () = let _ = Dbconn.init () in let c = pgc () in let res = 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#')" in prop_pool := Some ( List.map (function a::b::_ -> (a, b) | _ -> print_endline "no"; assert false ) res#get_list ) ;; let get_prop_id prop = if prop="refObj" then "F" else if prop="backPointer" then "B" else List.assoc prop (match !prop_pool with Some l -> l | _ -> assert false) ;; (* execute_ex env q *) (* [env] is the attributed uri environment in which the query [q] *) (* must be evaluated *) (* [q] is the query to evaluate *) (* It returns a [Mathql_semantics.result] *) let rec execute_ex env = function MQSelect (apvar, alist, abool) -> select_ex env apvar (execute_ex env alist) abool | MQUsedBy (alist, asvar) -> use_ex (execute_ex env alist) asvar (get_prop_id "refObj") (* "F" (*"refObj"*) *) | MQUse (alist, asvar) -> use_ex (execute_ex env alist) asvar (get_prop_id "backPointer") (* "B" (*"backPointer"*) *) | MQPattern (apreamble, apattern, afragid) -> pattern_ex (apreamble, apattern, afragid) | MQUnion (l1, l2) -> union_ex (execute_ex env l1) (execute_ex env l2) | MQDiff (l1, l2) -> diff_ex (execute_ex env l1) (execute_ex env l2) | MQSortedBy (l, o, f) -> sortedby_ex (execute_ex env l) o f | MQIntersect (l1, l2) -> intersect_ex (execute_ex env l1) (execute_ex env l2) | MQListRVar rvar -> [List.assoc rvar env] | MQLetIn (lvar, l1, l2) -> let t = Unix.time () in let res = (*CSC: The interesting code *) let _ = letin_ex lvar (execute_ex env l1) in execute_ex env l2 (*CSC: end of the interesting code *) in letdispose (); print_string ("LETIN = " ^ string_of_int (List.length res) ^ ": ") ; print_endline (string_of_float (Unix.time () -. t) ^ "s") ; flush stdout ; res | MQListLVar lvar -> letref_ex lvar | MQReference l -> let rec build_result = function | [] -> [] | s :: tail -> {uri = s ; attributes = [] ; extra = ""} :: build_result tail in build_result (List.sort compare l) ;; (* Let's initialize the execute in Select, creating a cyclical recursion *) Select.execute := execute_ex;; (* * converte il risultato interno di una query (uri + contesto) * in un risultato di sole uri * * parametri: * l: string list list; * * output: mqresult; * * note: * il tipo del risultato mantenuto internamente e' diverso dal tipo di risultato * restituito in output poiche', mentre chi effettua le query vuole come risultato * solo le eventuali uri che soddisfano le query stesse, internamente ad una uri * sono associati anche i valori delle variabili che ancora non sono state valutate * perche', ad esempio, si trovano in altri rami dell'albero. * * Esempio: * SELECT x IN USE PATTERN "cic:/**.con" POSITION $a WHERE $a IS MainConclusion * L'albero corrispondente a questa query e': * * SELECT * / | \ * x USE IS * / \ /\ * PATTERN $a $a MainConclusion * * Nel momento in cui si esegue il ramo USE non sono noti i vincoli sullla variabile $a * percui e' necessario considerare, oltre alle uri, i valori della variabile per i quali * la uri puo' far parte del risultato. *) let xres_to_res l = MQRefs (List.map (function {Mathql_semantics.uri = uri} -> uri) l) (* let tmp = List.map (function {Mathql_semantics.uri = uri} -> uri) l in MQRefs (List.map (function l -> (*let _ = print_endline ("DEBUG: (mqint.ml: xres_to_res)" ^ l) in*) match Str.split (Str.regexp ":\|#\|/\|(\|)") l with hd::""::tl -> ( match List.rev tl with n::"1"::"xpointer"::tail -> ( Some hd, List.fold_left (fun par t -> match par with [] -> [MQBC t] | _ -> (MQBC t) :: MQBD :: par ) [] tail, [MQFC (int_of_string n)] ) | n::m::"1"::"xpointer"::tail -> ( Some hd, List.fold_left (fun par t -> match par with [] -> [MQBC t] | _ -> (MQBC t) :: MQBD :: par ) [] tail, [MQFC (int_of_string m); MQFC (int_of_string n)] ) | tail -> ( Some hd, List.fold_left (fun par t -> match par with [] -> [MQBC t] | _ -> (MQBC t) :: MQBD :: par ) [] tail, [] ) ) | _ -> assert false ) tmp ) *) ;; (* * *) let execute q = match q with MQList qq -> xres_to_res (execute_ex [] qq) ;; (* * chiusura della connessione al database *) let close () = Dbconn.close ();;