]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/use.ml
First very-very-very-very-alfa release of a MathQL Interpreter implemented
[helm.git] / helm / ocaml / mathql_interpreter / use.ml
1
2 (*
3  * implementazione dei comandi USE/USED BY
4  *)
5
6 open Utility;;
7 open Dbconn;;
8
9 (*
10  * implementazione dei comandi USE/USED BY
11  *
12  * parametri:
13  * alist: string list list; lista su cui eseguire il comando USE/USED BY
14  * asvar: string; nome della variabile del comando use
15  * usek: string; nome della tabella in cui ricercare le occorrenze;
16  *               la distinzione fra l'esecuzione del comando USE e USED BY
17  *               sta nell'utilizzo della tabella 'backPointer' per USE
18  *               e 'refObj' per USED BY
19  *
20  * output: string list list; lista su cui e' stato eseguito il 
21  *                           comando USE/USED BY
22  *
23  * TODO
24  * USE e USED BY sono identici dal punto di vista algoritmico, per questo
25  * sono stati accorpati in una sola funzione; stilisticamente, sarebbe meglio
26  * avere due implementazioni distinte...
27  *)
28 let use_ex alist asvar usek =
29  let c = pgc () in
30   List.fold_left
31    (fun parziale xres ->
32     let r1 = pgresult_to_string (c#exec
33      ("select att0 from property where att2='" ^ usek ^ "'"))
34     and r2 = pgresult_to_string (c#exec
35      "select att0 from property where att2='position'")
36     and r3 = pgresult_to_string (c#exec
37      "select att0 from property where att2='occurrence'")
38     in
39      let res = c#exec (
40       "select distinct t" ^ r3 ^ ".att1, t" ^ r2 ^ ".att1 " ^
41       "from t" ^ r3 ^ ", t" ^ r2 ^ ", t" ^ r1 ^ " " ^
42       "where " ^ "t" ^ r1 ^ ".att0 = '" ^ (List.hd xres) ^ "' and t" ^ r1 ^
43       ".att1 = t" ^ r2 ^ ".att0 and t" ^ r1 ^ ".att1 = t" ^ r3 ^
44       ".att0")
45      in
46       parziale
47       @
48       if not (List.mem asvar (List.tl (List.hd alist))) then
49        List.map
50         (fun l -> [List.hd l] @ List.tl xres @ List.tl l)
51         res#get_list
52       else
53        List.map
54         (fun l ->
55          let t =
56           match xres with
57              hd::tl -> (List.hd l)::tl
58           |  [] -> []
59          in
60           List.map
61            snd
62            (Utility.set_assoc
63             asvar
64             (List.hd (List.tl l))
65             (List.combine (List.hd alist) t)
66            )
67         )
68         (List.find_all
69          (fun l ->
70           let currv =
71            List.hd (List.tl l)
72           and xresv =
73            try (
74             List.assoc
75              asvar
76              (List.combine
77               (List.tl (List.hd alist))
78               (List.tl xres)
79              )
80            ) with
81             Not_found -> ""
82           in
83            xresv = "" or xresv = currv
84          )
85          res#get_list
86         )
87    )
88    [ (List.hd alist)
89      @
90      if not (List.mem asvar (List.tl (List.hd alist))) then
91       [asvar]
92      else
93       []
94    ]
95    (List.tl alist)
96 ;;
97
98 (** TEST **)
99
100 (*
101 let use_ex alist asvar = 
102  if (List.find_all asvar (List.tl (List.hd alist))) = [] then
103   use_ex_nc alist asvar
104  else
105   use_ex_co alist asvar
106 ;;
107
108 List.map
109  (fun l -> 
110   let t =
111    match xres with
112       hd::tl -> (List.hd l)::tl
113    |  [] -> []
114   in
115    let hash = List.combine (List.hd alist) t in
116     snd (set_assoc asvar (snd l) hash)
117  )
118  (List.find_all
119   (fun l ->
120    let currv =
121     List.hd (List.tl l)
122    and xresv =
123     try (
124      List.assoc asvar (List.combine (List.tl (List.hd alist)) (List.tl xres))
125     ) with
126      Not_found -> ""
127    in
128     xresv = "" or xresv = currv
129   )
130   res#get_list
131  )
132 ;;
133 *)