]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/intersect.ml
7a3f47f341a5b6a72b0b629a7d3bb8cae3d64cc2
[helm.git] / helm / ocaml / mathql_interpreter / intersect.ml
1
2 (*
3  * implementazione del comando INTERSECT
4  *)
5
6 (*
7  * eccezione sollevata quando il join dei contesti
8  * deve essere vuoto
9  *)
10 exception Join_must_be_empty;;
11
12 (*
13  * join fra due contesti
14  *)
15 let xres_join_context h1 l1 h2 l2 =
16  match (l1, l2) with
17     ([], _) -> l2
18  |  (_, []) -> l1
19  |  (_,  _) ->
20      let hh = h2 @ (List.find_all (function t -> not (List.mem t h2)) h1)
21      and m1 = List.combine h1 l1
22      and m2 = List.combine h2 l2
23      in
24       try 
25        (List.map
26         (fun elem ->
27          let value1 = try (List.assoc elem m1) with Not_found -> List.assoc elem m2
28          and value2 = try (List.assoc elem m2) with Not_found -> List.assoc elem m1
29          in
30           if value1 = value2 then value1 else raise Join_must_be_empty
31         )
32         hh
33        ) with
34         Join_must_be_empty -> []
35 ;;
36
37 (*
38  * implementazione del comando INTERSECT
39  *)
40 let intersect_ex alist1 alist2 =
41  let head1 = List.hd alist1
42  and tail1 = List.tl alist1
43  and head2 = List.hd alist2
44  and tail2 = List.tl alist2 (* e fin qui ... *)
45  in
46   match (head1, head2) with
47      ([], _) -> assert false (* gli header non devono mai essere vuoti *)
48   |  (_, []) -> assert false (* devono contenere almeno [retVal] *)
49   |  (_,  _) ->
50       (match (tail1, tail2) with
51           ([], _) -> [["retVal"]] (* se una delle due code e' vuota... *)
52        |  (_, []) -> [["retVal"]] (* ... l'intersezione e' vuota *)
53        |  (_,  _) ->
54            [head2 @
55             (List.find_all
56              (function t -> not (List.mem t head2))
57              head1
58             )
59            ] (* header del risultato finale *)
60            @
61            List.fold_left
62             (fun par1 elem1 -> par1 @
63              List.map
64               (fun elem2 ->
65                [(List.hd elem1)] @
66                (xres_join_context (List.tl head1) (List.tl elem1)
67                                   (List.tl head2) (List.tl elem2))
68               )
69               (List.find_all
70                (fun elem2 -> (* trova tutti gli elementi della lista tail2 *)
71                 ((List.hd elem1) = (List.hd elem2)) && (* che stanno in tail1 *)
72                 not ((xres_join_context (List.tl head1) (List.tl elem1)
73                                         (List.tl head2) (List.tl elem2)) = [])
74                 (* e per i quali la xres_join_context non sia vuota *)
75                )
76                tail2
77               )
78              )
79            []
80            tail1 (* per ogni elemento di tail1 applica la List.fold_left *)
81       ) (* match *)
82 ;;
83
84 (*
85 let h1 = ["retVal"; "a"; "b"];;
86 let l1 = ["pippo";  "3"; "3"];;
87 let l3 = ["pluto"; "7";"8"]
88 let r1 = [h1; l1; l3];;
89
90 let h2 = ["retVal"; "b"; "c"];;
91 let l2 = ["pippo"; "3"; "1"];;
92 let r2 = [h2; l2];;
93
94 List.map (fun l -> List.iter print_endline l) (xres_intersect (r1, r2));;
95 *)