Skip to content

Commit

Permalink
Restore test cases lost when removing vanilla driver
Browse files Browse the repository at this point in the history
  • Loading branch information
rickard-green committed Feb 9, 2024
1 parent d1f1a08 commit 8a97f69
Show file tree
Hide file tree
Showing 2 changed files with 52 additions and 2 deletions.
4 changes: 4 additions & 0 deletions erts/emulator/test/binary_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1566,6 +1566,9 @@ ordering(Config) when is_list(Config) ->
true = B1 > fun() -> 1 end,
true = B1 > fun erlang:send/2,

Port = hd(erlang:ports()),
true = B1 > Port,

true = B1 >= 0,
true = B1 >= 39827491247298471289473333333333333333333333333333,
true = B1 >= -3489274937438742190467869234328742398347,
Expand All @@ -1578,6 +1581,7 @@ ordering(Config) when is_list(Config) ->
true = B1 >= xxx,
true = B1 >= fun() -> 1 end,
true = B1 >= fun erlang:send/2,
true = B1 >= Port,

ok.

Expand Down
50 changes: 48 additions & 2 deletions erts/emulator/test/fun_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
bad_apply/1,bad_fun_call/1,badarity/1,ext_badarity/1,
bad_arglist/1,
equality/1,ordering/1,
t_phash/1,t_phash2/1,md5/1,
fun_to_port/1,t_phash/1,t_phash2/1,md5/1,
refc/1,refc_ets/1,refc_dist/1,
const_propagation/1,t_arity/1,t_is_function2/1,
t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1]).
Expand All @@ -42,7 +42,7 @@ suite() ->
all() ->
[bad_apply, bad_fun_call, badarity, ext_badarity,
bad_arglist,
equality, ordering, t_phash,
equality, ordering, fun_to_port, t_phash,
t_phash2, md5, refc, refc_ets, refc_dist,
const_propagation, t_arity, t_is_function2, t_fun_info,
t_fun_info_mfa,t_fun_to_list].
Expand Down Expand Up @@ -340,6 +340,28 @@ ordering(Config) when is_list(Config) ->
false = FF1 >= B,
false = B =< FF2,

%% Create a port and ref.

P = hd(erlang:ports()),
R = make_ref(),

%% Compare funs with ports and refs.

true = R < F3,
true = F3 > R,
true = F3 < P,
true = P > F3,

true = R =< F3,
true = F3 >= R,
true = F3 =< P,
true = P >= F3,

false = R > F3,
false = F3 < R,
false = F3 > P,
false = P < F3,

%% Compare funs with conses and nils.

true = F1 < [a],
Expand Down Expand Up @@ -378,6 +400,30 @@ ordering(Config) when is_list(Config) ->
make_fun(X, Y) ->
fun(A) -> A*X+Y end.

%% Try sending funs to ports (should fail).
fun_to_port(Config) when is_list(Config) ->
Port = open_port({spawn_executable, os:find_executable("erl")},
[{args, ["-noshell", "-eval", "timer:sleep(2000)",
"-run", "erlang", "halt"]},
use_stdio]),
fun_to_port(Port, xxx),
fun_to_port(Port, fun() -> 42 end),
fun_to_port(Port, [fun() -> 43 end]),
fun_to_port(Port, [1,fun() -> 44 end]),
fun_to_port(Port, [0,1|fun() -> 45 end]),
B64K = build_io_list(65536),
fun_to_port(Port, [B64K,fun() -> 45 end]),
fun_to_port(Port, [B64K|fun() -> 45 end]),
unlink(Port),
exit(Port, kill),
ok.

fun_to_port(Port, IoList) ->
case catch port_command(Port, IoList) of
{'EXIT',{badarg,_}} -> ok;
Other -> ct:fail({unexpected_retval,Other})
end.

build_io_list(0) -> [];
build_io_list(1) -> [7];
build_io_list(N) ->
Expand Down

0 comments on commit 8a97f69

Please sign in to comment.