]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/property.ml
Initial revision
[helm.git] / helm / ocaml / mathql_interpreter / property.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://cs.unibo.it/helm/.
24  *)
25
26 (*
27  *
28  *)
29
30 open Dbconn;;
31 open Utility;;
32 open Intersect;;
33
34
35 let getpid p =
36   if (p = "refObj") then "F"
37   else "B"
38 ;;
39
40 (*
41  * implementazione delle funzioni dublin core
42  *)
43 let rec property_ex rop path inv = function
44     [] -> []
45   | s::tl -> let mprop = fst path in
46              print_endline mprop;
47              let l_sub_p = snd path in
48                
49              let prop = (if (l_sub_p <> []) then List.hd l_sub_p 
50                         else "") 
51              in 
52              match mprop with
53                
54                "refObj" (* in base al valore di prop restituisco i valori del relativo campo della tabella relativa all'uri rappresentata da s *)
55              | "backPointer" ->
56                print_endline mprop;
57                let mpid = getpid mprop in
58                let res =
59                let c = pgc () in
60                let tv = pgresult_to_string (c#exec ("select distinct id from registry where uri='" ^ s ^ "' order by id")) in
61                let q = "select distinct t" ^ tv ^ "." ^ prop ^  "  from t" ^ tv ^ " where prop_id= '" ^ mpid ^ "' order by t" ^ tv ^ "." ^ prop in
62                 print_endline q;
63                 pgresult_to_string_list (c#exec q)
64                in
65                  append (res,(property_ex rop path inv tl))
66                
67                           (*Rimane da capire cosa restituire  nelle inverse!!!!*)
68                            
69                
70              | "refRel"
71              | "refSort" ->
72              if inv then     (* restituisco gli uri che il valore della prop richiesta uguale a s *)
73                let res =
74                let c = pgc () in
75                let q = ("select distinct h" ^ mprop ^ ".uri from h" ^ mprop ^ " where h" ^ mprop ^ "." ^ prop ^ "= '" ^ s ^ "' order by h" ^ mprop ^ ".uri") in
76                  print_endline q;
77                  pgresult_to_string_list (c#exec q)
78                in
79                  append (res,(property_ex rop path inv tl))
80                
81              else
82                let res =         (* restituisco il valore della prop relativo all'uri rappresentato da s*)
83                let c = pgc () in
84                let q = ("select distinct h" ^ mprop ^ "." ^ prop ^" from h" ^ mprop ^ " where h" ^ mprop ^ ".uri = '" ^ s ^ "' order by h" ^ mprop ^ "." ^ prop) in
85                  pgresult_to_string_list (c#exec q)
86                in
87                  append (res,(property_ex rop path inv tl))
88              
89              
90              | _ ->        (* metadati DC  !!!! Controllare se i nomi delle tabelle cominciano con h !!!!*)
91              print_endline "DC";
92              if inv then
93                let res =
94                let c = pgc () in
95                let q = ("select " ^ mprop ^ ".uri from " ^ mprop ^ " where " ^ mprop ^ ".value = '" ^ s ^ "'") in
96                  print_endline q;
97                  pgresult_to_string_list (c#exec q)
98                in
99                  append (res,(property_ex rop path inv tl))
100              else
101                let res =
102                let c = pgc () in
103                let q = ("select " ^ mprop ^ ".value from " ^ mprop ^ " where " ^ mprop ^ ".uri = '" ^ s ^ "'") in
104                  pgresult_to_string_list (c#exec q)
105                in
106                  append (res,(property_ex rop path inv tl))
107
108 ;;
109