(* Copyright (C) 2004, 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://helm.cs.unibo.it/ *) open MetadataTypes open Printf let prepare_insert () = (* let insert_owner a b = sprintf "INSERT %s VALUES (\"%s\", \"%s\")" (owners_tbl ())a b in *) let insert_sort a b c d = sprintf "INSERT %s VALUES (\"%s\", \"%s\", %d, \"%s\")" (sort_tbl ())a b c d in let insert_rel a b c = sprintf "INSERT %s VALUES (\"%s\", \"%s\", %d)" (rel_tbl ()) a b c in let insert_obj a b c d = sprintf "INSERT %s VALUES (\"%s\", \"%s\", \"%s\", %s)" (obj_tbl ()) a b c d in ((*insert_owner, *)insert_sort, insert_rel, insert_obj) let execute_insert dbd ((*insert_owner, *)insert_sort, insert_rel, insert_obj) uri (sort_cols, rel_cols, obj_cols) = (* ignore (Mysql.exec dbd (insert_owner uri owner)); *) List.iter (function | [`String a; `String b; `Int c; `String d] -> ignore (Mysql.exec dbd (insert_sort a b c d)) | _ -> assert false) sort_cols; List.iter (function | [`String a; `String b; `Int c] -> ignore (Mysql.exec dbd (insert_rel a b c)) | _ -> assert false) rel_cols; List.iter (function | [`String a; `String b; `String c; `Int d] -> ignore (Mysql.exec dbd (insert_obj a b c (string_of_int d))) | [`String a; `String b; `String c; `Null] -> ignore (Mysql.exec dbd (insert_obj a b c "NULL")) | _ -> assert false) obj_cols let insert_const_no dbd uri = let inconcl_no = sprintf "INSERT %s SELECT \"%s\", COUNT(DISTINCT h_occurrence) FROM %s WHERE (h_position=\"%s\" OR h_position=\"%s\") AND source LIKE \"%s%%\"" (conclno_tbl ()) uri (obj_tbl ()) inconcl_pos mainconcl_pos uri in let concl_hyp = sprintf "INSERT %s SELECT \"%s\",COUNT(DISTINCT h_occurrence) FROM %s WHERE NOT (h_position=\"%s\") AND (source = \"%s\")" (conclno_hyp_tbl ()) uri (obj_tbl ()) inbody_pos uri in ignore (Mysql.exec dbd inconcl_no); ignore (Mysql.exec dbd concl_hyp) let insert_name ~dbd ~uri ~name = let query = sprintf "INSERT %s VALUES (\"%s\", \"%s\")" (name_tbl ()) uri name in ignore (Mysql.exec dbd query) type columns = MetadataPp.t list list * MetadataPp.t list list * MetadataPp.t list list (* TODO ZACK: verify if an object has already been indexed *) let already_indexed _ = false let index_constant ~dbd = let query = prepare_insert () in fun ~uri ~body ~ty -> if not (already_indexed uri) then begin let name = UriManager.name_of_uri uri in let uri = UriManager.string_of_uri uri in let metadata = MetadataExtractor.compute ~body ~ty in let columns = MetadataPp.columns_of_metadata ~about:uri metadata in execute_insert dbd query uri (columns :> columns); insert_const_no dbd uri; insert_name ~dbd ~uri ~name end let index_inductive_def ~dbd = let query = prepare_insert () in fun ~uri ~types -> if not (already_indexed uri) then begin let metadata = MetadataExtractor.compute_ind ~uri ~types in let uri_of (a,b,c) = a in let uris = UriManager.string_of_uri uri :: List.map uri_of metadata in let uri = UriManager.string_of_uri uri in let columns = MetadataPp.columns_of_ind_metadata metadata in execute_insert dbd query uri (columns :> columns); List.iter (insert_const_no dbd) uris; List.iter (fun (uri, name, _) -> insert_name ~dbd ~uri ~name) metadata end let clean ~(dbd:Mysql.dbd) = let owned_uris = (* list of uris in list-of-columns format *) let query = sprintf "SELECT source FROM %s" (obj_tbl ()) in let result = Mysql.exec dbd query in let uris = Mysql.map result (fun cols -> match cols.(0) with | Some src -> src | None -> assert false) in (* and now some stuff to remove #xpointers and duplicates *) uris in let del_from tbl = let query s = sprintf "DELETE FROM %s WHERE source LIKE \"%s%%\"" (tbl ()) s in List.iter (fun source_col -> ignore (Mysql.exec dbd (query source_col))) owned_uris in List.iter del_from [sort_tbl; rel_tbl; obj_tbl; conclno_tbl; conclno_hyp_tbl; name_tbl]; owned_uris