diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/erl_eval_SUITE.erl | 25 | ||||
-rw-r--r-- | lib/stdlib/test/erl_expand_records_SUITE.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 30 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 16 | ||||
-rw-r--r-- | lib/stdlib/test/ms_transform_SUITE.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/test/re_SUITE.erl | 54 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 29 | ||||
-rw-r--r-- | lib/stdlib/test/sofs_SUITE.erl | 64 |
8 files changed, 156 insertions, 79 deletions
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index 369d8b224e..ca2f18a05a 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -1167,15 +1167,22 @@ do_funs(LFH, EFH) -> [[[0]]], ['F'], LFH, EFH), %% Tests for a bug found by the Dialyzer - used to crash. - ?line check(fun() -> Pmod = erl_eval_helper:new(42), Pmod:add(5) end, - "begin Pmod = erl_eval_helper:new(42), Pmod:add(5) end.", - 47, - ['Pmod'], LFH, EFH), - ?line check(fun() -> Pmod = erl_eval_helper:new(42), B = Pmod:add(7), B end, - "begin Pmod = erl_eval_helper:new(42), B = Pmod:add(7), B end.", - 49, - ['B','Pmod'], LFH, EFH), - + case test_server:is_native(erl_eval) of + true -> + %% Parameterized modules are not supported by HiPE. + ok; + false -> + check(fun() -> Pmod = erl_eval_helper:new(42), Pmod:add(5) end, + "begin Pmod = erl_eval_helper:new(42), Pmod:add(5) end.", + 47, + ['Pmod'], LFH, EFH), + check(fun() -> Pmod = erl_eval_helper:new(42), + B = Pmod:add(7), B end, + "begin Pmod = erl_eval_helper:new(42), " + "B = Pmod:add(7), B end.", + 49, + ['B','Pmod'], LFH, EFH) + end, ok. count_down(F, N) when N > 0 -> diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index f8c1ad783c..8b162cfda0 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -178,6 +178,9 @@ expr(Config) when is_list(Config) -> true -> not_ok end. + + is_record(_, _, _) -> + error(wrong_is_record). ">> ], @@ -366,6 +369,8 @@ strict(Config) when is_list(Config) -> end catch error:_ -> ok end. + element(_, _) -> + error(wrong_element). ">> ], ?line run(Config, Ts1, [strict_record_tests]), @@ -380,6 +385,8 @@ strict(Config) when is_list(Config) -> case foo of _ when A#r2.a =:= 1 -> ok end. + element(_, _) -> + error(wrong_element). ">> ], ?line run(Config, Ts2, [no_strict_record_tests]), @@ -415,6 +422,11 @@ update(Config) when is_list(Config) -> t2() -> R0 = #r{}, #r{_ = R0#r{a = ok}}. + + %% Implicit calls to setelement/3 must go to the BIF, + %% not to this function. + setelement(_, _, _) -> + erlang:error(wrong_setelement_called). ">> ], ?line run(Config, Ts), diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 9041adbe5c..4e93f056ad 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -2631,7 +2631,35 @@ bif_clash(Config) when is_list(Config) -> binary_part(A,B,C). ">>, [warn_unused_import], - {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}} + {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, + %% Don't accept call to a guard BIF if there is a local definition + %% or an import with the same name. Note: is_record/2 is an + %% exception, since it is more of syntatic sugar than a real BIF. + {clash21, + <<"-export([is_list/1]). + -import(x, [is_tuple/1]). + -record(r, {a,b}). + x(T) when is_tuple(T) -> ok; + x(T) when is_list(T) -> ok. + y(T) when is_tuple(T) =:= true -> ok; + y(T) when is_list(T) =:= true -> ok; + y(T) when is_record(T, r, 3) -> ok; + y(T) when is_record(T, r, 3) =:= true -> ok; + y(T) when is_record(T, r) =:= true -> ok. + is_list(_) -> + ok. + is_record(_, _) -> + ok. + is_record(_, _, _) -> + ok. + ">>, + [{no_auto_import,[{is_tuple,1}]}], + {errors,[{4,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {5,erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {6,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {7,erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {8,erl_lint,{illegal_guard_local_call,{is_record,3}}}, + {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}} ], ?line [] = run(Config, Ts), diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 0e8849b5b3..101828fdef 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -74,7 +74,7 @@ -export([bad_table/1, types/1]). -export([otp_9423/1]). --export([init_per_testcase/2]). +-export([init_per_testcase/2, end_per_testcase/2]). %% Convenience for manual testing -export([random_test/0]). @@ -2385,6 +2385,8 @@ setopts_do(Opts) -> ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,private,false})), ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,protection)), ?line ets:delete(T), + unlink(Heir), + exit(Heir, bang), ok. bad_table(doc) -> ["All kinds of operations with bad table argument"]; @@ -5645,7 +5647,8 @@ spawn_logger(Procs) -> true -> exit(Proc, kill); _ -> ok end, - erlang:display(process_info(Proc)), + erlang:display({"Waiting for 'DOWN' from", Proc, + process_info(Proc), pid_status(Proc)}), receive {'DOWN', Mon, _, _, _} -> ok @@ -5656,6 +5659,15 @@ spawn_logger(Procs) -> spawn_logger([From]) end. +pid_status(Pid) -> + try + erts_debug:get_internal_state({process_status, Pid}) + catch + error:undef -> + erts_debug:set_internal_state(available_internal_state, true), + pid_status(Pid) + end. + start_spawn_logger() -> case whereis(ets_test_spawn_logger) of Pid when is_pid(Pid) -> true; diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl index c9688354b1..a17307b07b 100644 --- a/lib/stdlib/test/ms_transform_SUITE.erl +++ b/lib/stdlib/test/ms_transform_SUITE.erl @@ -455,7 +455,6 @@ old_guards(Config) when is_list(Config) -> ?line setup(Config), Tests = [ {atom,is_atom}, - {constant,is_constant}, {float,is_float}, {integer,is_integer}, {list,is_list}, @@ -490,7 +489,6 @@ old_guards(Config) when is_list(Config) -> ?line [{'$1',[{is_integer,'$1'}, {is_float,'$1'}, {is_atom,'$1'}, - {is_constant,'$1'}, {is_list,'$1'}, {is_number,'$1'}, {is_pid,'$1'}, @@ -502,7 +500,7 @@ old_guards(Config) when is_list(Config) -> [true]}] = compile_and_run(RD, << "ets:fun2ms(fun(X) when integer(X)," - "float(X), atom(X), constant(X)," + "float(X), atom(X)," "list(X), number(X), pid(X)," "port(X), reference(X), tuple(X)," "binary(X), record(X,a) -> true end)" @@ -530,7 +528,6 @@ autoimported(Config) when is_list(Config) -> {self,0}, %{float,1}, see float_1_function/1 {is_atom,1}, - {is_constant,1}, {is_float,1}, {is_integer,1}, {is_list,1}, diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index 3b2e637c84..d6d946a28f 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -445,9 +445,17 @@ split_specials(Config) when is_list(Config) -> ok. -error_handling(doc) -> - ["Test that errors are handled correctly by the erlang code."]; -error_handling(Config) when is_list(Config) -> +%% Test that errors are handled correctly by the erlang code. +error_handling(_Config) -> + case test_server:is_native(re) of + true -> + %% Exceptions from native code look too different. + {skip,"re is native"}; + false -> + error_handling() + end. + +error_handling() -> % This test checks the exception tuples manufactured in the erlang % code to hide the trapping from the user at least when it comes to errors Dog = ?t:timetrap(?t:minutes(1)), @@ -455,14 +463,14 @@ error_handling(Config) when is_list(Config) -> % the trap to re:grun from grun, in the grun function clause % that handles precompiled expressions ?line {'EXIT',{badarg,[{re,run,["apa",{1,2,3,4},[global]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:run("apa",{1,2,3,4},[global])), % An invalid capture list will also cause a badarg late, % but with a non pre compiled RE, the exception should be thrown by the % grun function clause that handles RE's compiled implicitly by % the run/3 BIF before trapping. ?line {'EXIT',{badarg,[{re,run,["apa","p",[{capture,[1,{a}]},global]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:run("apa","p",[{capture,[1,{a}]},global])), % And so the case of a precompiled expression together with % a compile-option (binary and list subject): @@ -473,88 +481,88 @@ error_handling(Config) when is_list(Config) -> [<<"apa">>, {re_pattern,1,0,_}, [global,unicode]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:run(<<"apa">>,RE,[global,unicode])), ?line {'EXIT',{badarg,[{re,run, ["apa", {re_pattern,1,0,_}, [global,unicode]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:run("apa",RE,[global,unicode])), ?line {'EXIT',{badarg,_}} = (catch re:run("apa","(p",[])), ?line {'EXIT',{badarg,_}} = (catch re:run("apa","(p",[global])), % The replace errors: ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:replace("apa",{1,2,3,4},"X",[])), ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[global]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:replace("apa",{1,2,3,4},"X",[global])), ?line {'EXIT',{badarg,[{re,replace, ["apa", {re_pattern,1,0,_}, "X", [unicode]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:replace("apa",RE,"X",[unicode])), ?line <<"aXa">> = iolist_to_binary(re:replace("apa","p","X",[])), ?line {'EXIT',{badarg,[{re,replace, ["apa","p","X",[{capture,all,binary}]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch iolist_to_binary(re:replace("apa","p","X", [{capture,all,binary}]))), ?line {'EXIT',{badarg,[{re,replace, ["apa","p","X",[{capture,all}]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch iolist_to_binary(re:replace("apa","p","X", [{capture,all}]))), ?line {'EXIT',{badarg,[{re,replace, ["apa","p","X",[{return,banana}]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch iolist_to_binary(re:replace("apa","p","X", [{return,banana}]))), ?line {'EXIT',{badarg,_}} = (catch re:replace("apa","(p","X",[])), % Badarg, not compile error. ?line {'EXIT',{badarg,[{re,replace, ["apa","(p","X",[{return,banana}]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch iolist_to_binary(re:replace("apa","(p","X", [{return,banana}]))), % And the split errors: ?line [<<"a">>,<<"a">>] = (catch re:split("apa","p",[])), ?line [<<"a">>,<<"p">>,<<"a">>] = (catch re:split("apa",RE,[])), ?line {'EXIT',{badarg,[{re,split,["apa","p",[global]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa","p",[global])), ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all}]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa","p",[{capture,all}])), ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all,binary}]],_}, - {?MODULE, error_handling,1,_} | _]}} = + {?MODULE, error_handling,0,_} | _]}} = (catch re:split("apa","p",[{capture,all,binary}])), ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",{1,2,3,4})), ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",{1,2,3,4},[])), ?line {'EXIT',{badarg,[{re,split, ["apa", RE, [unicode]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",RE,[unicode])), ?line {'EXIT',{badarg,[{re,split, ["apa", RE, [{return,banana}]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",RE,[{return,banana}])), ?line {'EXIT',{badarg,[{re,split, ["apa", RE, [banana]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",RE,[banana])), ?line {'EXIT',{badarg,_}} = (catch re:split("apa","(p")), %Exception on bad argument, not compilation error @@ -562,7 +570,7 @@ error_handling(Config) when is_list(Config) -> ["apa", "(p", [banana]],_}, - {?MODULE,error_handling,1,_} | _]}} = + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa","(p",[banana])), ?t:timetrap_cancel(Dog), ok. diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index b6019b86f0..a881742f13 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2388,13 +2388,28 @@ otp_6554(Config) when is_list(Config) -> comm_err(<<"V = lists:seq(1, 20), case V of a -> ok end.">>), ?line "exception error: no function clause matching" = comm_err(<<"fun(P) when is_pid(P) -> true end(a).">>), - ?line "exception error: {function_clause," = - comm_err(<<"erlang:error(function_clause, [unproper | list]).">>), + case test_server:is_native(erl_eval) of + true -> + %% Native code has different exit reason. Don't bother + %% testing them. + ok; + false -> + "exception error: {function_clause," = + comm_err(<<"erlang:error(function_clause, " + "[unproper | list]).">>), + %% Cheating: + "exception error: no function clause matching " + "erl_eval:do_apply(4)" ++ _ = + comm_err(<<"erlang:error(function_clause, [4]).">>), + "exception error: no function clause matching " + "lists:reverse(" ++ _ = + comm_err(<<"F=fun() -> hello end, lists:reverse(F).">>), + "exception error: no function clause matching " + "lists:reverse(34) (lists.erl, line " ++ _ = + comm_err(<<"lists:reverse(34).">>) + end, ?line "exception error: function_clause" = comm_err(<<"erlang:error(function_clause, 4).">>), - %% Cheating: - ?line "exception error: no function clause matching erl_eval:do_apply(4)" ++ _ = - comm_err(<<"erlang:error(function_clause, [4]).">>), ?line "exception error: no function clause matching" ++ _ = comm_err(<<"fun(a, b, c, d) -> foo end" " (lists:seq(1,17)," @@ -2404,10 +2419,6 @@ otp_6554(Config) when is_list(Config) -> ?line "exception error: no function clause matching" = comm_err(<<"fun(P, q) when is_pid(P) -> true end(a, b).">>), - ?line "exception error: no function clause matching lists:reverse(" ++ _ = - comm_err(<<"F=fun() -> hello end, lists:reverse(F).">>), - ?line "exception error: no function clause matching lists:reverse(34) (lists.erl, line " ++ _ = - comm_err(<<"lists:reverse(34).">>), ?line "exception error: no true branch found when evaluating an if expression" = comm_err(<<"if length([a,b]) > 17 -> a end.">>), ?line "exception error: no such process or port" = diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl index 73b282149a..f11c6ec4d6 100644 --- a/lib/stdlib/test/sofs_SUITE.erl +++ b/lib/stdlib/test/sofs_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2011. All Rights Reserved. +%% Copyright Ericsson AB 2001-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -536,7 +536,7 @@ projection(Conf) when is_list(Conf) -> from_term([], [[atom]]))), ?line {'EXIT', {badarg, _}} = (catch projection({external, fun(X) -> X end}, from_term([[a]]))), - ?line eval(projection({sofs,union}, + ?line eval(projection(fun sofs:union/1, from_term([[[1,2],[2,3]], [[a,b],[b,c]]])), from_term([[1,2,3], [a,b,c]])), ?line eval(projection(fun(_) -> from_term([a]) end, @@ -628,7 +628,7 @@ substitution(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch substitution({external, fun(X) -> X end}, from_term([[a]]))), ?line eval(substitution(fun(X) -> X end, from_term([], [[atom]])), E), - ?line eval(substitution({sofs,union}, + ?line eval(substitution(fun sofs:union/1, from_term([[[1,2],[2,3]], [[a,b],[b,c]]])), from_term([{[[1,2],[2,3]],[1,2,3]}, {[[a,b],[b,c]],[a,b,c]}])), ?line eval(substitution(fun(_) -> from_term([a]) end, @@ -745,7 +745,7 @@ restriction(Conf) when is_list(Conf) -> ?line eval(restriction(Id, S3, E), E), ?line eval(restriction(Id, from_term([], [[atom]]), set([a])), from_term([], [[atom]])), - ?line eval(restriction({sofs,union}, + ?line eval(restriction(fun sofs:union/1, from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]), from_term([[a,b],[1,2,3],[b,c]])), @@ -862,7 +862,7 @@ drestriction(Conf) when is_list(Conf) -> ?line eval(drestriction(Id, S3, E), S3), ?line eval(drestriction(Id, from_term([], [[atom]]), set([a])), from_term([], [[atom]])), - ?line eval(drestriction({sofs,union}, + ?line eval(drestriction(fun sofs:union/1, from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]), from_term([[a,b],[1,2,3],[b,c]])), @@ -1028,7 +1028,7 @@ specification(Conf) when is_list(Conf) -> end, ?line eval(specification({external,Fun2x}, S2), from_term([[1],[3]])), - Fun3 = fun(_) -> neither_true_or_false end, + Fun3 = fun(_) -> neither_true_nor_false end, ?line {'EXIT', {badarg, _}} = (catch specification(Fun3, set([a]))), ?line {'EXIT', {badarg, _}} = @@ -1810,8 +1810,8 @@ partition_3(Conf) when is_list(Conf) -> S12a = from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]), S12b = from_term([[a,b],[1,2,3],[b,c]]), - ?line eval(partition({sofs,union}, S12a, S12b), - lpartition({sofs,union}, S12a, S12b)), + ?line eval(partition(fun sofs:union/1, S12a, S12b), + lpartition(fun sofs:union/1, S12a, S12b)), Fun13 = fun(_) -> from_term([a]) end, S13a = from_term([], [[atom]]), @@ -1879,12 +1879,9 @@ digraph(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch family_to_digraph(set([a]))), - ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_],_}|_]}} = - (catch family_to_digraph(set([a]), [foo])), - ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_],_}|_]}} = - (catch family_to_digraph(F, [foo])), - ?line {'EXIT', {cyclic, [{sofs,family_to_digraph,[_,_],_}|_]}} = - (catch family_to_digraph(family([{a,[a]}]),[acyclic])), + digraph_fail(badarg, catch family_to_digraph(set([a]), [foo])), + digraph_fail(badarg, catch family_to_digraph(F, [foo])), + digraph_fail(cyclic, catch family_to_digraph(family([{a,[a]}]),[acyclic])), ?line G1 = family_to_digraph(E), ?line {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, foo)), @@ -1927,6 +1924,13 @@ digraph(Conf) when is_list(Conf) -> ?line true = T0 == ets:all(), ok. +digraph_fail(ExitReason, Fail) -> + {'EXIT', {ExitReason, [{sofs,family_to_digraph,A,_}|_]}} = Fail, + case {test_server:is_native(sofs),A} of + {false,[_,_]} -> ok; + {true,2} -> ok + end. + constant_function(suite) -> []; constant_function(doc) -> [""]; constant_function(Conf) when is_list(Conf) -> @@ -1952,10 +1956,8 @@ misc(Conf) when is_list(Conf) -> % the "functional" part: ?line eval(union(intersection(partition(1,S), partition(Id,S))), difference(S, RR)), - - %% The function external:foo/1 is undefined. ?line {'EXIT', {undef, _}} = - (catch projection({external,foo}, set([a,b,c]))), + (catch projection(fun external:foo/1, set([a,b,c]))), ok. relational_restriction(R) -> @@ -1968,19 +1970,19 @@ family_specification(doc) -> [""]; family_specification(Conf) when is_list(Conf) -> E = empty_set(), %% internal - ?line eval(family_specification({sofs, is_set}, E), E), + ?line eval(family_specification(fun sofs:is_set/1, E), E), ?line {'EXIT', {badarg, _}} = - (catch family_specification({sofs,is_set}, set([]))), + (catch family_specification(fun sofs:is_set/1, set([]))), ?line F1 = from_term([{1,[1]}]), - ?line eval(family_specification({sofs,is_set}, F1), F1), + ?line eval(family_specification(fun sofs:is_set/1, F1), F1), Fun = fun(S) -> is_subset(S, set([0,1,2,3,4])) end, ?line F2 = family([{a,[1,2]},{b,[3,4,5]}]), ?line eval(family_specification(Fun, F2), family([{a,[1,2]}])), ?line F3 = from_term([{a,[]},{b,[]}]), - ?line eval(family_specification({sofs,is_set}, F3), F3), + ?line eval(family_specification(fun sofs:is_set/1, F3), F3), Fun2 = fun(_) -> throw(fippla) end, ?line fippla = (catch family_specification(Fun2, family([{a,[1]}]))), - Fun3 = fun(_) -> neither_true_or_false end, + Fun3 = fun(_) -> neither_true_nor_false end, ?line {'EXIT', {badarg, _}} = (catch family_specification(Fun3, F3)), @@ -2095,22 +2097,22 @@ family_projection(Conf) when is_list(Conf) -> ?line eval(family_projection(fun(X) -> X end, family([])), E), ?line L1 = [{a,[]}], - ?line eval(family_projection({sofs,union}, E), E), - ?line eval(family_projection({sofs,union}, from_term(L1, SSType)), + ?line eval(family_projection(fun sofs:union/1, E), E), + ?line eval(family_projection(fun sofs:union/1, from_term(L1, SSType)), family(L1)), ?line {'EXIT', {badarg, _}} = - (catch family_projection({sofs,union}, set([]))), + (catch family_projection(fun sofs:union/1, set([]))), ?line {'EXIT', {badarg, _}} = - (catch family_projection({sofs,union}, from_term([{1,[1]}]))), + (catch family_projection(fun sofs:union/1, from_term([{1,[1]}]))), ?line F2 = from_term([{a,[[1],[2]]},{b,[[3,4],[5]]}], SSType), - ?line eval(family_projection({sofs,union}, F2), + ?line eval(family_projection(fun sofs:union/1, F2), family_union(F2)), ?line F3 = from_term([{1,[{a,b},{b,c},{c,d}]},{3,[]},{5,[{3,5}]}], SRType), - ?line eval(family_projection({sofs,domain}, F3), family_domain(F3)), - ?line eval(family_projection({sofs,range}, F3), family_range(F3)), + ?line eval(family_projection(fun sofs:domain/1, F3), family_domain(F3)), + ?line eval(family_projection(fun sofs:range/1, F3), family_range(F3)), ?line eval(family_projection(fun(_) -> E end, family([{a,[b,c]}])), from_term([{a,[]}])), @@ -2290,7 +2292,7 @@ partition_family(Conf) when is_list(Conf) -> ?line eval(partition_family(1, E), E), ?line eval(partition_family(2, E), E), - ?line eval(partition_family({sofs,union}, E), E), + ?line eval(partition_family(fun sofs:union/1, E), E), ?line eval(partition_family(1, ER), EF), ?line eval(partition_family(2, ER), EF), ?line {'EXIT', {badarg, _}} = (catch partition_family(1, set([]))), @@ -2354,7 +2356,7 @@ partition_family(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch partition_family({external, fun(X) -> X end}, from_term([[a]]))), - ?line eval(partition_family({sofs,union}, + ?line eval(partition_family(fun sofs:union/1, from_term([[[1],[1,2]], [[1,2]]])), from_term([{[1,2], [[[1],[1,2]],[[1,2]]]}])), ?line eval(partition_family(fun(X) -> X end, |