]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/utility.ml
sortedby implemented and new uri result format
[helm.git] / helm / ocaml / mathql_interpreter / utility.ml
index 38856a0e1fb2e7ec5d284089f41a524b6f3e935a..e3776cfbd1ff5e4ff5090016b41e0a4dcf449096 100644 (file)
@@ -1,8 +1,34 @@
+(* 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/.
+ *)
 
 (*
  * funzioni di utilita' generale
  *)
 
+open Dbconn;;
+
 (*
  * converte il risultato di una query in una lista di stringhe
  *
@@ -33,7 +59,11 @@ let pgresult_to_string_list l = List.map (List.hd) l#get_list;;
  * TODO
  * verificare che l sia costruita come richiesto
  *)
-let pgresult_to_string l = List.hd (List.hd l#get_list);;
+let pgresult_to_string l =
+ match l#get_list with
+    [] -> ""
+ |  t  -> List.hd (List.hd t)
+;;
 
 (*
  * parametri:
@@ -59,12 +89,31 @@ let set_assoc x v l =
   spila [] x v l
 ;;
 
-(** TEST **)
+(*
+ * parametri:
+ * p: string; nome della proprieta'
+ *
+ * output: string; id interno associato alla proprieta'
+ *)
+let helm_property_id p =
+ let c = pgc () in
+  let q1 = "select att0 from namespace where att1='http://www.cs.unibo.it/helm/schemas/mattone.rdf#'" in
+   let ns = pgresult_to_string (c#exec q1) in
+    let q2 = ("select att0 from property where att2='" ^ p ^ "' and att1=" ^ ns) in
+     let retval = pgresult_to_string (c#exec q2) in
+     (*let _ = print_endline ("utility:q2: "  ^ q2 ^ " : " ^ retval) in*)
+      retval
+;;
 
 (*
-let h = ["d";"b"];;
-let v = ["1";"2"];;
-let c = List.combine h v;;
+ * parametri:
+ * c: string; nome della classe
+ *
+ * output: string; id interno associato alla classe
+ *)
+let helm_class_id cl =
+ let c = pgc () in
+  let ns = pgresult_to_string (c#exec ("select att0 from namespace where att1='http://www.cs.unibo.it/helm/schemas/mattone.rdf#'")) in
+   pgresult_to_string (c#exec ("select att0 from class where att2='" ^ cl ^ "' and att1=" ^ ns))
+;;
 
-List.iter (fun (a,b) -> print_endline (a ^ ": " ^ b)) (set_assoc "a" "3" c);;
-*)