1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2001-2017. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(sofs_SUITE).
21
22%%-define(debug, true).
23
24-ifdef(debug).
25-define(format(S, A), io:format(S, A)).
26-define(line, put(line, ?LINE), ).
27-define(config(X,Y), foo).
28-define(t, test_server).
29-else.
30-include_lib("common_test/include/ct.hrl").
31-define(format(S, A), ok).
32-endif.
33
34-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
35	 init_per_group/2,end_per_group/2]).
36
37-export([ from_term_1/1, set_1/1, from_sets_1/1, relation_1/1,
38	  a_function_1/1, family_1/1, projection/1,
39	  relation_to_family_1/1, domain_1/1, range_1/1, image/1,
40	  inverse_image/1, inverse_1/1, converse_1/1, no_elements_1/1,
41	  substitution/1, restriction/1, drestriction/1,
42	  strict_relation_1/1, extension/1, weak_relation_1/1,
43	  to_sets_1/1, specification/1, union_1/1, intersection_1/1,
44	  difference/1, symdiff/1, symmetric_partition/1,
45	  is_sofs_set_1/1, is_set_1/1, is_equal/1, is_subset/1,
46	  is_a_function_1/1, is_disjoint/1, join/1, canonical/1,
47	  composite_1/1, relative_product_1/1, relative_product_2/1,
48	  product_1/1, partition_1/1, partition_3/1,
49	  multiple_relative_product/1, digraph/1, constant_function/1,
50	  misc/1]).
51
52-export([ family_specification/1,
53	  family_domain_1/1, family_range_1/1,
54	  family_to_relation_1/1,
55	  union_of_family_1/1, intersection_of_family_1/1,
56	  family_projection/1, family_difference/1,
57	  family_intersection_1/1, family_union_1/1,
58	  family_intersection_2/1, family_union_2/1,
59	  partition_family/1]).
60
61-import(sofs,
62	[a_function/1, a_function/2, constant_function/2,
63	 canonical_relation/1, composite/2,
64	 converse/1, extension/3, from_term/1, from_term/2,
65	 difference/2, domain/1, empty_set/0, family_difference/2,
66	 family_intersection/1, family_intersection/2, family_union/1,
67	 family_union/2, family/1, family/2, family_specification/2,
68	 family_domain/1, family_range/1, family_field/1,
69	 family_projection/2, family_to_relation/1, union_of_family/1,
70	 field/1, from_external/2, image/2, intersection/1,
71	 intersection/2, intersection_of_family/1, inverse/1,
72	 inverse_image/2, is_disjoint/2, is_empty_set/1, is_equal/2,
73	 is_a_function/1, is_set/1, is_sofs_set/1, is_subset/2,
74	 join/4, from_sets/1, multiple_relative_product/2,
75	 no_elements/1, partition/1, partition/2, partition/3,
76	 partition_family/2, product/1, product/2, projection/2,
77	 range/1, relation/1, relation/2, relation_to_family/1,
78	 relative_product/1, relative_product/2, relative_product1/2,
79	 strict_relation/1, weak_relation/1, restriction/2,
80	 restriction/3, drestriction/2, drestriction/3, to_sets/1,
81	 is_type/1, set/1, set/2, specification/2, substitution/2,
82	 symdiff/2, symmetric_partition/2, to_external/1, type/1,
83	 union/1, union/2, family_to_digraph/1, family_to_digraph/2,
84	 digraph_to_family/1, digraph_to_family/2]).
85
86-export([init_per_testcase/2, end_per_testcase/2]).
87
88-compile({inline,[{eval,2}]}).
89
90suite() ->
91    [{ct_hooks,[ts_install_cth]},
92     {timetrap,{minutes,2}}].
93
94all() ->
95    [{group, sofs}, {group, sofs_family}].
96
97groups() ->
98    [{sofs, [],
99      [from_term_1, set_1, from_sets_1, relation_1,
100       a_function_1, family_1, relation_to_family_1, domain_1,
101       range_1, image, inverse_image, inverse_1, converse_1,
102       no_elements_1, substitution, restriction, drestriction,
103       projection, strict_relation_1, extension,
104       weak_relation_1, to_sets_1, specification, union_1,
105       intersection_1, difference, symdiff,
106       symmetric_partition, is_sofs_set_1, is_set_1, is_equal,
107       is_subset, is_a_function_1, is_disjoint, join,
108       canonical, composite_1, relative_product_1,
109       relative_product_2, product_1, partition_1, partition_3,
110       multiple_relative_product, digraph, constant_function,
111       misc]},
112     {sofs_family, [],
113      [family_specification, family_domain_1, family_range_1,
114       family_to_relation_1, union_of_family_1,
115       intersection_of_family_1, family_projection,
116       family_difference, family_intersection_1,
117       family_intersection_2, family_union_1, family_union_2,
118       partition_family]}].
119
120init_per_suite(Config) ->
121    Config.
122
123end_per_suite(_Config) ->
124    ok.
125
126init_per_group(_GroupName, Config) ->
127    Config.
128
129end_per_group(_GroupName, Config) ->
130    Config.
131
132
133init_per_testcase(_Case, Config) ->
134    Config.
135
136end_per_testcase(_Case, _Config) ->
137    ok.
138
139%% [{2,b},{1,a,b}] == lists:sort([{2,b},{1,a,b}])
140%% [{1,a,b},{2,b}] == lists:keysort(1,[{2,b},{1,a,b}])
141
142
143from_term_1(Conf) when is_list(Conf) ->
144    %% would go wrong: projection(1,from_term([{2,b},{1,a,b}])),
145
146    {'EXIT', {badarg, _}} = (catch from_term([], {atom,'_',atom})),
147    {'EXIT', {badarg, _}} = (catch from_term([], [])),
148    {'EXIT', {badarg, _}} = (catch from_term([], [atom,atom])),
149
150    [] = to_external(from_term([])),
151    eval(from_term([]), empty_set()),
152    [] = to_external(from_term([], ['_'])),
153    eval(from_term([], ['_']), empty_set()),
154    [[]] = to_external(from_term([[]])),
155    [[['_']]] = type(from_term([[],[[]]])),
156    [[],[[]]] = to_external(from_term([[],[[]]])),
157    [[['_']]] = type(from_term([[],[[]]])),
158    eval(from_term([a],['_']), set([a])),
159    [[],[a]] = to_external(from_term([[],[a]])),
160    [[],[{a}]] = to_external(from_term([[{a}],[]])),
161    [{[],[{a,b,[d]}]},{[{a,b}],[]}] =
162	to_external(from_term([{[],[{a,b,[d]}]},{[{a,b}],[]}])),
163
164    [{[a,b],[c,d]}] = to_external(from_term([{[a,b],[c,d]}])),
165    [{{a,b},[a,b],{{a},{b}}}] =
166	to_external(from_term([{{a,b},[a,b],{{a},{b}}}])),
167    [{{a,{[a,b]},a}},{{z,{[y,z]},z}}] =
168	to_external(from_term([{{a,{[a,b,a]},a}},{{z,{[y,y,z]},z}}])),
169    {'EXIT', {badarg, _}} =
170	(catch from_term([{m1,[{m1,f1,1},{m1,f2,2}]},{m2,[]},{m3,[a]}])),
171    MS1 = [{m1,[{m1,f1,1},{m1,f2,2}]},{m2,[]},{m3,[{m3,f3,3}]}],
172    eval(to_external(from_term(MS1)), MS1),
173
174    eval(to_external(from_term(a)), a),
175    eval(to_external(from_term({a})), {a}),
176
177    eval(to_external(from_term([[a],[{b,c}]],[[atomic]])),
178	 [[a],[{b,c}]]),
179    eval(type(from_term([[a],[{b,c}]],[[atomic]])),
180	 [[atomic]]),
181
182    {'EXIT', {badarg, _}} = (catch from_term([[],[],a])),
183    {'EXIT', {badarg, _}} = (catch from_term([{[a,b],[c,{d}]}])),
184    {'EXIT', {badarg, _}} = (catch from_term([[],[a],[{a}]])),
185    {'EXIT', {badarg, _}} = (catch from_term([a,{a,b}])),
186    {'EXIT', {badarg, _}} = (catch from_term([[a],[{b,c}]],[['_']])),
187    {'EXIT', {badarg, _}} = (catch from_term([a | {a,b}])),
188    {'EXIT', {badarg, _}} =
189	(catch from_term([{{a},b,c},{d,e,f}],[{{atom},atom,atom}])),
190    {'EXIT', {badarg, _}} =
191	(catch from_term([{a,{b,c}} | tail], [{atom,{atom,atom}}])),
192    {'EXIT', {badarg, _}} = (catch from_term({})),
193    {'EXIT', {badarg, _}} = (catch from_term([{}])),
194
195    [{foo,bar},[b,a]] =
196        to_external(from_term([[b,a],{foo,bar},[b,a]], [atom])),
197    [{[atom],{atom,atom}}] =
198	type(from_term([{[], {a,b}},{[a,b],{e,f}}])),
199    [{[atom],{atom,atom}}] =
200	type(from_term([{[], {a,b}},{[a,b],{e,f}}], [{[atom],{atom,atom}}])),
201    [[atom]] = type(from_term([[a],[{b,c}]],[[atom]])),
202
203    {atom, atom} = type(from_term({a,b}, {atom, atom})),
204    atom = type(from_term(a, atom)),
205    {'EXIT', {badarg, _}} = (catch from_term({a,b},{atom})),
206    [{{a},b,c},{{d},e,f}] =
207	to_external(from_term([{{a},b,c},{{a},b,c},{{d},e,f}],
208			      [{{atom},atom,atom}])),
209
210    %% from_external too...
211    e = to_external(from_external(e, atom)),
212    {e} = to_external(from_external({e}, {atom})),
213    [e] = to_external(from_external([e], [atom])),
214
215    %% and is_type...
216    true = is_type(['_']),
217    false = is_type('_'),
218    true = is_type([['_']]),
219    false = is_type({atom,[],atom}),
220    false = is_type({atom,'_',atom}),
221    true = is_type({atom,atomic,atom}),
222    true = is_type({atom,atom}),
223    true = is_type(atom),
224    true = is_type([atom]),
225    true = is_type(type),
226
227    ok.
228
229set_1(Conf) when is_list(Conf) ->
230    %% set/1
231    {'EXIT', {badarg, _}} = (catch set(a)),
232    {'EXIT', {badarg, _}} = (catch set({a})),
233    eval(set([]), from_term([],[atom])),
234    eval(set([a,b,c]), from_term([a,b,c])),
235    eval(set([a,b,a,a,b]), from_term([a,b])),
236    eval(set([a,b,c,a,d,d,c,1]), from_term([1,a,b,c,d])),
237    eval(set([a,b,d,a,c]), from_term([a,b,c,d])),
238    eval(set([f,e,d,c,d]), from_term([c,d,e,f])),
239    eval(set([h,f,d,g,g,d,c]), from_term([c,d,f,g,h])),
240    eval(set([h,e,d,k,l]), from_term([d,e,h,k,l])),
241    eval(set([h,e,c,k,d]), from_term([c,d,e,h,k])),
242
243    %% set/2
244    {'EXIT', {badarg, _}} = (catch set(a, [a])),
245    {'EXIT', {badarg, _}} = (catch set({a}, [a])),
246    {'EXIT', {badarg, _}} = (catch set([a], {a})),
247    {'EXIT', {badarg, _}} = (catch set([a], a)),
248    {'EXIT', {badarg, _}} = (catch set([a], [a,b])),
249    {'EXIT', {badarg, _}} = (catch set([a | b],[foo])),
250    {'EXIT', {badarg, _}} = (catch set([a | b],['_'])),
251    {'EXIT', {badarg, _}} = (catch set([a | b],[[atom]])),
252    {'EXIT', {badarg, _}} = (catch set([{}],[{}])),
253    eval(set([a],['_']), from_term([a],['_'])),
254    eval(set([], ['_']), empty_set()),
255    eval(set([a,b,a,b],[foo]), from_term([a,b],[foo])),
256
257    ok.
258
259from_sets_1(Conf) when is_list(Conf) ->
260    E = empty_set(),
261
262    %% unordered
263    eval(from_sets([]), E),
264    {'EXIT', {type_mismatch, _}} =
265	(catch from_sets([from_term([{a,b}]),
266                          E,
267                          from_term([{a,b,c}])])),
268    eval(from_sets([from_term([{a,b}]), E]),
269	 from_term([[],[{a,b}]])),
270
271    eval(from_sets([from_term({a,b},{atom,atom}),
272		    from_term({b,c},{atom,atom})]),
273	 relation([{a,b}, {b,c}])),
274    {'EXIT', {type_mismatch, _}} =
275	(catch from_sets([from_term({a,b},{atom,atom}),
276			  from_term({a,b,c},{atom,atom,atom})])),
277    {'EXIT', {badarg, _}} = (catch from_sets(foo)),
278    eval(from_sets([E]), from_term([[]])),
279    eval(from_sets([E,E]), from_term([[]])),
280    eval(from_sets([E,set([a])]), from_term([[],[a]])),
281    {'EXIT', {badarg, _}} = (catch from_sets([E,{a}])),
282    {'EXIT', {type_mismatch, _}} =
283	(catch from_sets([E,from_term({a}),E])),
284    {'EXIT', {type_mismatch, _}} = (catch from_sets([from_term({a}),E])),
285
286    %% ordered
287    O = {from_term(a,atom), from_term({b}, {atom}), set([c,d])},
288    eval(from_sets(O), from_term({a,{b},[c,d]}, {atom,{atom},[atom]})),
289    {'EXIT', {badarg, _}} = (catch from_sets([a,b])),
290    {'EXIT', {badarg, _}} = (catch from_sets({a,b})),
291    eval(from_sets({from_term({a}),E}), from_term({{a},[]})),
292    ok.
293
294relation_1(Conf) when is_list(Conf) ->
295    %% relation/1
296    eval(relation([]), from_term([], [{atom,atom}])),
297    eval(from_term([{a}]), relation([{a}])),
298    {'EXIT', {badarg, _}} = (catch relation(a)),
299    {'EXIT', {badarg, _}} = (catch relation([{a} | a])),
300    {'EXIT', {badarg, _}} = (catch relation([{}])),
301    {'EXIT', {badarg, _}} = (catch relation([],0)),
302    {'EXIT', {badarg, _}} = (catch relation([{a}],a)),
303
304    %% relation/2
305    eval(relation([{a},{b}], 1), from_term([{a},{b}])),
306    eval(relation([{1,a},{2,b},{1,a}], [{x,y}]),
307	 from_term([{1,a},{2,b}], [{x,y}])),
308    eval(relation([{[1,2],a},{[2,1],b},{[2,1],a}], [{[x],y}]),
309	 from_term([{[1,2],a},{[1,2],b}], [{[x],y}])),
310    {'EXIT', {badarg, _}} = (catch relation([{1,a},{2,b}], [{[x],y}])),
311    {'EXIT', {badarg, _}} = (catch relation([{1,a},{1,a,b}], [{x,y}])),
312    {'EXIT', {badarg, _}} = (catch relation([{a}], 2)),
313    {'EXIT', {badarg, _}} = (catch relation([{a},{b},{c,d}], 1)),
314    eval(relation([{{a},[{foo,bar}]}], ['_']),
315	 from_term([{{a},[{foo,bar}]}], ['_'])),
316    eval(relation([], ['_']), from_term([], ['_'])),
317    {'EXIT', {badarg, _}} = (catch relation([[a]],['_'])),
318    eval(relation([{[a,b,a]}], [{[atom]}]), from_term([{[a,b,a]}])),
319    eval(relation([{[a,b,a],[[d,e,d]]}], [{[atom],[[atom]]}]),
320	 from_term([{[a,b,a],[[d,e,d]]}])),
321    eval(relation([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}]),
322	 from_term([{[a,b,a],[[d,e,d]]}], [{atom,[[atom]]}])),
323    ok.
324
325a_function_1(Conf) when is_list(Conf) ->
326    %% a_function/1
327    eval(a_function([]), from_term([], [{atom,atom}])),
328    eval(a_function([{a,b},{a,b},{b,c}]), from_term([{a,b},{b,c}])),
329    {'EXIT', {badarg, _}} = (catch a_function([{a}])),
330    {'EXIT', {badarg, _}} = (catch a_function([{a},{b},{c,d}])),
331    {'EXIT', {badarg, _}} = (catch a_function(a)),
332    {'EXIT', {badarg, _}} = (catch a_function([{a,b} | a])),
333    {'EXIT', {bad_function, _}} =
334	(catch a_function([{a,b},{b,c},{a,c}])),
335    F = 0.0, I = round(F),
336    if
337        F == I -> % term ordering
338            {'EXIT', {bad_function, _}} =
339                (catch a_function([{I,a},{F,b}])),
340            {'EXIT', {bad_function, _}} =
341		(catch a_function([{[I],a},{[F],b}],[{[a],b}]));
342        true ->
343            2 = no_elements(a_function([{I,a},{F,b}])),
344            2 = no_elements(a_function([{[I],a},{[F],b}],[{[a],b}]))
345    end,
346
347    %% a_function/2
348    FT = [{atom,atom}],
349    eval(a_function([], FT), from_term([], FT)),
350    eval(a_function([{a,b},{b,c},{b,c}], FT),
351	 from_term([{a,b},{b,c}], FT)),
352    {'EXIT', {badarg, _}} = (catch a_function([{a,b}], [{a}])),
353    {'EXIT', {badarg, _}} = (catch a_function([{a,b}], [{a,[b,c]}])),
354    {'EXIT', {badarg, _}} = (catch a_function([{a}], FT)),
355    {'EXIT', {badarg, _}} = (catch a_function([{a},{b},{c,d}], FT)),
356    {'EXIT', {badarg, _}} = (catch a_function(a, FT)),
357    {'EXIT', {badarg, _}} = (catch a_function([{a,b} | a], FT)),
358    eval(a_function([{{a},[{foo,bar}]}], ['_']),
359	 from_term([{{a},[{foo,bar}]}], ['_'])),
360    eval(a_function([], ['_']), from_term([], ['_'])),
361    {'EXIT', {badarg, _}} = (catch a_function([[a]],['_'])),
362    {'EXIT', {bad_function, _}} =
363	(catch a_function([{a,b},{b,c},{a,c}], FT)),
364    eval(a_function([{a,[a]},{a,[a,a]}], [{atom,[atom]}]),
365	 from_term([{a,[a]}])),
366    eval(a_function([{[b,a],c},{[a,b],c}], [{[atom],atom}]),
367	 from_term([{[a,b],c}])),
368    ok.
369
370family_1(Conf) when is_list(Conf) ->
371    %% family/1
372    eval(family([]), from_term([],[{atom,[atom]}])),
373    {'EXIT', {badarg, _}} = (catch family(a)),
374    {'EXIT', {badarg, _}} = (catch family([a])),
375    {'EXIT', {badarg, _}} = (catch family([{a,b}])),
376    {'EXIT', {badarg, _}} = (catch family([{a,[]} | a])),
377    {'EXIT', {badarg, _}} = (catch family([{a,[a|b]}])),
378    {'EXIT', {bad_function, _}} =
379        (catch family([{a,[a]},{a,[]}])),
380    {'EXIT', {bad_function, _}} =
381	(catch family([{a,[]},{b,[]},{a,[a]}])),
382    F = 0.0, I = round(F),
383    if
384        F == I -> % term ordering
385            {'EXIT', {bad_function, _}} =
386                (catch family([{I,[a]},{F,[b]}])),
387            true = (1 =:= no_elements(family([{a,[I]},{a,[F]}])));
388        true ->
389            {'EXIT', {bad_function, _}} =
390                (catch family([{a,[I]},{a,[F]}]))
391    end,
392    eval(family([{a,[]},{b,[b]},{a,[]}]), from_term([{a,[]},{b,[b]}])),
393    eval(to_external(family([{b,[{hej,san},tjo]},{a,[]}])),
394	 [{a,[]},{b,[tjo,{hej,san}]}]),
395    eval(family([{a,[a]},{a,[a,a]}]), family([{a,[a]}])),
396
397    %% family/2
398    FT = [{a,[a]}],
399    eval(family([], FT), from_term([],FT)),
400    {'EXIT', {badarg, _}} = (catch family(a,FT)),
401    {'EXIT', {badarg, _}} = (catch family([a],FT)),
402    {'EXIT', {badarg, _}} = (catch family([{a,b}],FT)),
403    {'EXIT', {badarg, _}} = (catch family([{a,[]} | a],FT)),
404    {'EXIT', {badarg, _}} = (catch family([{a,[a|b]}], FT)),
405    {'EXIT', {bad_function, _}} =
406        (catch family([{a,[a]},{a,[]}], FT)),
407    {'EXIT', {bad_function, _}} =
408	(catch family([{a,[]},{b,[]},{a,[a]}], FT)),
409    eval(family([{a,[]},{b,[b,b]},{a,[]}], FT),
410	 from_term([{a,[]},{b,[b]}], FT)),
411    eval(to_external(family([{b,[{hej,san},tjo]},{a,[]}], FT)),
412	 [{a,[]},{b,[tjo,{hej,san}]}]),
413
414    eval(family([{{a},[{foo,bar}]}], ['_']),
415	 from_term([{{a},[{foo,bar}]}], ['_'])),
416    eval(family([], ['_']), from_term([], ['_'])),
417    {'EXIT', {badarg, _}} = (catch family([[a]],['_'])),
418    {'EXIT', {badarg, _}} = (catch family([{a,b}],['_'])),
419    {'EXIT', {badarg, _}} =
420	(catch family([{a,[foo]}], [{atom,atom}])),
421    eval(family([{{a},[{foo,bar}]}], [{{dt},[{r1,t2}]}]),
422	 from_term([{{a},[{foo,bar}]}], [{{dt},[{r1,t2}]}])),
423    eval(family([{a,[a]},{a,[a,a]}],[{atom,[atom]}]),
424	 family([{a,[a]}])),
425    eval(family([{[a,b],[a]},{[b,a],[a,a]}],[{[atom],[atom]}]),
426	 from_term([{[a,b],[a]},{[b,a],[a,a]}])),
427    ok.
428
429projection(Conf) when is_list(Conf) ->
430    E = empty_set(),
431    ER = relation([]),
432
433    %% set of ordered sets
434    S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
435    S2 = relation([{a,1},{a,2},{a,3},{b,4},{b,5},{b,6}]),
436
437    eval(projection(1, E), E),
438    eval(projection(1, ER), set([])),
439    eval(projection(1, relation([{a,1}])), set([a])),
440    eval(projection(1, S1), set([a,b,c])),
441    eval(projection(1, S2), set([a,b])),
442    eval(projection(2, S1), set([0,1,2,22])),
443    eval(projection(2, relation([{1,a},{2,a},{3,b}])), set([a,b])),
444    eval(projection(1, relation([{a},{b},{c}])), set([a,b,c])),
445
446    Fun1 = {external, fun({A,B,C}) -> {A,{B,C}} end},
447    eval(projection(Fun1, E), E),
448    %% No check here:
449    eval(projection(3, projection(Fun1, empty_set())), E),
450    E2 = relation([], 3),
451    eval(projection(Fun1, E2), from_term([], [{atom,{atom,atom}}])),
452
453    Fun2 = {external, fun({A,_B}) -> {A} end},
454    eval(projection(Fun2, ER), from_term([], [{atom}])),
455    eval(projection(Fun2, relation([{a,1}])), relation([{a}])),
456    eval(projection(Fun2, relation([{a,1},{b,3},{a,2}])),
457	 relation([{a},{b}])),
458    Fun3 = {external, fun({A,_B,C}) -> {C,{A},C} end},
459    eval(projection(Fun3, relation([{a,1,x},{b,3,y},{a,2,z}])),
460	 from_term([{x,{a},x},{y,{b},y},{z,{a},z}])),
461    Fun4 = {external, fun(A={B,_C,_D}) -> {B, A} end},
462    eval(projection(Fun4, relation([{a,1,x},{b,3,y},{a,2,z}])),
463	 from_term([{a,{a,1,x}},{b,{b,3,y}},{a,{a,2,z}}])),
464
465    eval(projection({external, fun({A,B,_C,D}) -> {A,B,A,D} end},
466		    relation([{1,1,1,2}, {1,1,3,1}])),
467	 relation([{1,1,1,1}, {1,1,1,2}])),
468
469    {'EXIT', {badarg, _}} = (catch projection(1, set([]))),
470    {'EXIT', {function_clause, _}} =
471	(catch projection({external, fun({A}) -> A end}, S1)),
472    {'EXIT', {badarg, _}} =
473	(catch projection({external, fun({A,_}) -> {A,0} end},
474			  from_term([{1,a}]))),
475
476    %% {} is not an ordered set
477    {'EXIT', {badarg, _}} =
478        (catch projection({external, fun(_) -> {} end}, ER)),
479    {'EXIT', {badarg, _}} =
480        (catch projection({external, fun(_) -> {{}} end}, ER)),
481    eval(projection({external, fun({T,_}) -> T end},
482		    relation([{{},a},{{},b}])),
483	 set([{}])),
484    eval(projection({external, fun({T}) -> T end}, relation([{{}}])),
485	 set([{}])),
486
487    eval(projection({external, fun(A) -> {A} end},
488		    relation([{1,a},{2,b}])),
489	 from_term([{{1,a}},{{2,b}}])),
490    eval(projection({external, fun({A,B}) -> {B,A} end},
491		    relation([{1,a},{2,b}])),
492	 relation([{a,1},{b,2}])),
493    eval(projection({external, fun(X=Y=A) -> {X,Y,A} end}, set([a,b,c])),
494	 relation([{a,a,a},{b,b,b},{c,c,c}])),
495
496    eval(projection({external, fun({A,{_},B}) -> {A,B} end},
497		    from_term([{a,{a},b},{a,{b},c}])),
498	 relation([{a,b},{a,c}])),
499    eval(projection({external, fun({A,_,B}) -> {A,B} end},
500		    relation([{a,{},b},{a,{},c}])),
501	 relation([{a,b},{a,c}])),
502    Fun5 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
503    eval(projection(Fun5, E), E),
504    eval(projection(Fun5, set([a,b])), from_term([{a,0},{b,0}])),
505    eval(projection(Fun5, relation([{a,1},{b,2}])),
506	 from_term([{{a,1},0},{{b,2},0}])),
507    eval(projection(Fun5, from_term([[a],[b]])),
508	 from_term([{[a],0},{[b],0}])),
509
510    F = 0.0, I = round(F),
511    FR = relation([{I},{F}]),
512    if
513        F == I -> % term ordering
514            true = (no_elements(projection(1, FR)) =:= 1);
515        true ->
516            eval(projection(1, FR), set([I,F]))
517    end,
518
519    %% set of sets
520    {'EXIT', {badarg, _}} =
521        (catch projection({external, fun(X) -> X end},
522			  from_term([], [[atom]]))),
523    {'EXIT', {badarg, _}} =
524        (catch projection({external, fun(X) -> X end}, from_term([[a]]))),
525    eval(projection(fun sofs:union/1,
526		    from_term([[[1,2],[2,3]], [[a,b],[b,c]]])),
527	 from_term([[1,2,3], [a,b,c]])),
528    eval(projection(fun(_) -> from_term([a]) end,
529		    from_term([[b]], [[a]])),
530	 from_term([[a]])),
531    eval(projection(fun(_) -> from_term([a]) end,
532		    from_term([[1,2],[3,4]])),
533	 from_term([[a]])),
534    Fun10 = fun(S) ->
535		    %% Cheating a lot...
536		    case to_external(S) of
537			[1] -> from_term({1,1});
538			_ -> S
539		    end
540	    end,
541    eval(projection(Fun10, from_term([[1]])), from_term([{1,1}])),
542    eval(projection(fun(_) -> from_term({a}) end, from_term([[a]])),
543	 from_term([{a}])),
544    {'EXIT', {badarg, _}} =
545	(catch projection(fun(_) -> {a} end, from_term([[a]]))),
546
547    ok.
548
549substitution(Conf) when is_list(Conf) ->
550    E = empty_set(),
551    ER = relation([]),
552
553    %% set of ordered sets
554    S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
555    S2 = relation([{a,1},{a,2},{a,3},{b,4},{b,5},{b,6}]),
556
557    eval(substitution(1, E), E),
558    %% No check here:
559    Fun0 = {external, fun({A,B,C}) -> {A,{B,C}} end},
560    eval(substitution(3, substitution(Fun0, empty_set())), E),
561    eval(substitution(1, ER), from_term([],[{{atom,atom},atom}])),
562    eval(substitution(1, relation([{a,1}])), from_term([{{a,1},a}])),
563    eval(substitution(1, S1),
564	 from_term([{{a,1},a},{{b,2},b},{{b,22},b},{{c,0},c}])),
565    eval(substitution(1, S2),
566	 from_term([{{a,1},a},{{a,2},a},{{a,3},a},{{b,4},b},
567		    {{b,5},b},{{b,6},b}])),
568    eval(substitution(2, S1),
569	 from_term([{{a,1},1},{{b,2},2},{{b,22},22},{{c,0},0}])),
570
571    Fun1 = fun({A,_B}) -> {A} end,
572    XFun1 = {external, Fun1},
573    eval(substitution(XFun1, E), E),
574    eval(substitution(Fun1, E), E),
575    eval(substitution(XFun1, ER), from_term([], [{{atom,atom},{atom}}])),
576    eval(substitution(XFun1, relation([{a,1}])),
577	 from_term([{{a,1},{a}}])),
578    eval(substitution(XFun1, relation([{a,1},{b,3},{a,2}])),
579	 from_term([{{a,1},{a}},{{a,2},{a}},{{b,3},{b}}])),
580    eval(substitution({external, fun({A,_B,C}) -> {C,A,C} end},
581		      relation([{a,1,x},{b,3,y},{a,2,z}])),
582	 from_term([{{a,1,x},{x,a,x}},{{a,2,z},{z,a,z}},
583		    {{b,3,y},{y,b,y}}])),
584    Fun2 = fun(S) -> {A,_B} = to_external(S), from_term({A}) end,
585    eval(substitution(Fun2, ER), E),
586    eval(substitution(Fun2, relation([{a,1}])),
587	 from_term([{{a,1},{a}}])),
588    Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
589    eval(substitution(Fun3, E), E),
590    eval(substitution(Fun3, set([a,b])),
591	 from_term([{a,{a,0}},{b,{b,0}}])),
592    eval(substitution(Fun3, relation([{a,1},{b,2}])),
593	 from_term([{{a,1},{{a,1},0}},{{b,2},{{b,2},0}}])),
594    eval(substitution(Fun3, from_term([[a],[b]])),
595	 from_term([{[a],{[a],0}},{[b],{[b],0}}])),
596
597    eval(substitution(fun(_) -> E end, from_term([[a],[b]])),
598	 from_term([{[a],[]},{[b],[]}])),
599
600    {'EXIT', {badarg, _}} = (catch substitution(1, set([]))),
601    eval(substitution(1, ER), from_term([], [{{atom,atom},atom}])),
602    {'EXIT', {function_clause, _}} =
603	(catch substitution({external, fun({A,_}) -> A end}, set([]))),
604    {'EXIT', {badarg, _}} =
605	(catch substitution({external, fun({A,_}) -> {A,0} end},
606			    from_term([{1,a}]))),
607
608    %% set of sets
609    {'EXIT', {badarg, _}} =
610        (catch substitution({external, fun(X) -> X end},
611			    from_term([], [[atom]]))),
612    {'EXIT', {badarg, _}} =
613        (catch substitution({external, fun(X) -> X end}, from_term([[a]]))),
614    eval(substitution(fun(X) -> X end, from_term([], [[atom]])), E),
615    eval(substitution(fun sofs:union/1,
616		      from_term([[[1,2],[2,3]], [[a,b],[b,c]]])),
617	 from_term([{[[1,2],[2,3]],[1,2,3]}, {[[a,b],[b,c]],[a,b,c]}])),
618    eval(substitution(fun(_) -> from_term([a]) end,
619		      from_term([[b]], [[a]])),
620	 from_term([{[b],[a]}], [{[a],[atom]}])),
621    eval(substitution(fun(_) -> from_term([a]) end,
622		      from_term([[1,2],[3,4]])),
623	 from_term([{[1,2],[a]},{[3,4],[a]}])),
624    Fun10 = fun(S) ->
625		    %% Cheating a lot...
626		    case to_external(S) of
627			[1] -> from_term({1,1});
628			_ -> S
629		    end
630	    end,
631    eval(substitution(Fun10, from_term([[1]])),
632	 from_term([{[1],{1,1}}])),
633    {'EXIT', {type_mismatch, _}} =
634        (catch substitution(Fun10, from_term([[1],[2]]))),
635    {'EXIT', {type_mismatch, _}} =
636        (catch substitution(Fun10, from_term([[1],[0]]))),
637
638    eval(substitution(fun(_) -> from_term({a}) end, from_term([[a]])),
639	 from_term([{[a],{a}}])),
640    {'EXIT', {badarg, _}} =
641	(catch substitution(fun(_) -> {a} end, from_term([[a]]))),
642
643    ok.
644
645restriction(Conf) when is_list(Conf) ->
646    E = empty_set(),
647    ER = relation([], 2),
648
649    %% set of ordered sets
650    S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
651    eval(restriction(S1, set([a,b])),
652	 relation([{a,1},{b,2},{b,22}])),
653    eval(restriction(2, S1, set([1,2])),
654	 relation([{a,1},{b,2}])),
655    eval(restriction(S1, set([a,b,c])), S1),
656    eval(restriction(1, S1, set([0,1,d,e])), ER),
657    eval(restriction(1, S1, E), ER),
658    eval(restriction({external, fun({_A,B,C}) -> {B,C} end},
659		     relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
660		     relation([{bb,2},{cc,3}])),
661	 relation([{b,bb,2},{c,cc,3}])),
662    R1 = relation([],[{a,b}]),
663    eval(restriction(2, R1,sofs:set([],[b])), R1),
664    Id = fun(X) -> X end,
665    XId = {external, Id},
666    eval(restriction(XId, relation([{a,b}]), E), ER),
667    eval(restriction(XId, E, relation([{b,d}])), E),
668    Fun1 = fun(S) -> {_A,B,C} = to_external(S), from_term({B,C}) end,
669    eval(restriction(Fun1,
670		     relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
671		     relation([{bb,2},{cc,3}])),
672	 relation([{b,bb,2},{c,cc,3}])),
673    eval(restriction({external, fun({_,{A},B}) -> {A,B} end},
674		     from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
675		     from_term([{bb,2},{cc,3}])),
676	 from_term([{b,{bb},2},{c,{cc},3}])),
677    S5 = relation([{1,a},{2,b},{3,c}]),
678    eval(restriction(2, S5, set([b,c])), relation([{2,b},{3,c}])),
679    S4 = relation([{a,1},{b,2},{b,27},{c,0}]),
680    eval(restriction(2, S4, E), ER),
681    S6 = relation([{1,a},{2,c},{3,b}]),
682    eval(restriction(2, S6, set([d,e])), ER),
683    eval(restriction(2,
684		     relation([{1,d},{2,c},{3,b},{4,a},{5,e}]),
685		     set([c])),
686	 relation([{2,c}])),
687    eval(restriction(XId,
688		     relation([{1,a},{3,b},{4,c},{4,d}]),
689		     relation([{2,a},{2,c},{4,c}])),
690	 relation([{4,c}])),
691    eval(restriction(2, relation([{a,b}]), E), ER),
692    eval(restriction(2, E, relation([{b,d}])), E),
693    eval(restriction(2, relation([{b,d}]), E), ER),
694    eval(restriction(XId, E, set([a])), E),
695    eval(restriction(1, S1, E), ER),
696    {'EXIT', {badarg, _}} =
697	(catch restriction(3, relation([{a,b}]), E)),
698    {'EXIT', {badarg, _}} =
699	(catch restriction(3, relation([{a,b}]), relation([{b,d}]))),
700    {'EXIT', {badarg, _}} =
701	(catch restriction(3, relation([{a,b}]), set([{b,d}]))),
702    {'EXIT', {type_mismatch, _}} =
703	(catch restriction(2, relation([{a,b}]), relation([{b,d}]))),
704    {'EXIT', {type_mismatch, _}} =
705	(catch restriction({external, fun({A,_B}) -> A end},
706			   relation([{a,b}]), relation([{b,d}]))),
707    {'EXIT', {badarg, _}} =
708	(catch restriction({external, fun({A,_}) -> {A,0} end},
709			   from_term([{1,a}]),
710			   from_term([{1,0}]))),
711    eval(restriction(2, relation([{a,d},{b,e},{c,b},{d,c}]), set([b,d])),
712	 relation([{a,d},{c,b}])),
713    {'EXIT', {function_clause, _}} =
714	(catch restriction({external, fun({A,_B}) -> A end}, set([]), E)),
715
716    Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
717    eval(restriction(Fun3, set([1,2]), from_term([{1,0}])),
718	 from_term([1])),
719
720    %% set of sets
721    {'EXIT', {badarg, _}} =
722        (catch restriction({external, fun(X) -> X end},
723			   from_term([], [[atom]]), set([a]))),
724    S2 = from_term([], [[atom]]),
725    eval(restriction(Id, S2, E), E),
726    S3 = from_term([[a],[b]], [[atom]]),
727    eval(restriction(Id, S3, E), E),
728    eval(restriction(Id, from_term([], [[atom]]), set([a])),
729	 from_term([], [[atom]])),
730    eval(restriction(fun sofs:union/1,
731		     from_term([[[a],[b]], [[b],[c]],
732				[[], [a,b]], [[1],[2]]]),
733		     from_term([[a,b],[1,2,3],[b,c]])),
734	 from_term([[[],[a,b]], [[a],[b]],[[b],[c]]])),
735    eval(restriction(fun(_) -> from_term([a]) end,
736		     from_term([], [[atom]]),
737		     from_term([], [[a]])),
738	 from_term([], [[atom]])),
739    {'EXIT', {type_mismatch, _}} =
740        (catch restriction(fun(_) -> from_term([a]) end,
741                           from_term([[1,2],[3,4]]),
742                           from_term([], [atom]))),
743    Fun10 = fun(S) ->
744		    %% Cheating a lot...
745		    case to_external(S) of
746			[1] -> from_term({1,1});
747			_ -> S
748		    end
749	    end,
750    {'EXIT', {type_mismatch, _}} =
751        (catch restriction(Fun10, from_term([[1]]), from_term([], [[atom]]))),
752    {'EXIT', {type_mismatch, _}} =
753        (catch restriction(fun(_) -> from_term({a}) end,
754                           from_term([[a]]),
755                           from_term([], [atom]))),
756    {'EXIT', {badarg, _}} =
757        (catch restriction(fun(_) -> {a} end,
758                           from_term([[a]]),
759                           from_term([], [atom]))),
760    ok.
761
762drestriction(Conf) when is_list(Conf) ->
763    E = empty_set(),
764    ER = relation([], 2),
765
766    %% set of ordered sets
767    S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
768    eval(drestriction(S1, set([a,b])), relation([{c,0}])),
769    eval(drestriction(2, S1, set([1,2])),
770	 relation([{b,22},{c,0}])),
771    eval(drestriction(S1, set([a,b,c])), ER),
772    eval(drestriction(2, ER, set([a,b])), ER),
773    eval(drestriction(1, S1, set([0,1,d,e])), S1),
774    eval(drestriction(1, S1, E), S1),
775    eval(drestriction({external, fun({_A,B,C}) -> {B,C} end},
776		      relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
777		      relation([{bb,2},{cc,3}])),
778	 relation([{a,aa,1}])),
779    Id = fun(X) -> X end,
780    XId = {external, Id},
781    eval(drestriction(XId, relation([{a,b}]), E), relation([{a,b}])),
782    eval(drestriction(XId, E, relation([{b,d}])), E),
783    Fun1 = fun(S) -> {_A,B,C} = to_external(S), from_term({B,C}) end,
784    eval(drestriction(Fun1,
785		      relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
786		      relation([{bb,2},{cc,3}])),
787	 relation([{a,aa,1}])),
788    eval(drestriction({external, fun({_,{A},B}) -> {A,B} end},
789		      from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
790		      from_term([{bb,2},{cc,3}])),
791	 from_term([{a,{aa},1}])),
792    S5 = relation([{1,a},{2,b},{3,c}]),
793    eval(drestriction(2, S5, set([b,c])), relation([{1,a}])),
794    S4 = relation([{a,1},{b,2},{b,27},{c,0}]),
795    eval(drestriction(2, S4, set([])), S4),
796    S6 = relation([{1,a},{2,c},{3,b}]),
797    eval(drestriction(2, S6, set([d,e])), S6),
798    eval(drestriction(2,
799		      relation([{1,d},{2,c},{3,b},{4,a},{5,e}]),
800		      set([c])),
801	 relation([{1,d},{3,b},{4,a},{5,e}])),
802    eval(drestriction(XId,
803		      relation([{1,a},{3,b},{4,c},{4,d}]),
804		      relation([{2,a},{2,c},{4,c}])),
805	 relation([{1,a},{3,b},{4,d}])),
806    eval(drestriction(2, relation([{a,b}]), E), relation([{a,b}])),
807    eval(drestriction(2, E, relation([{b,d}])), E),
808    eval(drestriction(2, relation([{b,d}]), E), relation([{b,d}])),
809    eval(drestriction(XId, E, set([a])), E),
810    eval(drestriction(1, S1, E), S1),
811    {'EXIT', {badarg, _}} =
812	(catch drestriction(3, relation([{a,b}]), E)),
813    {'EXIT', {badarg, _}} =
814	(catch drestriction(3, relation([{a,b}]), relation([{b,d}]))),
815    {'EXIT', {badarg, _}} =
816	(catch drestriction(3, relation([{a,b}]), set([{b,d}]))),
817    {'EXIT', {type_mismatch, _}} =
818	(catch drestriction(2, relation([{a,b}]), relation([{b,d}]))),
819    {'EXIT', {type_mismatch, _}} =
820	(catch drestriction({external, fun({A,_B}) -> A end},
821			    relation([{a,b}]), relation([{b,d}]))),
822    {'EXIT', {badarg, _}} =
823	(catch drestriction({external, fun({A,_}) -> {A,0} end},
824			    from_term([{1,a}]),
825			    from_term([{1,0}]))),
826    eval(drestriction(2, relation([{a,d},{b,e},{c,b},{d,c}]), set([b,d])),
827	 relation([{b,e},{d,c}])),
828    {'EXIT', {function_clause, _}} =
829	(catch drestriction({external, fun({A,_B}) -> A end}, set([]), E)),
830
831    Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
832    eval(drestriction(Fun3, set([1,2]), from_term([{1,0}])),
833	 from_term([2])),
834
835    %% set of sets
836    {'EXIT', {badarg, _}} =
837        (catch drestriction({external, fun(X) -> X end},
838			    from_term([], [[atom]]), set([a]))),
839    S2 = from_term([], [[atom]]),
840    eval(drestriction(Id, S2, E), S2),
841    S3 = from_term([[a],[b]], [[atom]]),
842    eval(drestriction(Id, S3, E), S3),
843    eval(drestriction(Id, from_term([], [[atom]]), set([a])),
844	 from_term([], [[atom]])),
845    eval(drestriction(fun sofs:union/1,
846		      from_term([[[a],[b]], [[b],[c]],
847				 [[], [a,b]], [[1],[2]]]),
848		      from_term([[a,b],[1,2,3],[b,c]])),
849	 from_term([[[1],[2]]])),
850    eval(drestriction(fun(_) -> from_term([a]) end,
851		      from_term([], [[atom]]),
852		      from_term([], [[a]])),
853	 from_term([], [[atom]])),
854    {'EXIT', {type_mismatch, _}} =
855        (catch drestriction(fun(_) -> from_term([a]) end,
856                            from_term([[1,2],[3,4]]),
857                            from_term([], [atom]))),
858    Fun10 = fun(S) ->
859		    %% Cheating a lot...
860		    case to_external(S) of
861			[1] -> from_term({1,1});
862			_ -> S
863		    end
864	    end,
865    {'EXIT', {type_mismatch, _}} =
866        (catch drestriction(Fun10, from_term([[1]]), from_term([], [[atom]]))),
867    {'EXIT', {type_mismatch, _}} =
868        (catch drestriction(fun(_) -> from_term({a}) end,
869                            from_term([[a]]),
870                            from_term([], [atom]))),
871    {'EXIT', {badarg, _}} =
872        (catch drestriction(fun(_) -> {a} end,
873			    from_term([[a]]),
874			    from_term([], [atom]))),
875    ok.
876
877strict_relation_1(Conf) when is_list(Conf) ->
878    E = empty_set(),
879    ER = relation([], 2),
880    eval(strict_relation(E), E),
881    eval(strict_relation(ER), ER),
882    eval(strict_relation(relation([{1,a},{a,a},{2,b}])),
883	 relation([{1,a},{2,b}])),
884    {'EXIT', {badarg, _}} =
885        (catch strict_relation(relation([{1,2,3}]))),
886    F = 0.0, I = round(F),
887    FR = relation([{F,I}]),
888    if
889        F == I -> % term ordering
890            eval(strict_relation(FR), ER);
891        true ->
892            eval(strict_relation(FR), FR)
893    end,
894    ok.
895
896extension(Conf) when is_list(Conf) ->
897    E = empty_set(),
898    ER = relation([], 2),
899    EF = family([]),
900    C1 = from_term(3),
901    C2 = from_term([3]),
902    {'EXIT', {function_clause, _}} = (catch extension(foo, E, C1)),
903    {'EXIT', {function_clause, _}} = (catch extension(ER, foo, C1)),
904    {'EXIT', {{case_clause, _},_}} = (catch extension(ER, E, foo)),
905    {'EXIT', {type_mismatch, _}} = (catch extension(ER, E, E)),
906    {'EXIT', {badarg, _}} = (catch extension(C2, E, E)),
907    eval(E, extension(E, E, E)),
908    eval(EF, extension(EF, E, E)),
909    eval(family([{3,[]}]), extension(EF, set([3]), E)),
910    eval(ER, extension(ER, E, C1)),
911    eval(E, extension(E, ER, E)),
912    eval(from_term([],[{{atom,atom},type(ER)}]), extension(E, ER, ER)),
913
914    R1 = relation([{c,7},{c,9},{c,11},{d,17},{f,20}]),
915    S1 = set([a,c,d,e]),
916    eval(extension(R1, S1, C1), lextension(R1, S1, C1)),
917
918    S2 = set([1,2,3]),
919    eval(extension(ER, S2, C1), lextension(ER, S2, C1)),
920
921    R3 = relation([{4,a},{8,b}]),
922    S3 = set([1,2,3,4,5,6,7,8,9,10,11]),
923    eval(extension(R3, S3, C1), lextension(R3, S3, C1)),
924
925    R4 = relation([{2,b},{4,d},{6,f}]),
926    S4 = set([1,3,5,7]),
927    eval(extension(R4, S4, C1), lextension(R4, S4, C1)),
928
929    F1 = family([{a,[1]},{c,[2]}]),
930    S5 = set([a,b,c,d]),
931    eval(extension(F1, S5, C2), lextension(F1, S5, C2)),
932    ok.
933
934lextension(R, S, C) ->
935    union(R, drestriction(1, constant_function(S, C), domain(R))).
936
937weak_relation_1(Conf) when is_list(Conf) ->
938    E = empty_set(),
939    ER = relation([], 2),
940    eval(weak_relation(E), E),
941    eval(weak_relation(ER), ER),
942    eval(weak_relation(relation([{a,1},{a,2},{b,2},{c,c}])),
943	 relation([{1,1},{2,2},{a,1},{a,2},{a,a},{b,2},{b,b},{c,c}])),
944    eval(weak_relation(relation([{a,1},{a,a},{a,b}])),
945	 relation([{1,1},{a,1},{a,a},{a,b},{b,b}])),
946    eval(weak_relation(relation([{a,1},{a,b},{7,w}])),
947	 relation([{1,1},{7,7},{7,w},{a,1},{a,a},{a,b},{b,b},{w,w}])),
948    {'EXIT', {badarg, _}} =
949	(catch weak_relation(from_term([{{a},a}]))),
950    {'EXIT', {badarg, _}} =
951	(catch weak_relation(from_term([{a,a}],[{d,r}]))),
952    {'EXIT', {badarg, _}} = (catch weak_relation(relation([{1,2,3}]))),
953
954    F = 0.0, I = round(F),
955    if
956        F == I -> % term ordering
957            FR1 = relation([{F,I}]),
958            eval(weak_relation(FR1), FR1),
959            FR2 = relation([{F,2},{I,1}]),
960            true = no_elements(weak_relation(FR2)) =:= 5,
961            FR3 = relation([{1,0},{1.0,1}]),
962            true = no_elements(weak_relation(FR3)) =:= 3;
963        true ->
964            ok
965    end,
966    ok.
967
968to_sets_1(Conf) when is_list(Conf) ->
969    {'EXIT', {badarg, _}} = (catch to_sets(from_term(a))),
970    {'EXIT', {function_clause, _}} = (catch to_sets(a)),
971    %% unordered
972    [] = to_sets(empty_set()),
973    eval(to_sets(from_term([a])), [from_term(a)]),
974    eval(to_sets(from_term([[]],[[atom]])), [set([])]),
975
976    L = [from_term([a,b]),from_term([c,d])],
977    eval(to_sets(from_sets(L)), L),
978
979    eval(to_sets(relation([{a,1},{b,2}])),
980	 [from_term({a,1},{atom,atom}), from_term({b,2},{atom,atom})]),
981
982    %% ordered
983    O = {from_term(a,atom), from_term({b}, {atom}), set([c,d])},
984    eval(to_sets(from_sets(O)), O),
985    ok.
986
987
988specification(Conf) when is_list(Conf) ->
989    Fun = {external, fun(I) when is_integer(I) -> true; (_) -> false end},
990    [1,2,3] = to_external(specification(Fun, set([a,1,b,2,c,3]))),
991
992    Fun2 = fun(S) -> is_subset(S, set([1,3,5,7,9])) end,
993    S2 = from_term([[1],[2],[3],[4],[5],[6],[7]]),
994    eval(specification(Fun2, S2), from_term([[1],[3],[5],[7]])),
995    Fun2x = fun([1]) -> true;
996	       ([3]) -> true;
997	       (_) -> false
998	    end,
999    eval(specification({external,Fun2x}, S2), from_term([[1],[3]])),
1000
1001    Fun3 = fun(_) -> neither_true_nor_false end,
1002    {'EXIT', {badarg, _}} =
1003	(catch specification(Fun3, set([a]))),
1004    {'EXIT', {badarg, _}} =
1005	(catch specification({external, Fun3}, set([a]))),
1006    {'EXIT', {badarg, _}} =
1007	(catch specification(Fun3, from_term([[a]]))),
1008    {'EXIT', {function_clause, _}} =
1009	(catch specification(Fun, a)),
1010    ok.
1011
1012union_1(Conf) when is_list(Conf) ->
1013    E = empty_set(),
1014    ER = relation([], 2),
1015    {'EXIT', {badarg, _}} = (catch union(ER)),
1016    {'EXIT', {type_mismatch, _}} =
1017	(catch union(relation([{a,b}]), relation([{a,b,c}]))),
1018    {'EXIT', {type_mismatch, _}} =
1019	(catch union(from_term([{a,b}]), from_term([{c,[x]}]))),
1020    {'EXIT', {type_mismatch, _}} =
1021	(catch union(from_term([{a,b}]), from_term([{c,d}], [{d,r}]))),
1022    {'EXIT', {badarg, _}} = (catch union(set([a,b,c]))),
1023    eval(union(E), E),
1024    eval(union(from_term([[]],[[atom]])), set([])),
1025    eval(union(from_term([[{a,b},{b,c}],[{b,c}]])),
1026	 relation([{a,b},{b,c}])),
1027    eval(union(from_term([[1,2,3],[2,3,4],[3,4,5]])),
1028	 set([1,2,3,4,5])),
1029
1030    eval(union(from_term([{[a],[],c}]), from_term([{[],[],q}])),
1031	 from_term([{[a],[],c},{[],[],q}])),
1032
1033    eval(union(E, E), E),
1034    eval(union(set([a,b]), E), set([a,b])),
1035    eval(union(E, set([a,b])), set([a,b])),
1036
1037    eval(union(from_term([[a,b]])), from_term([a,b])),
1038    ok.
1039
1040intersection_1(Conf) when is_list(Conf) ->
1041    E = empty_set(),
1042    {'EXIT', {badarg, _}} = (catch intersection(from_term([a,b]))),
1043    {'EXIT', {badarg, _}} = (catch intersection(E)),
1044    {'EXIT', {type_mismatch, _}} =
1045	(catch intersection(relation([{a,b}]), relation([{a,b,c}]))),
1046    {'EXIT', {type_mismatch, _}} =
1047	(catch intersection(relation([{a,b}]), from_term([{a,b}],[{d,r}]))),
1048
1049    eval(intersection(from_term([[a,b,c],[d,e,f],[g,h,i]])), set([])),
1050
1051    eval(intersection(E, E), E),
1052    eval(intersection(set([a,b,c]),set([0,b,q])),
1053	 set([b])),
1054    eval(intersection(set([0,b,q]),set([a,b,c])),
1055	 set([b])),
1056    eval(intersection(set([a,b,c]),set([a,b,c])),
1057	 set([a,b,c])),
1058    eval(intersection(set([a,b,d]),set([c,d])),
1059	 set([d])),
1060    ok.
1061
1062difference(Conf) when is_list(Conf) ->
1063    E = empty_set(),
1064    {'EXIT', {type_mismatch, _}} =
1065	(catch difference(relation([{a,b}]), relation([{a,b,c}]))),
1066    eval(difference(E, E), E),
1067    {'EXIT', {type_mismatch, _}} =
1068	(catch difference(relation([{a,b}]), from_term([{a,c}],[{d,r}]))),
1069    eval(difference(set([a,b,c,d,f]), set([a,d,e,g])),
1070	 set([b,c,f])),
1071    eval(difference(set([a,b,c]), set([d,e,f])),
1072	 set([a,b,c])),
1073    eval(difference(set([a,b,c]), set([a,b,c,d,e,f])),
1074	 set([])),
1075    eval(difference(set([e,f,g]), set([a,b,c,e])),
1076	 set([f,g])),
1077    eval(difference(set([a,b,d,e,f]), set([c])),
1078	 set([a,b,d,e,f])),
1079    ok.
1080
1081symdiff(Conf) when is_list(Conf) ->
1082    E = empty_set(),
1083    {'EXIT', {type_mismatch, _}} =
1084	(catch symdiff(relation([{a,b}]), relation([{a,b,c}]))),
1085    {'EXIT', {type_mismatch, _}} =
1086	(catch symdiff(relation([{a,b}]), from_term([{a,b}], [{d,r}]))),
1087    eval(symdiff(E, E), E),
1088    eval(symdiff(set([a,b,c,d,e,f]), set([0,1,a,c])),
1089	 union(set([b,d,e,f]), set([0,1]))),
1090    eval(symdiff(set([a,b,c]), set([q,v,w,x,y])),
1091	 union(set([a,b,c]), set([q,v,w,x,y]))),
1092    eval(symdiff(set([a,b,c,d,e,f]), set([a,b,c])),
1093	 set([d,e,f])),
1094    eval(symdiff(set([c,e,g,h,i]), set([b,d,f])),
1095	 union(set([c,e,g,h,i]), set([b,d,f]))),
1096    eval(symdiff(set([c,d,g,h,k,l]),
1097		 set([a,b,e,f,i,j,m,n])),
1098	 union(set([c,d,g,h,k,l]), set([a,b,e,f,i,j,m,n]))),
1099    eval(symdiff(set([c,d,g,h,k,l]),
1100		 set([d,e,h,i,l,m,n,o,p])),
1101	 union(set([c,g,k]), set([e,i,m,n,o,p]))),
1102    ok.
1103
1104symmetric_partition(Conf) when is_list(Conf) ->
1105    E = set([]),
1106    S1 = set([1,2,3,4]),
1107    S2 = set([3,4,5,6]),
1108    S3 = set([3,4]),
1109    S4 = set([1,2,3,4,5,6]),
1110    T1 = set([1,2]),
1111    T2 = set([3,4]),
1112    T3 = set([5,6]),
1113    T4 = set([1,2,5,6]),
1114    {'EXIT', {type_mismatch, _}} =
1115	(catch symmetric_partition(relation([{a,b}]), relation([{a,b,c}]))),
1116    {E, E, E} = symmetric_partition(E, E),
1117    {'EXIT', {type_mismatch, _}} =
1118	(catch symmetric_partition(relation([{a,b}]),
1119                                   from_term([{a,c}],[{d,r}]))),
1120    {E, E, S1} = symmetric_partition(E, S1),
1121    {S1, E, E} = symmetric_partition(S1, E),
1122    {T1, T2, T3} = symmetric_partition(S1, S2),
1123    {T3, T2, T1} = symmetric_partition(S2, S1),
1124    {E, T2, T4} = symmetric_partition(S3, S4),
1125    {T4, T2, E} = symmetric_partition(S4, S3),
1126
1127    S5 = set([1,3,5]),
1128    S6 = set([2,4,6,7,8]),
1129    {S5, E, S6} = symmetric_partition(S5, S6),
1130    {S6, E, S5} = symmetric_partition(S6, S5),
1131    EE = empty_set(),
1132    {EE, EE, EE} = symmetric_partition(EE, EE),
1133
1134    ok.
1135
1136is_sofs_set_1(Conf) when is_list(Conf) ->
1137    E = empty_set(),
1138    true = is_sofs_set(E),
1139    true = is_sofs_set(from_term([a])),
1140    true = is_sofs_set(from_term({a})),
1141    true = is_sofs_set(from_term(a)),
1142    false = is_sofs_set(a),
1143    ok.
1144
1145is_set_1(Conf) when is_list(Conf) ->
1146    E = empty_set(),
1147    true = is_set(E),
1148    true = is_set(from_term([a])),
1149    false = is_set(from_term({a})),
1150    false = is_set(from_term(a)),
1151    {'EXIT', _} = (catch is_set(a)),
1152
1153    true = is_empty_set(E),
1154    false = is_empty_set(from_term([a])),
1155    false = is_empty_set(from_term({a})),
1156    false = is_empty_set(from_term(a)),
1157    {'EXIT', _} = (catch is_empty_set(a)),
1158
1159    ok.
1160
1161is_equal(Conf) when is_list(Conf) ->
1162    E = empty_set(),
1163    true = is_equal(E, E),
1164    false = is_equal(from_term([a]), E),
1165    {'EXIT', {type_mismatch, _}} =
1166	(catch is_equal(intersection(set([a]), set([b])),
1167			intersection(from_term([{a}]), from_term([{b}])))),
1168    {'EXIT', {type_mismatch, _}} =
1169	(catch is_equal(from_term([],[{[atom],atom,[atom]}]),
1170			from_term([],[{[atom],{atom},[atom]}]))),
1171    {'EXIT', {type_mismatch, _}} =
1172	(catch is_equal(set([a]), from_term([a],[type]))),
1173
1174    E2 = from_sets({from_term(a,atom)}),
1175    true = is_equal(E2, E2),
1176    true = is_equal(from_term({a}, {atom}), E2),
1177    false = is_equal(from_term([{[a],[],c}]),
1178		     from_term([{[],[],q}])),
1179
1180    {'EXIT', {type_mismatch, _}} =
1181        (catch is_equal(E, E2)),
1182    {'EXIT', {type_mismatch, _}} =
1183        (catch is_equal(E2, E)),
1184    true = is_equal(from_term({[],a,[]},{[atom],atom,[atom]}),
1185		    from_term({[],a,[]},{[atom],atom,[atom]})),
1186    {'EXIT', {type_mismatch, _}} =
1187	(catch is_equal(from_term({[],a,[]},{[atom],atom,[atom]}),
1188			from_term({[],{a},[]},{[atom],{atom},[atom]}))),
1189    {'EXIT', {type_mismatch, _}} =
1190	(catch is_equal(from_term({a}), from_term({a},{type}))),
1191
1192    ok.
1193
1194is_subset(Conf) when is_list(Conf) ->
1195    E = empty_set(),
1196    true = is_subset(E, E),
1197    true = is_subset(set([a,c,e]), set([a,b,c,d,e])),
1198    false = is_subset(set([a,b]), E),
1199    false = is_subset(set([d,e,f]), set([b,c,d,e])),
1200    false = is_subset(set([a,b,c]), set([b,c])),
1201    false = is_subset(set([b,c]), set([a,c])),
1202    false = is_subset(set([d,e]), set([a,b])),
1203    {'EXIT', {type_mismatch, _}} =
1204	(catch is_subset(intersection(set([a]), set([b])),
1205			 intersection(from_term([{a}]), from_term([{b}])))),
1206    {'EXIT', {type_mismatch, _}} =
1207        (catch is_subset(set([a]), from_term([a,b], [at]))),
1208    ok.
1209
1210is_a_function_1(Conf) when is_list(Conf) ->
1211    E = empty_set(),
1212    ER = relation([], 2),
1213    {'EXIT', {badarg, _}} = (catch is_a_function(set([a,b]))),
1214    true = is_a_function(E),
1215    true = is_a_function(ER),
1216    true = is_a_function(relation([])),
1217    true = is_a_function(relation([],2)),
1218    true = is_a_function(relation([{a,b},{b,c}])),
1219    false = is_a_function(relation([{a,b},{b,c},{b,d},{e,f}])),
1220    IS = relation([{{a,b},c},{{a,b},d}]),
1221    false = is_a_function(IS),
1222    F = 0.0, I = round(F),
1223    FR = relation([{I,F},{F,1}]),
1224    if
1225        F == I -> % term ordering
1226            false = is_a_function(FR);
1227        true ->
1228            true = is_a_function(FR)
1229    end,
1230    ok.
1231
1232is_disjoint(Conf) when is_list(Conf) ->
1233    E = empty_set(),
1234    {'EXIT', {type_mismatch, _}} =
1235	(catch is_disjoint(relation([{a,1}]), set([a,b]))),
1236    {'EXIT', {type_mismatch, _}} =
1237	(catch is_disjoint(set([a]), from_term([a],[mota]))),
1238    true = is_disjoint(E, E),
1239    false = is_disjoint(set([a,b,c]),set([b,c,d])),
1240    false = is_disjoint(set([b,c,d]),set([a,b,c])),
1241    true = is_disjoint(set([a,c,e]),set([b,d,f])),
1242    ok.
1243
1244join(Conf) when is_list(Conf) ->
1245    E = empty_set(),
1246
1247    {'EXIT', {badarg, _}} = (catch join(relation([{a,1}]), 3, E, 5)),
1248    {'EXIT', {badarg, _}} = (catch join(E, 1, relation([{a,1}]), 3)),
1249    {'EXIT', {badarg, _}} = (catch join(E, 1, from_term([a]), 1)),
1250
1251    eval(join(E, 1, E, 2), E),
1252    eval(join(E, 1, from_term([{{a},b}]), 2), E),
1253    eval(join(from_term([{{a},b}]), 2, E, 1), E),
1254    eval(join(from_term([{{a},b,e}]), 2, from_term([{c,{d}}]), 1),
1255	 from_term([], [{{atom},atom,atom,{atom}}])),
1256    eval(join(relation([{a}]), 1, relation([{1,a},{2,a}]), 2),
1257	 relation([{a,1},{a,2}])),
1258    eval(join(relation([{a,b,c},{b,c,d}]), 2,
1259	      relation([{1,b},{2,a},{3,c}]), 2),
1260	 relation([{a,b,c,1},{b,c,d,3}])),
1261    eval(join(relation([{1,a,aa},{1,b,bb},{1,c,cc},{2,a,aa},{2,b,bb}]),
1262	      1,
1263	      relation([{1,c,cc},{1,d,dd},{1,e,ee},{2,c,cc},{2,d,dd}]),
1264	      1),
1265	 relation([{1,a,aa,c,cc},{1,a,aa,d,dd},{1,a,aa,e,ee},{1,b,bb,c,cc},
1266		   {1,b,bb,d,dd},{1,b,bb,e,ee},{1,c,cc,c,cc},{1,c,cc,d,dd},
1267		   {1,c,cc,e,ee},{2,a,aa,c,cc},{2,a,aa,d,dd},{2,b,bb,c,cc},
1268		   {2,b,bb,d,dd}])),
1269
1270    R1 = relation([{a,b},{b,c}]),
1271    R2 = relation([{b,1},{a,2},{c,3},{c,4}]),
1272    eval(join(R1, 1, R2, 1), from_term([{a,b,2},{b,c,1}])),
1273    eval(join(R1, 2, R2, 1), from_term([{a,b,1},{b,c,3},{b,c,4}])),
1274    eval(join(R1, 1, converse(R2), 2),
1275	 from_term([{a,b,2},{b,c,1}])),
1276    eval(join(R1, 2, converse(R2), 2),
1277	 from_term([{a,b,1},{b,c,3},{b,c,4}])),
1278    ok.
1279
1280canonical(Conf) when is_list(Conf) ->
1281    E = empty_set(),
1282    {'EXIT', {badarg, _}} =
1283        (catch canonical_relation(set([a,b]))),
1284    eval(canonical_relation(E), E),
1285    eval(canonical_relation(from_term([[]])), E),
1286    eval(canonical_relation(from_term([[a,b,c]])),
1287	 from_term([{a,[a,b,c]},{b,[a,b,c]},{c,[a,b,c]}])),
1288    ok.
1289
1290relation_to_family_1(Conf) when is_list(Conf) ->
1291    E = empty_set(),
1292    EF = family([]),
1293    eval(relation_to_family(E), E),
1294    eval(relation_to_family(relation([])), EF),
1295    eval(relation_to_family(relation([], 2)), EF),
1296    R = relation([{b,1},{c,7},{c,9},{c,11}]),
1297    F = family([{b,[1]},{c,[7,9,11]}]),
1298    eval(relation_to_family(R), F),
1299    eval(sofs:rel2fam(R), F),
1300    {'EXIT', {badarg, _}} = (catch relation_to_family(set([a]))),
1301    ok.
1302
1303domain_1(Conf) when is_list(Conf) ->
1304    E = empty_set(),
1305    ER = relation([]),
1306    {'EXIT', {badarg, _}} = (catch domain(relation([],3))),
1307    eval(domain(E), E),
1308    eval(domain(ER), set([])),
1309    eval(domain(relation([{1,a},{1,b},{2,a},{2,b}])), set([1,2])),
1310    eval(domain(relation([{a,1},{b,2},{c,3}])), set([a,b,c])),
1311    eval(field(relation([{a,1},{b,2},{c,3}])),
1312	 set([a,b,c,1,2,3])),
1313    F = 0.0, I = round(F),
1314    FR = relation([{I,a},{F,b}]),
1315    if
1316        F == I -> % term ordering
1317            true = (1 =:= no_elements(domain(FR)));
1318        true ->
1319            true = (2 =:= no_elements(domain(FR)))
1320    end,
1321    ok.
1322
1323range_1(Conf) when is_list(Conf) ->
1324    E = empty_set(),
1325    ER = relation([]),
1326    {'EXIT', {badarg, _}} = (catch range(relation([],3))),
1327    eval(range(E), E),
1328    eval(range(ER), set([])),
1329    eval(range(relation([{1,a},{1,b},{2,a},{2,b}])), set([a,b])),
1330    eval(range(relation([{a,1},{b,2},{c,3}])), set([1,2,3])),
1331    ok.
1332
1333inverse_1(Conf) when is_list(Conf) ->
1334    E = empty_set(),
1335    ER = relation([]),
1336    {'EXIT', {badarg, _}} = (catch inverse(relation([],3))),
1337    {'EXIT', {bad_function, _}} =
1338	(catch inverse(relation([{1,a},{1,b}]))),
1339    {'EXIT', {bad_function, _}} =
1340	(catch inverse(relation([{1,a},{2,a}]))),
1341    eval(inverse(E), E),
1342    eval(inverse(ER), ER),
1343    eval(inverse(relation([{a,1},{b,2},{c,3}])),
1344	 relation([{1,a},{2,b},{3,c}])),
1345    F = 0.0, I = round(F),
1346    FR = relation([{I,a},{F,b}]),
1347    if
1348        F == I -> % term ordering
1349            {'EXIT', {bad_function, _}} = (catch inverse(FR));
1350        true ->
1351            eval(inverse(FR), relation([{a,I},{b,F}]))
1352    end,
1353    ok.
1354
1355converse_1(Conf) when is_list(Conf) ->
1356    E = empty_set(),
1357    ER = relation([]),
1358    {'EXIT', {badarg, _}} = (catch converse(relation([],3))),
1359    eval(converse(ER), ER),
1360    eval(converse(E), E),
1361    eval(converse(relation([{a,1},{b,2},{c,3}])),
1362	 relation([{1,a},{2,b},{3,c}])),
1363    eval(converse(relation([{1,a},{1,b}])),
1364	 relation([{a,1},{b,1}])),
1365    eval(converse(relation([{1,a},{2,a}])),
1366	 relation([{a,1},{a,2}])),
1367    ok.
1368
1369no_elements_1(Conf) when is_list(Conf) ->
1370    0 = no_elements(empty_set()),
1371    0 = no_elements(set([])),
1372    1 = no_elements(from_term([a])),
1373    10 = no_elements(from_term(lists:seq(1,10))),
1374    3 = no_elements(from_term({a,b,c},{atom,atom,atom})),
1375    {'EXIT', {badarg, _}} = (catch no_elements(from_term(a))),
1376    {'EXIT', {function_clause, _}} = (catch no_elements(a)),
1377    ok.
1378
1379image(Conf) when is_list(Conf) ->
1380    E = empty_set(),
1381    ER = relation([]),
1382    eval(image(E, E), E),
1383    eval(image(ER, E), set([])),
1384    eval(image(relation([{a,1},{b,2},{c,3},{f,6}]), set([a,b,c,d,f])),
1385	 set([1,2,3,6])),
1386    eval(image(relation([{a,1},{b,2},{c,3},{d,4},{r,17}]),
1387	       set([b,c,q,r])),
1388	 set([2,3,17])),
1389    eval(image(from_term([{[a],{1}},{[b],{2}}]), from_term([[a]])),
1390	 from_term([{1}])),
1391    eval(image(relation([{1,a},{2,a},{3,a},{4,b},{2,b}]), set([1,2,4])),
1392	 set([a,b])),
1393    {'EXIT', {badarg, _}} =
1394	(catch image(from_term([a,b]), E)),
1395    {'EXIT', {type_mismatch, _}} =
1396	(catch image(from_term([{[a],1}]), set([[a]]))),
1397    ok.
1398
1399inverse_image(Conf) when is_list(Conf) ->
1400    E = empty_set(),
1401    ER = relation([]),
1402    eval(inverse_image(E, E), E),
1403    eval(inverse_image(ER, E), set([])),
1404    eval(inverse_image(converse(relation([{a,1},{b,2},{c,3},{f,6}])),
1405		       set([a,b,c,d,f])),
1406	 set([1,2,3,6])),
1407    eval(inverse_image(converse(relation([{a,1},{b,2},{c,3},
1408					  {d,4},{r,17}])),
1409		       set([b,c,q,r])),
1410	 set([2,3,17])),
1411    eval(inverse_image(converse(from_term([{[a],{1}},{[b],{2}}])),
1412		       from_term([[a]])),
1413	 from_term([{1}])),
1414    eval(inverse_image(converse(relation([{1,a},{2,a},
1415					  {3,a},{4,b},{2,b}])),
1416		       set([1,2,4])),
1417	 set([a,b])),
1418    {'EXIT', {badarg, _}} =
1419	(catch inverse_image(from_term([a,b]), E)),
1420    {'EXIT', {type_mismatch, _}} =
1421	(catch inverse_image(converse(from_term([{[a],1}])), set([[a]]))),
1422    ok.
1423
1424composite_1(Conf) when is_list(Conf) ->
1425    E = empty_set(),
1426    EF = a_function([]),
1427    eval(composite(E, E), E),
1428    eval(composite(E, a_function([{a,b}])), E),
1429    eval(composite(relation([{a,b}]), E), E),
1430    {'EXIT', {bad_function, _}} =
1431	(catch composite(EF, relation([{a,b},{a,c}]))),
1432    {'EXIT', {bad_function, _}} =
1433	(catch composite(a_function([{b,a}]), EF)),
1434    {'EXIT', {bad_function, _}} =
1435	(catch composite(relation([{1,a},{2,b},{2,a}]),
1436			 a_function([{a,1},{b,3}]))),
1437    {'EXIT', {bad_function, _}} =
1438	(catch composite(a_function([{1,a},{2,b}]), a_function([{b,3}]))),
1439    eval(composite(EF, EF), EF),
1440    eval(composite(a_function([{b,a}]), from_term([{a,{b,c}}])),
1441	 from_term([{b,{b,c}}])),
1442    eval(composite(a_function([{q,1},{z,2}]),
1443		   a_function([{1,a},{2,a}])),
1444	 a_function([{q,a},{z,a}])),
1445    eval(composite(a_function([{a,0},{b,0},{c,1},{d,1},{e,2},{f,3}]),
1446		   a_function([{0,p},{1,q},{2,r},{3,w},{4,aa}])),
1447	 a_function([{c,q},{d,q},{f,w},{e,r},{a,p},{b,p}])),
1448    eval(composite(a_function([{1,c}]),
1449		   a_function([{a,1},{b,3},{c,4}])),
1450	 a_function([{1,4}])),
1451    {'EXIT', {bad_function, _}} =
1452	(catch composite(a_function([{1,a},{2,b}]),
1453			 a_function([{a,1},{c,3}]))),
1454    {'EXIT', {badarg, _}} =
1455	(catch composite(from_term([a,b]), E)),
1456    {'EXIT', {badarg, _}} =
1457	(catch composite(E, from_term([a,b]))),
1458    {'EXIT', {type_mismatch, _}} =
1459        (catch composite(from_term([{a,b}]), from_term([{{a},b}]))),
1460    {'EXIT', {type_mismatch, _}} =
1461        (catch composite(from_term([{a,b}]),
1462			 from_term([{b,c}], [{d,r}]))),
1463    F = 0.0, I = round(F),
1464    FR1 = relation([{1,c}]),
1465    FR2 = relation([{I,1},{F,3},{c,4}]),
1466    if
1467        F == I -> % term ordering
1468            {'EXIT', {bad_function, _}} = (catch composite(FR1, FR2));
1469        true ->
1470            eval(composite(FR1, FR2), a_function([{1,4}]))
1471    end,
1472    ok.
1473
1474relative_product_1(Conf) when is_list(Conf) ->
1475    E = empty_set(),
1476    ER = relation([]),
1477    eval(relative_product1(E, E), E),
1478    eval(relative_product1(E, relation([{a,b}])), E),
1479    eval(relative_product1(relation([{a,b}]), E), E),
1480    eval(relative_product1(relation([{a,b}]), from_term([{a,{b,c}}])),
1481	 from_term([{b,{b,c}}])),
1482    eval(relative_product1(relation([{1,z},{1,q},{2,z}]),
1483			   relation([{1,a},{1,b},{2,a}])),
1484	 relation([{q,a},{q,b},{z,a},{z,b}])),
1485    eval(relative_product1(relation([{0,a},{0,b},{1,c},
1486				     {1,d},{2,e},{3,f}]),
1487			   relation([{1,q},{3,w}])),
1488	 relation([{c,q},{d,q},{f,w}])),
1489    {'EXIT', {badarg, _}} =
1490	(catch relative_product1(from_term([a,b]), ER)),
1491    {'EXIT', {badarg, _}} =
1492	(catch relative_product1(ER, from_term([a,b]))),
1493    {'EXIT', {type_mismatch, _}} =
1494        (catch relative_product1(from_term([{a,b}]), from_term([{{a},b}]))),
1495    {'EXIT', {type_mismatch, _}} =
1496        (catch relative_product1(from_term([{a,b}]),
1497				 from_term([{b,c}], [{d,r}]))),
1498    ok.
1499
1500relative_product_2(Conf) when is_list(Conf) ->
1501    E = empty_set(),
1502    ER = relation([]),
1503
1504    {'EXIT', {badarg, _}} = (catch relative_product({from_term([a,b])})),
1505    {'EXIT', {type_mismatch, _}} =
1506	(catch relative_product({from_term([{a,b}]), from_term([{{a},b}])})),
1507    {'EXIT', {badarg, _}} = (catch relative_product({})),
1508    true = is_equal(relative_product({ER}),
1509		    from_term([], [{atom,{atom}}])),
1510    eval(relative_product({relation([{a,b},{c,a}]),
1511			   relation([{a,1},{a,2}]),
1512			   relation([{a,aa},{c,1}])}),
1513	 from_term([{a,{b,1,aa}},{a,{b,2,aa}}])),
1514    eval(relative_product({relation([{a,b}])}, E), E),
1515    eval(relative_product({E}, relation([{a,b}])), E),
1516    eval(relative_product({E,from_term([], [{{atom,atom,atom},atom}])}),
1517	 E),
1518    {'EXIT', {badarg, _}} =
1519        (catch relative_product({from_term([a,b])}, E)),
1520    {'EXIT', {badarg, _}} =
1521	(catch relative_product({relation([])}, set([]))),
1522    {'EXIT', {type_mismatch, _}} =
1523	(catch relative_product({from_term([{a,b}]),
1524				 from_term([{{a},b}])}, ER)),
1525
1526    {'EXIT', {badarg, _}} = (catch relative_product({}, ER)),
1527    relprod2({relation([{a,b}])}, from_term([],[{{atom},atom}]), ER),
1528    relprod2({relation([{a,b}]),relation([{a,1}])},
1529	     from_term([{{b,1},{tjo,hej,sa}}]),
1530	     from_term([{a,{tjo,hej,sa}}])),
1531    relprod2({relation([{a,b}]), ER}, from_term([{{a,b},b}]), ER),
1532    relprod2({relation([{a,b},{c,a}]),
1533	      relation([{a,1},{a,2}])},
1534	     from_term([{{b,1},b1},{{b,2},b2}]),
1535	     relation([{a,b1},{a,b2}])),
1536    eval(relative_product({relation([{a,b}]), ER}),
1537	 from_term([],[{atom,{atom,atom}}])),
1538    eval(relative_product({from_term([{{a,[a,b]},[a]}]),
1539			   from_term([{{a,[a,b]},[[a,b]]}])}),
1540	 from_term([{{a,[a,b]},{[a],[[a,b]]}}])),
1541    ok.
1542
1543relprod2(A1T, A2, R) ->
1544    %% A tuple as first argument is the old interface:
1545    eval(relative_product(A1T, A2), R),
1546    eval(relative_product(tuple_to_list(A1T), A2), R).
1547
1548product_1(Conf) when is_list(Conf) ->
1549    E = empty_set(),
1550    eval(product(E, E), E),
1551    eval(product(relation([]), E), E),
1552    eval(product(E, relation([])), E),
1553    eval(product(relation([{a,b}]),relation([{c,d}])),
1554	 from_term([{{a,b},{c,d}}],[{{atom,atom},{atom,atom}}])),
1555
1556    eval(product({E, set([a,b,c])}), E),
1557    eval(product({set([a,b,c]), E}), E),
1558    eval(product({set([a,b,c]), E, E}), E),
1559    eval(product({E,E}), E),
1560    eval(product({set([a,b]),set([1,2])}),
1561	 relation([{a,1},{a,2},{b,1},{b,2}])),
1562    eval(product({from_term([a,b]), from_term([{a,b},{c,d}]),
1563		  from_term([1])}),
1564	 from_term([{a,{a,b},1},{a,{c,d},1},{b,{a,b},1},{b,{c,d},1}])),
1565    {'EXIT', {badarg, _}} = (catch product({})),
1566    {'EXIT', {badarg, _}} = (catch product({foo})),
1567    eval(product({E}), E),
1568    eval(product({E, E}), E),
1569    eval(product(set([a,b]), set([1,2])),
1570	 relation([{a,1},{a,2},{b,1},{b,2}])),
1571    eval(product({relation([]), E}), E),
1572    ok.
1573
1574partition_1(Conf) when is_list(Conf) ->
1575    E = empty_set(),
1576    ER = relation([]),
1577    Id = fun(A) -> A end,
1578    S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
1579    eval(partition(1, E), E),
1580    eval(partition(2, E), E),
1581    eval(partition(1, ER), from_term([], [type(ER)])),
1582    eval(partition(2, ER), from_term([], [type(ER)])),
1583    eval(partition(1, relation([{1,a},{1,b},{2,c},{2,d}])),
1584	 from_term([[{1,a},{1,b}],[{2,c},{2,d}]])),
1585    eval(partition(2, relation([{1,a},{1,b},{2,a},{2,b},{3,c}])),
1586	 from_term([[{1,a},{2,a}],[{1,b},{2,b}],[{3,c}]])),
1587    eval(partition(2, relation([{1,a}])), from_term([[{1,a}]])),
1588    eval(partition(2, relation([{1,a},{2,b}])),
1589	 from_term([[{1,a}],[{2,b}]])),
1590    eval(partition(2, relation([{1,a},{2,a},{3,a}])),
1591	 from_term([[{1,a},{2,a},{3,a}]])),
1592    eval(partition(2, relation([{1,b},{2,a}])), % OTP-4516
1593	 from_term([[{1,b}],[{2,a}]])),
1594    eval(union(partition(Id, S1)), S1),
1595    eval(partition({external, fun({A,{B,_}}) -> {A,B} end},
1596		   from_term([{a,{b,c}},{b,{c,d}},{a,{b,f}}])),
1597	 from_term([[{a,{b,c}},{a,{b,f}}],[{b,{c,d}}]])),
1598    F = 0.0, I = round(F),
1599    FR = relation([{I,a},{F,b}]),
1600    if
1601        F == I -> % term ordering
1602            eval(partition(1, FR), from_term([[{I,a},{F,b}]]));
1603        true ->
1604            eval(partition(1, FR), from_term([[{I,a}],[{F,b}]]))
1605    end,
1606    {'EXIT', {badarg, _}} = (catch partition(2, set([a]))),
1607    {'EXIT', {badarg, _}} = (catch partition(1, set([a]))),
1608    eval(partition(Id, set([a])), from_term([[a]])),
1609
1610    eval(partition(E), E),
1611    P1 = from_term([[a,b,c],[d,e,f],[g,h]]),
1612    P2 = from_term([[a,d],[b,c,e,f,q,v]]),
1613    eval(partition(union(P1, P2)),
1614	 from_term([[a],[b,c],[d],[e,f],[g,h],[q,v]])),
1615    {'EXIT', {badarg, _}} = (catch partition(from_term([a]))),
1616    ok.
1617
1618partition_3(Conf) when is_list(Conf) ->
1619    E = empty_set(),
1620    ER = relation([]),
1621
1622    %% set of ordered sets
1623    S1 = relation([{a,1},{b,2},{b,22},{c,0}]),
1624    eval(partition(1, S1, set([0,1,d,e])),
1625	 lpartition(1, S1, set([0,1,d,e]))),
1626    eval(partition(1, S1, E), lpartition(1, S1, E)),
1627    eval(partition(2, ER, set([a,b])), lpartition(2, ER, set([a,b]))),
1628
1629    XFun1 = {external, fun({_A,B,C}) -> {B,C} end},
1630    R1a = relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
1631    R1b = relation([{bb,2},{cc,3}]),
1632    eval(partition(XFun1, R1a, R1b), lpartition(XFun1, R1a, R1b)),
1633
1634    Id = fun(X) -> X end,
1635    XId = {external, Id},
1636    R2 = relation([{a,b}]),
1637    eval(partition(XId, R2, E), lpartition(XId, R2, E)),
1638
1639    R3 = relation([{b,d}]),
1640    eval(partition(XId, E, R3), lpartition(XId, E, R3)),
1641
1642    Fun1 = fun(S) -> {_A,B,C} = to_external(S), from_term({B,C}) end,
1643    R4a = relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
1644    R4b = relation([{bb,2},{cc,3}]),
1645    eval(partition(Fun1,R4a,R4b), lpartition(Fun1,R4a,R4b)),
1646
1647    XFun2 = {external, fun({_,{A},B}) -> {A,B} end},
1648    R5a = from_term([{a,{aa},1},{b,{bb},2},{c,{cc},3}]),
1649    R5b = from_term([{bb,2},{cc,3}]),
1650    eval(partition(XFun2,R5a, R5b), lpartition(XFun2,R5a, R5b)),
1651
1652    R6 = relation([{a,b}]),
1653    eval(partition(2, R6, E), lpartition(2, R6, E)),
1654
1655    R7 = relation([{b,d}]),
1656    eval(partition(2, E, R7), lpartition(2, E, R7)),
1657
1658    S2 = set([a]),
1659    eval(partition(XId, E, S2), lpartition(XId, E, S2)),
1660    eval(partition(XId, S1, E), lpartition(XId, S1, E)),
1661    {'EXIT', {badarg, _}} =
1662	(catch partition(3, relation([{a,b}]), E)),
1663    {'EXIT', {badarg, _}} =
1664	(catch partition(3, relation([{a,b}]), relation([{b,d}]))),
1665    {'EXIT', {badarg, _}} =
1666	(catch partition(3, relation([{a,b}]), set([{b,d}]))),
1667    {'EXIT', {type_mismatch, _}} =
1668	(catch partition(2, relation([{a,b}]), relation([{b,d}]))),
1669    {'EXIT', {type_mismatch, _}} =
1670	(catch partition({external, fun({A,_B}) -> A end},
1671			 relation([{a,b}]), relation([{b,d}]))),
1672    {'EXIT', {badarg, _}} =
1673	(catch partition({external, fun({A,_}) -> {A,0} end},
1674			 from_term([{1,a}]),
1675			 from_term([{1,0}]))),
1676
1677    S18a = relation([{1,e},{2,b},{3,c},{4,b},{5,a},{6,0}]),
1678    S18b = set([b,d,f]),
1679    eval(partition({external,fun({_,X}) -> X end}, S18a, S18b),
1680	 lpartition({external,fun({_,X}) -> X end}, S18a, S18b)),
1681    S19a = sofs:relation([{3,a},{8,b}]),
1682    S19b = set([2,6,7]),
1683    eval(partition({external,fun({X,_}) -> X end}, S19a, S19b),
1684	 lpartition({external,fun({X,_}) -> X end}, S19a, S19b)),
1685
1686    R8a = relation([{a,d},{b,e},{c,b},{d,c}]),
1687    S8 = set([b,d]),
1688    eval(partition(2, R8a, S8), lpartition(2, R8a, S8)),
1689
1690    S16a = relation([{1,e},{2,b},{3,c},{4,b},{5,a},{6,0}]),
1691    S16b = set([b,c,d]),
1692    eval(partition(2, S16a, S16b), lpartition(2, S16a, S16b)),
1693    S17a = relation([{e,1},{b,2},{c,3},{b,4},{a,5},{0,6}]),
1694    S17b = set([b,c,d]),
1695    eval(partition(1, S17a, S17b), lpartition(1, S17a, S17b)),
1696
1697    {'EXIT', {function_clause, _}} =
1698	(catch partition({external, fun({A,_B}) -> A end}, set([]), E)),
1699
1700    Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
1701    S9a = set([1,2]),
1702    S9b = from_term([{1,0}]),
1703    eval(partition(Fun3, S9a, S9b), lpartition(Fun3, S9a, S9b)),
1704
1705    S14a = relation([{1,a},{2,b},{3,c},{0,0}]),
1706    S14b = set([b,c]),
1707    eval(partition(2, S14a, S14b), lpartition(2, S14a, S14b)),
1708    S15a = relation([{a,1},{b,2},{c,3},{0,0}]),
1709    S15b = set([b,c]),
1710    eval(partition(1, S15a, S15b), lpartition(1, S15a, S15b)),
1711
1712    %% set of sets
1713    {'EXIT', {badarg, _}} =
1714        (catch partition({external, fun(X) -> X end},
1715			 from_term([], [[atom]]), set([a]))),
1716
1717    S10 = from_term([], [[atom]]),
1718    eval(partition(Id, S10, E), lpartition(Id, S10, E)),
1719
1720    S10e = from_term([[a],[b]], [[atom]]),
1721    eval(partition(Id, S10e, E), lpartition(Id, S10e, E)),
1722
1723    S11a = from_term([], [[atom]]),
1724    S11b = set([a]),
1725    eval(partition(Id, S11a, S11b), lpartition(Id, S11a, S11b)),
1726
1727    S12a = from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]),
1728    S12b = from_term([[a,b],[1,2,3],[b,c]]),
1729    eval(partition(fun sofs:union/1, S12a, S12b),
1730	 lpartition(fun sofs:union/1, S12a, S12b)),
1731
1732    Fun13 = fun(_) -> from_term([a]) end,
1733    S13a = from_term([], [[atom]]),
1734    S13b = from_term([], [[a]]),
1735    eval(partition(Fun13, S13a, S13b), lpartition(Fun13, S13a, S13b)),
1736
1737    {'EXIT', {type_mismatch, _}} =
1738        (catch partition(fun(_) -> from_term([a]) end,
1739			 from_term([[1,2],[3,4]]),
1740			 from_term([], [atom]))),
1741    Fun10 = fun(S) ->
1742		    %% Cheating a lot...
1743		    case to_external(S) of
1744			[1] -> from_term({1,1});
1745			_ -> S
1746		    end
1747	    end,
1748    {'EXIT', {type_mismatch, _}} =
1749        (catch partition(Fun10, from_term([[1]]), from_term([], [[atom]]))),
1750    {'EXIT', {type_mismatch, _}} =
1751        (catch partition(fun(_) -> from_term({a}) end,
1752			 from_term([[a]]),
1753			 from_term([], [atom]))),
1754    {'EXIT', {badarg, _}} =
1755        (catch partition(fun(_) -> {a} end,
1756			 from_term([[a]]),
1757			 from_term([], [atom]))),
1758    ok.
1759
1760lpartition(F, S1, S2) ->
1761    {restriction(F, S1, S2), drestriction(F, S1, S2)}.
1762
1763multiple_relative_product(Conf) when is_list(Conf) ->
1764    E = empty_set(),
1765    ER = relation([]),
1766    T = relation([{a,1},{a,11},{b,2},{c,3},{c,33},{d,4}]),
1767    {'EXIT', {badarg, _}} =
1768        (catch multiple_relative_product({}, ER)),
1769    {'EXIT', {badarg, _}} =
1770	(catch multiple_relative_product({}, relation([{a,b}]))),
1771    eval(multiple_relative_product({E,T,T}, relation([], 3)), E),
1772    eval(multiple_relative_product({T,T,T}, E), E),
1773    eval(multiple_relative_product({T,T,T}, relation([],3)),
1774	 from_term([],[{{atom,atom,atom},{atom,atom,atom}}])),
1775    eval(multiple_relative_product({T,T,T},
1776                                   relation([{a,b,c},{c,d,a}])),
1777	 from_term([{{a,b,c},{1,2,3}}, {{a,b,c},{1,2,33}},
1778		    {{a,b,c},{11,2,3}}, {{a,b,c},{11,2,33}},
1779		    {{c,d,a},{3,4,1}}, {{c,d,a},{3,4,11}},
1780		    {{c,d,a},{33,4,1}}, {{c,d,a},{33,4,11}}])),
1781    {'EXIT', {type_mismatch, _}} =
1782	(catch multiple_relative_product({T}, from_term([{{a}}]))),
1783    ok.
1784
1785digraph(Conf) when is_list(Conf) ->
1786    T0 = lists:sort(ets:all()),
1787    E = empty_set(),
1788    R = relation([{a,b},{b,c},{c,d},{d,a}]),
1789    F = relation_to_family(R),
1790    Type = type(F),
1791
1792    {'EXIT', {badarg, _}} =
1793        (catch family_to_digraph(set([a]))),
1794    digraph_fail(badarg, catch family_to_digraph(set([a]), [foo])),
1795    digraph_fail(badarg, catch family_to_digraph(F, [foo])),
1796    digraph_fail(cyclic, catch family_to_digraph(family([{a,[a]}]),[acyclic])),
1797
1798    G1 = family_to_digraph(E),
1799    {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, foo)),
1800    {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, atom)),
1801    true = [] == to_external(digraph_to_family(G1)),
1802    true = [] == to_external(digraph_to_family(G1, Type)),
1803    true = digraph:delete(G1),
1804
1805    G1a = family_to_digraph(E, [protected]),
1806    true = [] == to_external(digraph_to_family(G1a)),
1807    true = [] == to_external(digraph_to_family(G1a, Type)),
1808    true = digraph:delete(G1a),
1809
1810    G2 = family_to_digraph(F),
1811    true = F == digraph_to_family(G2),
1812    true = F == digraph_to_family(G2, type(F)),
1813    true = digraph:delete(G2),
1814
1815    R2 = from_term([{{a},b},{{c},d}]),
1816    F2 = relation_to_family(R2),
1817    Type2 = type(F2),
1818    G3 = family_to_digraph(F2, [protected]),
1819    true = is_subset(F2, digraph_to_family(G3, Type2)),
1820    true = digraph:delete(G3),
1821
1822    Fl = 0.0, I = round(Fl),
1823    if
1824        Fl == I -> % term ordering
1825            G4 = digraph:new(),
1826            digraph:add_vertex(G4, Fl),
1827            digraph:add_vertex(G4, I),
1828            {'EXIT', {badarg, _}} =
1829                (catch digraph_to_family(G4, Type)),
1830            {'EXIT', {badarg, _}} =
1831                (catch digraph_to_family(G4)),
1832            true = digraph:delete(G4);
1833        true -> ok
1834    end,
1835
1836    true = T0 == lists:sort(ets:all()),
1837    ok.
1838
1839digraph_fail(ExitReason, Fail) ->
1840    {'EXIT', {ExitReason, [{sofs,family_to_digraph,2,_}|_]}} = Fail,
1841    ok.
1842
1843constant_function(Conf) when is_list(Conf) ->
1844    E = empty_set(),
1845    C = from_term(3),
1846    eval(constant_function(E, C), E),
1847    eval(constant_function(set([a,b]), E), from_term([{a,[]},{b,[]}])),
1848    eval(constant_function(set([a,b]), C), from_term([{a,3},{b,3}])),
1849    {'EXIT', {badarg, _}} = (catch constant_function(C, C)),
1850    {'EXIT', {badarg, _}} = (catch constant_function(set([]), foo)),
1851    ok.
1852
1853misc(Conf) when is_list(Conf) ->
1854    %% find "relational" part of relation:
1855    S = relation([{a,b},{b,c},{b,d},{c,d}]),
1856    Id = fun(A) -> A end,
1857    RR = relational_restriction(S),
1858    eval(union(difference(partition(Id,S), partition(1,S))), RR),
1859    eval(union(difference(partition(1,S), partition(Id,S))), RR),
1860
1861    %% the "functional" part:
1862    eval(union(intersection(partition(1,S), partition(Id,S))),
1863	 difference(S, RR)),
1864    {'EXIT', {undef, _}} =
1865        (catch projection(fun external:foo/1, set([a,b,c]))),
1866    ok.
1867
1868relational_restriction(R) ->
1869    Fun = fun(S) -> no_elements(S) > 1 end,
1870    family_to_relation(family_specification(Fun, relation_to_family(R))).
1871
1872
1873family_specification(Conf) when is_list(Conf) ->
1874    E = empty_set(),
1875    %% internal
1876    eval(family_specification(fun sofs:is_set/1, E), E),
1877    {'EXIT', {badarg, _}} =
1878	(catch family_specification(fun sofs:is_set/1, set([]))),
1879    F1 = from_term([{1,[1]}]),
1880    eval(family_specification(fun sofs:is_set/1, F1), F1),
1881    Fun = fun(S) -> is_subset(S, set([0,1,2,3,4])) end,
1882    F2 = family([{a,[1,2]},{b,[3,4,5]}]),
1883    eval(family_specification(Fun, F2), family([{a,[1,2]}])),
1884    F3 = from_term([{a,[]},{b,[]}]),
1885    eval(family_specification(fun sofs:is_set/1, F3), F3),
1886    Fun2 = fun(_) -> throw(fippla) end,
1887    fippla = (catch family_specification(Fun2, family([{a,[1]}]))),
1888    Fun3 = fun(_) -> neither_true_nor_false end,
1889    {'EXIT', {badarg, _}} =
1890	(catch family_specification(Fun3, F3)),
1891
1892    %% external
1893    IsList = {external, fun(L) when is_list(L) -> true; (_) -> false end},
1894    eval(family_specification(IsList, E), E),
1895    eval(family_specification(IsList, F1), F1),
1896    MF = {external, fun(L) -> lists:member(3, L) end},
1897    eval(family_specification(MF, F2), family([{b,[3,4,5]}])),
1898    fippla = (catch family_specification(Fun2, family([{a,[1]}]))),
1899    {'EXIT', {badarg, _}} =
1900	(catch family_specification({external, Fun3}, F3)),
1901    ok.
1902
1903family_domain_1(Conf) when is_list(Conf) ->
1904    E = empty_set(),
1905    ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
1906    EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
1907    eval(family_domain(E), E),
1908    eval(family_domain(ER), EF),
1909    FR = from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
1910    eval(family_domain(FR), from_term([{a,[1,2,3]},{b,[]},{c,[4,5]}])),
1911    eval(family_field(E), E),
1912    eval(family_field(FR),
1913	 from_term([{a,[a,b,c,1,2,3]},{b,[]},{c,[d,e,4,5]}])),
1914    eval(family_domain(from_term([{{a},[{{1,[]},c}]}])),
1915	 from_term([{{a},[{1,[]}]}])),
1916    eval(family_domain(from_term([{{a},[{{1,[a]},c}]}])),
1917	 from_term([{{a},[{1,[a]}]}])),
1918    eval(family_domain(from_term([{{a},[]}])),
1919	 from_term([{{a},[]}])),
1920    eval(family_domain(from_term([], type(FR))),
1921	 from_term([], [{atom,[atom]}])),
1922    {'EXIT', {badarg, _}} = (catch family_domain(set([a]))),
1923    {'EXIT', {badarg, _}} = (catch family_field(set([a]))),
1924    {'EXIT', {badarg, _}} = (catch family_domain(set([{a,[b]}]))),
1925    ok.
1926
1927family_range_1(Conf) when is_list(Conf) ->
1928    E = empty_set(),
1929    ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
1930    EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
1931    eval(family_range(E), E),
1932    eval(family_range(ER), EF),
1933    FR = from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
1934    eval(family_range(FR), from_term([{a,[a,b,c]},{b,[]},{c,[d,e]}])),
1935    eval(family_range(from_term([{{a},[{c,{1,[a]}}]}])),
1936	 from_term([{{a},[{1,[a]}]}])),
1937    eval(family_range(from_term([{{a},[{c,{1,[]}}]}])),
1938	 from_term([{{a},[{1,[]}]}])),
1939    eval(family_range(from_term([{{a},[]}])),
1940	 from_term([{{a},[]}])),
1941    eval(family_range(from_term([], type(FR))),
1942	 from_term([], [{atom,[atom]}])),
1943    {'EXIT', {badarg, _}} = (catch family_range(set([a]))),
1944    {'EXIT', {badarg, _}} = (catch family_range(set([{a,[b]}]))),
1945    ok.
1946
1947family_to_relation_1(Conf) when is_list(Conf) ->
1948    E = empty_set(),
1949    ER = relation([]),
1950    EF = family([]),
1951    eval(family_to_relation(E), E),
1952    eval(family_to_relation(EF), ER),
1953    eval(sofs:fam2rel(EF), ER),
1954    F = family([{a,[]},{b,[1]},{c,[7,9,11]}]),
1955    eval(family_to_relation(F), relation([{b,1},{c,7},{c,9},{c,11}])),
1956    {'EXIT', {badarg, _}} = (catch family_to_relation(set([a]))),
1957    ok.
1958
1959union_of_family_1(Conf) when is_list(Conf) ->
1960    E = empty_set(),
1961    EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
1962    eval(union_of_family(E), E),
1963    eval(union_of_family(EF), set([])),
1964    eval(union_of_family(family([])), set([])),
1965    FR = from_term([{a,[1,2,3]},{b,[]},{c,[4,5]}]),
1966    eval(union_of_family(FR), set([1,2,3,4,5])),
1967    eval(union_of_family(sofs:family([{a,[1,2]},{b,[1,2]}])),
1968	 set([1,2])),
1969    {'EXIT', {badarg, _}} = (catch union_of_family(set([a]))),
1970    ok.
1971
1972intersection_of_family_1(Conf) when is_list(Conf) ->
1973    EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
1974    eval(intersection_of_family(EF), set([])),
1975    FR = from_term([{a,[1,2,3]},{b,[2,3]},{c,[3,4,5]}]),
1976    eval(intersection_of_family(FR), set([3])),
1977    {'EXIT', {badarg, _}} =
1978        (catch intersection_of_family(family([]))),
1979    EE = from_term([], [[atom]]),
1980    {'EXIT', {badarg, _}} = (catch intersection_of_family(EE)),
1981    {'EXIT', {badarg, _}} = (catch intersection_of_family(set([a]))),
1982    ok.
1983
1984family_projection(Conf) when is_list(Conf) ->
1985    SSType = [{atom,[[atom]]}],
1986    SRType = [{atom,[{atom,atom}]}],
1987    E = empty_set(),
1988
1989    eval(family_projection(fun(X) -> X end, family([])), E),
1990    L1 = [{a,[]}],
1991    eval(family_projection(fun sofs:union/1, E), E),
1992    eval(family_projection(fun sofs:union/1, from_term(L1, SSType)),
1993	 family(L1)),
1994    {'EXIT', {badarg, _}} =
1995        (catch family_projection(fun sofs:union/1, set([]))),
1996    {'EXIT', {badarg, _}} =
1997        (catch family_projection(fun sofs:union/1, from_term([{1,[1]}]))),
1998
1999    F2 = from_term([{a,[[1],[2]]},{b,[[3,4],[5]]}], SSType),
2000    eval(family_projection(fun sofs:union/1, F2),
2001	 family_union(F2)),
2002
2003    F3 = from_term([{1,[{a,b},{b,c},{c,d}]},{3,[]},{5,[{3,5}]}],
2004		   SRType),
2005    eval(family_projection(fun sofs:domain/1, F3), family_domain(F3)),
2006    eval(family_projection(fun sofs:range/1, F3), family_range(F3)),
2007
2008    eval(family_projection(fun(_) -> E end, family([{a,[b,c]}])),
2009	 from_term([{a,[]}])),
2010
2011    Fun1 = fun(S) ->
2012                   case to_external(S) of
2013                       [1] -> from_term({1,1});
2014                       _ -> S
2015                   end
2016           end,
2017    eval(family_projection(Fun1, family([{a,[1]}])),
2018	 from_term([{a,{1,1}}])),
2019    Fun2 = fun(_) -> throw(fippla) end,
2020    fippla =
2021        (catch family_projection(Fun2, family([{a,[1]}]))),
2022    {'EXIT', {type_mismatch, _}} =
2023        (catch family_projection(Fun1, from_term([{1,[1]},{2,[2]}]))),
2024    {'EXIT', {type_mismatch, _}} =
2025        (catch family_projection(Fun1, from_term([{1,[1]},{0,[0]}]))),
2026
2027    eval(family_projection(fun(_) -> E end, from_term([{a,[]}])),
2028	 from_term([{a,[]}])),
2029    F4 = from_term([{a,[{1,2,3}]},{b,[{4,5,6}]},{c,[]},{m3,[]}]),
2030    Z = from_term(0),
2031    eval(family_projection(fun(S) -> local_adjoin(S, Z) end, F4),
2032	 from_term([{a,[{{1,2,3},0}]},{b,[{{4,5,6},0}]},{c,[]},{m3,[]}])),
2033    {'EXIT', {badarg, _}} =
2034        (catch family_projection({external, fun(X) -> X end},
2035				 from_term([{1,[1]}]))),
2036
2037    %% ordered set element
2038    eval(family_projection(fun(_) -> from_term(a, atom) end,
2039			   from_term([{1,[a]}])),
2040	 from_term([{1,a}])),
2041    ok.
2042
2043family_difference(Conf) when is_list(Conf) ->
2044    E = empty_set(),
2045    EF = family([]),
2046    F9 = from_term([{b,[b,c]}]),
2047    F10 = from_term([{a,[b,c]}]),
2048    eval(family_difference(E, E), E),
2049    eval(family_difference(E, F10), from_term([], type(F10))),
2050    eval(family_difference(F10, E), F10),
2051    eval(family_difference(F9, F10), F9),
2052    eval(family_difference(F10, F10), family([{a,[]}])),
2053    F20 = from_term([{a,[1,2,3]},{b,[1,2,3]},{c,[1,2,3]}]),
2054    F21 = from_term([{b,[1,2,3]},{c,[1,2,3]}]),
2055    eval(family_difference(F20, from_term([{a,[2]}])),
2056	 from_term([{a,[1,3]},{b,[1,2,3]},{c,[1,2,3]}])),
2057    eval(family_difference(F20, from_term([{0,[2]},{q,[1,2]}])), F20),
2058    eval(family_difference(F20, F21),
2059	 from_term([{a,[1,2,3]},{b,[]},{c,[]}])),
2060
2061    eval(family_difference(from_term([{e,[f,g]}]), family([])),
2062	 from_term([{e,[f,g]}])),
2063    eval(family_difference(from_term([{e,[f,g]}]), EF),
2064	 from_term([{e,[f,g]}])),
2065    eval(family_difference(from_term([{a,[a,b,c,d]},{c,[b,c]}]),
2066			   from_term([{a,[b,c]},{b,[d]},{d,[e,f]}])),
2067	 from_term([{a,[a,d]},{c,[b,c]}])),
2068    {'EXIT', {badarg, _}} =
2069	(catch family_difference(set([]), set([]))),
2070    {'EXIT', {type_mismatch, _}} =
2071	(catch family_difference(from_term([{a,[b,c]}]),
2072                                 from_term([{e,[{f}]}]))),
2073    {'EXIT', {type_mismatch, _}} =
2074	(catch family_difference(from_term([{a,[b]}]),
2075                                 from_term([{c,[d]}], [{i,[s]}]))),
2076    ok.
2077
2078family_intersection_1(Conf) when is_list(Conf) ->
2079    E = empty_set(),
2080    EF = family([]),
2081    ES = from_term([], [{atom,[[atom]]}]),
2082    eval(family_intersection(E), E),
2083    {'EXIT', {badarg, _}} = (catch family_intersection(EF)),
2084    eval(family_intersection(ES), EF),
2085    {'EXIT', {badarg, _}} = (catch family_intersection(set([]))),
2086    {'EXIT', {badarg, _}} =
2087        (catch family_intersection(from_term([{a,[1,2]}]))),
2088    F1 = from_term([{a,[[1],[2],[2,3]]},{b,[]},{c,[[4]]}]),
2089    {'EXIT', {badarg, _}} = (catch family_intersection(F1)),
2090    F2 = from_term([{b,[[1],[2],[2,3]]},{a,[]},{c,[[4]]}]),
2091    {'EXIT', {badarg, _}} = (catch family_intersection(F2)),
2092    F3 = from_term([{a,[[1,2,3],[2],[2,3]]},{c,[[4,5,6],[5,6,7]]}]),
2093    eval(family_intersection(F3), family([{a,[2]},{c,[5,6]}])),
2094    ok.
2095
2096family_intersection_2(Conf) when is_list(Conf) ->
2097    E = empty_set(),
2098    EF = family([]),
2099    F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
2100    F2 = from_term([{c,[6,7]},{d,[9,10,11]},{q,[1]}]),
2101    F3 = from_term([{a,[1,2]},{b,[4,5]},{c,[6,7,8]},{d,[9,10,11]},
2102		    {q,[1]}]),
2103
2104    eval(family_intersection(E, E), E),
2105    eval(family_intersection(EF, EF), EF),
2106    eval(family_intersection(F1, F2),
2107	 from_term([{c,[7]},{d,[10,11]}])),
2108    eval(family_intersection(F1, F3), F1),
2109    eval(family_intersection(F2, F3), F2),
2110
2111    eval(family_intersection(EF, from_term([{e,[f,g]}])), EF),
2112    eval(family_intersection(E, from_term([{e,[f,g]}])), EF),
2113    eval(family_intersection(from_term([{e,[f,g]}]), EF), EF),
2114    eval(family_intersection(from_term([{e,[f,g]}]), E), EF),
2115    {'EXIT', {type_mismatch, _}} =
2116	(catch family_intersection(from_term([{a,[b,c]}]),
2117                                   from_term([{e,[{f}]}]))),
2118
2119    F11 = family([{a,[1,2,3]},{b,[0,2,4]},{c,[0,3,6,9]}]),
2120    eval(union_of_family(F11), set([0,1,2,3,4,6,9])),
2121    F12 = from_term([{a,[1,2,3,4]},{b,[0,2,4]},{c,[2,3,4,5]}]),
2122    eval(intersection_of_family(F12), set([2,4])),
2123    ok.
2124
2125family_union_1(Conf) when is_list(Conf) ->
2126    E = empty_set(),
2127    EF = family([]),
2128    ES = from_term([], [{atom,[[atom]]}]),
2129    eval(family_union(E), E),
2130    eval(family_union(ES), EF),
2131    {'EXIT', {badarg, _}} = (catch family_union(set([]))),
2132    {'EXIT', {badarg, _}} =
2133        (catch family_union(from_term([{a,[1,2]}]))),
2134    eval(family_union(from_term([{a,[[1],[2],[2,3]]},{b,[]},{c,[[4]]}])),
2135	 family([{a,[1,2,3]},{b,[]},{c,[4]}])),
2136    ok.
2137
2138family_union_2(Conf) when is_list(Conf) ->
2139    E = empty_set(),
2140    EF = family([]),
2141    F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
2142    F2 = from_term([{c,[6,7]},{d,[9,10,11]},{q,[1]}]),
2143    F3 = from_term([{a,[1,2]},{b,[4,5]},{c,[6,7,8]},{d,[9,10,11]},
2144		    {q,[1]}]),
2145
2146    eval(family_union(E, E), E),
2147    eval(family_union(F1, E), F1),
2148    eval(family_union(E, F2), F2),
2149    eval(family_union(F1, F2), F3),
2150    eval(family_union(F2, F1), F3),
2151
2152    eval(family_union(E, from_term([{e,[f,g]}])),
2153	 from_term([{e,[f,g]}])),
2154    eval(family_union(EF, from_term([{e,[f,g]}])),
2155	 from_term([{e,[f,g]}])),
2156    eval(family_union(from_term([{e,[f,g]}]), E),
2157	 from_term([{e,[f,g]}])),
2158    {'EXIT', {badarg, _}} =
2159	(catch family_union(set([]),set([]))),
2160    {'EXIT', {type_mismatch, _}} =
2161	(catch family_union(from_term([{a,[b,c]}]),
2162                            from_term([{e,[{f}]}]))),
2163    ok.
2164
2165partition_family(Conf) when is_list(Conf) ->
2166    E = empty_set(),
2167
2168    %% set of ordered sets
2169    ER = relation([]),
2170    EF = from_term([], [{atom,[{atom,atom}]}]),
2171
2172    eval(partition_family(1, E), E),
2173    eval(partition_family(2, E), E),
2174    eval(partition_family(fun sofs:union/1, E), E),
2175    eval(partition_family(1, ER), EF),
2176    eval(partition_family(2, ER), EF),
2177    {'EXIT', {badarg, _}} = (catch partition_family(1, set([]))),
2178    {'EXIT', {badarg, _}} = (catch partition_family(2, set([]))),
2179    {'EXIT', {function_clause, _}} =
2180	(catch partition_family(fun({_A,B}) -> {B} end, from_term([{1}]))),
2181    eval(partition_family(1, relation([{1,a},{1,b},{2,c},{2,d}])),
2182	 from_term([{1,[{1,a},{1,b}]},{2,[{2,c},{2,d}]}])),
2183    eval(partition_family(1, relation([{1,a},{2,b}])),
2184	 from_term([{1,[{1,a}]},{2,[{2,b}]}])),
2185    eval(partition_family(2, relation([{1,a},{1,b},{2,a},{2,b},{3,c}])),
2186	 from_term([{a,[{1,a},{2,a}]},{b,[{1,b},{2,b}]},{c,[{3,c}]}])),
2187    eval(partition_family(2, relation([{1,a}])),
2188	 from_term([{a,[{1,a}]}])),
2189    eval(partition_family(2, relation([{1,a},{2,a},{3,a}])),
2190	 from_term([{a,[{1,a},{2,a},{3,a}]}])),
2191    eval(partition_family(2, relation([{1,a},{2,b}])),
2192	 from_term([{a,[{1,a}]},{b,[{2,b}]}])),
2193    F13 = from_term([{a,b,c},{a,b,d},{b,b,c},{a,c,c},{a,c,d},{b,c,c}]),
2194    eval(partition_family(2, F13),
2195	 from_term([{b,[{a,b,c},{a,b,d},{b,b,c}]},
2196		    {c,[{a,c,c},{a,c,d},{b,c,c}]}])),
2197
2198    Fun1 = {external, fun({A,_B}) -> {A} end},
2199    eval(partition_family(Fun1, relation([{a,1},{a,2},{b,3}])),
2200	 from_term([{{a},[{a,1},{a,2}]},{{b},[{b,3}]}])),
2201    Fun2 = fun(S) -> {A,_B} = to_external(S), from_term({A}) end,
2202    eval(partition_family(Fun2, relation([{a,1},{a,2},{b,3}])),
2203	 from_term([{{a},[{a,1},{a,2}]},{{b},[{b,3}]}])),
2204
2205    {'EXIT', {badarg, _}} =
2206	(catch partition_family({external, fun({A,_}) -> {A,0} end},
2207				from_term([{1,a}]))),
2208    [{{atom,atom},[{atom,atom,atom,atom}]}] =
2209	type(partition_family({external, fun({A,_B,C,_D}) -> {C,A} end},
2210			      relation([],4))),
2211
2212    Fun3 = fun(S) -> from_term({to_external(S),0}, {type(S),atom}) end,
2213    eval(partition_family(Fun3, E), E),
2214    eval(partition_family(Fun3, set([a,b])),
2215	 from_term([{{a,0},[a]}, {{b,0},[b]}])),
2216    eval(partition_family(Fun3, relation([{a,1},{b,2}])),
2217	 from_term([{{{a,1},0},[{a,1}]},{{{b,2},0},[{b,2}]}])),
2218    eval(partition_family(Fun3, from_term([[a],[b]])),
2219	 from_term([{{[a],0},[[a]]}, {{[b],0},[[b]]}])),
2220    partition_family({external, fun(X) -> X end}, E),
2221
2222    F = 0.0, I = round(F),
2223    FR = relation([{I,a},{F,b}]),
2224    if
2225        F == I -> % term ordering
2226            true = (1 =:= no_elements(partition_family(1, FR)));
2227        true ->
2228            eval(partition_family(1, FR),
2229		 from_term([{I,[{I,a}]},{F,[{F,b}]}]))
2230    end,
2231    %% set of sets
2232    {'EXIT', {badarg, _}} =
2233        (catch partition_family({external, fun(X) -> X end},
2234				from_term([], [[atom]]))),
2235    {'EXIT', {badarg, _}} =
2236        (catch partition_family({external, fun(X) -> X end},
2237				from_term([[a]]))),
2238    eval(partition_family(fun sofs:union/1,
2239			  from_term([[[1],[1,2]], [[1,2]]])),
2240	 from_term([{[1,2], [[[1],[1,2]],[[1,2]]]}])),
2241    eval(partition_family(fun(X) -> X end,
2242			  from_term([[1],[1,2],[1,2,3]])),
2243	 from_term([{[1],[[1]]},{[1,2],[[1,2]]},{[1,2,3],[[1,2,3]]}])),
2244
2245    eval(partition_family(fun(_) -> from_term([a]) end,
2246			  from_term([], [[atom]])),
2247	 E),
2248    Fun10 = fun(S) ->
2249		    %% Cheating a lot...
2250		    case to_external(S) of
2251			[1] -> from_term({1,1});
2252			_ -> S
2253		    end
2254	    end,
2255
2256    eval(partition_family(Fun10, from_term([[1]])),
2257	 from_term([{{1,1},[[1]]}])),
2258    eval(partition_family(fun(_) -> from_term({a}) end,
2259			  from_term([[a]])),
2260	 from_term([{{a},[[a]]}])),
2261    {'EXIT', {badarg, _}} =
2262	(catch partition_family(fun(_) -> {a} end, from_term([[a]]))),
2263    ok.
2264
2265%% Not meant to be efficient...
2266local_adjoin(S, C) ->
2267    X = to_external(C),
2268    T = type(C),
2269    F = fun(Y) -> from_term({to_external(Y),X}, {type(Y),T}) end,
2270    projection(F, S).
2271
2272eval(R, E) when R == E ->
2273    R;
2274eval(R, E) ->
2275    io:format("expected ~p~n got ~p~n", [E, R]),
2276    exit({R,E}).
2277
2278