~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/test/sofs_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2001-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(sofs_SUITE).
26
26
-define(config(X,Y), foo).
27
27
-define(t, test_server).
28
28
-else.
29
 
-include("test_server.hrl").
 
29
-include_lib("test_server/include/test_server.hrl").
30
30
-define(format(S, A), ok).
31
31
-endif.
32
32
 
33
 
-export([all/1]).
 
33
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
34
         init_per_group/2,end_per_group/2]).
34
35
 
35
 
-export([sofs/1, from_term_1/1, set_1/1, from_sets_1/1, relation_1/1,
 
36
-export([ from_term_1/1, set_1/1, from_sets_1/1, relation_1/1,
36
37
         a_function_1/1, family_1/1, projection/1,
37
38
         relation_to_family_1/1, domain_1/1, range_1/1, image/1,
38
39
         inverse_image/1, inverse_1/1, converse_1/1, no_elements_1/1,
47
48
         multiple_relative_product/1, digraph/1, constant_function/1,
48
49
         misc/1]).
49
50
 
50
 
-export([sofs_family/1, family_specification/1,
 
51
-export([ family_specification/1,
51
52
         family_domain_1/1, family_range_1/1,
52
53
         family_to_relation_1/1, 
53
54
         union_of_family_1/1, intersection_of_family_1/1,
81
82
         union/1, union/2, family_to_digraph/1, family_to_digraph/2,
82
83
         digraph_to_family/1, digraph_to_family/2]).
83
84
 
84
 
-export([init_per_testcase/2, fin_per_testcase/2]).
 
85
-export([init_per_testcase/2, end_per_testcase/2]).
85
86
 
86
87
-compile({inline,[{eval,2}]}).
87
88
 
88
 
all(suite) ->
89
 
    [sofs, sofs_family].
 
89
suite() -> [{ct_hooks,[ts_install_cth]}].
 
90
 
 
91
all() -> 
 
92
    [{group, sofs}, {group, sofs_family}].
 
93
 
 
94
groups() -> 
 
95
    [{sofs, [],
 
96
      [from_term_1, set_1, from_sets_1, relation_1,
 
97
       a_function_1, family_1, relation_to_family_1, domain_1,
 
98
       range_1, image, inverse_image, inverse_1, converse_1,
 
99
       no_elements_1, substitution, restriction, drestriction,
 
100
       projection, strict_relation_1, extension,
 
101
       weak_relation_1, to_sets_1, specification, union_1,
 
102
       intersection_1, difference, symdiff,
 
103
       symmetric_partition, is_sofs_set_1, is_set_1, is_equal,
 
104
       is_subset, is_a_function_1, is_disjoint, join,
 
105
       canonical, composite_1, relative_product_1,
 
106
       relative_product_2, product_1, partition_1, partition_3,
 
107
       multiple_relative_product, digraph, constant_function,
 
108
       misc]},
 
109
     {sofs_family, [],
 
110
      [family_specification, family_domain_1, family_range_1,
 
111
       family_to_relation_1, union_of_family_1,
 
112
       intersection_of_family_1, family_projection,
 
113
       family_difference, family_intersection_1,
 
114
       family_intersection_2, family_union_1, family_union_2,
 
115
       partition_family]}].
 
116
 
 
117
init_per_suite(Config) ->
 
118
    Config.
 
119
 
 
120
end_per_suite(_Config) ->
 
121
    ok.
 
122
 
 
123
init_per_group(_GroupName, Config) ->
 
124
    Config.
 
125
 
 
126
end_per_group(_GroupName, Config) ->
 
127
    Config.
 
128
 
90
129
 
91
130
init_per_testcase(_Case, Config) ->
92
131
    Dog=?t:timetrap(?t:minutes(2)),
93
132
    [{watchdog, Dog}|Config].
94
133
 
95
 
fin_per_testcase(_Case, Config) ->
 
134
end_per_testcase(_Case, Config) ->
96
135
    Dog=?config(watchdog, Config),
97
136
    test_server:timetrap_cancel(Dog),
98
137
    ok.
100
139
%% [{2,b},{1,a,b}] == lists:sort([{2,b},{1,a,b}])
101
140
%% [{1,a,b},{2,b}] == lists:keysort(1,[{2,b},{1,a,b}])
102
141
 
103
 
sofs(suite) ->
104
 
    [from_term_1, set_1, from_sets_1, relation_1, a_function_1,
105
 
     family_1, relation_to_family_1, domain_1, range_1, image,
106
 
     inverse_image, inverse_1, converse_1, no_elements_1,
107
 
     substitution, restriction, drestriction, projection,
108
 
     strict_relation_1, extension, weak_relation_1, to_sets_1,
109
 
     specification, union_1, intersection_1, difference, symdiff,
110
 
     symmetric_partition, is_sofs_set_1, is_set_1, is_equal,
111
 
     is_subset, is_a_function_1, is_disjoint, join, canonical,
112
 
     composite_1, relative_product_1, relative_product_2, product_1,
113
 
     partition_1, partition_3, multiple_relative_product, digraph,
114
 
     constant_function, misc].
115
142
 
116
143
from_term_1(suite) -> [];
117
144
from_term_1(doc) -> [""];
118
 
from_term_1(Conf) when list(Conf) ->
 
145
from_term_1(Conf) when is_list(Conf) ->
119
146
    %% would go wrong: projection(1,from_term([{2,b},{1,a,b}])),
120
147
 
121
148
    ?line {'EXIT', {badarg, _}} = (catch from_term([], {atom,'_',atom})),
203
230
 
204
231
set_1(suite) -> [];
205
232
set_1(doc) -> [""];
206
 
set_1(Conf) when list(Conf) ->
 
233
set_1(Conf) when is_list(Conf) ->
207
234
    %% set/1
208
235
    ?line {'EXIT', {badarg, _}} = (catch set(a)),
209
236
    ?line {'EXIT', {badarg, _}} = (catch set({a})),
235
262
 
236
263
from_sets_1(suite) -> [];
237
264
from_sets_1(doc) -> [""];
238
 
from_sets_1(Conf) when list(Conf) ->
 
265
from_sets_1(Conf) when is_list(Conf) ->
239
266
    ?line E = empty_set(),
240
267
 
241
268
    %% unordered
272
299
 
273
300
relation_1(suite) -> [];
274
301
relation_1(doc) -> [""];
275
 
relation_1(Conf) when list(Conf) ->
 
302
relation_1(Conf) when is_list(Conf) ->
276
303
    %% relation/1
277
304
    ?line eval(relation([]), from_term([], [{atom,atom}])),
278
305
    ?line eval(from_term([{a}]), relation([{a}])),
305
332
 
306
333
a_function_1(suite) -> [];
307
334
a_function_1(doc) -> [""];
308
 
a_function_1(Conf) when list(Conf) ->
 
335
a_function_1(Conf) when is_list(Conf) ->
309
336
    %% a_function/1
310
337
    ?line eval(a_function([]), from_term([], [{atom,atom}])),
311
338
    ?line eval(a_function([{a,b},{a,b},{b,c}]), from_term([{a,b},{b,c}])),
352
379
 
353
380
family_1(suite) -> [];
354
381
family_1(doc) -> [""];
355
 
family_1(Conf) when list(Conf) ->
 
382
family_1(Conf) when is_list(Conf) ->
356
383
    %% family/1
357
384
    ?line eval(family([]), from_term([],[{atom,[atom]}])),
358
385
    ?line {'EXIT', {badarg, _}} = (catch family(a)),
413
440
 
414
441
projection(suite) -> [];
415
442
projection(doc) -> [""];
416
 
projection(Conf) when list(Conf) ->
 
443
projection(Conf) when is_list(Conf) ->
417
444
    ?line E = empty_set(),
418
445
    ?line ER = relation([]),
419
446
 
535
562
 
536
563
substitution(suite) -> [];
537
564
substitution(doc) -> [""];
538
 
substitution(Conf) when list(Conf) ->
 
565
substitution(Conf) when is_list(Conf) ->
539
566
    ?line E = empty_set(),
540
567
    ?line ER = relation([]),
541
568
 
633
660
 
634
661
restriction(suite) -> [];
635
662
restriction(doc) -> [""];
636
 
restriction(Conf) when list(Conf) ->
 
663
restriction(Conf) when is_list(Conf) ->
637
664
    ?line E = empty_set(),
638
665
    ?line ER = relation([], 2),
639
666
 
752
779
 
753
780
drestriction(suite) -> [];
754
781
drestriction(doc) -> [""];
755
 
drestriction(Conf) when list(Conf) ->
 
782
drestriction(Conf) when is_list(Conf) ->
756
783
    ?line E = empty_set(),
757
784
    ?line ER = relation([], 2),
758
785
 
869
896
 
870
897
strict_relation_1(suite) -> [];
871
898
strict_relation_1(doc) -> [""];
872
 
strict_relation_1(Conf) when list(Conf) ->
 
899
strict_relation_1(Conf) when is_list(Conf) ->
873
900
    ?line E = empty_set(),
874
901
    ?line ER = relation([], 2),
875
902
    ?line eval(strict_relation(E), E),
890
917
 
891
918
extension(suite) -> [];
892
919
extension(doc) -> [""];
893
 
extension(Conf) when list(Conf) ->
 
920
extension(Conf) when is_list(Conf) ->
894
921
    ?line E = empty_set(),
895
922
    ?line ER = relation([], 2),
896
923
    ?line EF = family([]),
933
960
 
934
961
weak_relation_1(suite) -> [];
935
962
weak_relation_1(doc) -> [""];
936
 
weak_relation_1(Conf) when list(Conf) ->
 
963
weak_relation_1(Conf) when is_list(Conf) ->
937
964
    ?line E = empty_set(),
938
965
    ?line ER = relation([], 2),
939
966
    ?line eval(weak_relation(E), E),
966
993
 
967
994
to_sets_1(suite) ->  [];
968
995
to_sets_1(doc) -> [""];
969
 
to_sets_1(Conf) when list(Conf) ->
 
996
to_sets_1(Conf) when is_list(Conf) ->
970
997
    ?line {'EXIT', {badarg, _}} = (catch to_sets(from_term(a))),
971
998
    ?line {'EXIT', {function_clause, _}} = (catch to_sets(a)),
972
999
    %% unordered
988
1015
 
989
1016
specification(suite) -> [];
990
1017
specification(doc) -> [""];
991
 
specification(Conf) when list(Conf) ->
992
 
    Fun = {external, fun(I) when integer(I) -> true; (_) -> false end},
 
1018
specification(Conf) when is_list(Conf) ->
 
1019
    Fun = {external, fun(I) when is_integer(I) -> true; (_) -> false end},
993
1020
    ?line [1,2,3] = to_external(specification(Fun, set([a,1,b,2,c,3]))),
994
1021
 
995
1022
    Fun2 = fun(S) -> is_subset(S, set([1,3,5,7,9])) end,
1014
1041
 
1015
1042
union_1(suite) -> [];
1016
1043
union_1(doc) -> [""];
1017
 
union_1(Conf) when list(Conf) ->
 
1044
union_1(Conf) when is_list(Conf) ->
1018
1045
    ?line E = empty_set(),
1019
1046
    ?line ER = relation([], 2),
1020
1047
    ?line {'EXIT', {badarg, _}} = (catch union(ER)),
1044
1071
 
1045
1072
intersection_1(suite) -> [];
1046
1073
intersection_1(doc) -> [""];
1047
 
intersection_1(Conf) when list(Conf) ->
 
1074
intersection_1(Conf) when is_list(Conf) ->
1048
1075
    ?line E = empty_set(),
1049
1076
    ?line {'EXIT', {badarg, _}} = (catch intersection(from_term([a,b]))),
1050
1077
    ?line {'EXIT', {badarg, _}} = (catch intersection(E)),
1068
1095
 
1069
1096
difference(suite) -> [];
1070
1097
difference(doc) -> [""];
1071
 
difference(Conf) when list(Conf) ->
 
1098
difference(Conf) when is_list(Conf) ->
1072
1099
    ?line E = empty_set(),
1073
1100
    ?line {'EXIT', {type_mismatch, _}} =
1074
1101
        (catch difference(relation([{a,b}]), relation([{a,b,c}]))),
1089
1116
 
1090
1117
symdiff(suite) -> [];
1091
1118
symdiff(doc) -> [""];
1092
 
symdiff(Conf) when list(Conf) ->
 
1119
symdiff(Conf) when is_list(Conf) ->
1093
1120
    ?line E = empty_set(),
1094
1121
    ?line {'EXIT', {type_mismatch, _}} =
1095
1122
        (catch symdiff(relation([{a,b}]), relation([{a,b,c}]))),
1114
1141
 
1115
1142
symmetric_partition(suite) -> [];
1116
1143
symmetric_partition(doc) -> [""];
1117
 
symmetric_partition(Conf) when list(Conf) ->
 
1144
symmetric_partition(Conf) when is_list(Conf) ->
1118
1145
    ?line E = set([]),
1119
1146
    ?line S1 = set([1,2,3,4]),
1120
1147
    ?line S2 = set([3,4,5,6]),
1148
1175
 
1149
1176
is_sofs_set_1(suite) -> [];
1150
1177
is_sofs_set_1(doc) -> [""];
1151
 
is_sofs_set_1(Conf) when list(Conf) ->
 
1178
is_sofs_set_1(Conf) when is_list(Conf) ->
1152
1179
    ?line E = empty_set(),
1153
1180
    ?line true = is_sofs_set(E),
1154
1181
    ?line true = is_sofs_set(from_term([a])),
1159
1186
 
1160
1187
is_set_1(suite) -> [];
1161
1188
is_set_1(doc) -> [""];
1162
 
is_set_1(Conf) when list(Conf) ->
 
1189
is_set_1(Conf) when is_list(Conf) ->
1163
1190
    ?line E = empty_set(),
1164
1191
    ?line true = is_set(E),
1165
1192
    ?line true = is_set(from_term([a])),
1177
1204
 
1178
1205
is_equal(suite) -> [];
1179
1206
is_equal(doc) -> [""];
1180
 
is_equal(Conf) when list(Conf) ->
 
1207
is_equal(Conf) when is_list(Conf) ->
1181
1208
    ?line E = empty_set(),
1182
1209
    ?line true = is_equal(E, E),
1183
1210
    ?line false = is_equal(from_term([a]), E),
1212
1239
 
1213
1240
is_subset(suite) -> [];
1214
1241
is_subset(doc) -> [""];
1215
 
is_subset(Conf) when list(Conf) ->
 
1242
is_subset(Conf) when is_list(Conf) ->
1216
1243
    ?line E = empty_set(),
1217
1244
    ?line true = is_subset(E, E),
1218
1245
    ?line true = is_subset(set([a,c,e]), set([a,b,c,d,e])),
1230
1257
 
1231
1258
is_a_function_1(suite) -> [];
1232
1259
is_a_function_1(doc) -> [""];
1233
 
is_a_function_1(Conf) when list(Conf) ->
 
1260
is_a_function_1(Conf) when is_list(Conf) ->
1234
1261
    ?line E = empty_set(),
1235
1262
    ?line ER = relation([], 2),
1236
1263
    ?line {'EXIT', {badarg, _}} = (catch is_a_function(set([a,b]))),
1254
1281
 
1255
1282
is_disjoint(suite) -> [];
1256
1283
is_disjoint(doc) -> [""];
1257
 
is_disjoint(Conf) when list(Conf) ->
 
1284
is_disjoint(Conf) when is_list(Conf) ->
1258
1285
    ?line E = empty_set(),
1259
1286
    ?line {'EXIT', {type_mismatch, _}} = 
1260
1287
        (catch is_disjoint(relation([{a,1}]), set([a,b]))),
1268
1295
 
1269
1296
join(suite) -> [];
1270
1297
join(doc) -> [""];
1271
 
join(Conf) when list(Conf) ->
 
1298
join(Conf) when is_list(Conf) ->
1272
1299
    ?line E = empty_set(),
1273
1300
 
1274
1301
    ?line {'EXIT', {badarg, _}} = (catch join(relation([{a,1}]), 3, E, 5)),
1306
1333
 
1307
1334
canonical(suite) -> [];
1308
1335
canonical(doc) -> [""];
1309
 
canonical(Conf) when list(Conf) ->
 
1336
canonical(Conf) when is_list(Conf) ->
1310
1337
    ?line E = empty_set(),    
1311
1338
    ?line {'EXIT', {badarg, _}} = 
1312
1339
        (catch canonical_relation(set([a,b]))),
1318
1345
 
1319
1346
relation_to_family_1(suite) -> [];
1320
1347
relation_to_family_1(doc) -> [""];
1321
 
relation_to_family_1(Conf) when list(Conf) ->
 
1348
relation_to_family_1(Conf) when is_list(Conf) ->
1322
1349
    ?line E = empty_set(),
1323
1350
    ?line EF = family([]),
1324
1351
    ?line eval(relation_to_family(E), E),
1333
1360
 
1334
1361
domain_1(suite) -> [];
1335
1362
domain_1(doc) -> [""];
1336
 
domain_1(Conf) when list(Conf) ->
 
1363
domain_1(Conf) when is_list(Conf) ->
1337
1364
    ?line E = empty_set(),
1338
1365
    ?line ER = relation([]),
1339
1366
    ?line {'EXIT', {badarg, _}} = (catch domain(relation([],3))),
1355
1382
 
1356
1383
range_1(suite) -> [];
1357
1384
range_1(doc) -> [""];
1358
 
range_1(Conf) when list(Conf) ->
 
1385
range_1(Conf) when is_list(Conf) ->
1359
1386
    ?line E = empty_set(),
1360
1387
    ?line ER = relation([]),
1361
1388
    ?line {'EXIT', {badarg, _}} = (catch range(relation([],3))),
1367
1394
    
1368
1395
inverse_1(suite) -> [];
1369
1396
inverse_1(doc) -> [""];
1370
 
inverse_1(Conf) when list(Conf) ->
 
1397
inverse_1(Conf) when is_list(Conf) ->
1371
1398
    ?line E = empty_set(),
1372
1399
    ?line ER = relation([]),
1373
1400
    ?line {'EXIT', {badarg, _}} = (catch inverse(relation([],3))),
1391
1418
    
1392
1419
converse_1(suite) -> [];
1393
1420
converse_1(doc) -> [""];
1394
 
converse_1(Conf) when list(Conf) ->
 
1421
converse_1(Conf) when is_list(Conf) ->
1395
1422
    ?line E = empty_set(),
1396
1423
    ?line ER = relation([]),
1397
1424
    ?line {'EXIT', {badarg, _}} = (catch converse(relation([],3))),
1407
1434
    
1408
1435
no_elements_1(suite) -> [];
1409
1436
no_elements_1(doc) -> [""];
1410
 
no_elements_1(Conf) when list(Conf) ->
 
1437
no_elements_1(Conf) when is_list(Conf) ->
1411
1438
    ?line 0 = no_elements(empty_set()),
1412
1439
    ?line 0 = no_elements(set([])),
1413
1440
    ?line 1 = no_elements(from_term([a])),
1419
1446
 
1420
1447
image(suite) -> [];
1421
1448
image(doc) -> [""];
1422
 
image(Conf) when list(Conf) ->
 
1449
image(Conf) when is_list(Conf) ->
1423
1450
    ?line E = empty_set(),
1424
1451
    ?line ER = relation([]),
1425
1452
    ?line eval(image(E, E), E),
1441
1468
 
1442
1469
inverse_image(suite) -> [];
1443
1470
inverse_image(doc) -> [""];
1444
 
inverse_image(Conf) when list(Conf) ->
 
1471
inverse_image(Conf) when is_list(Conf) ->
1445
1472
    ?line E = empty_set(),
1446
1473
    ?line ER = relation([]),
1447
1474
    ?line eval(inverse_image(E, E), E),
1468
1495
 
1469
1496
composite_1(suite) -> [];
1470
1497
composite_1(doc) -> [""];
1471
 
composite_1(Conf) when list(Conf) ->
 
1498
composite_1(Conf) when is_list(Conf) ->
1472
1499
    ?line E = empty_set(),
1473
1500
    ?line EF = a_function([]),
1474
1501
    ?line eval(composite(E, E), E),
1520
1547
 
1521
1548
relative_product_1(suite) -> [];
1522
1549
relative_product_1(doc) -> [""];
1523
 
relative_product_1(Conf) when list(Conf) ->
 
1550
relative_product_1(Conf) when is_list(Conf) ->
1524
1551
    ?line E = empty_set(),
1525
1552
    ?line ER = relation([]),
1526
1553
    ?line eval(relative_product1(E, E), E),
1548
1575
 
1549
1576
relative_product_2(suite) -> [];
1550
1577
relative_product_2(doc) -> [""];
1551
 
relative_product_2(Conf) when list(Conf) ->
 
1578
relative_product_2(Conf) when is_list(Conf) ->
1552
1579
    ?line E = empty_set(),
1553
1580
    ?line ER = relation([]),
1554
1581
 
1597
1624
 
1598
1625
product_1(suite) -> [];
1599
1626
product_1(doc) -> [""];
1600
 
product_1(Conf) when list(Conf) ->
 
1627
product_1(Conf) when is_list(Conf) ->
1601
1628
    ?line E = empty_set(),
1602
1629
    ?line eval(product(E, E), E),
1603
1630
    ?line eval(product(relation([]), E), E),
1625
1652
 
1626
1653
partition_1(suite) -> [];
1627
1654
partition_1(doc) -> [""];
1628
 
partition_1(Conf) when list(Conf) ->
 
1655
partition_1(Conf) when is_list(Conf) ->
1629
1656
    ?line E = empty_set(),
1630
1657
    ?line ER = relation([]),
1631
1658
    ?line Id = fun(A) -> A end,
1671
1698
 
1672
1699
partition_3(suite) -> [];
1673
1700
partition_3(doc) -> [""];
1674
 
partition_3(Conf) when list(Conf) ->
 
1701
partition_3(Conf) when is_list(Conf) ->
1675
1702
    ?line E = empty_set(),
1676
1703
    ?line ER = relation([]),
1677
1704
 
1818
1845
 
1819
1846
multiple_relative_product(suite) -> [];
1820
1847
multiple_relative_product(doc) -> [""];
1821
 
multiple_relative_product(Conf) when list(Conf) ->
 
1848
multiple_relative_product(Conf) when is_list(Conf) ->
1822
1849
    ?line E = empty_set(),
1823
1850
    ?line ER = relation([]),
1824
1851
    ?line T = relation([{a,1},{a,11},{b,2},{c,3},{c,33},{d,4}]), 
1842
1869
 
1843
1870
digraph(suite) -> [];
1844
1871
digraph(doc) -> [""];
1845
 
digraph(Conf) when list(Conf) ->
 
1872
digraph(Conf) when is_list(Conf) ->
1846
1873
    ?line T0 = ets:all(),
1847
1874
    ?line E = empty_set(),
1848
1875
    ?line R = relation([{a,b},{b,c},{c,d},{d,a}]),
1901
1928
 
1902
1929
constant_function(suite) -> [];
1903
1930
constant_function(doc) -> [""];
1904
 
constant_function(Conf) when list(Conf) ->
 
1931
constant_function(Conf) when is_list(Conf) ->
1905
1932
    ?line E = empty_set(),
1906
1933
    ?line C = from_term(3),
1907
1934
    ?line eval(constant_function(E, C), E),
1913
1940
 
1914
1941
misc(suite) -> [];
1915
1942
misc(doc) -> [""];
1916
 
misc(Conf) when list(Conf) ->
 
1943
misc(Conf) when is_list(Conf) ->
1917
1944
    % find "relational" part of relation:
1918
1945
    ?line S = relation([{a,b},{b,c},{b,d},{c,d}]),
1919
1946
    Id = fun(A) -> A end,
1934
1961
    Fun = fun(S) -> no_elements(S) > 1 end,
1935
1962
    family_to_relation(family_specification(Fun, relation_to_family(R))).
1936
1963
 
1937
 
sofs_family(suite) ->
1938
 
    [family_specification, family_domain_1, family_range_1, 
1939
 
     family_to_relation_1, union_of_family_1, intersection_of_family_1, 
1940
 
     family_projection, family_difference, 
1941
 
     family_intersection_1, family_intersection_2, 
1942
 
     family_union_1, family_union_2, partition_family].
1943
1964
 
1944
1965
family_specification(suite) -> [];
1945
1966
family_specification(doc) -> [""];
1946
 
family_specification(Conf) when list(Conf) ->
 
1967
family_specification(Conf) when is_list(Conf) ->
1947
1968
    E = empty_set(),
1948
1969
    %% internal
1949
1970
    ?line eval(family_specification({sofs, is_set}, E), E),
1963
1984
        (catch family_specification(Fun3, F3)),
1964
1985
 
1965
1986
    %% external
1966
 
    IsList = {external, fun(L) when list(L) -> true; (_) -> false end},
 
1987
    IsList = {external, fun(L) when is_list(L) -> true; (_) -> false end},
1967
1988
    ?line eval(family_specification(IsList, E), E),
1968
1989
    ?line eval(family_specification(IsList, F1), F1),
1969
1990
    MF = {external, fun(L) -> lists:member(3, L) end},
1975
1996
 
1976
1997
family_domain_1(suite) -> [];
1977
1998
family_domain_1(doc) -> [""];
1978
 
family_domain_1(Conf) when list(Conf) ->
 
1999
family_domain_1(Conf) when is_list(Conf) ->
1979
2000
    ?line E = empty_set(),
1980
2001
    ?line ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
1981
2002
    ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
2001
2022
 
2002
2023
family_range_1(suite) -> [];
2003
2024
family_range_1(doc) -> [""];
2004
 
family_range_1(Conf) when list(Conf) ->
 
2025
family_range_1(Conf) when is_list(Conf) ->
2005
2026
    ?line E = empty_set(),
2006
2027
    ?line ER = from_term([{a,[]},{b,[]}],[{atom,[{atom,atom}]}]),
2007
2028
    ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
2023
2044
 
2024
2045
family_to_relation_1(suite) -> [];
2025
2046
family_to_relation_1(doc) -> [""];
2026
 
family_to_relation_1(Conf) when list(Conf) ->
 
2047
family_to_relation_1(Conf) when is_list(Conf) ->
2027
2048
    ?line E = empty_set(),
2028
2049
    ?line ER = relation([]),
2029
2050
    ?line EF = family([]),
2037
2058
 
2038
2059
union_of_family_1(suite) -> [];
2039
2060
union_of_family_1(doc) -> [""];
2040
 
union_of_family_1(Conf) when list(Conf) ->
 
2061
union_of_family_1(Conf) when is_list(Conf) ->
2041
2062
    ?line E = empty_set(),
2042
2063
    ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
2043
2064
    ?line eval(union_of_family(E), E),
2052
2073
 
2053
2074
intersection_of_family_1(suite) -> [];
2054
2075
intersection_of_family_1(doc) -> [""];
2055
 
intersection_of_family_1(Conf) when list(Conf) ->
 
2076
intersection_of_family_1(Conf) when is_list(Conf) ->
2056
2077
    ?line EF = from_term([{a,[]},{b,[]}],[{atom,[atom]}]),
2057
2078
    ?line eval(intersection_of_family(EF), set([])),
2058
2079
    ?line FR = from_term([{a,[1,2,3]},{b,[2,3]},{c,[3,4,5]}]),
2066
2087
 
2067
2088
family_projection(suite) -> [];
2068
2089
family_projection(doc) -> [""];
2069
 
family_projection(Conf) when list(Conf) ->
 
2090
family_projection(Conf) when is_list(Conf) ->
2070
2091
    SSType = [{atom,[[atom]]}],
2071
2092
    SRType = [{atom,[{atom,atom}]}],
2072
2093
    ?line E = empty_set(),
2127
2148
 
2128
2149
family_difference(suite) -> [];
2129
2150
family_difference(doc) -> [""];
2130
 
family_difference(Conf) when list(Conf) ->
 
2151
family_difference(Conf) when is_list(Conf) ->
2131
2152
    ?line E = empty_set(),
2132
2153
    ?line EF = family([]),
2133
2154
    ?line F9 = from_term([{b,[b,c]}]),
2164
2185
 
2165
2186
family_intersection_1(suite) -> [];
2166
2187
family_intersection_1(doc) -> [""];
2167
 
family_intersection_1(Conf) when list(Conf) ->
 
2188
family_intersection_1(Conf) when is_list(Conf) ->
2168
2189
    ?line E = empty_set(),
2169
2190
    ?line EF = family([]),
2170
2191
    ?line ES = from_term([], [{atom,[[atom]]}]),
2184
2205
 
2185
2206
family_intersection_2(suite) -> [];
2186
2207
family_intersection_2(doc) -> [""];
2187
 
family_intersection_2(Conf) when list(Conf) ->
 
2208
family_intersection_2(Conf) when is_list(Conf) ->
2188
2209
    ?line E = empty_set(),
2189
2210
    ?line EF = family([]),
2190
2211
    ?line F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
2215
2236
 
2216
2237
family_union_1(suite) -> [];
2217
2238
family_union_1(doc) -> [""];
2218
 
family_union_1(Conf) when list(Conf) ->
 
2239
family_union_1(Conf) when is_list(Conf) ->
2219
2240
    ?line E = empty_set(),
2220
2241
    ?line EF = family([]),
2221
2242
    ?line ES = from_term([], [{atom,[[atom]]}]),
2230
2251
 
2231
2252
family_union_2(suite) -> [];
2232
2253
family_union_2(doc) -> [""];
2233
 
family_union_2(Conf) when list(Conf) ->
 
2254
family_union_2(Conf) when is_list(Conf) ->
2234
2255
    ?line E = empty_set(),
2235
2256
    ?line EF = family([]),
2236
2257
    ?line F1 = from_term([{a,[1,2]},{b,[4,5]},{c,[7,8]},{d,[10,11]}]),
2259
2280
 
2260
2281
partition_family(suite) -> [];
2261
2282
partition_family(doc) -> [""];
2262
 
partition_family(Conf) when list(Conf) ->
 
2283
partition_family(Conf) when is_list(Conf) ->
2263
2284
    ?line E = empty_set(),
2264
2285
 
2265
2286
    %% set of ordered sets