]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/union.ml
5573c192ed74d77d3dcaaec436c84f4d23e00090
[helm.git] / helm / ocaml / mathql_interpreter / union.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  * implementazione del comando UNION
28  *)
29
30 (*
31  * 
32  *)
33 let xres_fill_context hr h1 l1 =
34  match l1 with
35     [] -> []
36  |   _ ->
37      let hh = List.combine h1 l1
38      in
39       List.map
40        (fun x ->
41         if (List.mem_assoc x hh) then
42          List.assoc x hh
43         else
44          ""
45        )
46        hr
47 ;;
48
49 (*
50  * implementazione del comando UNION
51  *)
52 let union_ex alist1 alist2 =
53  let head1 = List.hd alist1
54  and tail1 = List.tl alist1
55  and head2 = List.hd alist2
56  and tail2 = List.tl alist2 (* e fin qui ... *)
57  in
58   match (head1, head2) with
59      ([], _) -> assert false (* gli header non devono mai essere vuoti *)
60   |  (_, []) -> assert false (* devono contenere almeno [retVal] *)
61   |  (_,  _) -> let headr = (head2 @
62                             (List.find_all
63                              (function t -> not (List.mem t head2))
64                              head1)
65                             ) in (* header del risultato finale *)
66       List.append (* il risultato finale e' la concatenazione ...*)
67        [headr]             (* ... dell'header costruito prima ...*)
68        (Sort.list
69         (fun l m -> List.hd l < List.hd m)
70         (match (tail1, tail2) with      (* e di una coda "unione" *)
71             ([], _) -> tail2 (* va bene perche' l'altra lista e' vuota *)
72          |  (_, []) -> tail1 (* va bene perche' l'altra lista e' vuota *)
73          |  (_,  _) ->
74              let first = (* parte dell'unione che riguarda solo il primo set *)
75               List.map
76                (
77                 fun l ->
78                  [List.hd l] @
79                  xres_fill_context (List.tl headr) (List.tl head1) (List.tl l)
80                )
81                tail1
82              in
83               List.fold_left
84                (fun par x ->
85                 let y = (* elemento candidato ad entrare *)
86                  [List.hd x]
87                  @
88                  xres_fill_context
89                   (List.tl headr) (List.tl head2) (List.tl x)
90                 in
91                  par @ if (List.find_all (fun t -> t = y) par) = [] then
92                         [y]
93                        else
94                         []
95                )
96                first (* List.fold_left *)
97                tail2 (* List.fold_left *)
98 (*           first @
99              List.map (fun l -> [List.hd l] @
100                        xres_fill_context
101                         (List.tl headr) (List.tl head2) (List.tl l)
102                       ) tail2
103 *)
104         ) (* match *)
105        )
106 ;;
107