(* 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/. *) (* AUTOR: Ferruccio Guidi *) module U = MQueryUtil type pg_map = (MathQL.path * (bool * string * string option)) list type pg_tables = (bool * string) list type pg_alias = (string * string) list let empty_map () = [], [] let read_map () = let map = Helm_registry.get "mathql_interpreter.db_map" in let ich = open_in map in let rec aux r s = let d = input_line ich in match Str.split (Str.regexp "[ \t]+") d with | [] -> aux r s | "#" :: _ -> aux r s | t :: "<-" :: p -> aux ((p, (false, t, None)) :: r) s | t :: c :: "<-" :: p -> aux ((p, (false, t, Some c)) :: r) s | t :: "<+" :: p -> aux ((p, (true, t, None)) :: r) s | t :: c :: "<+" :: p -> aux ((p, (true, t, Some c)) :: r) s | [a; "->"; t] -> aux r ((a, t) :: s) | ["->"] -> r, s | _ -> raise (Failure "MQIMap.read_map") in let pgm, pga = aux [] [] in close_in ich; pgm, pga let comp c1 c2 = match c1, c2 with | (_, t1), (_, t2) when t1 < t2 -> U.Lt | (_, t1), (_, t2) when t1 > t2 -> U.Gt | (b1, t), (b2, _) -> U.Eq (b1 || b2, t) let get_tables pgm p = let aux l = function | q, (b, t, _) when q = p -> U.list_join comp l [(b, t)] | _, _ -> l in List.fold_left aux [] pgm let rec refine_tables l1 l2 = U.list_meet comp l1 l2 let default_table = function | [(_, a)] -> a | l -> try List.assoc true l with Not_found -> raise (Failure "MQIMap.default_table") let get_field pgm p t = let aux = function | q, (_, u, _) when q = p && u = t -> true | _ -> false in match List.filter aux pgm with | [_, (_, _, None)] -> "" | [_, (_, _, Some c)] -> c | _ -> raise (Failure "MQIMap.get_field") let resolve pga a = try List.assoc a pga with Not_found -> a