]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/mathql_interpreter/union.ml
* New operators (Subset, SetEqual and RVarOccurrence) added to MathQL
[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  *)
34 let xres_fill_context hr h1 l1 =
35  match l1 with
36     [] -> []
37  |   _ ->
38      let hh = List.combine h1 l1
39      in
40       List.map
41        (fun x ->
42         if (List.mem_assoc x hh) then
43          List.assoc x hh
44         else
45          ""
46        )
47        hr
48 ;;
49
50 (*
51  * implementazione del comando UNION
52  *)
53 let union_ex alist1 alist2 =
54  let head1 = List.hd alist1
55  and tail1 = List.tl alist1
56  and head2 = List.hd alist2
57  and tail2 = List.tl alist2 (* e fin qui ... *)
58  in
59   match (head1, head2) with
60      ([], _) -> assert false (* gli header non devono mai essere vuoti *)
61   |  (_, []) -> assert false (* devono contenere almeno [retVal] *)
62   |  (_,  _) -> let headr = (head2 @
63                             (List.find_all
64                              (function t -> not (List.mem t head2))
65                              head1)
66                             ) in (* header del risultato finale *)
67       List.append (* il risultato finale e' la concatenazione ...*)
68        [headr]             (* ... dell'header costruito prima ...*)
69        (Sort.list
70         (fun l m -> List.hd l < List.hd m)
71         (match (tail1, tail2) with      (* e di una coda "unione" *)
72             ([], _) -> tail2 (* va bene perche' l'altra lista e' vuota *)
73          |  (_, []) -> tail1 (* va bene perche' l'altra lista e' vuota *)
74          |  (_,  _) ->
75              let first = (* parte dell'unione che riguarda solo il primo set *)
76               List.map
77                (
78                 fun l ->
79                  [List.hd l] @
80                  xres_fill_context (List.tl headr) (List.tl head1) (List.tl l)
81                )
82                tail1
83              in
84               List.fold_left
85                (fun par x ->
86                 let y = (* elemento candidato ad entrare *)
87                  [List.hd x]
88                  @
89                  xres_fill_context
90                   (List.tl headr) (List.tl head2) (List.tl x)
91                 in
92                  par @ if (List.find_all (fun t -> t = y) par) = [] then
93                         [y]
94                        else
95                         []
96                )
97                first (* List.fold_left *)
98                tail2 (* List.fold_left *)
99 (*           first @
100              List.map (fun l -> [List.hd l] @
101                        xres_fill_context
102                         (List.tl headr) (List.tl head2) (List.tl l)
103                       ) tail2
104 *)
105         ) (* match *)
106        )
107 ;;
108 *)
109
110 (* preserves order and gets rid of duplicates *)
111 let rec union_ex l1 l2 =
112  let module S = Mathql_semantics in
113   match (l1, l2) with
114      [],l
115    | l,[] -> l
116    | ({S.uri = uri1} as entry1)::tl1,
117      ({S.uri = uri2} as entry2)::_ when uri1 < uri2 || entry1 < entry2 ->
118        entry1::(union_ex tl1 l2)
119    | ({S.uri = uri1} as entry1)::_,
120      ({S.uri = uri2} as entry2)::tl2 when uri2 < uri1 || entry2 < entry1 ->
121        entry2::(union_ex l1 tl2)
122    | entry1::tl1,entry2::tl2 -> (* same entry *)
123      entry1::(union_ex tl1 tl2)
124 ;;
125
126 let union_ex l1 l2 =
127  let before = Unix.time () in
128  let res = union_ex l1 l2 in
129  let after = Unix.time () in
130   let ll1 = string_of_int (List.length l1) in
131   let ll2 = string_of_int (List.length l2) in
132   let diff = string_of_float (after -. before) in
133   prerr_endline ("UNION(" ^ ll1 ^ "," ^ ll2 ^ "): " ^ diff ^ "s") ;
134   flush stderr ;
135   res
136 ;;