]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/utility.ml
Initial revision
[helm.git] / helm / ocaml / mathql_interpreter / utility.ml
1 (* Copyright (C) 2000, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://www.cs.unibo.it/helm/.
24  *)
25
26 (*
27  * funzioni di utilita' generale
28  *)
29
30 open Dbconn;;
31
32 (*
33  * converte il risultato di una query in una lista di stringhe
34  *
35  * parametri:
36  * l: Postgres.result; risultato della query
37  *
38  * output: string list; lista di stringhe (una per tupla)
39  *
40  * assumo che il risultato della query sia
41  * costituito da un solo valore per tupla
42  *
43  * TODO
44  * verificare che l sia effettivamente costruita come richiesto
45  *)
46 let pgresult_to_string_list l = List.map (List.hd) l#get_list;;
47
48 (*
49  * converte il risultato di una query in una stringa
50  *
51  * paramteri:
52  * l: Postgres.result; risultato della query
53  *
54  * output: string; valore dell'unica tupla del risultato
55  *
56  * mi aspetto che il risultato contenga una sola tupla
57  * formata da un solo valore
58  *
59  * TODO
60  * verificare che l sia costruita come richiesto
61  *)
62 let pgresult_to_string l =
63  match l#get_list with
64     [] -> ""
65  |  t  -> List.hd (List.hd t)
66 ;;
67
68 (*
69  * parametri:
70  * x: 'a; chiave di cui settare il valore
71  * v: 'b; valore da assegnare alla chiave
72  * l: ('a * 'b) list; lista di coppie in cui effettuare
73  *    l'assegnamento
74  *
75  * output: ('a * 'b) list; lista di coppie contenente (x, v)
76  *
77  * TODO
78  * gestire i casi in cui in l compaiono piu' coppie (x, _)
79  * si sostituiscono tutte? se ne sostituisce una e si eliminano
80  * le altre?
81  *)
82 let set_assoc x v l =
83  let rec spila testa key value lista =
84   match lista with
85      []                      -> testa @ [(key, value)]
86   |  (j, _)::tl when j = key -> testa @ [(key, value)] @ tl
87   |  hd::tl                  -> spila (testa @ [hd]) key value tl
88  in
89   spila [] x v l
90 ;;
91
92 (*
93  * parametri:
94  * p: string; nome della proprieta'
95  *
96  * output: string; id interno associato alla proprieta'
97  *)
98 let helm_property_id p =
99  let c = pgc () in
100   let q1 = "select att0 from namespace where att1='http://www.cs.unibo.it/helm/schemas/mattone.rdf#'" in
101    let ns = pgresult_to_string (c#exec q1) in
102     let q2 = ("select att0 from property where att2='" ^ p ^ "' and att1=" ^ ns) in
103      let retval = pgresult_to_string (c#exec q2) in
104      (*let _ = print_endline ("utility:q2: "  ^ q2 ^ " : " ^ retval) in*)
105       retval
106 ;;
107
108 (*
109  * parametri:
110  * c: string; nome della classe
111  *
112  * output: string; id interno associato alla classe
113  *)
114 let helm_class_id cl =
115  let c = pgc () in
116   let ns = pgresult_to_string (c#exec ("select att0 from namespace where att1='http://www.cs.unibo.it/helm/schemas/mattone.rdf#'")) in
117    pgresult_to_string (c#exec ("select att0 from class where att2='" ^ cl ^ "' and att1=" ^ ns))
118 ;;
119