(* 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;; 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) ) ^ ")" ;; (* * inizializzazione della connessione al database *) let init () = Dbconn.init ();; (* * esecuzione di una query * * parametri: * q * * output: string list list; risultato internto formato da uri + contesto. *) let rec execute_ex q = match q with MQSelect (apvar, alist, abool) -> select_ex apvar (execute_ex alist) abool | MQUsedBy (alist, asvar) -> use_ex (execute_ex alist) asvar "refObj" | MQUse (alist, asvar) -> use_ex (execute_ex alist) asvar "backPointer" | MQPattern (apreamble, apattern, afragid) -> let _ = print_endline ("*********" ^ (fi_to_string afragid)); flush stdout in pattern_ex apreamble apattern afragid | MQUnion (l1, l2) -> union_ex (execute_ex l1) (execute_ex l2) | MQDiff (l1, l2) -> diff_ex (execute_ex l1) (execute_ex l2) | MQSortedBy (l, o, f) -> sortedby_ex (execute_ex l) o f | MQIntersect (l1, l2) -> intersect_ex (execute_ex l1) (execute_ex l2) ;; (* * 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 = let tmp = List.map List.hd (List.tl l) in MQRefs (List.map (function l -> match Str.split (Str.regexp ":\|#\|/") l with hd::tl -> ( match List.rev tl with ")"::n::"xpointer(1"::tail -> ( hd, List.fold_left (fun par t -> match par with [] -> [MQString t] | _ -> (MQString t) :: MQSlash :: par ) [] tail, (Some (int_of_string n), None) ) | ")"::n::m::"xpointer(1"::tail -> ( hd, List.fold_left (fun par t -> match par with [] -> [MQString t] | _ -> (MQString t) :: MQSlash :: par ) [] tail, (Some (int_of_string m), Some (int_of_string n)) ) | tail -> ( hd, List.fold_left (fun par t -> match par with [] -> [MQString t] | _ -> (MQString t) :: MQSlash :: par ) [] tail, (None, None) ) ) | [] -> 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 ();;