From 211ce03aeb85b3fa14fbda8dd7a971ce0091d371 Mon Sep 17 00:00:00 2001 From: jakob svenningsson Date: Tue, 26 Mar 2024 13:56:21 +0100 Subject: [PATCH 001/422] ssh: start monitor ConnPid before casting socket_control --- lib/ssh/src/ssh_connection_handler.erl | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl index d39ca05ea2d8..12db85d015fb 100644 --- a/lib/ssh/src/ssh_connection_handler.erl +++ b/lib/ssh/src/ssh_connection_handler.erl @@ -129,12 +129,13 @@ takeover(ConnPid, _, Socket, Options) -> {_, Callback, _} = ?GET_OPT(transport, Options), case Callback:controlling_process(Socket, ConnPid) of ok -> + Ref = erlang:monitor(process, ConnPid), gen_statem:cast(ConnPid, socket_control), NegTimeout = ?GET_INTERNAL_OPT(negotiation_timeout, Options, ?GET_OPT(negotiation_timeout, Options) ), - handshake(ConnPid, erlang:monitor(process,ConnPid), NegTimeout); + handshake(ConnPid, Ref, NegTimeout); {error, Reason} -> {error, Reason} end. From b9f1921d87f9f80c399ec89ae8bb193552338941 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 9 Apr 2024 12:32:16 +0200 Subject: [PATCH 002/422] [esock] Read on Windows with timeout = 0 failure On Windows, when a recv (recv, recvfrom and recvmsg) is called with Timeout = 0 (zero) and the operation could not complete immediately complete, this would result in a (case clause) crash (in the socket module). OTP-19063 --- erts/emulator/nifs/win32/win_socket_asyncio.c | 60 +++++++++---------- 1 file changed, 30 insertions(+), 30 deletions(-) diff --git a/erts/emulator/nifs/win32/win_socket_asyncio.c b/erts/emulator/nifs/win32/win_socket_asyncio.c index bb6ad47960b1..6c4b6c86857a 100644 --- a/erts/emulator/nifs/win32/win_socket_asyncio.c +++ b/erts/emulator/nifs/win32/win_socket_asyncio.c @@ -3869,7 +3869,7 @@ ERL_NIF_TERM recv_check_result(ErlNifEnv* env, } else { - eres = esock_atom_ok; + eres = esock_atom_timeout; // Will trigger {error, timeout} } @@ -3901,7 +3901,7 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, ERL_NIF_TERM sockRef, ERL_NIF_TERM recvRef) { - ERL_NIF_TERM data, result; + ERL_NIF_TERM data, eres; DWORD read = 0, flags = 0; SSDBG( descP, @@ -3940,7 +3940,7 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, ESOCK_CNT_INC(env, descP, sockRef, esock_atom_read_fails, &descP->readFails, 1); - result = esock_make_error(env, esock_atom_closed); + eres = esock_make_error(env, esock_atom_closed); } else { @@ -3980,7 +3980,7 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, if (read > descP->readPkgMax) descP->readPkgMax = read; - result = esock_make_ok2(env, data); + eres = esock_make_ok2(env, data); } @@ -4000,8 +4000,8 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, if (! IS_ZERO(recvRef)) { - result = recv_check_pending(env, descP, opP, caller, - sockRef, recvRef); + eres = recv_check_pending(env, descP, opP, caller, + sockRef, recvRef); } else { /* But we are not allowed to wait! => cancel */ @@ -4024,11 +4024,11 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, "\r\n %T" "\r\n", sockRef, descP->sock, reason) ); - result = esock_make_error(env, MKT2(env, tag, reason)); + eres = esock_make_error(env, MKT2(env, tag, reason)); } else { - result = esock_atom_ok; // Will trigger {error, timeout} + eres = esock_atom_timeout; // Will trigger {error, timeout} } } @@ -4050,7 +4050,7 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, MUNLOCK(ctrl.cntMtx); - result = esock_make_error(env, reason); + eres = esock_make_error(env, reason); } break; } @@ -4061,7 +4061,7 @@ ERL_NIF_TERM recv_check_ok(ErlNifEnv* env, "\r\n", sockRef, descP->sock) ); - return result; + return eres; } @@ -4310,7 +4310,7 @@ ERL_NIF_TERM recvfrom_check_result(ErlNifEnv* env, } else { - eres = esock_atom_ok; // Will trigger {error, timeout} + eres = esock_atom_timeout; // Will trigger {error, timeout} } @@ -4342,7 +4342,7 @@ ERL_NIF_TERM recvfrom_check_ok(ErlNifEnv* env, ERL_NIF_TERM sockRef, ERL_NIF_TERM recvRef) { - ERL_NIF_TERM data, result; + ERL_NIF_TERM data, eres; DWORD read = 0, flags = 0; SSDBG( descP, @@ -4393,7 +4393,7 @@ ERL_NIF_TERM recvfrom_check_ok(ErlNifEnv* env, * This is: {ok, {Source, Data}} * But it should really be: {ok, {Source, Flags, Data}} */ - result = esock_make_ok2(env, MKT2(env, eSockAddr, data)); + eres = esock_make_ok2(env, MKT2(env, eSockAddr, data)); } else { @@ -4411,8 +4411,8 @@ ERL_NIF_TERM recvfrom_check_ok(ErlNifEnv* env, if (! IS_ZERO(recvRef)) { - result = recv_check_pending(env, descP, opP, caller, - sockRef, recvRef); + eres = recv_check_pending(env, descP, opP, caller, + sockRef, recvRef); } else { @@ -4436,11 +4436,11 @@ ERL_NIF_TERM recvfrom_check_ok(ErlNifEnv* env, "\r\n %T" "\r\n", sockRef, descP->sock, reason) ); - result = esock_make_error(env, MKT2(env, tag, reason)); + eres = esock_make_error(env, MKT2(env, tag, reason)); } else { - result = esock_atom_ok; // Will trigger {error, timeout} + eres = esock_atom_timeout; // Will trigger {error, timeout} } } @@ -4462,7 +4462,7 @@ ERL_NIF_TERM recvfrom_check_ok(ErlNifEnv* env, MUNLOCK(ctrl.cntMtx); - result = esock_make_error(env, reason); + eres = esock_make_error(env, reason); } break; } @@ -4472,9 +4472,9 @@ ERL_NIF_TERM recvfrom_check_ok(ErlNifEnv* env, ("WIN-ESAIO", "recvfrom_check_ok(%T) {%d} -> done with" "\r\n result: %T" "\r\n", - sockRef, descP->sock, result) ); + sockRef, descP->sock, eres) ); - return result; + return eres; } @@ -4722,7 +4722,7 @@ ERL_NIF_TERM recvmsg_check_result(ErlNifEnv* env, } else { - eres = esock_atom_ok; // Will trigger {error, timeout} + eres = esock_atom_timeout; // Will trigger {error, timeout} } @@ -4757,7 +4757,7 @@ ERL_NIF_TERM recvmsg_check_ok(ErlNifEnv* env, ERL_NIF_TERM sockRef, ERL_NIF_TERM recvRef) { - ERL_NIF_TERM eMsg, result; + ERL_NIF_TERM eMsg, eres; DWORD read = 0, flags = 0; SSDBG( descP, @@ -4793,7 +4793,7 @@ ERL_NIF_TERM recvmsg_check_ok(ErlNifEnv* env, if (read > descP->readPkgMax) descP->readPkgMax = read; - result = esock_make_ok2(env, eMsg); + eres = esock_make_ok2(env, eMsg); } else { @@ -4811,8 +4811,8 @@ ERL_NIF_TERM recvmsg_check_ok(ErlNifEnv* env, if (! IS_ZERO(recvRef)) { - result = recv_check_pending(env, descP, opP, caller, - sockRef, recvRef); + eres = recv_check_pending(env, descP, opP, caller, + sockRef, recvRef); } else { @@ -4836,11 +4836,11 @@ ERL_NIF_TERM recvmsg_check_ok(ErlNifEnv* env, "\r\n %T" "\r\n", sockRef, descP->sock, reason) ); - result = esock_make_error(env, MKT2(env, tag, reason)); + eres = esock_make_error(env, MKT2(env, tag, reason)); } else { - result = esock_atom_ok; // Will trigger {error, timeout} + eres = esock_atom_timeout; // Will trigger {error, timeout} } } @@ -4862,7 +4862,7 @@ ERL_NIF_TERM recvmsg_check_ok(ErlNifEnv* env, MUNLOCK(ctrl.cntMtx); - result = esock_make_error(env, reason); + eres = esock_make_error(env, reason); } break; } @@ -4872,9 +4872,9 @@ ERL_NIF_TERM recvmsg_check_ok(ErlNifEnv* env, ("WIN-ESAIO", "recvmsg_check_ok(%T) {%d} -> done with" "\r\n result: %T" "\r\n", - sockRef, descP->sock, result) ); + sockRef, descP->sock, eres) ); - return result; + return eres; } From 8d07a31178a669db75f0ae7703e1ccee5dd6d035 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 9 Apr 2024 12:36:34 +0200 Subject: [PATCH 003/422] [esock] Preliminary test case OTP-19063 --- lib/kernel/test/socket_SUITE.erl | 56 +++++++++++++++++++++++++++++--- 1 file changed, 51 insertions(+), 5 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 15d52cdc91a4..4decec796459 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -749,7 +749,8 @@ otp16359_maccept_tcpL/1, otp18240_accept_mon_leak_tcp4/1, otp18240_accept_mon_leak_tcp6/1, - otp18635/1 + otp18635/1, + otp19063/1 ]). @@ -2353,7 +2354,8 @@ tickets_cases() -> [ {group, otp16359}, {group, otp18240}, - otp18635 + otp18635, + otp19063 ]. otp16359_cases() -> @@ -51697,7 +51699,7 @@ do_otp18635(_) -> %% ok = socket:setopt(LSock, otp, debug, true), - % show handle returned from nowait accept + % show handle returned from nowait accept ?P("try accept with timeout = nowait - expect select when" "~n (gen socket) info: ~p" "~n Sockets: ~p", @@ -51738,7 +51740,7 @@ do_otp18635(_) -> ?P("[connector] try create socket"), {ok, CSock} = socket:open(inet, stream), ?P("[connector] try connect: " - "~n (server) ~p", [SA]), + "~n (server) ~p", [SA]), ok = socket:connect(CSock, SA), ?P("[connector] connected - inform parent"), Parent ! {self(), connected}, @@ -51749,7 +51751,7 @@ do_otp18635(_) -> (catch socket:close(CSock)), exit(normal) end - end), + end), ?P("await (connection-) confirmation from connector (~p)", [Connector]), receive @@ -51817,6 +51819,42 @@ do_otp18635(_) -> Result. +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% This test case is to verify recv on UDP with timeout zero (0) on Windows. +otp19063(Config) when is_list(Config) -> + ?TT(?SECS(10)), + tc_try(?FUNCTION_NAME, + fun() -> + is_windows(), + has_support_ipv4() + end, + fun() -> + InitState = #{}, + ok = do_otp19063(InitState) + end). + + +do_otp19063(_) -> + ?P("Get \"proper\" local socket address"), + LSA = which_local_socket_addr(inet), + + ?P("Create socket"), + {ok, Sock} = socket:open(inet, dgram), + + ?P("bind socket to: " + "~n ~p", [LSA]), + ok = socket:bind(Sock, LSA), + + ?SLEEP(?SECS(1)), + + {error, timeout} = socket:recv(Sock, 0, 0), + + ?P("done"), + + ok. + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% sock_open(Domain, Type, Proto) -> @@ -52275,6 +52313,14 @@ is_not_windows() -> ok end. +is_windows() -> + case os:type() of + {win32, nt} -> + ok; + _ -> + skip("This does not work on *non* Windows"); + end. + is_not_platform(Platform, PlatformStr) when is_atom(Platform) andalso is_list(PlatformStr) -> case os:type() of From a9cc6de93cacee12955d889eeed893e49be3bad8 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 9 Apr 2024 17:52:30 +0200 Subject: [PATCH 004/422] [esock|test] Improve test case OTP-19063 --- lib/kernel/test/socket_SUITE.erl | 124 ++++++++++++++++++++++++++++--- 1 file changed, 115 insertions(+), 9 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 4decec796459..7da225e7967b 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -51697,9 +51697,7 @@ do_otp18635(_) -> ?P("get sockname for listen socket"), {ok, SA} = socket:sockname(LSock), - %% ok = socket:setopt(LSock, otp, debug, true), - - % show handle returned from nowait accept + %% show handle returned from nowait accept ?P("try accept with timeout = nowait - expect select when" "~n (gen socket) info: ~p" "~n Sockets: ~p", @@ -51826,7 +51824,7 @@ otp19063(Config) when is_list(Config) -> ?TT(?SECS(10)), tc_try(?FUNCTION_NAME, fun() -> - is_windows(), + %% is_windows(), has_support_ipv4() end, fun() -> @@ -51836,19 +51834,127 @@ otp19063(Config) when is_list(Config) -> do_otp19063(_) -> + Parent = self(), + ?P("Get \"proper\" local socket address"), LSA = which_local_socket_addr(inet), - ?P("Create socket"), - {ok, Sock} = socket:open(inet, dgram), + + %% --- recv --- + + ?P("Testing recv (tcp) - create (listen) socket"), + {ok, LSock1} = socket:open(inet, stream), + + ?P("bind (listen) socket to: " + "~n ~p", [LSA]), + ok = socket:bind(LSock1, LSA), + + ?P("make listen socket"), + ok = socket:listen(LSock1), + + ?P("get sockname for listen socket"), + {ok, SA1} = socket:sockname(LSock1), + + ?P("attempt a nowait-accept"), + {Tag, Handle} = + case socket:accept(LSock1, nowait) of + {select, {select_info, _, SH}} -> + {select, SH}; + {completion, {completion_info, _, CH}} -> + {completion, CH} + end, + + ?P("spawn the connector process"), + {Connector, MRef} = + spawn_monitor( + fun() -> + ?P("[connector] try create socket"), + {ok, CSock1} = socket:open(inet, stream), + ?P("[connector] try connect: " + "~n (server) ~p", [SA1]), + ok = socket:connect(CSock1, SA1), + ?P("[connector] connected - inform parent"), + Parent ! {self(), connected}, + ?P("[connector] await termination command"), + receive + {Parent, terminate} -> + ?P("[connector] terminate - close socket"), + (catch socket:close(CSock1)), + exit(normal) + end + end), + + ?P("await (connection-) confirmation from connector (~p)", [Connector]), + receive + {Connector, connected} -> + ?P("connector connected"), + ok + end, + + ?P("receive the accepted socket"), + ASock1 = + receive + {'$socket', LSock1, completion, {Handle, {ok, AS}}} + when (Tag =:= completion) -> + AS; + {'$socket', LSock1, completion, {Handle, {error, Reason1C}}} + when (Tag =:= completion) -> + exit({accept_failed, Reason1C}); + {'$socket', LSock1, select, Handle} -> + case socket:accept(LSock1, nowait) of + {ok, AS} -> + AS; + {error, Reason1S} -> + exit({accept_failed, Reason1S}) + end + end, + + ?SLEEP(?SECS(1)), + + ?P("and finally try recv"), + {error, timeout} = socket:recv(ASock1, 0, 0), + + + %% --- recvfrom --- + + ?P("Testing recvfrom - create socket"), + {ok, Sock2} = socket:open(inet, dgram), + + ?P("bind socket to: " + "~n ~p", [LSA]), + ok = socket:bind(Sock2, LSA), + + ?SLEEP(?SECS(1)), + + {error, timeout} = socket:recvfrom(Sock2, 1024, 0), + + + %% --- recvmsg --- + + ?P("Testing recvmsg - create socket"), + {ok, Sock3} = socket:open(inet, dgram), ?P("bind socket to: " "~n ~p", [LSA]), - ok = socket:bind(Sock, LSA), + ok = socket:bind(Sock3, LSA), ?SLEEP(?SECS(1)), - {error, timeout} = socket:recv(Sock, 0, 0), + {error, timeout} = socket:recvmsg(Sock3, 0, 0), + + + ?P("cleanup"), + + Connector ! {self(), terminate}, + receive + {'DOWN', MRef, process, Connector, _} -> + ?P("connector terminated"), + ok + end, + _ = socket:close(ASock1), + _ = socket:close(LSock1), + _ = socket:close(Sock2), + _ = socket:close(Sock3), ?P("done"), @@ -52318,7 +52424,7 @@ is_windows() -> {win32, nt} -> ok; _ -> - skip("This does not work on *non* Windows"); + skip("This does not work on *non* Windows") end. is_not_platform(Platform, PlatformStr) From 50555347d3300f5bcdc7958c37c36b5b21838f86 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 9 Apr 2024 18:52:50 +0200 Subject: [PATCH 005/422] [esock|test] More test OTP-19063 --- lib/kernel/test/socket_SUITE.erl | 40 +++++++++++++++++++------------- 1 file changed, 24 insertions(+), 16 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 7da225e7967b..93c07b83fe14 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -51837,25 +51837,27 @@ do_otp19063(_) -> Parent = self(), ?P("Get \"proper\" local socket address"), - LSA = which_local_socket_addr(inet), + LSA0 = which_local_socket_addr(inet), + LSA = LSA0#{port => 0}, + %% --- recv --- - ?P("Testing recv (tcp) - create (listen) socket"), + ?P("[recv] - create (listen) socket"), {ok, LSock1} = socket:open(inet, stream), - ?P("bind (listen) socket to: " + ?P("[recv] bind (listen) socket to: " "~n ~p", [LSA]), ok = socket:bind(LSock1, LSA), - ?P("make listen socket"), + ?P("[recv] make listen socket"), ok = socket:listen(LSock1), - ?P("get sockname for listen socket"), + ?P("[recv] get sockname for listen socket"), {ok, SA1} = socket:sockname(LSock1), - ?P("attempt a nowait-accept"), + ?P("[recv] attempt a nowait-accept"), {Tag, Handle} = case socket:accept(LSock1, nowait) of {select, {select_info, _, SH}} -> @@ -51864,12 +51866,15 @@ do_otp19063(_) -> {completion, CH} end, - ?P("spawn the connector process"), + ?P("[recv] spawn the connector process"), {Connector, MRef} = spawn_monitor( fun() -> ?P("[connector] try create socket"), {ok, CSock1} = socket:open(inet, stream), + ?P("[connector] bind socket to: " + "~n ~p", [LSA]), + ok = socket:bind(CSock1, LSA), ?P("[connector] try connect: " "~n (server) ~p", [SA1]), ok = socket:connect(CSock1, SA1), @@ -51884,14 +51889,15 @@ do_otp19063(_) -> end end), - ?P("await (connection-) confirmation from connector (~p)", [Connector]), + ?P("[recv] await (connection-) confirmation from connector (~p)", + [Connector]), receive {Connector, connected} -> - ?P("connector connected"), + ?P("[recv] connector connected"), ok end, - ?P("receive the accepted socket"), + ?P("[recv] receive the accepted socket"), ASock1 = receive {'$socket', LSock1, completion, {Handle, {ok, AS}}} @@ -51911,36 +51917,38 @@ do_otp19063(_) -> ?SLEEP(?SECS(1)), - ?P("and finally try recv"), + ?P("[recv] try read"), {error, timeout} = socket:recv(ASock1, 0, 0), %% --- recvfrom --- - ?P("Testing recvfrom - create socket"), + ?P("[recvfrom} create socket"), {ok, Sock2} = socket:open(inet, dgram), - ?P("bind socket to: " + ?P("[recvfrom} bind socket to: " "~n ~p", [LSA]), ok = socket:bind(Sock2, LSA), ?SLEEP(?SECS(1)), + ?P("[recvfrom] try read"), {error, timeout} = socket:recvfrom(Sock2, 1024, 0), %% --- recvmsg --- - ?P("Testing recvmsg - create socket"), + ?P("[recvmsg] create socket"), {ok, Sock3} = socket:open(inet, dgram), - ?P("bind socket to: " + ?P("[recvmsg] bind socket to: " "~n ~p", [LSA]), ok = socket:bind(Sock3, LSA), ?SLEEP(?SECS(1)), - {error, timeout} = socket:recvmsg(Sock3, 0, 0), + ?P("[recvmsg] try read"), + {error, timeout} = socket:recvmsg(Sock3, 0), ?P("cleanup"), From 640b8525e3e9ae15afb745a126c672b0e4a006fa Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 10 Apr 2024 10:09:54 +0200 Subject: [PATCH 006/422] [esock|test] Fixes OTP-19063 --- lib/kernel/test/socket_SUITE.erl | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 93c07b83fe14..54ad0b621dc3 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -51824,7 +51824,7 @@ otp19063(Config) when is_list(Config) -> ?TT(?SECS(10)), tc_try(?FUNCTION_NAME, fun() -> - %% is_windows(), + is_windows(), has_support_ipv4() end, fun() -> @@ -51918,7 +51918,10 @@ do_otp19063(_) -> ?SLEEP(?SECS(1)), ?P("[recv] try read"), - {error, timeout} = socket:recv(ASock1, 0, 0), + case socket:recv(ASock1, 0, 0) of + {error, timeout} -> ok; + Any1 -> ?P("Unexpected result: ~p", [Any1]), exit({unexpected_recv_result, Any1}) + end, %% --- recvfrom --- From e54538fb6c8971b42c41798fcf8ccac379cbe281 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Mon, 6 Nov 2023 17:17:46 +0100 Subject: [PATCH 007/422] ct: Add dark mode support to coverage pages When common test is tasked with generating coverage via `-cover`, invert the colours of the webpage when the user prefers a dark color scheme. Similar support was added to the other CT-generated pages in commit bbe14c9ff74d7f87d74622f7918e6a8d53963a4d. --- lib/common_test/src/test_server_ctrl.erl | 29 ++++++++++++++++++++---- lib/tools/priv/styles.css | 14 ++++++++++++ 2 files changed, 39 insertions(+), 4 deletions(-) diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index 664e0b96a0fa..dab512e64114 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -101,6 +101,25 @@ -define(last_link, "last_link"). -define(last_test, "last_test"). -define(html_ext, ".html"). +-define(cover_html_stylesheet, + "\n"). -define(now, os:timestamp()). -define(void_fun, fun() -> ok end). @@ -5614,7 +5633,8 @@ analyse_modules(_Dir, [], _DetailsFun, Acc) -> %% Support functions for writing the cover logs (both cross and normal) write_coverlog_header(CoverLog) -> - case catch io:put_chars(CoverLog,html_header("Coverage results")) of + Style = [?cover_html_stylesheet], + case catch io:put_chars(CoverLog,html_header("Coverage results", Style)) of {'EXIT',Reason} -> io:format("\n\nERROR: Could not write normal heading in coverlog.\n" "CoverLog: ~tw\n" @@ -5664,7 +5684,8 @@ pc(Cov,NotCov) -> write_not_covered(CoverOut,M,Lines) -> - io:put_chars(CoverOut,html_header("Coverage results for "++atom_to_list(M))), + Style = [?cover_html_stylesheet], + io:put_chars(CoverOut,html_header("Coverage results for "++atom_to_list(M), Style)), io:fwrite(CoverOut, "The following lines in module ~w are not covered:\n" "\n" @@ -5741,12 +5762,12 @@ html_header(Title) -> "\n"]. -html_header(Title, Meta) -> +html_header(Title, Extra) -> ["\n" "\n" "\n" "\n" - "", Title, "\n"] ++ Meta ++ ["\n"]. + "", Title, "\n"] ++ Extra ++ ["\n"]. open_html_file(File) -> open_utf8_file(File). diff --git a/lib/tools/priv/styles.css b/lib/tools/priv/styles.css index 84f00be9fd0a..80fb608fbc30 100644 --- a/lib/tools/priv/styles.css +++ b/lib/tools/priv/styles.css @@ -94,3 +94,17 @@ td.source { white-space: pre; font: 12px monospace; } + + +@media (prefers-color-scheme: dark) { + body { + filter: invert(100%) hue-rotate(180deg) brightness(105%) contrast(95%); + background-color: #000000; + } + a:link { + color: #2B507D; + } + a:visited, a:active { + color: #85ABD5; + } +} From c6ad0d56eb9ef333ecbb931acc1deca236b5aa07 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Sun, 28 Apr 2024 13:05:08 +0200 Subject: [PATCH 008/422] Optimize maps:merge_with/3 for maps of equal size Previously, we were wrapping the combiner function without an actual need. We also use this opportunity to remove an unused argument. --- lib/stdlib/src/maps.erl | 17 +++++++---------- 1 file changed, 7 insertions(+), 10 deletions(-) diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl index c3c7da928406..f48a5673af6b 100644 --- a/lib/stdlib/src/maps.erl +++ b/lib/stdlib/src/maps.erl @@ -379,33 +379,30 @@ _Example:_ merge_with(Combiner, Map1, Map2) when is_map(Map1), is_map(Map2), is_function(Combiner, 3) -> - case map_size(Map1) > map_size(Map2) of + %% Use >= because we want to avoid reversing the combiner if we can + case map_size(Map1) >= map_size(Map2) of true -> Iterator = maps:iterator(Map2), - merge_with_1(maps:next(Iterator), - Map1, - Map2, - Combiner); + merge_with_1(maps:next(Iterator), Map1, Combiner); false -> Iterator = maps:iterator(Map1), merge_with_1(maps:next(Iterator), Map2, - Map1, fun(K, V1, V2) -> Combiner(K, V2, V1) end) end; merge_with(Combiner, Map1, Map2) -> error_with_info(error_type_merge_intersect(Map1, Map2, Combiner), [Combiner, Map1, Map2]). -merge_with_1({K, V2, Iterator}, Map1, Map2, Combiner) -> +merge_with_1({K, V2, Iterator}, Map1, Combiner) -> case Map1 of #{ K := V1 } -> NewMap1 = Map1#{ K := Combiner(K, V1, V2) }, - merge_with_1(maps:next(Iterator), NewMap1, Map2, Combiner); + merge_with_1(maps:next(Iterator), NewMap1, Combiner); #{ } -> - merge_with_1(maps:next(Iterator), maps:put(K, V2, Map1), Map2, Combiner) + merge_with_1(maps:next(Iterator), maps:put(K, V2, Map1), Combiner) end; -merge_with_1(none, Result, _, _) -> +merge_with_1(none, Result, _) -> Result. From d11e645b032491212d7bd6a331b8ea2c84d7ac25 Mon Sep 17 00:00:00 2001 From: Anupama Singh Date: Mon, 8 Apr 2024 05:31:07 +0000 Subject: [PATCH 009/422] fix pick_peer for diameter_packet --- lib/diameter/src/base/diameter_traffic.erl | 6 ++++++ lib/diameter/test/diameter_traffic_SUITE.erl | 21 +++++++++++++++++++- 2 files changed, 26 insertions(+), 1 deletion(-) diff --git a/lib/diameter/src/base/diameter_traffic.erl b/lib/diameter/src/base/diameter_traffic.erl index 110fdcafb0dd..c93af06935c4 100644 --- a/lib/diameter/src/base/diameter_traffic.erl +++ b/lib/diameter/src/base/diameter_traffic.erl @@ -1785,6 +1785,12 @@ pick_peer(SvcName, CallOpts) -> pick_peer(SvcName, App, Msg, CallOpts#options{extra = []}); +pick_peer(SvcName, + App, + #diameter_packet{msg = Msg}, + CallOpts) -> + pick_peer(SvcName, App, Msg, CallOpts#options{extra = []}); + pick_peer(_, _, undefined, _) -> {error, no_connection}; diff --git a/lib/diameter/test/diameter_traffic_SUITE.erl b/lib/diameter/test/diameter_traffic_SUITE.erl index 95ea6be02065..4b12954e1d3a 100644 --- a/lib/diameter/test/diameter_traffic_SUITE.erl +++ b/lib/diameter/test/diameter_traffic_SUITE.erl @@ -80,6 +80,7 @@ send_destination_4/1, send_destination_5/1, send_destination_6/1, + send_destination_7/1, send_bad_option_1/1, send_bad_option_2/1, send_bad_filter_1/1, @@ -889,6 +890,25 @@ send_destination_6(Config) -> ?answer_message(?UNABLE_TO_DELIVER) = call(Config, Req). +%% Send unknown host in diameter_packet with filtering and expect error. +send_destination_7(Config) -> + #group{client_service = CN, + client_dict = Dict0} + = group(Config), + Name = proplists:get_value(testcase, Config), + Svc = ?util:unique_string(), + SN = [$S | Svc], + Req = + #diameter_packet{msg = ['STR' | + #{'Termination-Cause' => ?LOGOUT, + 'Destination-Host' => [?HOST(SN, ?REALM)]}]}, + {error, no_connection} = + diameter:call(CN, + Dict0, + Req, + [{extra, [Name, diameter_lib:now()]}, + {filter, {all, [host, realm]}}]). + %% Specify an invalid option and expect failure. send_bad_option_1(Config) -> send_bad_option(Config, x). @@ -1173,7 +1193,6 @@ id(Id, {Pid, _Caps}, SvcName) -> lists:member({id, Id}, Opts). %% prepare_request/6-7 - prepare_request(_Pkt, [$C|_], {_Ref, _Caps}, _, send_discard, _) -> {discard, unprepared}; From 87840e1f8784c9c3d16ae86d5094133171a7c94e Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Mon, 13 May 2024 19:30:20 +0200 Subject: [PATCH 010/422] erts: Fix trace_session_SUITE:basic --- erts/emulator/test/trace_session_SUITE.erl | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/erts/emulator/test/trace_session_SUITE.erl b/erts/emulator/test/trace_session_SUITE.erl index 345da10f35ac..73fc834971f0 100644 --- a/erts/emulator/test/trace_session_SUITE.erl +++ b/erts/emulator/test/trace_session_SUITE.erl @@ -995,12 +995,11 @@ basic_do2(S1, Tracer1, Opts1, S2, Tracer2, Opts2) -> register(RegName, Tracee), unregister(RegName), - receive_unsorted( - [{Tracer1, {trace, Tracee, register, RegName}}, - {Tracer2, {trace, Tracee, register, RegName}}]), - receive_unsorted( - [{Tracer1, {trace, Tracee, unregister, RegName}}, - {Tracer2, {trace, Tracee, unregister, RegName}}]), + receive_parallel({[{Tracer1, {trace, Tracee, register, RegName}}, + {Tracer1, {trace, Tracee, unregister, RegName}}], + + [{Tracer2, {trace, Tracee, register, RegName}}, + {Tracer2, {trace, Tracee, unregister, RegName}}]}), 1 = erlang_trace(S1, self(), false, [procs | Opts1]), From d5b65fb55730d5cb4f11f52c2a4e05c312cd3896 Mon Sep 17 00:00:00 2001 From: Ingela Anderton Andin Date: Tue, 14 May 2024 11:52:37 +0200 Subject: [PATCH 011/422] ssl: Enhance alert handling Make it easier to distinguish between a invalid signature and unsupported signature Closes #8466 --- lib/ssl/src/ssl_certificate.erl | 14 +++++++------- lib/ssl/src/ssl_handshake.erl | 2 ++ lib/ssl/test/ssl_cert_SUITE.erl | 2 +- 3 files changed, 10 insertions(+), 8 deletions(-) diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl index 09705b949792..527a9d37f492 100644 --- a/lib/ssl/src/ssl_certificate.erl +++ b/lib/ssl/src/ssl_certificate.erl @@ -222,7 +222,7 @@ validate(Issuer, {bad_cert, cert_expired}, #{issuer := Issuer}) -> validate(_, {bad_cert, _} = Reason, _) -> {fail, Reason}; validate(Cert, valid, #{path_len := N} = UserState) -> - case verify_sign(Cert, UserState) of + case verify_sign_support(Cert, UserState) of true -> case maps:get(cert_ext, UserState, undefined) of undefined -> @@ -231,7 +231,7 @@ validate(Cert, valid, #{path_len := N} = UserState) -> verify_cert_extensions(Cert, UserState#{path_len => N-1}) end; false -> - {fail, {bad_cert, invalid_signature}} + {fail, {bad_cert, unsupported_signature}} end; validate(Cert, valid_peer, UserState = #{role := client, server_name := Hostname, customize_hostname_check := Customize}) when Hostname =/= disable -> @@ -592,22 +592,22 @@ verify_cert_extensions(Cert, UserState, [_|Exts], Context) -> %% Skip unknown extensions! verify_cert_extensions(Cert, UserState, Exts, Context). -verify_sign(_, #{version := Version}) +verify_sign_support(_, #{version := Version}) when ?TLS_LT(Version, ?TLS_1_2) -> %% This verification is not applicable pre TLS-1.2 true; -verify_sign(Cert, #{version := ?TLS_1_2, +verify_sign_support(Cert, #{version := ?TLS_1_2, signature_algs := SignAlgs, signature_algs_cert := undefined}) -> is_supported_signature_algorithm_1_2(Cert, SignAlgs); -verify_sign(Cert, #{version := ?TLS_1_2, +verify_sign_support(Cert, #{version := ?TLS_1_2, signature_algs_cert := SignAlgs}) -> is_supported_signature_algorithm_1_2(Cert, SignAlgs); -verify_sign(Cert, #{version := ?TLS_1_3, +verify_sign_support(Cert, #{version := ?TLS_1_3, signature_algs := SignAlgs, signature_algs_cert := undefined}) -> is_supported_signature_algorithm_1_3(Cert, SignAlgs); -verify_sign(Cert, #{version := ?TLS_1_3, +verify_sign_support(Cert, #{version := ?TLS_1_3, signature_algs_cert := SignAlgs}) -> is_supported_signature_algorithm_1_3(Cert, SignAlgs). diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 7dd60829a12e..09341905e956 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -2111,6 +2111,8 @@ path_validation_alert({bad_cert, invalid_issuer}) -> ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); path_validation_alert({bad_cert, invalid_signature}) -> ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); +path_validation_alert({bad_cert, unsupported_signature}) -> + ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE); path_validation_alert({bad_cert, name_not_permitted}) -> ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); path_validation_alert({bad_cert, unknown_critical_extension}) -> diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl index ef9e2cf75933..18fbddf83cb8 100644 --- a/lib/ssl/test/ssl_cert_SUITE.erl +++ b/lib/ssl/test/ssl_cert_SUITE.erl @@ -1216,7 +1216,7 @@ unsupported_sign_algo_cert_client_auth(Config) -> 'tlsv1.3' -> ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, certificate_required); _ -> - ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, bad_certificate) + ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, unsupported_certificate) end. %%-------------------------------------------------------------------- From 666a68c59f07b03f9b5f5372976a51b9c16ef8e8 Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Tue, 14 May 2024 18:07:24 +0200 Subject: [PATCH 012/422] tools: Fix doc typo in tprof.erl --- lib/tools/src/tprof.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/tools/src/tprof.erl b/lib/tools/src/tprof.erl index 8cda8c0dada7..bb16e2a048c5 100644 --- a/lib/tools/src/tprof.erl +++ b/lib/tools/src/tprof.erl @@ -210,7 +210,7 @@ Which processes that are profiled depends on the profiling type. * `call_time` and `call_memory` limits the profiling to the processes spawned from the user-provided function (using the `set_on_spawn` - option for `erlang:trace/3`). + option for `trace:process/4`). `call_time` and `call_memory` can be restricted to profile a single process: From 02575c975a47494c0878a611e74b24b53a8a8449 Mon Sep 17 00:00:00 2001 From: Lukas Larsson Date: Wed, 15 May 2024 11:55:00 +0200 Subject: [PATCH 013/422] erts: Fix erl -man lookup We cut the arguments to man at the first -- so that things in ERL_ZFLAGS don't end up as arguments to man. closes #8477 --- erts/etc/common/erlexec.c | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/erts/etc/common/erlexec.c b/erts/etc/common/erlexec.c index 957e1a83da79..ef29181f6b34 100644 --- a/erts/etc/common/erlexec.c +++ b/erts/etc/common/erlexec.c @@ -722,6 +722,12 @@ int main(int argc, char **argv) error("-man not supported on Windows"); #else argv[i] = "man"; + for (int j = i; argv[j]; j++) { + if (strncmp(argv[j],sep,2) == 0) { + argv[j] = NULL; + break; + } + } erts_snprintf(tmpStr, sizeof(tmpStr), "%s/man", rootdir); set_env("MANPATH", tmpStr); execvp("man", argv+i); From 358a51f7dfe9560e106404853cc72aa6dbe2c907 Mon Sep 17 00:00:00 2001 From: Cocoa Date: Mon, 20 May 2024 11:44:28 +0100 Subject: [PATCH 014/422] use C++17 list-initialization --- erts/emulator/beam/jit/arm/beam_asm_global.cpp | 7 ++++--- erts/emulator/beam/jit/arm/beam_asm_module.cpp | 18 ++++++------------ 2 files changed, 10 insertions(+), 15 deletions(-) diff --git a/erts/emulator/beam/jit/arm/beam_asm_global.cpp b/erts/emulator/beam/jit/arm/beam_asm_global.cpp index 7e294602e4e2..990f826e03ae 100644 --- a/erts/emulator/beam/jit/arm/beam_asm_global.cpp +++ b/erts/emulator/beam/jit/arm/beam_asm_global.cpp @@ -74,9 +74,10 @@ BeamGlobalAssembler::BeamGlobalAssembler(JitAllocator *allocator) stop = (ErtsCodePtr)((char *)getBaseAddress() + code.codeSize()); } - ranges.push_back({.start = start, - .stop = stop, - .name = code.labelEntry(labels[val.first])->name()}); + ranges.push_back(AsmRange{start, + stop, + code.labelEntry(labels[val.first])->name(), + {}}); } (void)beamasm_metadata_insert("global", diff --git a/erts/emulator/beam/jit/arm/beam_asm_module.cpp b/erts/emulator/beam/jit/arm/beam_asm_module.cpp index caec6c0eb890..82b530690ed4 100644 --- a/erts/emulator/beam/jit/arm/beam_asm_module.cpp +++ b/erts/emulator/beam/jit/arm/beam_asm_module.cpp @@ -541,10 +541,7 @@ const Label &BeamModuleAssembler::resolve_label(const Label &target, anchor = a.newNamedLabel(name.str().c_str()); } - auto it = _veneers.emplace(target.id(), - Veneer{.latestOffset = maxOffset, - .anchor = anchor, - .target = target}); + auto it = _veneers.emplace(target.id(), Veneer{maxOffset, anchor, target}); const Veneer &veneer = it->second; _pending_veneers.emplace(veneer); @@ -590,10 +587,8 @@ arm::Mem BeamModuleAssembler::embed_constant(const ArgVal &value, } } - auto it = _constants.emplace(value, - Constant{.latestOffset = maxOffset, - .anchor = a.newLabel(), - .value = value}); + auto it = + _constants.emplace(value, Constant{maxOffset, a.newLabel(), value}); const Constant &constant = it->second; _pending_constants.emplace(constant); @@ -608,10 +603,9 @@ arm::Mem BeamModuleAssembler::embed_label(const Label &label, ASSERT(disp >= dispMin && disp <= dispMax); - auto it = _embedded_labels.emplace(label.id(), - EmbeddedLabel{.latestOffset = maxOffset, - .anchor = a.newLabel(), - .label = label}); + auto it = _embedded_labels.emplace( + label.id(), + EmbeddedLabel{maxOffset, a.newLabel(), label}); ASSERT(it.second); const EmbeddedLabel &embedded_label = it.first->second; _pending_labels.emplace(embedded_label); From 92d8cac337404515a2d61609f785e95553045252 Mon Sep 17 00:00:00 2001 From: Cocoa Date: Mon, 20 May 2024 12:16:41 +0100 Subject: [PATCH 015/422] prepare nsis scripts for arm64 --- erts/etc/win32/nsis/Makefile | 3 +++ erts/etc/win32/nsis/erlang20.nsi | 12 ++++++++++-- erts/etc/win32/nsis/find_redist.sh | 15 +++++++++++++-- 3 files changed, 26 insertions(+), 4 deletions(-) diff --git a/erts/etc/win32/nsis/Makefile b/erts/etc/win32/nsis/Makefile index dd4bbd4de670..e007e3deafed 100644 --- a/erts/etc/win32/nsis/Makefile +++ b/erts/etc/win32/nsis/Makefile @@ -54,6 +54,9 @@ WTARGET_DIR=$(shell (w32_path.sh -d "$(TARGET_DIR)")) ifeq ($(CONFIG_SUBTYPE),win64) WINTYPE=win64 REDIST_TARGET=vcredist_x64.exe +else ifeq ($(CONFIG_SUBTYPE),arm64) + WINTYPE=arm64 + REDIST_TARGET=vcredist_arm64.exe else WINTYPE=win32 REDIST_TARGET=vcredist_x86.exe diff --git a/erts/etc/win32/nsis/erlang20.nsi b/erts/etc/win32/nsis/erlang20.nsi index 7d63671f89ca..2785a103d46c 100644 --- a/erts/etc/win32/nsis/erlang20.nsi +++ b/erts/etc/win32/nsis/erlang20.nsi @@ -68,7 +68,11 @@ Var STARTMENU_FOLDER !if ${WINTYPE} == "win64" !define MUI_STARTMENUPAGE_DEFAULTFOLDER "${OTP_PRODUCT} ${OTP_RELEASE} (x64)" !else - !define MUI_STARTMENUPAGE_DEFAULTFOLDER "${OTP_PRODUCT} ${OTP_RELEASE} (i386)" + !if ${WINTYPE} == "arm64" + !define MUI_STARTMENUPAGE_DEFAULTFOLDER "${OTP_PRODUCT} ${OTP_RELEASE} (arm64)" + !else + !define MUI_STARTMENUPAGE_DEFAULTFOLDER "${OTP_PRODUCT} ${OTP_RELEASE} (i386)" + !endif !endif ;-------------------------------- @@ -104,7 +108,7 @@ Var STARTMENU_FOLDER VIProductVersion "${OTP_VERSION_LONG}" VIAddVersionKey /LANG=${LANG_ENGLISH} "CompanyName" "Ericsson AB" -VIAddVersionKey /LANG=${LANG_ENGLISH} "FileVersion" "${OTP_VERSION}" +VIAddVersionKey /LANG=${LANG_ENGLISH} "FileVersion" "${OTP_VERSION}" VIAddVersionKey /LANG=${LANG_ENGLISH} "FileDescription" "Erlang/OTP installer" VIAddVersionKey /LANG=${LANG_ENGLISH} "LegalCopyright" "Copyright Ericsson AB 2010-${YEAR}. All Rights Reserved." VIAddVersionKey /LANG=${LANG_ENGLISH} "ProductName" "Erlang/OTP" @@ -385,6 +389,10 @@ Function .onInit StrCmpS ${WINTYPE} "win64" +1 +4 StrCpy $archprefix "amd64" StrCpy $sysnativedir "$WINDIR\sysnative" + Goto +4 + StrCmpS ${WINTYPE} "arm64" +1 +6 + StrCpy $archprefix "arm64" + StrCpy $sysnativedir "$WINDIR\sysnative" Goto +3 StrCpy $archprefix "x86" StrCpy $sysnativedir $SYSDIR diff --git a/erts/etc/win32/nsis/find_redist.sh b/erts/etc/win32/nsis/find_redist.sh index f551bc752749..6a43571ff822 100755 --- a/erts/etc/win32/nsis/find_redist.sh +++ b/erts/etc/win32/nsis/find_redist.sh @@ -85,13 +85,19 @@ add_path_element() if [ "$1" = "win64" ]; then AMD64DIR=true VCREDIST=vcredist_x64 + VCREDIST2=vcredist.x64 COMPONENTS="cl amd64 bin vc" elif [ "$1" = "win32" ]; then AMD64DIR=false VCREDIST=vcredist_x86 + VCREDIST2=vcredist.x86 COMPONENTS="cl bin vc" +elif [ "$1" = "arm64" ]; then + AMD64DIR=false + VCREDIST=vcredist_arm64 + VCREDIST2=vcredist.arm64 else - echo "TARGET argument should win32 or win64" + echo "TARGET argument should win32, win64 or arm64" exit 2 fi @@ -101,11 +107,16 @@ if [ x"$VCToolsRedistDir" != x"" ]; then echo "$File" exit 0 fi + File="$VCToolsRedistDir/$VCREDIST2.exe" + if [ -r "$File" ]; then + echo "$File" + exit 0 + fi fi CLPATH=`lookup_prog_in_path cl` if [ -z "$CLPATH" ]; then - echo "Can not locate cl.exe and vcredist_x86/x64.exe - OK if using mingw" >&2 + echo "Can not locate cl.exe and vcredist_x86/x64/arm64.exe - OK if using mingw" >&2 exit 1 fi From 6f316095b9096b587772e9c45e09c94f8f4e405e Mon Sep 17 00:00:00 2001 From: Ingela Anderton Andin Date: Tue, 21 May 2024 11:14:54 +0200 Subject: [PATCH 016/422] ssl: Enhance ALERT logs to help understand what causes the alert. --- lib/ssl/src/ssl_handshake.erl | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 7dd60829a12e..48663207d110 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -2108,25 +2108,24 @@ maybe_check_hostname(_, valid, _) -> path_validation_alert({bad_cert, cert_expired}) -> ?ALERT_REC(?FATAL, ?CERTIFICATE_EXPIRED); path_validation_alert({bad_cert, invalid_issuer}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, invalid_issuer); path_validation_alert({bad_cert, invalid_signature}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, invalid_signature); path_validation_alert({bad_cert, name_not_permitted}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, name_not_permitted); path_validation_alert({bad_cert, unknown_critical_extension}) -> - ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE); + ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE, unknown_critical_extension); path_validation_alert({bad_cert, {revoked, _}}) -> ?ALERT_REC(?FATAL, ?CERTIFICATE_REVOKED); path_validation_alert({bad_cert, {revocation_status_undetermined, Details}}) -> ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, Details); path_validation_alert({bad_cert, selfsigned_peer}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, selfsigned_peer); path_validation_alert({bad_cert, unknown_ca}) -> ?ALERT_REC(?FATAL, ?UNKNOWN_CA); path_validation_alert(Reason) -> ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason). - digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) -> try do_digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) catch From 945c940f6bc6c0bcb026cdc6ae8f3ce358e859bb Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Tue, 21 May 2024 17:31:13 +0200 Subject: [PATCH 017/422] Update pre-push hook after OTP 27.0 release --- scripts/pre-push | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/scripts/pre-push b/scripts/pre-push index f1a6de50fd8b..18d41a06b12d 100755 --- a/scripts/pre-push +++ b/scripts/pre-push @@ -23,14 +23,14 @@ # # Bump this version to give users an update notification. -PRE_PUSH_SCRIPT_VERSION=5 +PRE_PUSH_SCRIPT_VERSION=6 -NEW_RELEASES="26 25 24 23 22 21 20 19 18 17" +NEW_RELEASES="27 26 25 24 23 22 21 20 19 18 17" OLD_RELEASES="r16 r15 r14 r13" RELEASES="$NEW_RELEASES $OLD_RELEASES" # First commit on master, not allowed in other branches -MASTER_ONLY=c4a6a7a502cdb8ee0bd42d0e2cc58fe5bc0325a3 +MASTER_ONLY=bff328f24263af6c600efa8a2755a175c9dbb94f # Number of commits and files allowed in one push by this script NCOMMITS_MAX=100 From daa5bbf25a52f3db0ad722578a99f540461b2844 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 21 May 2024 17:49:08 +0200 Subject: [PATCH 018/422] [kernel] Handle timeout OTP-19063 --- lib/kernel/src/socket.erl | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/lib/kernel/src/socket.erl b/lib/kernel/src/socket.erl index 68e79e599c34..36952aa504a7 100644 --- a/lib/kernel/src/socket.erl +++ b/lib/kernel/src/socket.erl @@ -3440,6 +3440,8 @@ recv(?socket(SockRef), Length, Flags, Timeout) case prim_socket:recv(SockRef, Length, Flags, zero) of ok -> {error, timeout}; + timeout -> + {error, timeout}; Result -> Result end; @@ -3838,6 +3840,8 @@ recvfrom(?socket(SockRef), BufSz, Flags, Timeout) case prim_socket:recvfrom(SockRef, BufSz, Flags, zero) of ok -> {error, timeout}; + timeout -> + {error, timeout}; Result -> recvfrom_result(Result) end; @@ -4137,6 +4141,8 @@ recvmsg(?socket(SockRef), BufSz, CtrlSz, Flags, Timeout) case prim_socket:recvmsg(SockRef, BufSz, CtrlSz, Flags, zero) of ok -> {error, timeout}; + timeout -> + {error, timeout}; Result -> recvmsg_result(Result) end; From 633640c0dcc275a00bb3669a03e8a887f0751dcd Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Thu, 2 May 2024 13:27:28 +0200 Subject: [PATCH 019/422] [diameter|test] Improve debugging Improve test case analuyzis by adding various printouts... --- lib/diameter/test/Makefile | 4 +- .../test/diameter_distribution_SUITE.erl | 90 +++++++--- lib/diameter/test/diameter_examples_SUITE.erl | 65 +++++-- .../test/diameter_transport_SUITE.erl | 160 ++++++++++++++---- lib/diameter/test/diameter_util.erl | 35 ++-- lib/diameter/test/diameter_util.hrl | 38 +++++ 6 files changed, 312 insertions(+), 80 deletions(-) create mode 100644 lib/diameter/test/diameter_util.hrl diff --git a/lib/diameter/test/Makefile b/lib/diameter/test/Makefile index 36cc2ec17e85..8a0d1c9e53fa 100644 --- a/lib/diameter/test/Makefile +++ b/lib/diameter/test/Makefile @@ -40,6 +40,7 @@ RELSYSDIR = $(RELEASE_PATH)/diameter_test include modules.mk +HRL_FILES = diameter_util.hrl ERL_FILES = $(MODULES:%=%.erl) TARGET_FILES = $(MODULES:%=%.$(EMULATOR)) @@ -183,7 +184,8 @@ release_spec release_docs_spec: release_tests_spec: $(INSTALL_DIR) "$(RELSYSDIR)" - $(INSTALL_DATA) $(TEST_SPEC_FILE) \ + $(INSTALL_DATA) $(HRL_FILES) \ + $(TEST_SPEC_FILE) \ $(COVER_SPEC_FILE) \ "$(RELSYSDIR)" $(MAKE) $(DATA_DIRS:%/=release_data_%) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 013c42496e47..6ffd7031ec1f 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2022. All Rights Reserved. +%% Copyright Ericsson AB 2013-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -29,13 +29,19 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - traffic/1]). + + %% The test cases + traffic/1 + ]). %% rpc calls -export([ping/1, start/1, + stop/1, connect/1, call/1]). @@ -52,9 +58,13 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc6733.hrl"). +-include("diameter_util.hrl"). + + %% =========================================================================== --define(util, diameter_util). +-define(DL(F), ?DL(F, [])). +-define(DL(F, A), ?LOG("DDISTS", F, A)). -define(CLIENT, 'CLIENT'). -define(SERVER, 'SERVER'). @@ -92,11 +102,12 @@ %% The order here is significant and causes the server to listen %% before the clients connect. --define(NODES, [{server, ?SERVER}, +-define(NODES, [{server, ?SERVER}, {client0, ?CLIENT}, {client1, ?CLIENT}, {client2, ?CLIENT}]). + %% =========================================================================== suite() -> @@ -106,28 +117,43 @@ all() -> [traffic]. traffic(_Config) -> - traffic(). + ?DL("traffic -> entry"), + Res = traffic(), + ?DL("traffic -> done when" + "~n Res: ~p", [Res]), + Res. %% =========================================================================== run() -> - [] = ?util:run([{fun traffic/0, 60000}]). + [] = ?DUTIL:run([{fun traffic/0, 60000}]). %% process for linked peers to die with %% traffic/0 traffic() -> + ?DL("traffic -> make sure we have distro"), true = is_alive(), %% need distribution for peer nodes + ?DL("traffic -> get nodes"), Nodes = enslave(), + ?DL("traffic -> ping nodes"), [] = ping(Nodes), %% drop client node + ?DL("traffic -> start nodes"), [] = start(Nodes), + ?DL("traffic -> connect nodes"), [_] = connect(Nodes), - [] = send(Nodes). + ?DL("traffic -> send (to) nodes"), + [] = send(Nodes), + ?DL("traffic -> stop nodes"), + [] = stop(Nodes), + ?DL("traffic -> done"), + ok. %% enslave/0 %% -%% Start four slave nodes, one to implement a Diameter server, -%% three to implement a client. +%% Start four nodes; +%% - one to implement a Diameter server, +%% - three to implement a client. enslave() -> Here = filename:dirname(code:which(?MODULE)), @@ -136,7 +162,7 @@ enslave() -> [{N,S} || {M,S} <- ?NODES, N <- [start(M, Args)]]. start(Name, Args) -> - {ok, _, Node} = ?util:peer(#{name => Name, args => Args}), + {ok, _, Node} = ?DUTIL:peer(#{name => Name, args => Args}), Node. %% ping/1 @@ -171,6 +197,20 @@ start(Nodes) -> RC <- [rpc:call(N, ?MODULE, start, [S])], RC /= ok]. +%% stop/1 +%% +%% Stop diameter services. + +stop(SvcName) + when is_atom(SvcName) -> + ok = diameter:stop_service(SvcName), + ok = diameter:stop(); + +stop(Nodes) -> + [{N,RC} || {N,S} <- Nodes, + RC <- [rpc:call(N, ?MODULE, stop, [S])], + RC /= ok]. + sequence() -> sequence(sname()). @@ -203,10 +243,10 @@ peers(client2) -> nodes(). %% nodes. connect({?SERVER, _, []}) -> - [_LRef = ?util:listen(?SERVER, tcp)]; + [_LRef = ?DUTIL:listen(?SERVER, tcp)]; connect({?CLIENT, [{Node, _} | _], [LRef] = Acc}) -> - ?util:connect(?CLIENT, tcp, {Node, LRef}), + ?DUTIL:connect(?CLIENT, tcp, {Node, LRef}), Acc; connect(Nodes) -> @@ -221,31 +261,43 @@ connect(Nodes) -> %% send/1 send(Nodes) -> - ?util:run([[fun send/2, Nodes, T] - || T <- [local, remote, timeout, failover]]). + ?RUN([[fun send/2, Nodes, T] + || T <- [local, remote, timeout, failover]]). %% send/2 %% Send a request from the first client node, using a the local %% transport. send(Nodes, local) -> + ?DL("send(local) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 0, str(?LOGOUT)); + = send(Nodes, 0, str(?LOGOUT)), + ?DL("send(local) -> success (=success)"), + ok; %% Send a request from the first client node, using a transport on the %% another node. send(Nodes, remote) -> + ?DL("send(remote) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 1, str(?LOGOUT)); + = send(Nodes, 1, str(?LOGOUT)), + ?DL("send(remote) -> success (=success)"), + ok; %% Send a request that the server discards. send(Nodes, timeout) -> - {error, timeout} = send(Nodes, 1, str(?TIMEOUT)); + ?DL("send(timeout) -> entry - expect timeout"), + {error, timeout} = send(Nodes, 1, str(?TIMEOUT)), + ?DL("send(timeout) -> success (=timeout)"), + ok; %% Send a request that causes the server to take the transport down. send(Nodes, failover) -> + ?DL("send(failover) -> entry - expect busy (~p)", [?BUSY]), #'diameter_base_answer-message'{'Result-Code' = ?BUSY} - = send(Nodes, 2, str(?MOVED)). + = send(Nodes, 2, str(?MOVED)), + ?DL("send(failover) -> success (=busy)"), + ok. %% =========================================================================== diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 7bb39cace31b..0429a473cd04 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2022. All Rights Reserved. +%% Copyright Ericsson AB 2013-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -29,10 +29,15 @@ run/1]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, + + %% The test cases dict/1, - code/1]). + code/1 + ]). %% rpc calls -export([install/1, @@ -41,9 +46,13 @@ -include("diameter.hrl"). -%% =========================================================================== +-include("diameter_util.hrl"). + + +-define(EL(F, A), ?LOG("DEXS", F, A)). --define(util, diameter_util). + +%% =========================================================================== %% The order here is significant and causes the server to listen %% before the clients connect. @@ -60,11 +69,12 @@ -define(DICT0, [rfc3588_base, rfc6733_base]). %% Transport protocols over which the example Diameter nodes are run. --define(PROTS, [sctp || ?util:have_sctp()] ++ [tcp]). +-define(PROTS, [sctp || ?HAVE_SCTP()] ++ [tcp]). -define(L, atom_to_list). -define(A, list_to_atom). + %% =========================================================================== %% common_test wrapping @@ -74,11 +84,24 @@ suite() -> all() -> [dict, code]. + dict(Config) -> - run(dict, Config). + ?EL("dict -> entry with" + "~n Config: ~p", [Config]), + Res = run(dict, Config), + ?EL("dict -> done when" + "~n Res: ~p", [Res]), + Res. + code(Config) -> - run(code, Config). + ?EL("code -> entry with" + "~n Config: ~p", [Config]), + Res = run(code, Config), + ?EL("code -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== @@ -90,16 +113,27 @@ run() -> %% run/1 run({dict, Dir}) -> - compile_dicts(Dir); + ?EL("run(dict) -> entry with" + "~n Dir: ~p", [Dir]), + Res = compile_dicts(Dir), + ?EL("run(dict) -> done when" + "~n Res: ~p", [Res]), + Res; + %% The example code doesn't use the example dictionaries, so a %% separate testcase. run({code, Dir}) -> - run_code(Dir); + ?EL("run(code) -> entry with" + "~n Dir: ~p", [Dir]), + Res = run_code(Dir), + ?EL("run(code) -> done when" + "~n Res: ~p", [Res]), + Res; run(List) when is_list(List) -> - Tmp = ?util:mktemp("diameter_examples"), + Tmp = ?MKTEMP("diameter_examples"), try run(List, Tmp) after @@ -111,11 +145,12 @@ run(List) %% Eg. erl -noinput -s diameter_examples_SUITE run code -s init stop ... run(List, Dir) when is_list(List) -> - ?util:run([{[fun run/1, {F, Dir}], 60000} || F <- List]); + ?RUN([{[fun run/1, {F, Dir}], 60000} || F <- List]); run(F, Config) -> run([F], proplists:get_value(priv_dir, Config)). + %% =========================================================================== %% compile_dicts/1 %% @@ -301,7 +336,7 @@ enslave(Prefix) -> slave(Name, Dir) -> Args = ["-pa", Dir, filename:join([Dir, "..", "ebin"])], - {ok, _Pid, _Node} = ?util:peer(#{name => Name, args => Args}). + {ok, _Pid, _Node} = ?PEER(#{name => Name, args => Args}). here() -> filename:dirname(code:which(?MODULE)). @@ -320,7 +355,7 @@ start({server, Prot, Ebin}) -> ok = diameter:start(), ok = server:start(), {ok, Ref} = server:listen({Prot, any, 3868}), - [_] = ?util:lport(Prot, Ref), + [_] = ?LPORT(Prot, Ref), ok; start({client = Svc, Prot, Ebin}) -> @@ -365,7 +400,7 @@ traffic({Prot, Ebin}) -> run_code(Dir) -> true = is_alive(), %% need distribution for peer nodes {ok, Ebin} = compile_code(mkdir(Dir, "code")), - ?util:run([[fun traffic/1, {T, Ebin}] || T <- ?PROTS]). + ?RUN([[fun traffic/1, {T, Ebin}] || T <- ?PROTS]). %% call/1 diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index 9b763141ffe2..6b0f538ba357 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -29,9 +29,14 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - parallel/1]). + + %% The test cases + parallel/1 + ]). -export([accept/1, connect/1, @@ -41,7 +46,7 @@ -include_lib("kernel/include/inet_sctp.hrl"). -include("diameter.hrl"). --define(util, diameter_util). +-include("diameter_util.hrl"). %% Corresponding to diameter_* transport modules. -define(TRANSPORTS, [tcp, sctp]). @@ -77,6 +82,11 @@ %% Messages from gen_sctp. -define(SCTP(Sock, Data), {sctp, Sock, _, _, Data}). + +-define(TL(F), ?TL(F, [])). +-define(TL(F, A), ?LOG("DTRANSPS", F, A)). + + %% =========================================================================== %% common_test wrapping @@ -87,7 +97,12 @@ all() -> [parallel]. parallel(_) -> - run(). + ?TL("parallel -> entry"), + Res = run(), + ?TL("parallel -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== @@ -96,9 +111,9 @@ parallel(_) -> run() -> ok = diameter:start(), try - ?util:run([[fun run/1, {P,F}] - || P <- [sctp || ?util:have_sctp()] ++ [tcp], - F <- [connect, accept, reconnect]]) + ?RUN([[fun run/1, {P,F}] + || P <- [sctp || ?HAVE_SCTP()] ++ [tcp], + F <- [connect, accept, reconnect]]) after diameter:stop() end. @@ -106,13 +121,29 @@ run() -> %% run/1 run({Prot, reconnect}) -> - reconnect(Prot); + ?TL("run(reconnect) -> entry with" + "~n Prot: ~p", [Prot]), + Res = reconnect(Prot), + ?TL("run(reconnect) -> done when" + "~n Res: ~p", [Res]), + Res; run({Prot, accept}) -> - accept(Prot); + ?TL("run(accept) -> entry with" + "~n Prot: ~p", [Prot]), + Res = accept(Prot), + ?TL("run(accept) -> done when" + "~n Res: ~p", [Res]), + Res; run({Prot, connect}) -> - connect(Prot). + ?TL("run(connect) -> entry with" + "~n Prot: ~p", [Prot]), + Res = connect(Prot), + ?TL("run(connect) -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== %% accept/1 @@ -120,11 +151,19 @@ run({Prot, connect}) -> %% diameter transport accepting, test code connecting. accept(Prot) -> + ?TL("accept -> entry with" + "~n Prot: ~p", [Prot]), + Ref = make_ref(), true = diameter_reg:add_new({diameter_config, transport, Ref}), %% fake it T = {Prot, Ref}, - ?util:run([{{?MODULE, [init, X, T]}, 15000} - || X <- [accept, gen_connect]]). + Res = ?RUN([{{?MODULE, [init, X, T]}, 15000} + || X <- [accept, gen_connect]]), + + ?TL("accept -> done when" + "~n Res: ~p", [Res]), + ok. + %% =========================================================================== %% connect/1 @@ -132,9 +171,17 @@ accept(Prot) -> %% Test code accepting, diameter transport connecting. connect(Prot) -> + ?TL("connect -> entry with" + "~n Prot: ~p", [Prot]), + T = {Prot, make_ref()}, - ?util:run([{{?MODULE, [init, X, T]}, 15000} - || X <- [gen_accept, connect]]). + Res = ?RUN([{{?MODULE, [init, X, T]}, 15000} + || X <- [gen_accept, connect]]), + + ?TL("connect -> done when" + "~n Res: ~p", [Res]), + ok. + %% =========================================================================== %% reconnect/1 @@ -144,9 +191,11 @@ connect(Prot) -> %% broken. reconnect({listen, Ref}) -> + ?TL("reconnect(listen) -> entry with" + "~n Ref: ~p", [Ref]), SvcName = make_ref(), ok = start_service(SvcName), - LRef = ?util:listen(SvcName, tcp, [{watchdog_timer, 6000}]), + LRef = ?LISTEN(SvcName, tcp, [{watchdog_timer, 6000}]), [_] = diameter_reg:wait({diameter_tcp, listener, {LRef, '_'}}), true = diameter_reg:add_new({?MODULE, Ref, LRef}), @@ -157,15 +206,22 @@ reconnect({listen, Ref}) -> exit(TPid, kill), %% Wait for the partner again. - abort(SvcName, LRef, Ref); + Res = abort(SvcName, LRef, Ref), + + ?TL("reconnect(listen) -> done when" + "~n Res: ~p", [Res]), + ok; reconnect({connect, Ref}) -> + ?TL("reconnect(connect) -> entry with" + "~n Ref: ~p", [Ref]), + SvcName = make_ref(), true = diameter:subscribe(SvcName), ok = start_service(SvcName), [{{_, _, LRef}, Pid}] = diameter_reg:wait({?MODULE, Ref, '_'}), - CRef = ?util:connect(SvcName, tcp, LRef, [{connect_timer, 2000}, - {watchdog_timer, 6000}]), + CRef = ?CONNECT(SvcName, tcp, LRef, [{connect_timer, 2000}, + {watchdog_timer, 6000}]), %% Tell partner to kill transport after seeing that there are no %% reconnection attempts. @@ -181,13 +237,23 @@ reconnect({connect, Ref}) -> %% Wait for partner to die. MRef = erlang:monitor(process, Pid), - ?RECV({'DOWN', MRef, process, _, _}); + Res = ?RECV({'DOWN', MRef, process, _, _}), + + ?TL("reconnect(connect) -> done when" + "~n Res: ~p", [Res]), + ok; reconnect(Prot) -> + ?TL("reconnect -> entry with" + "~n Prot: ~p", [Prot]), Ref = make_ref(), - ?util:run([{{?MODULE, [reconnect, {T, Ref}]}, 240000} - || Prot == tcp, %% ignore sctp - T <- [listen, connect]]). + Res = ?RUN([{{?MODULE, [reconnect, {T, Ref}]}, 240000} + || Prot == tcp, %% ignore sctp + T <- [listen, connect]]), + + ?TL("reconnect -> done when" + "~n Res: ~p", [Res]), + ok. start_service(SvcName) -> OH = diameter_util:unique_string(), @@ -225,6 +291,10 @@ abort(SvcName, LRef, Ref) %% init/2 init(accept, {Prot, Ref}) -> + ?TL("init(accept) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Start an accepting transport and receive notification of a %% connection. TPid = start_accept(Prot, Ref), @@ -238,19 +308,34 @@ init(accept, {Prot, Ref}) -> %% Expect the transport process to die as a result of the peer %% closing the connection. MRef = erlang:monitor(process, TPid), - ?RECV({'DOWN', MRef, process, _, _}); + Res = ?RECV({'DOWN', MRef, process, _, _}), + + ?TL("init(accept) -> done when" + "~n Res: ~p", [Res]), + ok; init(gen_connect, {Prot, Ref}) -> + ?TL("init(gen_connect) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Lookup the peer's listening socket. - [PortNr] = ?util:lport(Prot, Ref), + [PortNr] = ?LPORT(Prot, Ref), %% Connect, send a message and receive it back. {ok, Sock} = gen_connect(Prot, PortNr), Bin = make_msg(), ok = gen_send(Prot, Sock, Bin), - Bin = gen_recv(Prot, Sock); + Bin = gen_recv(Prot, Sock), + + ?TL("init(gen_connect) -> done"), + ok; init(gen_accept, {Prot, Ref}) -> + ?TL("init(gen_accept) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Open a listening socket and publish the port number. {ok, LSock} = gen_listen(Prot), {ok, PortNr} = inet:port(LSock), @@ -261,14 +346,22 @@ init(gen_accept, {Prot, Ref}) -> {ok, Sock} = gen_accept(Prot, LSock), Bin = gen_recv(Prot, Sock), ok = gen_send(Prot, Sock, Bin), - receive - {tcp_closed, Sock} = T -> - T; - ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> - T - end; + Res = receive + {tcp_closed, Sock} = T -> + T; + ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> + T + end, + + ?TL("init(gen_accept) -> done when" + "~n T: ~p", [T]), + ok; init(connect, {Prot, Ref}) -> + ?TL("init(connect) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Lookup the peer's listening socket. [{?TEST_LISTENER(_, PortNr), _}] = diameter_reg:wait(?TEST_LISTENER(Ref, '_')), @@ -280,7 +373,10 @@ init(connect, {Prot, Ref}) -> %% Send a message and receive it back. Bin = make_msg(), TPid ! ?TMSG({send, Bin}), - Bin = bin(Prot, ?RECV(?TMSG({recv, P}), P)). + Bin = bin(Prot, ?RECV(?TMSG({recv, P}), P)), + + ?TL("init(connect) -> done"), + ok. bin(sctp, #diameter_packet{bin = Bin}) -> Bin; diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index a8c2555e08a6..075fc59c6001 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -37,7 +37,8 @@ peer/1, unique_string/0, have_sctp/0, - eprof/1]). + eprof/1, + log/4]). %% diameter-specific -export([lport/2, @@ -46,9 +47,12 @@ disconnect/4, info/0]). +-include("diameter_util.hrl"). + + -define(L, atom_to_list). --define(LOG(F, A), log(?LINE, F, A)). +-define(DL(F, A), ?LOG("DUTIL", F, A)). %% --------------------------------------------------------------------------- @@ -129,23 +133,23 @@ down(Parent, Worker) %% Die with the worker, kill the worker if the parent dies. down(ParentMRef, WorkerPid) -> - ?LOG("down -> await worker (~p) termination", [WorkerPid]), + ?DL("down -> await worker (~p) termination", [WorkerPid]), receive {'EXIT', TCPid, {timetrap_timeout = R, TCTimeout, TCStack}} -> - ?LOG("down -> test case timetrap timeout when" - "~n (test case) Pid: ~p" - "~n (test case) Timeout: ~p" - "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), + ?DL("down -> test case timetrap timeout when" + "~n (test case) Pid: ~p" + "~n (test case) Timeout: ~p" + "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), exit(WorkerPid, kill), %% So many wrapper levels, make sure we go with a bang exit({TCPid, R, TCStack}); {'DOWN', ParentMRef, process, PPid, PReason} -> - ?LOG("down -> parent process (~p) died: " - "~n Reason: ~p", [PPid, PReason]), + ?DL("down -> parent process (~p) died: " + "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); {'DOWN', _, process, WorkerPid, WReason} -> - ?LOG("down -> worker process (~p) died: " - "~n Reason: ~p", [WorkerPid, WReason]), + ?DL("down -> worker process (~p) died: " + "~n Reason: ~p", [WorkerPid, WReason]), ok end. @@ -470,5 +474,10 @@ info(S) -> info(Key, SvcName) -> [{Key, _}] = diameter:service_info(SvcName, [Key]). -log(LINE, F, A) -> - ct:log("[DUTIL:~w,~p] " ++ F ++ "~n", [LINE,self()|A]). + +log(ModStr, LINE, F, A) + when is_list(ModStr) andalso + is_integer(LINE) andalso + is_list(F) andalso + is_list(A) -> + ct:log("[~s:~w,~p] " ++ F ++ "~n", [ModStr, LINE, self()|A]). diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl new file mode 100644 index 000000000000..2bb67802cb1c --- /dev/null +++ b/lib/diameter/test/diameter_util.hrl @@ -0,0 +1,38 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2024-2024. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% + +-ifndef(diameter_util__). +-define(diameter_util__, true). + +-define(DUTIL, diameter_util). + +-define(LOG(F, A), ?LOG(atom_to_list(?MODULE), F, A)). +-define(LOG(MS, F, A), ?DUTIL:log(MS, ?LINE, F, A)). + +-define(HAVE_SCTP(), ?DUTIL:have_sctp()). +-define(MKTEMP(S), ?DUTIL:mktemp(S)). +-define(RUN(A), ?DUTIL:run(A)). +-define(PEER(P), ?DUTIL:peer(P)). +-define(LPORT(P, R), ?DUTIL:lport(P, R)). + +-define(LISTEN(SN, Proto, Opts), ?DUTIL:listen(SN, Proto, Opts)). +-define(CONNECT(SN, Proto, LR, Opts), ?DUTIL:connect(SN, Proto, LR, Opts)). + +-endif. From b0549b8cc7f89ed6615691830dd68649b0dd90ef Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 3 May 2024 10:32:01 +0200 Subject: [PATCH 020/422] [diameter|test] More test tweaking --- .../test/diameter_transport_SUITE.erl | 32 ++++++++++++------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index 6b0f538ba357..e86270d7fbbd 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -346,15 +346,15 @@ init(gen_accept, {Prot, Ref}) -> {ok, Sock} = gen_accept(Prot, LSock), Bin = gen_recv(Prot, Sock), ok = gen_send(Prot, Sock, Bin), - Res = receive - {tcp_closed, Sock} = T -> - T; - ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> - T - end, + _Res = receive + {tcp_closed, Sock} = T -> + T; + ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> + T + end, ?TL("init(gen_accept) -> done when" - "~n T: ~p", [T]), + "~n Res: ~p", [_Res]), ok; init(connect, {Prot, Ref}) -> @@ -486,12 +486,22 @@ gen_send(tcp, Sock, Bin) -> %% gen_recv/2 gen_recv(sctp, Sock) -> - {_OS, _IS, Id} = getr(assoc), + {OS, IS, Id} = getr(assoc), receive - ?SCTP(Sock, {[#sctp_sndrcvinfo{assoc_id = I}], Bin}) + ?SCTP(Sock, {[#sctp_sndrcvinfo{assoc_id = I} = INFO], Bin}) when is_binary(Bin) -> - {Id, _} = {I, Id}, %% assert - Bin + case {I, Id} of + {Id, _} -> % assert + Bin; + _ -> + ?TL("unexpected assoc id in received info msg:" + "~n Expected Assoc ID: ~p" + "~n OS: ~p" + "~n IS: ~p" + "~n Received Assoc ID: ~p" + "~n Info: ~p", [Id, OS, IS, I, INFO]), + ct:fail({unexpected_assoc_id, I, Id}) + end end; gen_recv(tcp, Sock) -> tcp_recv(Sock, <<>>). From 6fd4015ff74bc31521de8db0783d244b45b5aa96 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 3 May 2024 12:40:08 +0200 Subject: [PATCH 021/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_relay_SUITE.erl | 67 +++++++++++++++------- lib/diameter/test/diameter_util.hrl | 5 ++ 2 files changed, 50 insertions(+), 22 deletions(-) diff --git a/lib/diameter/test/diameter_relay_SUITE.erl b/lib/diameter/test/diameter_relay_SUITE.erl index 2502820e0f0e..c641d29b4fe9 100644 --- a/lib/diameter/test/diameter_relay_SUITE.erl +++ b/lib/diameter/test/diameter_relay_SUITE.erl @@ -38,9 +38,14 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - parallel/1]). + + %% The test cases + parallel/1 + ]). %% diameter callbacks -export([pick_peer/4, @@ -52,9 +57,10 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc3588.hrl"). -%% =========================================================================== +-include("diameter_util.hrl"). + --define(util, diameter_util). +%% =========================================================================== -define(ADDR, {127,0,0,1}). @@ -99,6 +105,10 @@ -define(LOGOUT, ?'DIAMETER_BASE_TERMINATION-CAUSE_LOGOUT'). -define(AUTHORIZE_ONLY, ?'DIAMETER_BASE_RE-AUTH-REQUEST-TYPE_AUTHORIZE_ONLY'). +-define(RL(F), ?RL(F, [])). +-define(RL(F, A), ?LOG("DRELAYS", F, A)). + + %% =========================================================================== suite() -> @@ -108,7 +118,12 @@ all() -> [parallel]. parallel(_Config) -> - run(). + ?RL("parallel -> entry"), + Res = run(), + ?RL("parallel -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== @@ -117,7 +132,7 @@ parallel(_Config) -> run() -> ok = diameter:start(), try - ?util:run([{fun traffic/0, 20000}]) + ?RUN([{fun traffic/0, 20000}]) after ok = diameter:stop() end. @@ -125,12 +140,20 @@ run() -> %% traffic/0 traffic() -> + ?RL("traffic -> start services"), Servers = start_services(), + ?RL("traffic -> connect"), Conns = connect(Servers), + ?RL("traffic -> send"), [] = send(), + ?RL("traffic -> check counters"), [] = counters(), + ?RL("traffic -> disconnect"), [] = disconnect(Conns), - [] = stop_services(). + ?RL("traffic -> stop services"), + [] = stop_services(), + ?RL("traffic -> done"), + ok. start_services() -> [S1,S2,S3,S4] = [server(N, ?DICT_COMMON) || N <- [?SERVER1, @@ -159,30 +182,30 @@ stop_services() -> %% Traffic cases run when services are started and connections %% established. send() -> - ?util:run([[fun traffic/1, T] || T <- [send1, - send2, - send3, - send4, - send_loop, - send_timeout_1, - send_timeout_2, - info]]). + ?RUN([[fun traffic/1, T] || T <- [send1, + send2, + send3, + send4, + send_loop, + send_timeout_1, + send_timeout_2, + info]]). %% ---------------------------------------- break({{CN,CR},{SN,SR}}) -> try - ?util:disconnect(CN,CR,SN,SR) + ?DISCONNECT(CN,CR,SN,SR) after diameter:remove_transport(SN, SR) end. server(Name, Dict) -> ok = diameter:start_service(Name, ?SERVICE(Name, Dict)), - {Name, ?util:listen(Name, tcp)}. + {Name, ?LISTEN(Name, tcp)}. connect(Name, Refs) -> - [{{Name, ?util:connect(Name, tcp, LRef)}, T} || {_, LRef} = T <- Refs]. + [{{Name, ?CONNECT(Name, tcp, LRef)}, T} || {_, LRef} = T <- Refs]. %% =========================================================================== %% traffic testcases @@ -226,12 +249,12 @@ traffic(info) -> %% Wait for RELAY1 to have answered all requests, so that the %% suite doesn't end before all answers are sent and counted. receive after 6000 -> ok end, - [] = ?util:info(). + [] = ?INFO(). counters() -> - ?util:run([[fun counters/2, K, S] - || K <- [statistics, transport, connections], - S <- ?SERVICES]). + ?RUN([[fun counters/2, K, S] + || K <- [statistics, transport, connections], + S <- ?SERVICES]). counters(Key, Svc) -> counters(Key, Svc, [_|_] = diameter:service_info(Svc, Key)). diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index 2bb67802cb1c..d8680a3b69dc 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -32,7 +32,12 @@ -define(PEER(P), ?DUTIL:peer(P)). -define(LPORT(P, R), ?DUTIL:lport(P, R)). +-define(LISTEN(SN, Proto), ?DUTIL:listen(SN, Proto)). -define(LISTEN(SN, Proto, Opts), ?DUTIL:listen(SN, Proto, Opts)). +-define(CONNECT(SN, Proto, LR), ?DUTIL:connect(SN, Proto, LR)). -define(CONNECT(SN, Proto, LR, Opts), ?DUTIL:connect(SN, Proto, LR, Opts)). +-define(DISCONNECT(CN, CR, SN, SR), ?DUTIL:disconnect(CN, CR, SN, SR)). + +-define(INFO(), ?DUTIL:info()). -endif. From 06ada887041853ed4ebadbc0c7d43d3b00fae5f9 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 3 May 2024 13:02:49 +0200 Subject: [PATCH 022/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_tls_SUITE.erl | 73 +++++++++++++++++------- lib/diameter/test/diameter_util.hrl | 1 + 2 files changed, 53 insertions(+), 21 deletions(-) diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl index 2033b60355c5..efdf282da685 100644 --- a/lib/diameter/test/diameter_tls_SUITE.erl +++ b/lib/diameter/test/diameter_tls_SUITE.erl @@ -38,11 +38,16 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, init_per_suite/1, end_per_suite/1, - parallel/1]). + + %% The test cases + parallel/1 + ]). %% diameter callbacks -export([prepare_request/3, @@ -53,9 +58,10 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc3588.hrl"). -%% =========================================================================== +-include("diameter_util.hrl"). + --define(util, diameter_util). +%% =========================================================================== -define(ADDR, {127,0,0,1}). @@ -97,7 +103,7 @@ %% Config for diameter:add_transport/2. In the listening case, listen %% on a free port that we then lookup using the implementation detail %% that diameter_tcp registers the port with diameter_reg. --define(CONNECT(PortNr, Caps, Opts), +-define(TCONNECT(PortNr, Caps, Opts), {connect, [{transport_module, diameter_tcp}, {transport_config, [{raddr, ?ADDR}, {rport, PortNr}, @@ -105,7 +111,7 @@ {port, 0} | Opts]}, {capabilities, Caps}]}). --define(LISTEN(Caps, Opts), +-define(TLISTEN(Caps, Opts), {listen, [{transport_module, diameter_tcp}, {transport_config, [{ip, ?ADDR}, {port, 0} | Opts]}, {capabilities, Caps}]}). @@ -113,6 +119,10 @@ -define(SUCCESS, 2001). -define(LOGOUT, ?'DIAMETER_BASE_TERMINATION-CAUSE_LOGOUT'). +-define(TL(F), ?TL(F, [])). +-define(TL(F, A), ?LOG("DTLSS", F, A)). + + %% =========================================================================== %% common_test wrapping @@ -141,7 +151,11 @@ end_per_suite(_Config) -> crypto:stop(). parallel(Config) -> - run(dir(Config), false). + ?TL("parallel -> entry"), + Res = run(dir(Config), false), + ?TL("parallel -> done when" + "~n Res: ~p", [Res]), + Res. dir(Config) -> proplists:get_value(priv_dir, Config). @@ -149,7 +163,7 @@ dir(Config) -> %% =========================================================================== run() -> - Tmp = ?util:mktemp("diameter_tls"), + Tmp = ?MKTEMP("diameter_tls"), try run(Tmp, true) after @@ -157,34 +171,51 @@ run() -> end. run(Dir, B) -> + ?TL("run -> start crypto"), crypto:start(), + ?TL("run -> start ssl"), ssl:start(), try - ?util:run([{[fun traffic/2, Dir, B], 60000}]) + ?TL("run -> try run traffic"), + ?RUN([{[fun traffic/2, Dir, B], 60000}]) after + ?TL("run(after) -> stop diameter"), diameter:stop(), + ?TL("run(after) -> stop ssl"), ssl:stop(), - crypto:stop() + ?TL("run(after) -> stop crypto"), + crypto:stop(), + ?TL("run(after) -> done"), + ok end. traffic(Dir, true) -> + ?TL("traffic(true) -> make certs"), [] = make_certs(Dir), traffic(Dir, false); traffic(Dir, false) -> + ?TL("traffic(false) -> start diameter"), ok = diameter:start(), + ?TL("traffic(false) -> start (diameter) services"), Servers = start_services(Dir), + ?TL("traffic(false) -> add transports"), Connections = add_transports(Dir, Servers), - [] = ?util:run([[fun call/1, S] || S <- ?util:scramble(?SERVERS)]), + ?TL("traffic(false) -> calls"), + [] = ?RUN([[fun call/1, S] || S <- ?SCRAMBLE(?SERVERS)]), + ?TL("traffic(false) -> remove transports"), [] = remove_transports(Connections), - [] = stop_services(). + ?TL("traffic(false) -> stop (diameter) services"), + [] = stop_services(), + ?TL("traffic(false) -> done"), + ok. make_certs(Dir) -> - ?util:run([[fun make_cert/2, Dir, B] || B <- ["server1", - "server2", - "server4", - "server5", - "client"]]). + ?RUN([[fun make_cert/2, Dir, B] || B <- ["server1", + "server2", + "server4", + "server5", + "client"]]). start_services(Dir) -> Servers = [{S, {_,_} = server(S, sopts(S, Dir))} || S <- ?SERVERS], @@ -200,7 +231,7 @@ add_transports(Dir, Servers) -> %% transport to go down. remove_transports(Connections) -> [] = [T || S <- ?SERVERS, T <- [diameter:subscribe(S)], T /= true], - [] = ?util:run([[fun disconnect/1, T] || T <- Connections]), + [] = ?RUN([[fun disconnect/1, T] || T <- Connections]), [S || S <- ?SERVERS, I <- [receive #diameter_event{service = S, info = I} -> I end], down /= catch element(1, I)]. @@ -308,8 +339,8 @@ join(Strs) -> server(Host, {Caps, Opts}) -> ok = diameter:start_service(Host, ?SERVICE(Host, ?DICT_COMMON)), - {ok, LRef} = diameter:add_transport(Host, ?LISTEN(Caps, Opts)), - {LRef, hd([_] = ?util:lport(tcp, LRef))}. + {ok, LRef} = diameter:add_transport(Host, ?TLISTEN(Caps, Opts)), + {LRef, hd([_] = ?LPORT(tcp, LRef))}. sopts(?SERVER1, Dir) -> {inband_security([?TLS]), @@ -330,7 +361,7 @@ ssl([{ssl_options = T, Opts}]) -> %% connect/3 connect(Host, {_LRef, PortNr}, {Caps, Opts}) -> - {ok, Ref} = diameter:add_transport(Host, ?CONNECT(PortNr, Caps, Opts)), + {ok, Ref} = diameter:add_transport(Host, ?TCONNECT(PortNr, Caps, Opts)), {up, Ref, _, _, #diameter_packet{}} = receive #diameter_event{service = Host, info = Info} diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index d8680a3b69dc..859a5b8c299c 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -39,5 +39,6 @@ -define(DISCONNECT(CN, CR, SN, SR), ?DUTIL:disconnect(CN, CR, SN, SR)). -define(INFO(), ?DUTIL:info()). +-define(SCRAMBLE(SS), ?DUTIL:scramble(SS)). -endif. From e541c753d212c77de107a5471d5d96016d86cba7 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Sat, 4 May 2024 10:24:53 +0200 Subject: [PATCH 023/422] [diameter|test] More test tweaking --- lib/diameter/test/diameter_util.erl | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 075fc59c6001..0bb49be33412 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -364,9 +364,27 @@ connect(Client, Prot, LRef) -> connect(Client, Prot, LRef, []). connect(Client, ProtOpts, LRef, Opts) -> + ?DL("connect -> entry with" + "~n Client: ~p" + "~n ProtOpts: ~p" + "~n LRef: ~p" + "~n Opts: ~p", [Client, ProtOpts, LRef, Opts]), Prot = head(ProtOpts), [PortNr] = lport(Prot, LRef), - Client = diameter:service_info(Client, name), %% assert + case diameter:service_info(Client, name) of + Client -> % assert + ok; + undefined -> + ?DL("no name: " + "~n Service Info: ~p", [diameter:service_info(Client)]), + ct:fail({undefined_name, Client}); + WrongName -> % This should not be possible but... + ?DL("Wrong Name: " + "~n ~p" + "~n Service Info: ~p", + [WrongName, diameter:service_info(Client)]), + ct:fail({undefined_name, Client, WrongName}) + end, true = diameter:subscribe(Client), Ref = add_transport(Client, {connect, opts(ProtOpts, PortNr) ++ Opts}), true = transport(Client, Ref), %% assert From d62f46223e9a834112158e95c7052526e0f9dd35 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Sun, 5 May 2024 10:19:11 +0200 Subject: [PATCH 024/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 21 +++++++++++++++------ 1 file changed, 15 insertions(+), 6 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 0bb49be33412..a29450a6dc26 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -376,14 +376,23 @@ connect(Client, ProtOpts, LRef, Opts) -> ok; undefined -> ?DL("no name: " - "~n Service Info: ~p", [diameter:service_info(Client)]), + "~n 'all' Service Info: ~p" + "~n 'info' Service Info: ~p" + "~n 'stats' Service Info: ~p", + [diameter:service_info(Client, all), + diameter:service_info(Client, info), + diameter:service_info(Client, statistics)]), ct:fail({undefined_name, Client}); WrongName -> % This should not be possible but... - ?DL("Wrong Name: " - "~n ~p" - "~n Service Info: ~p", - [WrongName, diameter:service_info(Client)]), - ct:fail({undefined_name, Client, WrongName}) + ?DL("Wrong Name: ~p" + "~n 'all' Service Info: ~p" + "~n 'info' Service Info: ~p" + "~n 'stats' Service Info: ~p", + [WrongName, + diameter:service_info(Client, all), + diameter:service_info(Client, info), + diameter:service_info(Client, statistics)]), + ct:fail({wrong_name, Client, WrongName}) end, true = diameter:subscribe(Client), Ref = add_transport(Client, {connect, opts(ProtOpts, PortNr) ++ Opts}), From e7471e92b38cacf3571988a5a3b02dbb4fc88ff3 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Sun, 5 May 2024 16:44:16 +0200 Subject: [PATCH 025/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index a29450a6dc26..cc2ff3507df7 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -376,19 +376,27 @@ connect(Client, ProtOpts, LRef, Opts) -> ok; undefined -> ?DL("no name: " + "~n Services: ~p" + "~n Service: ~p" "~n 'all' Service Info: ~p" "~n 'info' Service Info: ~p" "~n 'stats' Service Info: ~p", - [diameter:service_info(Client, all), + [diameter:services(), + Client, + diameter:service_info(Client, all), diameter:service_info(Client, info), diameter:service_info(Client, statistics)]), ct:fail({undefined_name, Client}); WrongName -> % This should not be possible but... ?DL("Wrong Name: ~p" + "~n Services: ~p" + "~n Service: ~p" "~n 'all' Service Info: ~p" "~n 'info' Service Info: ~p" "~n 'stats' Service Info: ~p", [WrongName, + diameter:services(), + Client, diameter:service_info(Client, all), diameter:service_info(Client, info), diameter:service_info(Client, statistics)]), From eec76598f73ad3dea442cad6549c10281d6ca29d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 09:29:23 +0200 Subject: [PATCH 026/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 34 ++++++++++++++++++++++------- 1 file changed, 26 insertions(+), 8 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index cc2ff3507df7..86de1be63fe7 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -52,7 +52,8 @@ -define(L, atom_to_list). --define(DL(F, A), ?LOG("DUTIL", F, A)). +-define(UL(F), ?UL(F, [])). +-define(UL(F, A), ?LOG("DUTIL", F, A)). %% --------------------------------------------------------------------------- @@ -133,10 +134,10 @@ down(Parent, Worker) %% Die with the worker, kill the worker if the parent dies. down(ParentMRef, WorkerPid) -> - ?DL("down -> await worker (~p) termination", [WorkerPid]), + ?UL("down -> await worker (~p) termination", [WorkerPid]), receive {'EXIT', TCPid, {timetrap_timeout = R, TCTimeout, TCStack}} -> - ?DL("down -> test case timetrap timeout when" + ?UL("down -> test case timetrap timeout when" "~n (test case) Pid: ~p" "~n (test case) Timeout: ~p" "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), @@ -144,11 +145,11 @@ down(ParentMRef, WorkerPid) -> %% So many wrapper levels, make sure we go with a bang exit({TCPid, R, TCStack}); {'DOWN', ParentMRef, process, PPid, PReason} -> - ?DL("down -> parent process (~p) died: " + ?UL("down -> parent process (~p) died: " "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); {'DOWN', _, process, WorkerPid, WReason} -> - ?DL("down -> worker process (~p) died: " + ?UL("down -> worker process (~p) died: " "~n Reason: ~p", [WorkerPid, WReason]), ok end. @@ -303,31 +304,48 @@ have_sctp(_) -> %% Evaluate a function in one of a number of forms. eval({F, infinity}) -> + ?UL("eval(infinity) -> entry"), eval(F); eval({F, Tmo}) when is_integer(Tmo) -> + ?UL("eval(~p) -> entry", [Tmo]), {ok, _} = timer:exit_after(Tmo, timeout), eval(F); eval({M,[F|A]}) when is_atom(F) -> + ?UL("eval -> entry with" + "~n M: ~p" + "~n F: ~p" + "~n A: ~p", [M, F, A]), apply(M,F,A); eval({M,F,A}) -> + ?UL("eval -> entry with" + "~n M: ~p" + "~n F: ~p" + "~n A: ~p", [M, F, A]), apply(M,F,A); eval([F|A]) when is_function(F) -> + ?UL("eval -> entry with" + "~n F: ~p" + "~n A: ~p", [F, A]), apply(F,A); eval(L) when is_list(L) -> + ?UL("eval -> entry with" + "~n length(L): ~p", [length(L)]), [eval(F) || F <- L]; eval(F) when is_function(F,0) -> + ?UL("eval -> entry"), F(). + %% --------------------------------------------------------------------------- %% lport/2 %% @@ -364,7 +382,7 @@ connect(Client, Prot, LRef) -> connect(Client, Prot, LRef, []). connect(Client, ProtOpts, LRef, Opts) -> - ?DL("connect -> entry with" + ?UL("connect -> entry with" "~n Client: ~p" "~n ProtOpts: ~p" "~n LRef: ~p" @@ -375,7 +393,7 @@ connect(Client, ProtOpts, LRef, Opts) -> Client -> % assert ok; undefined -> - ?DL("no name: " + ?UL("no name: " "~n Services: ~p" "~n Service: ~p" "~n 'all' Service Info: ~p" @@ -388,7 +406,7 @@ connect(Client, ProtOpts, LRef, Opts) -> diameter:service_info(Client, statistics)]), ct:fail({undefined_name, Client}); WrongName -> % This should not be possible but... - ?DL("Wrong Name: ~p" + ?UL("Wrong Name: ~p" "~n Services: ~p" "~n Service: ~p" "~n 'all' Service Info: ~p" From 2b1aa8ed0b8e46987c33328a3675d874d648bb4b Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 09:45:26 +0200 Subject: [PATCH 027/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_examples_SUITE.erl | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 0429a473cd04..1e238ab1264b 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -49,6 +49,7 @@ -include("diameter_util.hrl"). +-define(EL(F), ?EL(F, [])). -define(EL(F, A), ?LOG("DEXS", F, A)). @@ -157,7 +158,9 @@ run(F, Config) -> %% Compile example dictionaries in examples/dict. compile_dicts(Dir) -> + ?EL("compile_dicts -> entry"), Out = mkdir(Dir, "dict"), + ?EL("compile_dicts -> create paths"), Dirs = [filename:join(H ++ ["examples", "dict"]) || H <- [[code:lib_dir(diameter)], [here(), ".."]]], [] = [{F,D,RC} || {_,F} <- sort(find_files(Dirs, ".*\\.dia$")), @@ -198,18 +201,26 @@ make(Path, Dict0, Out) make(Path, atom_to_list(Dict0), Out); make(Path, Dict0, Out) -> + ?EL("make -> entry with" + "~n Path: ~p" + "~n Dict0: ~p" + "~n Out: ~p", [Path, Dict0, Out]), Dict = filename:rootname(filename:basename(Path)), {Mod, Pre} = make_name(Dict), {"diameter_gen_base" ++ Suf = Mod0, _} = make_name(Dict0), Name = Mod ++ Suf, try + ?EL("make -> try make codec: to erl"), ok = to_erl(Path, [{name, Name}, {prefix, Pre}, {outdir, Out}, {inherits, "common/" ++ Mod0} | [{inherits, D ++ "/" ++ M ++ Suf} || {D,M} <- dep(Dict)]]), - ok = to_beam(filename:join(Out, Name)) + ?EL("make -> try make codec: to beam"), + ok = to_beam(filename:join(Out, Name)), + ?EL("make -> done"), + ok catch throw: {_,_} = E -> E From ff16a721536844f8122e685eacd5041125f840f9 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 16:57:27 +0200 Subject: [PATCH 028/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 86de1be63fe7..dbb7d2d9ef37 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -309,7 +309,9 @@ eval({F, infinity}) -> eval({F, Tmo}) when is_integer(Tmo) -> ?UL("eval(~p) -> entry", [Tmo]), - {ok, _} = timer:exit_after(Tmo, timeout), + %% Since this function is used for all kinds of functions, + %% a timeout is not very informative, so include the "function". + {ok, _} = timer:exit_after(Tmo, {timeout, F}), eval(F); eval({M,[F|A]}) From 55c2a1849a895e9cb5dec8e7dc3a19188a8f0def Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 17:27:29 +0200 Subject: [PATCH 029/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 48 ++++++++++++++---------- lib/diameter/test/diameter_util.hrl | 1 + 2 files changed, 30 insertions(+), 19 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index e96133908f63..488f68ba7ee8 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -43,7 +43,11 @@ -include_lib("kernel/include/file.hrl"). --define(util, diameter_util). +-include("diameter_util.hrl"). + + +%% =========================================================================== + -define(A, list_to_atom). %% Modules not in the app and that should not have dependencies on it @@ -58,6 +62,10 @@ -define(INFO_MODULES, [diameter_dbg, diameter_info]). +-define(AL(F), ?AL(F, [])). +-define(AL(F, A), ?LOG("DAPPS", F, A)). + + %% =========================================================================== suite() -> @@ -78,7 +86,7 @@ run() -> run(all()). run(List) -> - Tmp = ?util:mktemp("diameter_app"), + Tmp = ?MKTEMP("diameter_app"), try run([{priv_dir, Tmp}], List) after @@ -86,8 +94,9 @@ run(List) -> end. run(Config, List) -> - [{application, diameter, App}] = ?util:consult(diameter, app), - ?util:run([{{?MODULE, F, [{App, Config}]}, 10000} || F <- List]). + [{application, diameter, App}] = ?CONSULT(diameter, app), + ?RUN([{{?MODULE, F, [{App, Config}]}, 10000} || F <- List]). + %% =========================================================================== %% # keys/1 @@ -178,7 +187,7 @@ release(Config) -> %% in the case of relup/1. appvsn(Name) -> - [{application, Name, App}] = ?util:consult(Name, app), + [{application, Name, App}] = ?CONSULT(Name, app), fetch(vsn, App). %% =========================================================================== @@ -196,10 +205,10 @@ xref({App, _Config}) -> Mods = fetch(modules, App), %% modules listed in the app file %% List of application names extracted from runtime_dependencies. - i("xref -> get deps"), + ?AL("xref -> get deps"), Deps = lists:map(fun unversion/1, fetch(runtime_dependencies, App)), - i("xref -> start xref"), + ?AL("xref -> start xref"), {ok, XRef} = xref:start(make_name(xref_test_name)), ok = xref:set_default(XRef, [{verbose, false}, {warnings, false}]), @@ -209,30 +218,30 @@ xref({App, _Config}) -> %% was previously in kernel. Erts isn't an application however, in %% the sense that there's no .app file, and isn't listed in %% applications. - i("xref -> add own and dep apps"), + ?AL("xref -> add own and dep apps"), ok = lists:foreach(fun(A) -> add_application(XRef, A) end, [diameter, erts | fetch(applications, App)]), - i("xref -> analyze undefined_function_calls"), + ?AL("xref -> analyze undefined_function_calls"), {ok, Undefs} = xref:analyze(XRef, undefined_function_calls), - i("xref -> analyze module use: " - "~n For mods: ~p", [Mods]), + ?AL("xref -> analyze module use: " + "~n For mods: ~p", [Mods]), {ok, RTmods} = xref:analyze(XRef, {module_use, Mods}), - i("xref -> analyze (compiler) module use: " - "~n For mods: ~p", [?COMPILER_MODULES]), + ?AL("xref -> analyze (compiler) module use: " + "~n For mods: ~p", [?COMPILER_MODULES]), {ok, CTmods} = xref:analyze(XRef, {module_use, ?COMPILER_MODULES}), - i("xref -> analyze module call: " - "~n For mods: ~p", [Mods]), + ?AL("xref -> analyze module call: " + "~n For mods: ~p", [Mods]), {ok, RTdeps} = xref:analyze(XRef, {module_call, Mods}), - i("xref -> stop xref"), + ?AL("xref -> stop xref"), xref:stop(XRef), - i("xref -> get OTP release"), + ?AL("xref -> get OTP release"), Rel = release(), %% otp_release-ish %% Only care about calls from our own application. - i("xref -> Only care about calls from our own application"), + ?AL("xref -> Only care about calls from our own application"), [] = lists:filter(fun({{F,_,_} = From, {_,_,_} = To}) -> lists:member(F, Mods) andalso not ignored(From, To, Rel) @@ -331,6 +340,7 @@ add_application(XRef, App) -> make_name(Suf) -> list_to_atom("diameter_" ++ atom_to_list(Suf)). + %% =========================================================================== %% # relup/1 %% @@ -342,7 +352,7 @@ relup({App, Config}) -> "~n App: ~p" "~n Config: ~p", [App, Config]), - [{Vsn, Up, Down}] = ?util:consult(diameter, appup), + [{Vsn, Up, Down}] = ?CONSULT(diameter, appup), true = is_vsn(Vsn), i("relup -> " diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index 859a5b8c299c..86ab23fccaf9 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -31,6 +31,7 @@ -define(RUN(A), ?DUTIL:run(A)). -define(PEER(P), ?DUTIL:peer(P)). -define(LPORT(P, R), ?DUTIL:lport(P, R)). +-define(CONSULT(N, S), ?DUTIL:consult(N, S)). -define(LISTEN(SN, Proto), ?DUTIL:listen(SN, Proto)). -define(LISTEN(SN, Proto, Opts), ?DUTIL:listen(SN, Proto, Opts)). From 83ecd758cc99a96d7e220d3adad4fe052793590d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 09:53:53 +0200 Subject: [PATCH 030/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_tls_SUITE.erl | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl index efdf282da685..e0531a276b13 100644 --- a/lib/diameter/test/diameter_tls_SUITE.erl +++ b/lib/diameter/test/diameter_tls_SUITE.erl @@ -288,14 +288,19 @@ handle_request(#diameter_packet{msg = #diameter_base_STR{'Session-Id' = SId}}, %% Send an STR intended for a specific server and expect success. call(Server) -> + ?TL("call -> entry with" + "~n Server: ~p", [Server]), Realm = realm(Server), Req = ['STR', {'Destination-Realm', Realm}, {'Termination-Cause', ?LOGOUT}, {'Auth-Application-Id', ?APP_ID}], - #diameter_base_STA{'Result-Code' = ?SUCCESS, - 'Origin-Host' = Server, + ?TL("call -> make (STR) call (with filter and realm) - expect STA"), + #diameter_base_STA{'Result-Code' = ?SUCCESS, + 'Origin-Host' = Server, 'Origin-Realm' = Realm} - = call(Req, [{filter, realm}]). + = call(Req, [{filter, realm}]), + ?TL("call -> done"), + ok. call(Req, Opts) -> diameter:call(?CLIENT, ?APP_ALIAS, Req, Opts). From 4a09fa89d7d8b9dffe139c0396219daa202219b1 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 10:11:38 +0200 Subject: [PATCH 031/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_distribution_SUITE.erl | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 6ffd7031ec1f..d211d4740f86 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -309,11 +309,15 @@ str(Cause) -> %% send/3 send([_, {Node, _} | _], Where, Req) -> + ?DL("send -> make rpc call to node ~p", [Node]), rpc:call(Node, ?MODULE, call, [{Where, Req}]). %% call/1 call({Where, Req}) -> + ?DL("call -> entry with" + "~n Where: ~p" + "~n Req: ~p", [Where, Req]), diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}]). %% sname/0 From 95add66750154fbf043dad818fb00a707ff92352 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 17:47:41 +0200 Subject: [PATCH 032/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index dbb7d2d9ef37..af2a38d2a942 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -174,7 +174,9 @@ fold(_, Acc, Map) fold(Fun, Acc, #{} = Map) -> receive - {'DOWN', MRef, process, _, Info} when is_map_key(MRef, Map) -> + {'DOWN', MRef, process, Pid, Info} when is_map_key(MRef, Map) -> + ?UL("fold -> process ~p terminated:" + "~n ~p", [Pid, Info]), fold(Fun, Fun(Info, Acc), maps:remove(MRef, Map)) end. From 98e37c2cc1fc37d1f44626efcfd71b00a8d9ceb7 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 19:03:58 +0200 Subject: [PATCH 033/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 38 ++++++++++++++++++++++++++--- 1 file changed, 35 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index af2a38d2a942..a55934aa99d1 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -135,25 +135,57 @@ down(Parent, Worker) %% Die with the worker, kill the worker if the parent dies. down(ParentMRef, WorkerPid) -> ?UL("down -> await worker (~p) termination", [WorkerPid]), + timer:send_after(1000, self(), check_worker_status), + await_down(ParentMRef, WorkerPid). + +await_down(ParentMRef, WorkerPid) -> receive + check_worker_status -> + ?UL("await_down -> check worker process (~p) status: " + "~n Current Function: ~p" + "~n Message Queue Length: ~p" + "~n Reductions: ~p" + "~n Status: ~p", + [WorkerPid, + pi(WorkerPid, current_function), + pi(WorkerPid, message_queue_len), + pi(WorkerPid, reductions), + pi(WorkerPid, status)]), + timer:send_after(1000, self(), check_worker_status), + await_down(ParentMRef, WorkerPid); + {'EXIT', TCPid, {timetrap_timeout = R, TCTimeout, TCStack}} -> - ?UL("down -> test case timetrap timeout when" + ?UL("await_down -> test case timetrap timeout when" "~n (test case) Pid: ~p" "~n (test case) Timeout: ~p" "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), exit(WorkerPid, kill), %% So many wrapper levels, make sure we go with a bang exit({TCPid, R, TCStack}); + {'DOWN', ParentMRef, process, PPid, PReason} -> - ?UL("down -> parent process (~p) died: " + ?UL("await_down -> parent process (~p) died: " "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); {'DOWN', _, process, WorkerPid, WReason} -> - ?UL("down -> worker process (~p) died: " + ?UL("await_down -> worker process (~p) died: " "~n Reason: ~p", [WorkerPid, WReason]), ok end. + +pi(Pid, Key) -> + try + begin + {Key, Value} = process_info(Pid, Key), + Value + end + catch + _:_:_ -> + undefined + end. + + %% --------------------------------------------------------------------------- %% fold/3 %% From 563d15848076a00a985a9e1c86c59710eea3708b Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 8 May 2024 10:16:26 +0200 Subject: [PATCH 034/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 488f68ba7ee8..6d2a55f32cff 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -218,9 +218,10 @@ xref({App, _Config}) -> %% was previously in kernel. Erts isn't an application however, in %% the sense that there's no .app file, and isn't listed in %% applications. - ?AL("xref -> add own and dep apps"), - ok = lists:foreach(fun(A) -> add_application(XRef, A) end, - [diameter, erts | fetch(applications, App)]), + Apps = [diameter, erts | fetch(applications, App)], + ?AL("xref -> add own and dep apps: " + "~n ~p", [Apps]), + ok = lists:foreach(fun(A) -> add_application(XRef, A) end, Apps), ?AL("xref -> analyze undefined_function_calls"), {ok, Undefs} = xref:analyze(XRef, undefined_function_calls), @@ -335,6 +336,8 @@ app(Mod) -> end. add_application(XRef, App) -> + ?AL("add_application -> entry with" + "~n App: ~p", [App]), {ok, App} = xref:add_application(XRef, code:lib_dir(App), []). make_name(Suf) -> From 1235bfe5ed1f002f3f4ec93ceae96636f343a0e1 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 8 May 2024 10:41:54 +0200 Subject: [PATCH 035/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 6d2a55f32cff..077f509480e6 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -336,9 +336,11 @@ app(Mod) -> end. add_application(XRef, App) -> - ?AL("add_application -> entry with" - "~n App: ~p", [App]), - {ok, App} = xref:add_application(XRef, code:lib_dir(App), []). + ?AL("add_application -> get lib dir for app ~p", [App]), + LibDir = code:lib_dir(App), + ?AL("add_application -> [xref] add lib dir:" + "~n ~p", [LibDir]), + {ok, App} = xref:add_application(XRef, LibDir, []). make_name(Suf) -> list_to_atom("diameter_" ++ atom_to_list(Suf)). From 07c5265ec05b62e3a63b95eb51a1d8436521c59b Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 8 May 2024 10:57:55 +0200 Subject: [PATCH 036/422] [diameter|test] More test case tweaking We should really analyze the host before we set the timeouts, bit will have to do for now. --- lib/diameter/test/diameter_examples_SUITE.erl | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 1e238ab1264b..d258207cdb36 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -80,7 +80,7 @@ %% common_test wrapping suite() -> - [{timetrap, {seconds, 75}}]. + [{timetrap, {seconds, 120}}]. all() -> [dict, code]. @@ -146,7 +146,7 @@ run(List) %% Eg. erl -noinput -s diameter_examples_SUITE run code -s init stop ... run(List, Dir) when is_list(List) -> - ?RUN([{[fun run/1, {F, Dir}], 60000} || F <- List]); + ?RUN([{[fun run/1, {F, Dir}], 90000} || F <- List]); run(F, Config) -> run([F], proplists:get_value(priv_dir, Config)). From bed84a9b15488f19972b86cfc9999cee1febddb7 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 13 May 2024 09:56:20 +0200 Subject: [PATCH 037/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 077f509480e6..027b816edc54 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -198,9 +198,9 @@ appvsn(Name) -> %% =========================================================================== xref({App, _Config}) -> - i("xref -> entry with" - "~n App: ~p" - "~n Config: ~p", [App, _Config]), + ?AL("xref -> entry with" + "~n App: ~p" + "~n Config: ~p", [App, _Config]), Mods = fetch(modules, App), %% modules listed in the app file @@ -254,30 +254,30 @@ xref({App, _Config}) -> %% depend on other diameter modules but it's a simple source of %% build errors if not properly encoded in the makefile so guard %% against it. - i("xref -> ensure only runtime and info mod"), + ?AL("xref -> ensure only runtime and info mod"), [] = (RTmods -- Mods) -- ?INFO_MODULES, %% Ensure that runtime modules don't call compiler modules. - i("xref -> ensure runtime mods don't call compiler mods"), + ?AL("xref -> ensure runtime mods don't call compiler mods"), CTmods = CTmods -- Mods, %% Ensure that runtime modules only call other runtime modules, or %% applications declared in runtime_dependencies in the app file. %% The declared application versions are ignored since we only %% know what we see now. - i("xref -> ensure runtime mods only call runtime mods"), + ?AL("xref -> ensure runtime mods only call runtime mods"), [] = lists:filter(fun(M) -> not lists:member(app(M), Deps) end, RTdeps -- Mods), - i("xref -> done"), + ?AL("xref -> done"), ok; xref(Config) -> - i("xref -> entry with" - "~n Config: ~p", [Config]), + ?AL("xref -> entry with" + "~n Config: ~p", [Config]), Res = run(Config, [xref]), - i("xref -> done when" - "~n Res: ~p", [Res]), + ?AL("xref -> done when" + "~n Res: ~p", [Res]), Res. ignored({FromMod,_,_}, {ToMod,_,_} = To, Rel)-> From 586cee87fff7c496fc341a61303281d6ff53c0d4 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 13 May 2024 09:57:47 +0200 Subject: [PATCH 038/422] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_dpr_SUITE.erl | 51 ++++++++++++++++++++---- 1 file changed, 43 insertions(+), 8 deletions(-) diff --git a/lib/diameter/test/diameter_dpr_SUITE.erl b/lib/diameter/test/diameter_dpr_SUITE.erl index 45f4ec9b5a3f..e4b8788ed64e 100644 --- a/lib/diameter/test/diameter_dpr_SUITE.erl +++ b/lib/diameter/test/diameter_dpr_SUITE.erl @@ -51,6 +51,9 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc6733.hrl"). +-include("diameter_util.hrl"). + + %% =========================================================================== -define(util, diameter_util). @@ -85,6 +88,11 @@ []] ++ [[{dpr, [{timeout, 5000}, {cause, T}]}] || T <- ?CAUSES]). + +-define(DL(F), ?DL(F, [])). +-define(DL(F, A), ?LOG("DDPRS", F, A)). + + %% =========================================================================== suite() -> @@ -93,7 +101,7 @@ suite() -> all() -> [client, server, uncommon, transport, service, application]. --define(tc(Name), Name(_) -> run([Name])). +-define(tc(Name), Name(_) -> ?DL("~w -> entry", [Name]), run([Name])). ?tc(client). ?tc(server). @@ -102,6 +110,7 @@ all() -> ?tc(service). ?tc(application). + %% =========================================================================== %% run/0 @@ -113,20 +122,34 @@ run() -> run(List) when is_list(List) -> + ?DL("run -> entry with" + "~n List: ~p", [List]), try - ?util:run([[{[fun run/1, T], 15000} || T <- List]]) + ?RUN([[{[fun run/1, T], 15000} || T <- List]]) after + ?DL("run(after) -> stop diameter"), diameter:stop() end; run(Grp) -> + ?DL("run(~w) -> start (diameter) app", [Grp]), ok = diameter:start(), + ?DL("run(~w) -> start (diameter) service 'server'", [Grp]), ok = diameter:start_service(?SERVER, service(?SERVER, Grp)), + ?DL("run(~w) -> start (diameter) service 'client'", [Grp]), ok = diameter:start_service(?CLIENT, service(?CLIENT, Grp)), - _ = lists:foldl(fun(F,A) -> apply(?MODULE, F, [A]) end, + _ = lists:foldl(fun(F,A) -> + ?DL("run(~w) -> apply" + "~n F: ~p" + "~n A: ~p", [F, A]), + apply(?MODULE, F, [A]) + end, [{group, Grp}], tc(Grp)), - ok = diameter:stop(). + ?DL("run(~w) -> stop (diameter) app", [Grp]), + ok = diameter:stop(), + ?DL("run(~w) -> done", [Grp]), + ok. tc(T) when T == client; @@ -178,10 +201,22 @@ service(?CLIENT = Svc, _) -> %% send_dpr/1 send_dpr(Config) -> - LRef = ?util:listen(?SERVER, tcp), - Ref = ?util:connect(?CLIENT, tcp, LRef, [{dpa_timeout, 10000}]), - Svc = sender(group(Config)), - [Info] = diameter:service_info(Svc, connections), + LRef = ?LISTEN(?SERVER, tcp), + Ref = ?CONNECT(?CLIENT, tcp, LRef, [{dpa_timeout, 10000}]), + Svc = sender(group(Config)), + Info = case diameter:service_info(Svc, connections) of + [I] -> + I; + [] -> + ?DL("send_dpr -> no connections: " + "~n Svc: ~p" + "~n Svc info: ~p" + "~n Services: ~p", + [Svc, + diameter:service_info(Svc, all), + diameter:services()]), + ct:fail({no_connections, Svc}) + end, {_, {TPid, _}} = lists:keyfind(peer, 1, Info), #diameter_base_DPA{'Result-Code' = 2001} = diameter:call(Svc, From 4c2941079b223ec36279984e1acc12e50bc67a85 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 12:21:47 +0200 Subject: [PATCH 039/422] [diameter|test|3xxx] More tweaking --- lib/diameter/test/diameter_3xxx_SUITE.erl | 67 ++++++++++++++++++++--- 1 file changed, 59 insertions(+), 8 deletions(-) diff --git a/lib/diameter/test/diameter_3xxx_SUITE.erl b/lib/diameter/test/diameter_3xxx_SUITE.erl index 63de2467a32c..2af853ea2723 100644 --- a/lib/diameter/test/diameter_3xxx_SUITE.erl +++ b/lib/diameter/test/diameter_3xxx_SUITE.erl @@ -60,9 +60,11 @@ -include("diameter_gen_base_rfc6733.hrl"). %% Use the fact that STR/STA is identical in RFC's 3588 and 6733. +-include("diameter_util.hrl"). + + %% =========================================================================== --define(util, diameter_util). -define(testcase(), get(?MODULE)). -define(L, atom_to_list). @@ -95,6 +97,10 @@ -define(LOGOUT, ?'DIAMETER_BASE_TERMINATION-CAUSE_LOGOUT'). +-define(XL(F), ?XL(F, [])). +-define(XL(F, A), ?LOG("D3XS", F, A)). + + %% =========================================================================== suite() -> @@ -104,6 +110,7 @@ all() -> [traffic]. traffic(_Config) -> + ?XL("traffic -> entry"), run(). %% =========================================================================== @@ -123,44 +130,68 @@ tc() -> %% run/0 run() -> - ?util:run([[{{?MODULE, run, [{E,D}]}, 60000} || E <- ?ERRORS, - D <- ?RFCS]]). + ?XL("run -> entry"), + ?RUN([[{{?MODULE, run, [{E,D}]}, 60000} || E <- ?ERRORS, + D <- ?RFCS]]). %% run/1 run({F, [_,_] = G}) -> + ?XL("run -> entry with" + "~n F: ~p" + "~n G: ~p", [F, G]), put(?MODULE, F), apply(?MODULE, F, [G]); run({E,D}) -> + ?XL("run -> entry with" + "~n E: ~p" + "~n D: ~p", [E, D]), try run([E,D]) after + ?XL("run(after) -> stop diameter app"), ok = diameter:stop() end; run([Errors, RFC] = G) -> + ?XL("run -> entry with" + "~n Errors: ~p" + "~n RFC: ~p", [Errors, RFC]), Name = ?L(Errors) ++ "," ++ ?L(RFC), + ?XL("run -> start diameter app"), ok = diameter:start(), + ?XL("run -> start service 'server' (~p)", [Name]), ok = diameter:start_service(?SERVER, ?SERVICE(Name, Errors, RFC)), + ?XL("run -> start service 'client'"), ok = diameter:start_service(?CLIENT, ?SERVICE(?CLIENT, callback, rfc6733)), - LRef = ?util:listen(?SERVER, tcp), - ?util:connect(?CLIENT, tcp, LRef), - ?util:run([{?MODULE, run, [{F,G}]} || F <- tc()]), + ?XL("run -> (server) listen"), + LRef = ?LISTEN(?SERVER, tcp), + ?XL("run -> (client) connect"), + ?CONNECT(?CLIENT, tcp, LRef), + ?XL("run -> run"), + ?RUN([{?MODULE, run, [{F,G}]} || F <- tc()]), + ?XL("run -> \"check\" counters"), _ = counters(G), + ?XL("run -> remove 'client' transport"), ok = diameter:remove_transport(?CLIENT, true), + ?XL("run -> remove 'server' transport"), ok = diameter:remove_transport(?SERVER, true), + ?XL("run -> stop service 'server'"), ok = diameter:stop_service(?SERVER), - ok = diameter:stop_service(?CLIENT). + ?XL("run -> stop service 'client'"), + ok = diameter:stop_service(?CLIENT), + ?XL("run -> done"), + ok. %% counters/1 %% %% Check that counters are as expected. counters([_Errors, _RFC] = G) -> - [] = ?util:run([[fun counters/3, K, S, G] + [] = ?RUN([[fun counters/3, K, S, G] || K <- [statistics, transport, connections], S <- [?CLIENT, ?SERVER]]). @@ -357,6 +388,7 @@ stats(?SERVER, callback, rfc6733, L) -> %% diameter answers. send_unknown_application([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3007, %% UNSUPPORTED_APPLICATION 'Failed-AVP' = [], @@ -369,10 +401,12 @@ send_unknown_application([_,_]) -> %% handle_request discards the request. send_unknown_command([callback, _]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), {error, timeout} = call(); %% diameter answers. send_unknown_command([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3001, %% UNSUPPORTED_COMMAND 'Failed-AVP' = [], @@ -385,6 +419,7 @@ send_unknown_command([_,_]) -> %% Callback answers. send_ok([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 5002, %% UNKNOWN_SESSION_ID 'Failed-AVP' = [], 'AVP' = []} @@ -396,6 +431,7 @@ send_ok([_,_]) -> %% Callback answers. send_invalid_hdr_bits([callback, _]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 2001, %% SUCCESS 'Failed-AVP' = [], 'AVP' = []} @@ -403,6 +439,7 @@ send_invalid_hdr_bits([callback, _]) -> %% diameter answers. send_invalid_hdr_bits([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3008, %% INVALID_HDR_BITS 'Failed-AVP' = [], 'AVP' = []} @@ -414,6 +451,7 @@ send_invalid_hdr_bits([_,_]) -> %% diameter answers. send_missing_avp([answer, rfc6733]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -421,6 +459,7 @@ send_missing_avp([answer, rfc6733]) -> %% Callback answers. send_missing_avp([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -432,6 +471,7 @@ send_missing_avp([_,_]) -> %% diameter answers. send_ignore_missing_avp([answer, rfc6733]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -439,6 +479,7 @@ send_ignore_missing_avp([answer, rfc6733]) -> %% Callback answers, ignores the error send_ignore_missing_avp([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 2001, %% SUCCESS 'Failed-AVP' = [], 'AVP' = []} @@ -451,6 +492,7 @@ send_ignore_missing_avp([_,_]) -> %% RFC 6733 allows 5xxx in an answer-message. send_5xxx_missing_avp([_, rfc6733]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -458,10 +500,12 @@ send_5xxx_missing_avp([_, rfc6733]) -> %% RFC 3588 doesn't: sending answer fails. send_5xxx_missing_avp([_, rfc3588]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), {error, timeout} = call(); %% Callback answers, ignores the error send_5xxx_missing_avp([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 2001, %% SUCCESS 'Failed-AVP' = [], 'AVP' = []} @@ -473,6 +517,7 @@ send_5xxx_missing_avp([_,_]) -> %% Callback answers with STA. send_double_error([callback, _]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -480,6 +525,7 @@ send_double_error([callback, _]) -> %% diameter answers with answer-message. send_double_error([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3008, %% INVALID_HDR_BITS 'Failed-AVP' = [], 'AVP' = []} @@ -491,6 +537,7 @@ send_double_error([_,_]) -> %% Callback answers. send_3xxx([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3999, 'Failed-AVP' = [], 'AVP' = []} @@ -503,10 +550,12 @@ send_3xxx([_,_]) -> %% Callback answers but fails since 5xxx isn't allowed in an RFC 3588 %% answer-message. send_5xxx([_, rfc3588]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), {error, timeout} = call(); %% Callback answers. send_5xxx([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5999, 'Failed-AVP' = [], 'AVP' = []} @@ -516,6 +565,7 @@ send_5xxx([_,_]) -> call() -> Name = ?testcase(), + ?XL("call -> make diameter call with Name: ~p", [Name]), diameter:call(?CLIENT, ?DICT, #diameter_base_STR @@ -524,6 +574,7 @@ call() -> 'Class' = [?L(Name)]}, [{extra, [Name]}]). + %% =========================================================================== %% diameter callbacks From a8dfa61d0190ba9f380bc6f2829d7c12553d7629 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 17:03:57 +0200 Subject: [PATCH 040/422] [diameter|test] Add host and os analyzis function(s) --- lib/diameter/test/diameter_util.erl | 2296 ++++++++++++++++++++++++++- 1 file changed, 2292 insertions(+), 4 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index a55934aa99d1..d247f0510e22 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -24,8 +24,15 @@ %% Utility functions. %% +%% Framework +-export([ + init_per_suite/1, + end_per_suite/1 + ]). + %% generic --export([name/1, +-export([ + name/1, consult/2, run/1, fold/3, @@ -38,14 +45,20 @@ unique_string/0, have_sctp/0, eprof/1, - log/4]). + log/4, + proxy_call/3 + ]). %% diameter-specific --export([lport/2, +-export([ + lport/2, listen/2, listen/3, connect/3, connect/4, disconnect/4, - info/0]). + info/0 + ]). + +-export([analyze_and_print_host_info/0]). -include("diameter_util.hrl"). @@ -56,6 +69,41 @@ -define(UL(F, A), ?LOG("DUTIL", F, A)). +%% --------------------------------------------------------------------------- + +init_per_suite(Config) -> + try analyze_and_print_host_info() of + {Factor, HostInfo} when is_integer(Factor) -> + try maybe_skip(HostInfo) of + true -> + {skip, "Unstable host and/or os (or combo thererof)"}; + false -> + case lists:keysearch(label, 1, HostInfo) of + {value, Label} -> + [{dia_factor, Factor}, Label | Config]; + false -> + [{dia_factor, Factor} | Config] + end + catch + throw:{skip, _} = SKIP -> + SKIP; + _:_:_ -> + [{dia_factor, Factor} | Config] + end; + _ -> + [{dia_factor, 1} | Config] + catch + throw:{skip, _} = SKIP -> + SKIP; + _:_:_ -> + [{dia_factor, 1} | Config] + end. + + +end_per_suite(_Config) -> + ok. + + %% --------------------------------------------------------------------------- eprof(start) -> @@ -549,6 +597,7 @@ cfg(listen) -> cfg(PortNr) -> [{raddr, ?ADDR}, {rport, PortNr}]. + %% --------------------------------------------------------------------------- %% info/0 @@ -570,3 +619,2242 @@ log(ModStr, LINE, F, A) is_list(F) andalso is_list(A) -> ct:log("[~s:~w,~p] " ++ F ++ "~n", [ModStr, LINE, self()|A]). + + +%% --------------------------------------------------------------------------- + +analyze_and_print_host_info() -> + {OsFam, OsName} = os:type(), + Version = + case os:version() of + {Maj, Min, Rel} -> + f("~w.~w.~w", [Maj, Min, Rel]); + VStr -> + VStr + end, + case {OsFam, OsName} of + {unix, linux} -> + analyze_and_print_linux_host_info(Version); + {unix, openbsd} -> + analyze_and_print_openbsd_host_info(Version); + {unix, freebsd} -> + analyze_and_print_freebsd_host_info(Version); + {unix, netbsd} -> + analyze_and_print_netbsd_host_info(Version); + {unix, darwin} -> + analyze_and_print_darwin_host_info(Version); + {unix, sunos} -> + analyze_and_print_solaris_host_info(Version); + {win32, nt} -> + analyze_and_print_win_host_info(Version); + _ -> + io:format("OS Family: ~p" + "~n OS Type: ~p" + "~n Version: ~p" + "~n Num Online Schedulers: ~s" + "~n", [OsFam, OsName, Version, str_num_schedulers()]), + {num_schedulers_to_factor(), []} + end. + + +%% -- Unix:Linux -- + +analyze_and_print_linux_host_info(Version) -> + {Distro, Label} = + case file:read_file_info("/etc/issue") of + {ok, _} -> + linux_which_distro(Version); + _ -> + L = ts_extra_platform_label(), + io:format("Linux: ~s" + "~n TS Extra Platform Label: ~s" + "~n", [Version, L]), + {other, simplify_label(L)} + end, + %% 'VirtFactor' will be 0 unless virtual + VirtFactor = linux_virt_factor(), + Factor = + case (catch linux_which_cpuinfo(Distro)) of + {ok, {CPU, BogoMIPS}} -> + io:format("CPU: " + "~n Model: ~s" + "~n BogoMIPS: ~w" + "~n Num Online Schedulers: ~s" + "~n", [CPU, BogoMIPS, str_num_schedulers()]), + if + (BogoMIPS > 50000) -> + 1; + (BogoMIPS > 40000) -> + 2; + (BogoMIPS > 30000) -> + 3; + (BogoMIPS > 20000) -> + 4; + (BogoMIPS > 10000) -> + 5; + (BogoMIPS > 5000) -> + 8; + (BogoMIPS > 3000) -> + 12; + true -> + 10 + end; + {ok, "POWER9" ++ _ = CPU} -> + %% For some reason this host is really slow + %% Consider the CPU, it really should not be... + %% But, to not fail a bunch of test cases, we add 5 + case linux_cpuinfo_clock() of + Clock when is_integer(Clock) andalso (Clock > 0) -> + io:format("CPU: " + "~n Model: ~s" + "~n CPU Speed: ~w" + "~n Num Online Schedulers: ~s" + "~n", [CPU, Clock, str_num_schedulers()]), + if + (Clock > 2000) -> + 5 + num_schedulers_to_factor(); + true -> + 10 + num_schedulers_to_factor() + end; + _ -> + num_schedulers_to_factor() + end; + {ok, CPU} -> + io:format("CPU: " + "~n Model: ~s" + "~n Num Online Schedulers: ~s" + "~n", [CPU, str_num_schedulers()]), + num_schedulers_to_factor(); + _ -> + 5 + end, + AddLabelFactor = label2factor(Label), + %% Check if we need to adjust the factor because of the memory + AddMemFactor = try linux_which_meminfo() + catch _:_:_ -> 0 + end, + TSScaleFactor = case timetrap_scale_factor() of + N when is_integer(N) andalso (N > 0) -> + N - 1; + _ -> + 0 + end, + io:format("Factor calc:" + "~n Base Factor: ~w" + "~n Label Factor: ~w" + "~n Mem Factor: ~w" + "~n Virtual Factor: ~w" + "~n TS Scale Factor: ~w" + "~n", [Factor, AddLabelFactor, AddMemFactor, VirtFactor, + TSScaleFactor]), + {Factor + AddLabelFactor + AddMemFactor + VirtFactor + TSScaleFactor, + [{label, Label}]}. + + +linux_which_distro(Version) -> + try do_linux_which_distro(Version) + catch + throw:{distro, DistroAndLabel} -> + DistroAndLabel + end. + +do_linux_which_distro(Version) -> + Label = ts_extra_platform_label(), + + %% Many (linux) distro's use the /etc/issue file, so try that first. + %% Then we just keep going until we are "done". + DistroStr = do_linux_which_distro_issue(Version, Label), + + %% Still not sure; try fedora + _ = do_linux_which_distro_fedora(Version, Label), + + %% Still not sure; try suse + _ = do_linux_which_distro_suse(Version, Label), + + %% Still not sure; try os-release + _ = do_linux_which_distro_os_release(Version, Label), + + %% And the fallback + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + {other, simplify_label(Label)}. + +do_linux_which_distro_issue(Version, Label) -> + case file:read_file_info("/etc/issue") of + {ok, _} -> + case [string:trim(S) || + S <- string:tokens(os:cmd("cat /etc/issue"), [$\n])] of + [DistroStr | _] -> + case DistroStr of + "Wind River Linux" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {wind_river, simplify_label(Label)}}); + "MontaVista" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {montavista, simplify_label(Label)}}); + "Yellow Dog" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {yellow_dog, simplify_label(Label)}}); + "Ubuntu" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {ubuntu, simplify_label(Label)}}); + "Linux Mint" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {linux_mint, simplify_label(Label)}}); + _ -> + DistroStr + end; + X -> + X + end; + _ -> + "Unknown" + end. + +do_linux_which_distro_fedora(Version, Label) -> + %% Check if fedora + case file:read_file_info("/etc/fedora-release") of + {ok, _} -> + case [string:trim(S) || + S <- string:tokens(os:cmd("cat /etc/fedora-release"), + [$\n])] of + [DistroStr | _] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, "Fedora", Label, + linux_product_name()]) + end, + throw({distro, {fedora, simplify_label(Label)}}); + _ -> + ignore + end. + +do_linux_which_distro_suse(Version, Label) -> + %% Check if its a SuSE + case file:read_file_info("/etc/SUSE-brand") of + {ok, _} -> + case file:read_file_info("/etc/SuSE-release") of + {ok, _} -> + case [string:trim(S) || + S <- string:tokens(os:cmd("cat /etc/SuSE-release"), + [$\n])] of + ["SUSE Linux Enterprise Server" ++ _ = DistroStr | _] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, {sles, simplify_label(Label)}}); + [DistroStr | _] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, {suse, simplify_label(Label)}}); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, "SuSE", Label, + linux_product_name()]), + throw({distro, {suse, simplify_label(Label)}}) + end; + _ -> + case string:tokens(os:cmd("cat /etc/SUSE-brand"), [$\n]) of + ["SLE" = DistroStr, VERSION | _] -> + case [string:strip(S) || + S <- string:tokens(VERSION, [$=])] of + ["VERSION", VersionNo] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Distro Version: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, + DistroStr, VersionNo, + Label, + linux_product_name()]), + throw({distro, + {sles, simplify_label(Label)}}); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {sles, simplify_label(Label)}}) + end; + ["openSUSE" = DistroStr, VERSION | _] -> + case [string:strip(S) || + S <- string:tokens(VERSION, [$=])] of + ["VERSION", VersionNo] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Distro Version: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, + DistroStr, VersionNo, + Label, + linux_product_name()]), + throw({distro, + {suse, simplify_label(Label)}}); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {suse, simplify_label(Label)}}) + end; + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, "Unknown SUSE", Label, + linux_product_name()]), + throw({distro, {suse, simplify_label(Label)}}) + end + end; + _ -> + ignore + end. + +do_linux_which_distro_os_release(Version, Label) -> + case file:read_file_info("/etc/os-release") of + {ok, _} -> + %% We want to 'catch' if our processing is wrong, + %% that's why we catch and re-throw the distro. + %% Actual errors will be returned as 'ignore'. + try + begin + Info = linux_process_os_release(), + {value, {_, DistroStr}} = lists:keysearch(name, 1, Info), + {value, {_, VersionNo}} = lists:keysearch(version, 1, Info), + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Distro Version: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, VersionNo, Label, + linux_product_name()]), + throw({distro, + {linux_distro_str_to_distro_id(DistroStr), + simplify_label(Label)}}) + end + catch + throw:{distro, _} = DISTRO -> + throw(DISTRO); + _:_ -> + ignore + end; + _ -> + ignore + end. + +linux_process_os_release() -> + %% Read the "raw" file + Raw = os:cmd("cat /etc/os-release"), + %% Split it into lines + Lines1 = string:tokens(Raw, [$\n]), + %% Just in case, skip any lines starting with '#'. + Lines2 = linux_process_os_release1(Lines1), + %% Each (remaining) line *should* be: = + %% Both sides will be strings, the value side will be a quoted string... + %% Convert those into a 2-tuple list: [{Tag, Value}] + linux_process_os_release2(Lines2). + +linux_process_os_release1(Lines) -> + linux_process_os_release1(Lines, []). + +linux_process_os_release1([], Acc) -> + lists:reverse(Acc); +linux_process_os_release1([H|T], Acc) -> + case H of + "#" ++ _ -> + linux_process_os_release1(T, Acc); + _ -> + linux_process_os_release1(T, [H|Acc]) + end. + +linux_process_os_release2(Lines) -> + linux_process_os_release2(Lines, []). + +linux_process_os_release2([], Acc) -> + lists:reverse(Acc); +linux_process_os_release2([H|T], Acc) -> + case linux_process_os_release3(H) of + {value, Value} -> + linux_process_os_release2(T, [Value|Acc]); + false -> + linux_process_os_release2(T, Acc) + end. + +linux_process_os_release3(H) -> + case [string:strip(S) || S <- string:tokens(H, [$=])] of + [Tag, Value] -> + Tag2 = list_to_atom(string:to_lower(Tag)), + Value2 = string:strip(Value, both, $"), + linux_process_os_release4(Tag2, Value2); + _ -> + false + end. + +linux_process_os_release4(name = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(version = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(version_id = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(id = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(pretty_name = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(_Tag, _Value) -> + false. + +linux_distro_str_to_distro_id("Debian" ++ _) -> + debian; +linux_distro_str_to_distro_id("Fedora" ++ _) -> + fedora; +linux_distro_str_to_distro_id("Linux Mint" ++ _) -> + linux_mint; +linux_distro_str_to_distro_id("MontaVista" ++ _) -> + montavista; +linux_distro_str_to_distro_id("openSUSE" ++ _) -> + suse; +linux_distro_str_to_distro_id("SLES" ++ _) -> + sles; +linux_distro_str_to_distro_id("Ubuntu" ++ _) -> + ubuntu; +linux_distro_str_to_distro_id("Wind River Linux" ++ _) -> + wind_river; +linux_distro_str_to_distro_id("Yellow Dog" ++ _) -> + yellow_dog; +linux_distro_str_to_distro_id(X) -> + X. + + +linux_virt_factor() -> + linux_virt_factor(linux_product_name()). + +linux_virt_factor("VMware" ++ _) -> + 2; +linux_virt_factor("VirtualBox" ++ _) -> + 4; +linux_virt_factor(_) -> + 0. + + +linux_product_name() -> + ProductNameFile = "/sys/devices/virtual/dmi/id/product_name", + case file:read_file_info(ProductNameFile) of + {ok, _} -> + case os:cmd("cat " ++ ProductNameFile) of + false -> + "-"; + Info -> + string:trim(Info) + end; + _ -> + "-" + end. + + +linux_info_lookup(Key, File) -> + LKey = string:to_lower(Key), + try [string:trim(S) || S <- string:tokens(os:cmd("grep -i " ++ "\"" ++ LKey ++ "\"" ++ " " ++ File), [$:,$\n])] of + Info -> + linux_info_lookup_collect(LKey, Info, []) + catch + _:_:_ -> + "-" + end. + +linux_info_lookup_collect(_Key, [], Values) -> + lists:reverse(Values); +linux_info_lookup_collect(Key, [Key, Value|Rest], Values) -> + linux_info_lookup_collect(Key, Rest, [Value|Values]); +linux_info_lookup_collect(Key1, [Key2, Value|Rest], Values) -> + case string:to_lower(Key2) of + Key1 -> + linux_info_lookup_collect(Key1, Rest, [Value|Values]); + _ -> + lists:reverse(Values) + end; +linux_info_lookup_collect(_, _, Values) -> + lists:reverse(Values). + + +linux_cpuinfo_lookup(Key) when is_list(Key) -> + linux_info_lookup(Key, "/proc/cpuinfo"). + +linux_cpuinfo_cpu() -> + case linux_cpuinfo_lookup("cpu") of + [Model] -> + Model; + ["POWER9" ++ _ = CPU|_] -> + CPU; + _ -> + "-" + end. + +linux_cpuinfo_motherboard() -> + case linux_cpuinfo_lookup("motherboard") of + [MB] -> + MB; + _ -> + "-" + end. + +linux_cpuinfo_bogomips() -> + case linux_cpuinfo_lookup("bogomips") of + [] -> + "-"; + BMips when is_list(BMips) -> + BMScale = 1.0, + try round(BMScale * lists:sum([bogomips_to_int(BM) || BM <- BMips])) + catch + _:_:_ -> + "-" + end; + _X -> + "-" + end. + +linux_cpuinfo_total_bogomips() -> + case linux_cpuinfo_lookup("total bogomips") of + [TBM] -> + try bogomips_to_int(TBM) + catch + _:_:_ -> + "-" + end; + _ -> + "-" + end. + +bogomips_to_int(BM) -> + try list_to_float(BM) of + F -> + floor(F) + catch + _:_:_ -> + try list_to_integer(BM) of + I -> + I + catch + _:_:_ -> + throw(noinfo) + end + end. + +linux_cpuinfo_model() -> + case linux_cpuinfo_lookup("model") of + [M] -> + M; + _X -> + "-" + end. + +linux_cpuinfo_platform() -> + case linux_cpuinfo_lookup("platform") of + [P] -> + P; + _ -> + "-" + end. + +linux_cpuinfo_model_name() -> + case linux_cpuinfo_lookup("model name") of + [P|_] -> + P; + _ -> + "-" + end. + +linux_cpuinfo_processor() -> + case linux_cpuinfo_lookup("Processor") of + [P] -> + P; + _ -> + "-" + end. + +linux_cpuinfo_machine() -> + case linux_cpuinfo_lookup("machine") of + [M] -> + M; + _ -> + "-" + end. + +linux_which_cpuinfo(montavista) -> + CPU = + case linux_cpuinfo_cpu() of + "-" -> + throw(noinfo); + Model -> + case linux_cpuinfo_motherboard() of + "-" -> + Model; + MB -> + Model ++ " (" ++ MB ++ ")" + end + end, + case linux_cpuinfo_bogomips() of + "-" -> + {ok, CPU}; + BMips -> + {ok, {CPU, BMips}} + end; + +linux_which_cpuinfo(yellow_dog) -> + CPU = + case linux_cpuinfo_cpu() of + "-" -> + throw(noinfo); + Model -> + case linux_cpuinfo_motherboard() of + "-" -> + Model; + MB -> + Model ++ " (" ++ MB ++ ")" + end + end, + {ok, CPU}; + +linux_which_cpuinfo(wind_river) -> + CPU = + case linux_cpuinfo_model() of + "-" -> + throw(noinfo); + Model -> + case linux_cpuinfo_platform() of + "-" -> + Model; + Platform -> + Model ++ " (" ++ Platform ++ ")" + end + end, + case linux_cpuinfo_total_bogomips() of + "-" -> + {ok, CPU}; + BMips -> + {ok, {CPU, BMips}} + end; + +%% Check for x86 (Intel or AMD) +linux_which_cpuinfo(Other) when (Other =:= debian) orelse + (Other =:= fedora) orelse + (Other =:= ubuntu) orelse + (Other =:= linux_mint) orelse + (Other =:= sles) orelse + (Other =:= suse) orelse + (Other =:= other) -> + CPU = + case linux_cpuinfo_model_name() of + "-" -> + %% This is for POWER9 + case linux_cpuinfo_cpu() of + "POWER9" ++ _ = PowerCPU -> + Machine = + case linux_cpuinfo_machine() of + "-" -> + ""; + M -> + " (" ++ M ++ ")" + end, + PowerCPU ++ Machine; + _X -> + %% ARM (at least some distros...) + case linux_cpuinfo_processor() of + "-" -> + case linux_cpuinfo_model() of + "-" -> + %% Ok, we give up + throw(noinfo); + Model -> + Model + end; + Proc -> + Proc + end + end; + ModelName -> + ModelName + end, + case linux_cpuinfo_bogomips() of + "-" -> + {ok, CPU}; + BMips -> + {ok, {CPU, BMips}} + end. + +linux_meminfo_lookup(Key) when is_list(Key) -> + linux_info_lookup(Key, "/proc/meminfo"). + +linux_meminfo_memtotal() -> + case linux_meminfo_lookup("MemTotal") of + [X] -> + X; + _ -> + "-" + end. + +%% We *add* the value this return to the Factor. +linux_which_meminfo() -> + case linux_meminfo_memtotal() of + "-" -> + 0; + MemTotal -> + io:format("Memory:" + "~n ~s" + "~n", [MemTotal]), + case string:tokens(MemTotal, [$ ]) of + [MemSzStr, MemUnit] -> + MemSz2 = list_to_integer(MemSzStr), + MemSz3 = + case string:to_lower(MemUnit) of + "kb" -> + MemSz2; + "mb" -> + MemSz2*1024; + "gb" -> + MemSz2*1024*1024; + _ -> + throw(noinfo) + end, + if + (MemSz3 >= 8388608) -> + 0; + (MemSz3 >= 4194304) -> + 1; + (MemSz3 >= 2097152) -> + 3; + true -> + 5 + end; + _X -> + 0 + end + end. + + +linux_cpuinfo_clock() -> + %% This is written as: "3783.000000MHz" + %% So, check unit MHz (handle nothing else). + %% Also, check for both float and integer + %% Also, the freq is per core, and can vary... + case linux_cpuinfo_lookup("clock") of + [C|_] when is_list(C) -> + case lists:reverse(string:to_lower(C)) of + "zhm" ++ CRev -> + try trunc(list_to_float(lists:reverse(CRev))) of + I -> + I + catch + _:_:_ -> + try list_to_integer(lists:reverse(CRev)) of + I -> + I + catch + _:_:_ -> + 0 + end + end; + _ -> + 0 + end; + _ -> + 0 + end. + + +%% -- Unix:OpenBSD -- + +%% Just to be clear: This is ***not*** scientific... +analyze_and_print_openbsd_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + io:format("OpenBSD:" + "~n Version: ~s" + "~n", [Version]), + Extract = + fun(Key) -> + string:tokens(string:trim(os:cmd("sysctl " ++ Key)), [$=]) + end, + try + begin + CPU = + case Extract("hw.model") of + ["hw.model", Model] -> + string:trim(Model); + _ -> + "-" + end, + CPUSpeed = + case Extract("hw.cpuspeed") of + ["hw.cpuspeed", Speed] -> + list_to_integer(Speed); + _ -> + -1 + end, + NCPU = + case Extract("hw.ncpufound") of + ["hw.ncpufound", N] -> + list_to_integer(N); + _ -> + -1 + end, + Memory = + case Extract("hw.physmem") of + ["hw.physmem", PhysMem] -> + list_to_integer(PhysMem) div 1024; + _ -> + -1 + end, + io:format("CPU:" + "~n Model: ~s" + "~n Speed: ~w" + "~n N: ~w" + "~nMemory:" + "~n ~w KB" + "~n", [CPU, CPUSpeed, NCPU, Memory]), + CPUFactor = + if + (CPUSpeed >= 3000) -> + if + (NCPU >= 8) -> + 1; + (NCPU >= 6) -> + 2; + (NCPU >= 4) -> + 3; + (NCPU >= 2) -> + 4; + true -> + 10 + end; + (CPUSpeed >= 2000) -> + if + (NCPU >= 8) -> + 2; + (NCPU >= 6) -> + 3; + (NCPU >= 4) -> + 4; + (NCPU >= 2) -> + 5; + true -> + 12 + end; + (CPUSpeed >= 1000) -> + if + (NCPU >= 8) -> + 3; + (NCPU >= 6) -> + 4; + (NCPU >= 4) -> + 5; + (NCPU >= 2) -> + 6; + true -> + 14 + end; + true -> + if + (NCPU >= 8) -> + 4; + (NCPU >= 6) -> + 6; + (NCPU >= 4) -> + 8; + (NCPU >= 2) -> + 10; + true -> + 20 + end + end, + MemAddFactor = + if + (Memory >= 16777216) -> + 0; + (Memory >= 8388608) -> + 1; + (Memory >= 4194304) -> + 3; + (Memory >= 2097152) -> + 5; + true -> + 10 + end, + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + {CPUFactor + MemAddFactor + AddLabelFactor, []} + end + catch + _:_:_ -> + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + {2 + AddLabelFactor, []} + end. + + +%% -- Unix:FreeBSD -- + +analyze_and_print_freebsd_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + FreeBSDVersion = which_freebsd_version(), + case FreeBSDVersion of + undefined -> + io:format("FreeBSD:" + "~n Version: ~s" + "~n", [Version]), + ""; + _ -> + io:format("FreeBSD:" + "~n Version: ~s (~s)" + "~n", [Version, FreeBSDVersion]) + end, + %% This test require that the program 'sysctl' is in the path. + %% First test with 'which sysctl', if that does not work + %% try with 'which /sbin/sysctl'. If that does not work either, + %% we skip the test... + try + begin + SysCtl = + case string:trim(os:cmd("which sysctl")) of + [] -> + case string:trim(os:cmd("which /sbin/sysctl")) of + [] -> + throw(sysctl); + SC2 -> + SC2 + end; + SC1 -> + SC1 + end, + Extract = + fun(Key) -> + string:tokens(string:trim(os:cmd(SysCtl ++ " " ++ Key)), + [$:]) + end, + CPU = analyze_freebsd_cpu(Extract), + CPUSpeed = analyze_freebsd_cpu_speed(Extract), + NCPU = analyze_freebsd_ncpu(Extract), + Memory = analyze_freebsd_memory(Extract), + io:format("CPU:" + "~n Model: ~s" + "~n Speed: ~w" + "~n N: ~w" + "~n Num Online Schedulers: ~s" + "~nMemory:" + "~n ~w KB" + "~n", + [CPU, CPUSpeed, NCPU, str_num_schedulers(), Memory]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + CPUFactor = + if + (CPUSpeed =:= -1) -> + 1; + (CPUSpeed >= 3000) -> + if + (NCPU >= 8) -> + 1; + (NCPU >= 6) -> + 2; + (NCPU >= 4) -> + 3; + (NCPU >= 2) -> + 4; + true -> + 5 + end; + (CPUSpeed >= 2000) -> + if + (NCPU >= 12) -> + 1; + (NCPU >= 8) -> + 2; + (NCPU >= 6) -> + 4; + (NCPU >= 4) -> + 6; + (NCPU >= 2) -> + 8; + true -> + 10 + end; + true -> + if + (NCPU =:= -1) -> + 2; + (NCPU >= 12) -> + 2; + (NCPU >= 8) -> + 3; + (NCPU >= 6) -> + 5; + (NCPU >= 4) -> + 7; + (NCPU >= 2) -> + 9; + true -> + 12 + end + end, + MemAddFactor = + if + (Memory =:= -1) -> + 0; + (Memory >= 8388608) -> + 0; + (Memory >= 4194304) -> + 1; + (Memory >= 2097152) -> + 2; + true -> + 3 + end, + {CPUFactor + MemAddFactor, []} + end + catch + _:_:_ -> + io:format("CPU:" + "~n Num Online Schedulers: ~s" + "~n", [str_num_schedulers()]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + {num_schedulers_to_factor() ++ AddLabelFactor, []} + end. + + +which_freebsd_version() -> + case string:trim(os:cmd("which freebsd-version")) of + [] -> + "-"; + FreeBSDVersion -> + case string:trim(os:cmd(FreeBSDVersion)) of + [] -> + undefined; + V -> + V + end + end. + + +analyze_freebsd_cpu(Extract) -> + analyze_freebsd_item(Extract, "hw.model", fun(X) -> X end, "-"). + +analyze_freebsd_cpu_speed(Extract) -> + analyze_freebsd_item(Extract, + "hw.clockrate", + fun(X) -> list_to_integer(X) end, + -1). + +analyze_freebsd_ncpu(Extract) -> + analyze_freebsd_item(Extract, + "hw.ncpu", + fun(X) -> list_to_integer(X) end, + -1). + +analyze_freebsd_memory(Extract) -> + analyze_freebsd_item(Extract, + "hw.physmem", + fun(X) -> list_to_integer(X) div 1024 end, + -1). + +analyze_freebsd_item(Extract, Key, Process, Default) -> + try + begin + case Extract(Key) of + [Key, Model] -> + Process(string:trim(Model)); + _ -> + Default + end + end + catch + _:_:_ -> + Default + end. + + +%% -- Unix:NetBSD -- + +analyze_and_print_netbsd_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + io:format("NetBSD:" + "~n Version: ~s" + "~n", [Version]), + %% This test require that the program 'sysctl' is in the path. + %% First test with 'which sysctl', if that does not work + %% try with 'which /sbin/sysctl'. If that does not work either, + %% we skip the test... + try + begin + SysCtl = + case string:trim(os:cmd("which sysctl")) of + [] -> + case string:trim(os:cmd("which /sbin/sysctl")) of + [] -> + throw(sysctl); + SC2 -> + SC2 + end; + SC1 -> + SC1 + end, + Extract = + fun(Key) -> + [string:trim(S) || + S <- + string:tokens(string:trim(os:cmd(SysCtl ++ " " ++ Key)), + [$=])] + end, + CPU = analyze_netbsd_cpu(Extract), + Machine = analyze_netbsd_machine(Extract), + Arch = analyze_netbsd_machine_arch(Extract), + CPUSpeed = analyze_netbsd_cpu_speed(Extract), + NCPU = analyze_netbsd_ncpu(Extract), + Memory = analyze_netbsd_memory(Extract), + io:format("CPU:" + "~n Model: ~s (~s, ~s)" + "~n Speed: ~w MHz" + "~n N: ~w" + "~n Num Schedulers: ~w" + "~nMemory:" + "~n ~w KB" + "~n", + [CPU, Machine, Arch, CPUSpeed, NCPU, + erlang:system_info(schedulers), Memory]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + CPUFactor = + if + (CPUSpeed =:= -1) -> + 1; + (CPUSpeed >= 2000) -> + if + (NCPU >= 4) -> + 1; + (NCPU >= 2) -> + 2; + true -> + 3 + end; + true -> + if + (NCPU =:= -1) -> + 1; + (NCPU >= 4) -> + 2; + (NCPU >= 2) -> + 3; + true -> + 4 + end + end, + MemAddFactor = + if + (Memory =:= -1) -> + 0; + (Memory >= 8388608) -> + 0; + (Memory >= 4194304) -> + 1; + (Memory >= 2097152) -> + 2; + true -> + 3 + end, + {CPUFactor + MemAddFactor + AddLabelFactor, []} + end + catch + _:_:_ -> + io:format("CPU:" + "~n Num Schedulers: ~w" + "~n", [erlang:system_info(schedulers)]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + Factor = num_schedulers_to_factor(), + {Factor + AddLabelFactor, []} + end. + + +analyze_netbsd_cpu(Extract) -> + analyze_netbsd_item(Extract, "hw.model", fun(X) -> X end, "-"). + +analyze_netbsd_machine(Extract) -> + analyze_netbsd_item(Extract, "hw.machine", fun(X) -> X end, "-"). + +analyze_netbsd_machine_arch(Extract) -> + analyze_netbsd_item(Extract, "hw.machine_arch", fun(X) -> X end, "-"). + +analyze_netbsd_cpu_speed(Extract) -> + analyze_netbsd_item(Extract, "machdep.dmi.processor-frequency", + fun(X) -> case string:tokens(X, [$\ ]) of + [MHz, "MHz"] -> + list_to_integer(MHz); + _ -> + -1 + end + end, "-"). + +analyze_netbsd_ncpu(Extract) -> + analyze_netbsd_item(Extract, + "hw.ncpu", + fun(X) -> list_to_integer(X) end, + -1). + +analyze_netbsd_memory(Extract) -> + analyze_netbsd_item(Extract, + "hw.physmem64", + fun(X) -> list_to_integer(X) div 1024 end, + -1). + +analyze_netbsd_item(Extract, Key, Process, Default) -> + analyze_freebsd_item(Extract, Key, Process, Default). + + +%% -- Unix:Darwin -- + +%% Model Identifier: Macmini7,1 +%% Processor Name: Intel Core i5 +%% Processor Speed: 2,6 GHz +%% Number of Processors: 1 +%% Total Number of Cores: 2 +%% L2 Cache (per Core): 256 KB +%% L3 Cache: 3 MB +%% Hyper-Threading Technology: Enabled +%% Memory: 16 GB + +%% Hardware: +%% +%% Hardware Overview: +%% +%% Model Name: MacBook Pro +%% Model Identifier: MacBookPro18,1 +%% Chip: Apple M1 Pro +%% Total Number of Cores: 10 (8 performance and 2 efficiency) +%% Memory: 32 GB +%% System Firmware Version: 7459.101.2 +%% OS Loader Version: 7459.101.2 +%% Serial Number (system): THF4W05C97 +%% Hardware UUID: 7C9AB2E1-73B1-5AD6-9BC8-7229DE7A748C +%% Provisioning UDID: 00006000-000259042662801E +%% Activation Lock Status: Enabled + + +analyze_and_print_darwin_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + %% This stuff is for macOS. + %% If we ever tested on a pure darwin machine, + %% we need to find some other way to find some info... + %% Also, I suppose its possible that we for some other + %% reason *fail* to get the info... + Label = ts_extra_platform_label(), + {BaseFactor, MemFactor} = + case analyze_darwin_software_info() of + [] -> + io:format("Darwin:" + "~n Version: ~s" + "~n Num Online Schedulers: ~s" + "~n TS Extra Platform Label: ~s" + "~n", [Version, str_num_schedulers(), Label]), + {num_schedulers_to_factor(), 1}; + SwInfo when is_list(SwInfo) -> + SystemVersion = analyze_darwin_sw_system_version(SwInfo), + KernelVersion = analyze_darwin_sw_kernel_version(SwInfo), + HwInfo = analyze_darwin_hardware_info(), + ModelName = analyze_darwin_hw_model_name(HwInfo), + ModelId = analyze_darwin_hw_model_identifier(HwInfo), + {Processor, CPUFactor} = analyze_darwin_hw_processor(HwInfo), + Memory = analyze_darwin_hw_memory(HwInfo), + Memory = analyze_darwin_hw_memory(HwInfo), + io:format("Darwin:" + "~n System Version: ~s" + "~n Kernel Version: ~s" + "~n Model: ~s (~s)" + "~n Processor: ~s" + "~n Memory: ~s" + "~n Num Online Schedulers: ~s" + "~n TS Extra Platform Label: ~s" + "~n~n", + [SystemVersion, KernelVersion, + ModelName, ModelId, + Processor, + Memory, + str_num_schedulers(), Label]), + {CPUFactor, analyze_darwin_memory_to_factor(Memory)} + end, + AddLabelFactor = label2factor(simplify_label(Label)), + AddMemFactor = if + (MemFactor > 0) -> + MemFactor - 1; + true -> + 0 + end, + TSScaleFactor = ts_scale_factor(), + io:format("Factor calc:" + "~n Base Factor: ~w" + "~n Label Factor: ~w" + "~n Mem Factor: ~w" + "~n TS Scale Factor: ~w" + "~n~n", + [BaseFactor, AddLabelFactor, AddMemFactor, TSScaleFactor]), + {BaseFactor + AddLabelFactor + AddMemFactor + TSScaleFactor, + [{label, Label}]}. + + +analyze_darwin_software_info() -> + analyze_darwin_system_profiler("SPSoftwareDataType"). + +analyze_darwin_hardware_info() -> + analyze_darwin_system_profiler("SPHardwareDataType"). + +analyze_darwin_system_profiler(DataType) -> + %% First, make sure the program actually exist (with the current PATH): + Prog0 = "system_profiler", + case os:cmd("which " ++ Prog0) of + [] -> + %% Ok, as a last resource, check if is /usr/sbin/system_profiler? + Prog1 = "/usr/sbin/system_profiler", + case os:cmd("which " ++ Prog1) of + [] -> + []; + _ -> + analyze_darwin_system_profiler(Prog1, DataType) + end; + _ -> + analyze_darwin_system_profiler(Prog0, DataType) + end. + +analyze_darwin_system_profiler(Prog, DataType) -> + D0 = os:cmd(Prog ++ " " ++ DataType), + D1 = string:tokens(D0, [$\n]), + D2 = [string:trim(S1) || S1 <- D1], + D3 = [string:tokens(S2, [$:]) || S2 <- D2], + analyze_darwin_system_profiler2(D3). + +analyze_darwin_system_profiler2(L) -> + analyze_darwin_system_profiler2(L, []). + +analyze_darwin_system_profiler2([], Acc) -> + [{string:to_lower(K), V} || {K, V} <- lists:reverse(Acc)]; +analyze_darwin_system_profiler2([[_]|T], Acc) -> + analyze_darwin_system_profiler2(T, Acc); +analyze_darwin_system_profiler2([[H1,H2]|T], Acc) -> + analyze_darwin_system_profiler2(T, [{H1, string:trim(H2)}|Acc]); +analyze_darwin_system_profiler2([[H|TH0]|T], Acc) -> + %% Some value parts has ':' in them, so put them together + TH1 = colonize(TH0), + analyze_darwin_system_profiler2(T, [{H, string:trim(TH1)}|Acc]). + + +analyze_darwin_sw_system_version(SwInfo) -> + proplists:get_value("system version", SwInfo, "-"). + +analyze_darwin_sw_kernel_version(SwInfo) -> + proplists:get_value("kernel version", SwInfo, "-"). + + +analyze_darwin_hw_chip(HwInfo) -> + proplists:get_value("chip", HwInfo, "-"). + +analyze_darwin_hw_model_name(HwInfo) -> + proplists:get_value("model name", HwInfo, "-"). + +analyze_darwin_hw_model_identifier(HwInfo) -> + proplists:get_value("model identifier", HwInfo, "-"). + +analyze_darwin_hw_processor(HwInfo) -> + case analyze_darwin_hw_processor_name(HwInfo) of + "-" -> % Maybe Apple Chip + case analyze_darwin_hw_chip(HwInfo) of + "-" -> + "-"; + Chip -> + NumCores = analyze_darwin_hw_total_number_of_cores(HwInfo), + CPUFactor = analyze_darwin_cpu_to_factor(Chip, NumCores), + {f("~s [~s]", [Chip, NumCores]), CPUFactor} + end; + ProcName -> + ProcSpeed = analyze_darwin_hw_processor_speed(HwInfo), + NumProc = analyze_darwin_hw_number_of_processors(HwInfo), + NumCores = analyze_darwin_hw_total_number_of_cores(HwInfo), + CPUFactor = analyze_darwin_cpu_to_factor(ProcName, + ProcSpeed, + NumProc, + NumCores), + {f("~s [~s, ~s, ~s]", + [ProcName, ProcSpeed, NumProc, NumCores]), CPUFactor} + end. + +analyze_darwin_hw_processor_name(HwInfo) -> + proplists:get_value("processor name", HwInfo, "-"). + +analyze_darwin_hw_processor_speed(HwInfo) -> + proplists:get_value("processor speed", HwInfo, "-"). + +analyze_darwin_hw_number_of_processors(HwInfo) -> + proplists:get_value("number of processors", HwInfo, "-"). + +analyze_darwin_hw_total_number_of_cores(HwInfo) -> + proplists:get_value("total number of cores", HwInfo, "-"). + +analyze_darwin_hw_memory(HwInfo) -> + proplists:get_value("memory", HwInfo, "-"). + + +%% The memory looks like this " ". Example: "2 GB" +analyze_darwin_memory_to_factor(Mem) -> + case [string:to_lower(S) || S <- string:tokens(Mem, [$\ ])] of + [_SzStr, "tb"] -> + 1; + [SzStr, "gb"] -> + try list_to_integer(SzStr) of + Sz when Sz < 2 -> + 20; + Sz when Sz < 4 -> + 10; + Sz when Sz < 8 -> + 5; + Sz when Sz < 16 -> + 2; + _ -> + 1 + catch + _:_:_ -> + 20 + end; + [_SzStr, "mb"] -> + 20; + _ -> + 20 + end. + +%% This is for the M1 family of chips +%% We don't actually know *how* fast it is, only that its fast. +%% the speed may be a float, which we transforms into an integer of MHz. +%% To calculate a factor based on processor "class" and number of cores +%% is ... not an exact ... science ... +analyze_darwin_cpu_to_factor("Apple M" ++ _ = _Chip, _NumCoresStr) -> + %% We know that pretty much every M processor is *fast*, + %% so there is no real need to "calculate" anything... + 1. + +analyze_darwin_cpu_to_factor(_ProcName, + ProcSpeedStr, NumProcStr, NumCoresStr) -> + Speed = + case [string:to_lower(S) || S <- string:tokens(ProcSpeedStr, [$\ ])] of + [SpeedStr, "mhz"] -> + try list_to_integer(SpeedStr) of + SpeedI -> + SpeedI + catch + _:_:_ -> + try list_to_float(SpeedStr) of + SpeedF -> + trunc(SpeedF) + catch + _:_:_ -> + -1 + end + end; + [SpeedStr, "ghz"] -> + try list_to_float(SpeedStr) of + SpeedF -> + trunc(1000*SpeedF) + catch + _:_:_ -> + try list_to_integer(SpeedStr) of + SpeedI -> + 1000*SpeedI + catch + _:_:_ -> + -1 + end + end; + _ -> + -1 + end, + NumProc = try list_to_integer(NumProcStr) of + NumProcI -> + NumProcI + catch + _:_:_ -> + 1 + end, + NumCores = try list_to_integer(NumCoresStr) of + NumCoresI -> + NumCoresI + catch + _:_:_ -> + 1 + end, + if + (Speed > 3000) -> + if + (NumProc =:= 1) -> + if + (NumCores < 2) -> + 5; + (NumCores < 4) -> + 3; + (NumCores < 6) -> + 2; + true -> + 1 + end; + true -> + if + (NumCores < 4) -> + 2; + true -> + 1 + end + end; + (Speed > 2000) -> + if + (NumProc =:= 1) -> + if + (NumCores < 2) -> + 8; + (NumCores < 4) -> + 5; + (NumCores < 6) -> + 3; + true -> + 1 + end; + true -> + if + (NumCores < 4) -> + 5; + (NumCores < 8) -> + 2; + true -> + 1 + end + end; + true -> + if + (NumProc =:= 1) -> + if + (NumCores < 2) -> + 10; + (NumCores < 4) -> + 7; + (NumCores < 6) -> + 5; + (NumCores < 8) -> + 3; + true -> + 1 + end; + true -> + if + (NumCores < 4) -> + 8; + (NumCores < 8) -> + 4; + true -> + 1 + end + end + end. + + +%% -- Unix:SunOS (Solaris) -- + +analyze_and_print_solaris_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + + Release = + case file:read_file_info("/etc/release") of + {ok, _} -> + case [string:trim(S) || S <- string:tokens(os:cmd("cat /etc/release"), [$\n])] of + [Rel | _] -> + Rel; + _ -> + "-" + end; + _ -> + "-" + end, + %% Display the firmware device tree root properties (prtconf -b) + Props = [list_to_tuple([string:trim(PS) || PS <- Prop]) || + Prop <- [string:tokens(S, [$:]) || + S <- string:tokens(os:cmd("prtconf -b"), [$\n])]], + BannerName = case lists:keysearch("banner-name", 1, Props) of + {value, {_, BN}} -> + string:trim(BN); + _ -> + "-" + end, + InstructionSet = + case string:trim(os:cmd("isainfo -k")) of + "Pseudo-terminal will not" ++ _ -> + "-"; + IS -> + IS + end, + PtrConf = [list_to_tuple([string:trim(S) || S <- Items]) || Items <- [string:tokens(S, [$:]) || S <- string:tokens(os:cmd("prtconf"), [$\n])], length(Items) > 1], + SysConf = + case lists:keysearch("System Configuration", 1, PtrConf) of + {value, {_, SC}} -> + SC; + _ -> + "-" + end, + %% Because we count the lines of the output (which may contain + %% any number of extra crap lines) we need to ensure we only + %% count the "proper" stdout. So send it to a tmp file first + %% and then count its number of lines... + NumPhysCPU = + try + begin + File1 = f("/tmp/psrinfo_p.~s.~w", [os:getpid(), os:system_time()]), + os:cmd("psrinfo -p > " ++ File1), + string:trim(os:cmd("cat " ++ File1)) + end + catch + _:_:_ -> + "-" + end, + %% Because we count the lines of the output (which may contain + %% any number of extra crap lines) we need to ensure we only + %% count the "proper" stdout. So send it to a tmp file first + %% and then count its number of lines... + NumVCPU = + try + begin + File2 = f("/tmp/psrinfo.~s.~w", [os:getpid(), os:system_time()]), + os:cmd("psrinfo > " ++ File2), + [NumVCPUStr | _] = string:tokens(os:cmd("wc -l " ++ File2), [$\ ]), + NumVCPUStr + end + catch + _:_:_ -> + "-" + end, + MemSz = + case lists:keysearch("Memory size", 1, PtrConf) of + {value, {_, MS}} -> + MS; + _ -> + "-" + end, + io:format("Solaris: ~s" + "~n Release: ~s" + "~n Banner Name: ~s" + "~n Instruction Set: ~s" + "~n CPUs: ~s (~s)" + "~n System Config: ~s" + "~n Memory Size: ~s" + "~n Num Online Schedulers: ~s" + "~n~n", [Version, Release, BannerName, InstructionSet, + NumPhysCPU, NumVCPU, + SysConf, MemSz, + str_num_schedulers()]), + AddMemFactor = + try string:tokens(MemSz, [$ ]) of + [SzStr, "Mega" ++ _] -> + try list_to_integer(SzStr) of + Sz when Sz > 16384 -> + 0; + Sz when Sz > 8192 -> + 1; + Sz when Sz > 4096 -> + 4; + Sz when Sz > 2048 -> + 8; + _ -> + 12 + catch + _:_:_ -> + 10 + end; + [SzStr, "Giga" ++ _] -> + try list_to_integer(SzStr) of + Sz when Sz > 16 -> + 0; + Sz when Sz > 8 -> + 1; + Sz when Sz > 4 -> + 4; + Sz when Sz > 2 -> + 8; + _ -> + 12 + catch + _:_:_ -> + 10 + end; + _ -> + 10 + catch + _:_:_ -> + 10 + end, + %% We don't really have enough info about the CPU to calculate the + %% base factor based on that, so we just use the number of schedulers. + BaseFactor = + try erlang:system_info(schedulers) of + 1 -> + 12; + 2 -> + 8; + N when (N =:= 3) orelse (N =:= 4) -> + 4; + N when (N =< 6) -> + 3; + _ -> + 2 + catch + _:_:_ -> + 12 + end, + TSScaleFactor = ts_scale_factor(), + io:format("Factor calc:" + "~n Base Factor: ~w" + "~n Label Factor: ~w" + "~n Mem Factor: ~w" + "~n TS Scale Factor: ~w" + "~n TS Extra Platform Label: ~s" + "~n~n", + [BaseFactor, AddLabelFactor, AddMemFactor, + TSScaleFactor, Label]), + {BaseFactor + AddMemFactor + AddLabelFactor + TSScaleFactor, + [{label, Label}]}. + + +%% -- Win32:NT -- + +analyze_and_print_win_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + + SysInfo = which_win_system_info(), + OsName = win_sys_info_lookup(os_name, SysInfo), + OsVersion = win_sys_info_lookup(os_version, SysInfo), + SysMan = win_sys_info_lookup(system_manufacturer, SysInfo), + SysMod = win_sys_info_lookup(system_model, SysInfo), + SysType = win_sys_info_lookup(system_type, SysInfo), + NumProcs = win_sys_info_lookup(num_processors, SysInfo), + TotPhysMem = win_sys_info_lookup(total_phys_memory, SysInfo), + io:format("Windows: ~s" + "~n OS Version: ~s (~p)" + "~n System Manufacturer: ~s" + "~n System Model: ~s" + "~n System Type: ~s" + "~n Number of Processor(s): ~s" + "~n Total Physical Memory: ~s" + "~n (Erlang) WordSize: ~w" + "~n Num Online Schedulers: ~s" + "~n~n", [OsName, OsVersion, Version, + SysMan, SysMod, SysType, + NumProcs, TotPhysMem, + erlang:system_info(wordsize), + str_num_schedulers()]), + io:format("TS: " + "~n TimeTrap Factor: ~w" + "~n Extra Platform Label: ~s" + "~n~n", + [timetrap_scale_factor(), Label]), + %% 'VirtFactor' will be 0 unless virtual + VirtFactor = win_virt_factor(SysMod), + + %% On some machines this is a badly formated string + %% (contains a char of 255), so we need to do some nasty stuff... + MemFactor = + try + begin + %% "Normally" this looks like this: "16,123 MB" + %% But sometimes the "," is replaced by a + %% 255 or 160 char, which I assume must be some + %% unicode screwup... + %% Anyway, filter out both of them! + TotPhysMem1 = lists:delete($,, TotPhysMem), + TotPhysMem2 = lists:delete(255, TotPhysMem1), + TotPhysMem3 = lists:delete(160, TotPhysMem2), + [MStr, MUnit|_] = string:tokens(TotPhysMem3, [$\ ]), + case string:to_lower(MUnit) of + "gb" -> + try list_to_integer(MStr) of + M when M >= 16 -> + 0; + M when M >= 8 -> + 1; + M when M >= 4 -> + 3; + M when M >= 2 -> + 6; + _ -> + 10 + catch + _:_:_ -> + %% For some reason the string contains + %% "unusual" characters... + %% ...so print the string as a list... + io:format("Bad memory string: " + "~n [gb] ~w" + "~n", [MStr]), + 10 + end; + "mb" -> + try list_to_integer(MStr) of + M when M >= 16384 -> + 0; + M when M >= 8192 -> + 1; + M when M >= 4096 -> + 3; + M when M >= 2048 -> + 6; + _ -> + 10 + catch + _:_:_ -> + %% For some reason the string contains + %% "unusual" characters... + %% ...so print the string as a list... + io:format("Bad memory string: " + "~n [mb] ~w" + "~n", [MStr]), + 10 + end; + _ -> + io:format("Bad memory string: " + "~n ~w" + "~n", [MStr]), + 10 + end + end + catch + _:_:_ -> + %% For some reason the string contains + %% "unusual" characters... + %% ...so print the string as a list... + io:format("Bad memory string: " + "~n (y) ~w" + "~n", [TotPhysMem]), + 10 + end, + CPUFactor = + case erlang:system_info(schedulers) of + 1 -> + 10; + 2 -> + 5; + _ -> + 2 + end, + io:format("Factor calc:" + "~n CPU Factor: ~w" + "~n Mem Factor: ~w" + "~n Label Factor: ~w" + "~n Virtual Factor: ~w" + "~n~n", + [CPUFactor, MemFactor, AddLabelFactor, VirtFactor]), + {CPUFactor + MemFactor + AddLabelFactor + VirtFactor, SysInfo}. + + +%% This function only extracts the prop we actually care about! +which_win_system_info() -> + F = fun() -> + try + begin + SysInfo = os:cmd("systeminfo"), + process_win_system_info( + string:tokens(SysInfo, [$\r, $\n]), []) + end + catch + C:E:S -> + io:format("Failed get or process System info: " + " Error Class: ~p" + " Error: ~p" + " Stack: ~p" + "~n", [C, E, S]), + [] + end + end, + proxy_call(F, timer:minutes(1), []). + + +win_sys_info_lookup(Key, SysInfo) -> + win_sys_info_lookup(Key, SysInfo, "-"). + +win_sys_info_lookup(Key, SysInfo, Def) -> + case lists:keysearch(Key, 1, SysInfo) of + {value, {Key, Value}} -> + Value; + false -> + Def + end. + + +win_virt_factor("VMware" ++ _) -> + 2; +win_virt_factor(_) -> + 0. + + +process_win_system_info([], Acc) -> + Acc; +process_win_system_info([H|T], Acc) -> + case string:tokens(H, [$:]) of + [Key, Value] -> + case string:to_lower(Key) of + "os name" -> + process_win_system_info(T, + [{os_name, string:trim(Value)}|Acc]); + "os version" -> + process_win_system_info(T, + [{os_version, string:trim(Value)}|Acc]); + "system manufacturer" -> + process_win_system_info(T, + [{system_manufacturer, string:trim(Value)}|Acc]); + "system model" -> + process_win_system_info(T, + [{system_model, string:trim(Value)}|Acc]); + "system type" -> + process_win_system_info(T, + [{system_type, string:trim(Value)}|Acc]); + "processor(s)" -> + [NumProcStr|_] = string:tokens(Value, [$\ ]), + T2 = lists:nthtail(list_to_integer(NumProcStr), T), + process_win_system_info(T2, + [{num_processors, NumProcStr}|Acc]); + "total physical memory" -> + process_win_system_info(T, + [{total_phys_memory, string:trim(Value)}|Acc]); + _ -> + process_win_system_info(T, Acc) + end; + _ -> + process_win_system_info(T, Acc) + end. + + +%% --------------------------------------------------------------------------- + +str_num_schedulers() -> + try erlang:system_info(schedulers_online) of + N -> f("~w", [N]) + catch + _:_:_ -> "-" + end. + +num_schedulers_to_factor() -> + try erlang:system_info(schedulers_online) of + 1 -> + 10; + 2 -> + 8; + 3 -> + 6; + 4 -> + 4; + N when (N =< 5) -> + 2; + _ -> + 1 + catch + _:_:_ -> + 10 + end. + + +ts_extra_platform_label() -> + case os:getenv("TS_EXTRA_PLATFORM_LABEL") of + false -> "-"; + Val -> Val + end. + +ts_scale_factor() -> + case timetrap_scale_factor() of + N when is_integer(N) andalso (N > 0) -> + N - 1; + _ -> + 0 + end. + + +timetrap_scale_factor() -> + case (catch test_server:timetrap_scale_factor()) of + {'EXIT', _} -> + 1; + N -> + N + end. + + +simplify_label("Systemtap" ++ _) -> + {host, systemtap}; +simplify_label("Meamax" ++ _) -> + {host, meamax}; +simplify_label("Cover" ++ _) -> + {host, cover}; +simplify_label(Label) -> + case string:find(string:to_lower(Label), "docker") of + "docker" ++ _ -> + docker; + _ -> + {host, undefined} + end. + +label2factor(docker) -> + 4; +label2factor({host, meamax}) -> + 2; +label2factor({host, cover}) -> + 6; +label2factor({host, _}) -> + 0. + + + +%% --------------------------------------------------------------------------- + +maybe_skip(_HostInfo) -> + + %% We have some crap machines that causes random test case failures + %% for no obvious reason. So, attempt to identify those without actually + %% checking for the host name... + + LinuxVersionVerify = + fun(V) when (V > {3,6,11}) -> + false; % OK - No skip + (V) when (V =:= {3,6,11}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "Fedora release 16 " ++ _ -> % Stone age Fedora => Skip + true; + _ -> + false + end; + (V) when (V =:= {3,4,20}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "Wind River Linux 5.0.1.0" ++ _ -> % *Old* Wind River => skip + true; + _ -> + false + end; + (V) when (V =:= {2,6,32}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "Debian GNU/Linux 6.0 " ++ _ -> % Stone age Debian => Skip + true; + _ -> + false + end; + (V) when (V > {2,6,24}) -> + false; % OK - No skip + (V) when (V =:= {2,6,10}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "MontaVista" ++ _ -> % Stone age MontaVista => Skip + %% The real problem is that the machine is *very* slow + true; + _ -> + false + end; + (_) -> + %% We are specifically checking for + %% a *really* old gento... + case string:find(string:strip(os:cmd("uname -a")), "gentoo") of + nomatch -> + false; + _ -> % Stone age gentoo => Skip + true + end + end, + DarwinVersionVerify = + fun(V) when (V > {9, 8, 0}) -> + %% This version is OK: No Skip + false; + (_V) -> + %% This version is *not* ok: Skip + true + end, + SkipWindowsOnVirtual = + %% fun() -> + %% SysMan = win_sys_info_lookup(system_manufacturer, HostInfo), + %% case string:to_lower(SysMan) of + %% "vmware" ++ _ -> + %% true; + %% _ -> + %% false + %% end + %% end, + fun() -> + %% The host has been replaced and the VM has been reinstalled + %% so for now we give it a chance... + false + end, + COND = [{unix, [{linux, LinuxVersionVerify}, + {darwin, DarwinVersionVerify}]}, + {win32, SkipWindowsOnVirtual}], + os_cond_skip(COND). + +os_cond_skip(any) -> + true; +os_cond_skip(Skippable) when is_list(Skippable) -> + os_cond_skip(Skippable, os:type()); +os_cond_skip(_Crap) -> + false. + +os_cond_skip(Skippable, {OsFam, OsName}) -> + os_cond_skip(Skippable, OsFam, OsName); +os_cond_skip(Skippable, OsFam) -> + os_cond_skip(Skippable, OsFam, undefined). + +os_cond_skip(Skippable, OsFam, OsName) -> + %% Check if the entire family is to be skipped + %% Example: [win32, unix] + case lists:member(OsFam, Skippable) of + true -> + true; + false -> + %% Example: [{unix, freebsd}] | [{unix, [freebsd, darwin]}] + case lists:keysearch(OsFam, 1, Skippable) of + {value, {OsFam, OsName}} -> + true; + {value, {OsFam, OsNames}} when is_list(OsNames) -> + %% OsNames is a list of: + %% [atom()|{atom(), function/0 | function/1}] + case lists:member(OsName, OsNames) of + true -> + true; + false -> + os_cond_skip_check(OsName, OsNames) + end; + {value, {OsFam, Check}} when is_function(Check, 0) -> + Check(); + {value, {OsFam, Check}} when is_function(Check, 1) -> + Check(os:version()); + _ -> + false + end + end. + +%% Performs a check via a provided fun with arity 0 or 1. +%% The argument is the result of os:version(). +os_cond_skip_check(OsName, OsNames) -> + case lists:keysearch(OsName, 1, OsNames) of + {value, {OsName, Check}} when is_function(Check, 0) -> + Check(); + {value, {OsName, Check}} when is_function(Check, 1) -> + Check(os:version()); + _ -> + false + end. + + + +%% --------------------------------------------------------------------------- + +proxy_call(F, Timeout, Default) + when is_function(F, 0) andalso is_integer(Timeout) andalso (Timeout > 0) -> + {P, M} = erlang:spawn_monitor(fun() -> exit(F()) end), + receive + {'DOWN', M, process, P, Reply} -> + Reply + after Timeout -> + erlang:demonitor(M, [flush]), + exit(P, kill), + Default + end. + + +%% --------------------------------------------------------------------------- + +f(F, A) -> + lists:flatten(io_lib:format(F, A)). + +%% This is only called if the length is at least 2 +colonize([L1, L2]) -> + L1 ++ ":" ++ L2; +colonize([H|T]) -> + H ++ ":" ++ colonize(T). + From 5e9b3804a4407f6fe50c2feaf5ff4925f2d97c09 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 17:04:37 +0200 Subject: [PATCH 041/422] [diameter|test|app] Add [init|end]_per_suite --- lib/diameter/test/diameter_app_SUITE.erl | 18 ++++++++++++++++-- 1 file changed, 16 insertions(+), 2 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 027b816edc54..896dca711947 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -29,8 +29,13 @@ run/1]). %% common_test wrapping --export([suite/0, - all/0]). +-export([ + %% Framework functions + suite/0, + all/0, + init_per_suite/1, + end_per_suite/1 + ]). %% testcases -export([keys/1, @@ -80,6 +85,15 @@ all() -> xref, relup]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + %% =========================================================================== run() -> From 81fdc21c378eb2aa356e06223297818e09a8dda2 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 17:51:10 +0200 Subject: [PATCH 042/422] [diameter|test] Misc cleanup --- lib/diameter/test/diameter_3xxx_SUITE.erl | 22 +++++++++++++++--- .../test/diameter_distribution_SUITE.erl | 11 +++++++++ lib/diameter/test/diameter_dpr_SUITE.erl | 23 +++++++++++++++---- lib/diameter/test/diameter_examples_SUITE.erl | 9 ++++++++ lib/diameter/test/diameter_relay_SUITE.erl | 12 +++++++++- lib/diameter/test/diameter_tls_SUITE.erl | 13 +++++++---- .../test/diameter_transport_SUITE.erl | 12 +++++++++- 7 files changed, 88 insertions(+), 14 deletions(-) diff --git a/lib/diameter/test/diameter_3xxx_SUITE.erl b/lib/diameter/test/diameter_3xxx_SUITE.erl index 2af853ea2723..d19f79c9c2e3 100644 --- a/lib/diameter/test/diameter_3xxx_SUITE.erl +++ b/lib/diameter/test/diameter_3xxx_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2022. All Rights Reserved. +%% Copyright Ericsson AB 2013-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -31,9 +31,16 @@ run/1]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - traffic/1]). + init_per_suite/1, + end_per_suite/1, + + %% The test cases + traffic/1 + ]). %% internal -export([send_unknown_application/1, @@ -109,10 +116,19 @@ suite() -> all() -> [traffic]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + traffic(_Config) -> ?XL("traffic -> entry"), run(). + %% =========================================================================== tc() -> diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index d211d4740f86..22d3a0ee5b49 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -33,6 +33,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases traffic/1 @@ -116,6 +118,14 @@ suite() -> all() -> [traffic]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + traffic(_Config) -> ?DL("traffic -> entry"), Res = traffic(), @@ -123,6 +133,7 @@ traffic(_Config) -> "~n Res: ~p", [Res]), Res. + %% =========================================================================== run() -> diff --git a/lib/diameter/test/diameter_dpr_SUITE.erl b/lib/diameter/test/diameter_dpr_SUITE.erl index e4b8788ed64e..5670dd9775c1 100644 --- a/lib/diameter/test/diameter_dpr_SUITE.erl +++ b/lib/diameter/test/diameter_dpr_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2012-2022. All Rights Reserved. +%% Copyright Ericsson AB 2012-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -29,14 +29,21 @@ run/1]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, + init_per_suite/1, + end_per_suite/1, + + %% The test cases client/1, server/1, uncommon/1, transport/1, service/1, - application/1]). + application/1 + ]). %% internal -export([connect/1, @@ -101,6 +108,14 @@ suite() -> all() -> [client, server, uncommon, transport, service, application]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + -define(tc(Name), Name(_) -> ?DL("~w -> entry", [Name]), run([Name])). ?tc(client). @@ -141,7 +156,7 @@ run(Grp) -> _ = lists:foldl(fun(F,A) -> ?DL("run(~w) -> apply" "~n F: ~p" - "~n A: ~p", [F, A]), + "~n A: ~p", [Grp, F, A]), apply(?MODULE, F, [A]) end, [{group, Grp}], diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index d258207cdb36..9ff45b35297c 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -33,6 +33,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases dict/1, @@ -86,6 +88,13 @@ all() -> [dict, code]. +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + dict(Config) -> ?EL("dict -> entry with" "~n Config: ~p", [Config]), diff --git a/lib/diameter/test/diameter_relay_SUITE.erl b/lib/diameter/test/diameter_relay_SUITE.erl index c641d29b4fe9..701552d91409 100644 --- a/lib/diameter/test/diameter_relay_SUITE.erl +++ b/lib/diameter/test/diameter_relay_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2022. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -42,6 +42,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases parallel/1 @@ -117,6 +119,14 @@ suite() -> all() -> [parallel]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + parallel(_Config) -> ?RL("parallel -> entry"), Res = run(), diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl index e0531a276b13..6f21ceafce28 100644 --- a/lib/diameter/test/diameter_tls_SUITE.erl +++ b/lib/diameter/test/diameter_tls_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2023. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -135,20 +135,22 @@ all() -> %% Shouldn't really have to know about crypto here but 'ok' from %% ssl:start() isn't enough to guarantee that TLS is available. init_per_suite(Config) -> + Config2 = ?DUTIL:init_per_suite(Config), try - [] == (catch make_certs(dir(Config))) + [] == (catch make_certs(dir(Config2))) orelse throw({?MODULE, no_certs}), ok == crypto:start() orelse throw({?MODULE, no_crypto}), ok == ssl:start() orelse throw({?MODULE, no_ssl}), - Config + Config2 catch {?MODULE, E} -> {skip, E} end. -end_per_suite(_Config) -> +end_per_suite(Config) -> ssl:stop(), - crypto:stop(). + crypto:stop(), + ?DUTIL:end_per_suite(Config). parallel(Config) -> ?TL("parallel -> entry"), @@ -160,6 +162,7 @@ parallel(Config) -> dir(Config) -> proplists:get_value(priv_dir, Config). + %% =========================================================================== run() -> diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index e86270d7fbbd..578871e95377 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2022. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -33,6 +33,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases parallel/1 @@ -96,6 +98,14 @@ suite() -> all() -> [parallel]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + parallel(_) -> ?TL("parallel -> entry"), Res = run(), From ba6b466d819b324835950507219e970c1772ece8 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 17 May 2024 12:03:46 +0200 Subject: [PATCH 043/422] [diameter|test|distribution] Tweaked test case Attempt to calculate the diameter call timeout depending on the "factor" (instead of just use the default timeout of 5 secs). --- .../test/diameter_distribution_SUITE.erl | 98 ++++++++++++------- 1 file changed, 62 insertions(+), 36 deletions(-) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 22d3a0ee5b49..d28cda4cb73a 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -66,7 +66,7 @@ %% =========================================================================== -define(DL(F), ?DL(F, [])). --define(DL(F, A), ?LOG("DDISTS", F, A)). +-define(DL(F, A), ?LOG("DDISTRS", F, A)). -define(CLIENT, 'CLIENT'). -define(SERVER, 'SERVER'). @@ -126,9 +126,10 @@ end_per_suite(Config) -> ?DUTIL:end_per_suite(Config). -traffic(_Config) -> +traffic(Config) -> ?DL("traffic -> entry"), - Res = traffic(), + Factor = dia_factor(Config), + Res = do_traffic(Factor), ?DL("traffic -> done when" "~n Res: ~p", [Res]), Res. @@ -137,27 +138,27 @@ traffic(_Config) -> %% =========================================================================== run() -> - [] = ?DUTIL:run([{fun traffic/0, 60000}]). + [] = ?RUN([{fun() -> do_traffic(1) end, 60000}]). %% process for linked peers to die with %% traffic/0 -traffic() -> - ?DL("traffic -> make sure we have distro"), +do_traffic(Factor) -> + ?DL("do_traffic -> make sure we have distro"), true = is_alive(), %% need distribution for peer nodes - ?DL("traffic -> get nodes"), + ?DL("do_traffic -> get nodes"), Nodes = enslave(), - ?DL("traffic -> ping nodes"), + ?DL("do_traffic -> ping nodes"), [] = ping(Nodes), %% drop client node - ?DL("traffic -> start nodes"), + ?DL("do_traffic -> start nodes"), [] = start(Nodes), - ?DL("traffic -> connect nodes"), + ?DL("do_traffic -> connect nodes"), [_] = connect(Nodes), - ?DL("traffic -> send (to) nodes"), - [] = send(Nodes), - ?DL("traffic -> stop nodes"), + ?DL("do_traffic -> send (to) nodes"), + [] = send(Nodes, Factor), + ?DL("do_traffic -> stop nodes"), [] = stop(Nodes), - ?DL("traffic -> done"), + ?DL("do_traffic -> done"), ok. %% enslave/0 @@ -254,10 +255,10 @@ peers(client2) -> nodes(). %% nodes. connect({?SERVER, _, []}) -> - [_LRef = ?DUTIL:listen(?SERVER, tcp)]; + [_LRef = ?LISTEN(?SERVER, tcp)]; connect({?CLIENT, [{Node, _} | _], [LRef] = Acc}) -> - ?DUTIL:connect(?CLIENT, tcp, {Node, LRef}), + ?CONNECT(?CLIENT, tcp, {Node, LRef}), Acc; connect(Nodes) -> @@ -269,47 +270,48 @@ connect(Nodes) -> %% =========================================================================== -%% send/1 +%% send/2 -send(Nodes) -> - ?RUN([[fun send/2, Nodes, T] +send(Nodes, Factor) -> + ?RUN([[fun send/3, Nodes, T, Factor] || T <- [local, remote, timeout, failover]]). -%% send/2 +%% send/3 %% Send a request from the first client node, using a the local %% transport. -send(Nodes, local) -> +send(Nodes, local, Factor) -> ?DL("send(local) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 0, str(?LOGOUT)), + = send(Nodes, 0, str(?LOGOUT), Factor), ?DL("send(local) -> success (=success)"), ok; %% Send a request from the first client node, using a transport on the %% another node. -send(Nodes, remote) -> +send(Nodes, remote, Factor) -> ?DL("send(remote) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 1, str(?LOGOUT)), + = send(Nodes, 1, str(?LOGOUT), Factor), ?DL("send(remote) -> success (=success)"), ok; %% Send a request that the server discards. -send(Nodes, timeout) -> +send(Nodes, timeout, Factor) -> ?DL("send(timeout) -> entry - expect timeout"), - {error, timeout} = send(Nodes, 1, str(?TIMEOUT)), + {error, timeout} = send(Nodes, 1, str(?TIMEOUT), Factor), ?DL("send(timeout) -> success (=timeout)"), ok; %% Send a request that causes the server to take the transport down. -send(Nodes, failover) -> +send(Nodes, failover, Factor) -> ?DL("send(failover) -> entry - expect busy (~p)", [?BUSY]), #'diameter_base_answer-message'{'Result-Code' = ?BUSY} - = send(Nodes, 2, str(?MOVED)), + = send(Nodes, 2, str(?MOVED), Factor), ?DL("send(failover) -> success (=busy)"), ok. + %% =========================================================================== str(Cause) -> @@ -317,25 +319,30 @@ str(Cause) -> 'Auth-Application-Id' = ?DICT:id(), 'Termination-Cause' = Cause}. -%% send/3 +%% send/4 -send([_, {Node, _} | _], Where, Req) -> +send([_, {Node, _} | _], Where, Req, Factor) -> ?DL("send -> make rpc call to node ~p", [Node]), - rpc:call(Node, ?MODULE, call, [{Where, Req}]). + rpc:call(Node, ?MODULE, call, [{Where, Req, Factor}]). %% call/1 -call({Where, Req}) -> - ?DL("call -> entry with" - "~n Where: ~p" - "~n Req: ~p", [Where, Req]), - diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}]). +call({Where, Req, Factor}) -> + Timeout = timeout(Factor), + ?DL("call -> make diameter call with" + "~n Where: ~p" + "~n Req: ~p" + "~nwhen" + "~n Timeout: ~w (~w)", [Where, Req, Timeout, Factor]), + diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}, + {timeout, Timeout}]). %% sname/0 sname() -> ?A(hd(string:tokens(?L(node()), "@"))). + %% =========================================================================== %% diameter callbacks @@ -428,3 +435,22 @@ fail(0, _) -> %% sent from the originating node ... fail(_, TPid) -> %% ... or through a remote node: force failover exit(TPid, kill), discard. + + +%% =========================================================================== + +-define(CALL_TO_DEFAULT, 5000). +timeout(Factor) when (Factor > 0) andalso (Factor =< 20) -> + (Factor - 1) * 500 + ?CALL_TO_DEFAULT; +timeout(Factor) when (Factor > 0) -> + 3*?CALL_TO_DEFAULT. % Max at 15 seconds + + +%% =========================================================================== + +dia_factor(Config) -> + config_lookup(?FUNCTION_NAME, Config). + +config_lookup(Key, Config) -> + {value, {Key, Value}} = lists:keysearch(Key, 1, Config), + Value. From d42b814e1a419f4a1cfd0408250bd234d76f250e Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 17 May 2024 17:11:38 +0200 Subject: [PATCH 044/422] [diameter|test|dist] Tweaked test case(s) Add diameter call timeout (other then default). --- lib/diameter/test/diameter_dist_SUITE.erl | 117 +++++++++++++++++----- 1 file changed, 93 insertions(+), 24 deletions(-) diff --git a/lib/diameter/test/diameter_dist_SUITE.erl b/lib/diameter/test/diameter_dist_SUITE.erl index 81d2dfbf3647..fa72c683d890 100644 --- a/lib/diameter/test/diameter_dist_SUITE.erl +++ b/lib/diameter/test/diameter_dist_SUITE.erl @@ -29,9 +29,16 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - traffic/1]). + init_per_suite/1, + end_per_suite/1, + + %% The test cases + traffic/1 + ]). %% diameter callbacks -export([peer_up/3, @@ -52,9 +59,13 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc6733.hrl"). +-include("diameter_util.hrl"). + + %% =========================================================================== --define(util, diameter_util). +-define(DL(F), ?DL(F, [])). +-define(DL(F, A), ?LOG("DDISTS", F, A)). -define(CLIENT, 'CLIENT'). -define(SERVER, 'SERVER'). @@ -105,26 +116,47 @@ suite() -> all() -> [traffic]. -traffic(_Config) -> - run(). +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + +traffic(Config) -> + ?DL("traffic -> entry"), + Factor = dia_factor(Config), + Res = do_traffic(Factor), + ?DL("traffic -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== %% run/0 run() -> - [] = ?util:run([{fun traffic/0, 60000}]). + [] = ?RUN([{fun() -> do_traffic(1) end, 60000}]). %% process for linked peers to die with %% traffic/0 -traffic() -> +do_traffic(Factor) -> + ?DL("do_traffic -> check we have distribution"), true = is_alive(), %% need distribution for peer nodes + ?DL("do_traffic -> get nodes"), Nodes = enslave(), + ?DL("do_traffic -> ping nodes (except client node)"), [] = ping(lists:droplast(Nodes)), %% drop client node + ?DL("do_traffic -> start nodes"), [] = start(Nodes), + ?DL("do_traffic -> connect nodes"), ok = connect(Nodes), - ok = send(Nodes). + ?DL("do_traffic -> send (to) nodes"), + ok = send(Nodes, Factor), + ?DL("do_traffic -> done"), + ok. %% enslave/1 %% @@ -138,8 +170,15 @@ enslave() -> [{N,S} || {M,S} <- ?NODES, N <- [start(M, Args)]]. start(Name, Args) -> - {ok, _, Node} = ?util:peer(#{name => Name, args => Args}), - Node. + case ?PEER(#{name => Name, args => Args}) of + {ok, _, Node} -> + Node; + {error, Reason} -> + ?DL("Failed starting node ~p" + "~n Reason: ~p", [Name, Reason]), + exit({skip, {failed_starting_node, Name, Reason}}) + end. + %% ping/1 %% @@ -211,14 +250,14 @@ origin(Server) -> connect({?SERVER, [{Node, _} | _], []}) when Node == node() -> %% server0 - [_LRef = ?util:listen(?SERVER, tcp)]; + [_LRef = ?LISTEN(?SERVER, tcp)]; connect({?SERVER, _, [_] = Acc}) -> %% server[12]: register to receive requests ok = diameter_dist:attach([?SERVER]), Acc; connect({?CLIENT, [{Node, _} | _], [LRef]}) -> - ?util:connect(?CLIENT, tcp, {Node, LRef}), + ?CONNECT(?CLIENT, tcp, {Node, LRef}), ok; connect(Nodes) -> @@ -231,17 +270,18 @@ connect(Nodes) -> %% =========================================================================== %% traffic testcases -%% send/1 +%% send/2 %% %% Send 100 requests and ensure the node name sent as User-Name isn't %% the node terminating transport. -send(Nodes) -> - send(Nodes, 100, dict:new()). +send(Nodes, Factor) -> + send(Nodes, 100, dict:new(), Factor). %% send/2 -send(Nodes, 0, Dict) -> +send(Nodes, 0, Dict, _Factor) -> + ?DL("send(0) -> entry - verify stats"), [{Server0, _} | _] = Nodes, Node = atom_to_binary(Server0, utf8), {false, _} = {dict:is_key(Node, Dict), dict:to_list(Dict)}, @@ -256,14 +296,17 @@ send(Nodes, 0, Dict) -> {[{send, 0, 100, 2001}], _} = {[{D,R,N,C} || {{{0,275,R}, D, {'Result-Code', C}}, N} <- Stats], Stats}, + ?DL("send(0) -> done"), ok; -send(Nodes, N, Dict) -> +send(Nodes, N, Dict, Factor) -> + ?DL("send(~w) -> entry", [N]), #diameter_base_STA{'Result-Code' = ?SUCCESS, 'User-Name' = [ServerNode]} - = send(Nodes, str(?LOGOUT)), + = send(Nodes, str(?LOGOUT), Factor), true = is_binary(ServerNode), - send(Nodes, N-1, dict:update_counter(ServerNode, 1, Dict)). + send(Nodes, N-1, dict:update_counter(ServerNode, 1, Dict), Factor). + %% =========================================================================== @@ -272,22 +315,29 @@ str(Cause) -> 'Auth-Application-Id' = ?DICT:id(), 'Termination-Cause' = Cause}. -%% send/2 +%% send/3 -send(Nodes, Req) -> +send(Nodes, Req, Factor) -> {Node, _} = lists:last(Nodes), - rpc:call(Node, ?MODULE, call, [Req]). + ?DL("send -> make rpc call (to call) to node ~p", [Node]), + rpc:call(Node, ?MODULE, call, [{Req, Factor}]). %% call/1 -call(Req) -> - diameter:call(?CLIENT, ?DICT, Req, []). +call({Req, Factor}) -> + Timeout = timeout(Factor), + ?DL("call -> make diameter call with" + "~n Req: ~p" + "~nwhen" + "~n Timeout: ~w (~w)", [Req, Timeout, Factor]), + diameter:call(?CLIENT, ?DICT, Req, [{timeout, Timeout}]). %% sname/0 sname() -> ?A(hd(string:tokens(?L(node()), "@"))). + %% =========================================================================== %% diameter callbacks @@ -347,3 +397,22 @@ handle_request(Pkt, ?SERVER, {_, Caps}) -> 'Origin-Host' = OH, 'Origin-Realm' = OR, 'User-Name' = [atom_to_binary(node(), utf8)]}}. + + +%% =========================================================================== + +-define(CALL_TO_DEFAULT, 5000). +timeout(Factor) when (Factor > 0) andalso (Factor =< 20) -> + (Factor - 1) * 500 + ?CALL_TO_DEFAULT; +timeout(Factor) when (Factor > 0) -> + 3*?CALL_TO_DEFAULT. % Max at 15 seconds + + +%% =========================================================================== + +dia_factor(Config) -> + config_lookup(?FUNCTION_NAME, Config). + +config_lookup(Key, Config) -> + {value, {Key, Value}} = lists:keysearch(Key, 1, Config), + Value. From de9001f940b341825d06f38eea653f620b6d7b8f Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 22 May 2024 08:26:05 +0200 Subject: [PATCH 045/422] [diameter|test|transport] More test case tweaking --- lib/diameter/test/diameter_transport_SUITE.erl | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index 578871e95377..1d9561c8929b 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -204,18 +204,25 @@ reconnect({listen, Ref}) -> ?TL("reconnect(listen) -> entry with" "~n Ref: ~p", [Ref]), SvcName = make_ref(), + ?TL("reconnect(listen) -> start service (~p)", [SvcName]), ok = start_service(SvcName), + ?TL("reconnect(listen) -> connect"), LRef = ?LISTEN(SvcName, tcp, [{watchdog_timer, 6000}]), + ?TL("reconnect(listen) -> wait"), [_] = diameter_reg:wait({diameter_tcp, listener, {LRef, '_'}}), + ?TL("reconnect(listen) -> register new transport"), true = diameter_reg:add_new({?MODULE, Ref, LRef}), %% Wait for partner to request transport death. + ?TL("reconnect(listen) -> abort: await (request for) transport death"), TPid = abort(SvcName, LRef, Ref), %% Kill transport to force the peer to reconnect. + ?TL("reconnect(listen) -> kill transport"), exit(TPid, kill), %% Wait for the partner again. + ?TL("reconnect(listen) -> abort: wait for partner again"), Res = abort(SvcName, LRef, Ref), ?TL("reconnect(listen) -> done when" @@ -227,25 +234,35 @@ reconnect({connect, Ref}) -> "~n Ref: ~p", [Ref]), SvcName = make_ref(), + ?TL("reconnect(connect) -> subscribe"), true = diameter:subscribe(SvcName), + ?TL("reconnect(connect) -> start service (~p)", [SvcName]), ok = start_service(SvcName), + ?TL("reconnect(connect) -> wait"), [{{_, _, LRef}, Pid}] = diameter_reg:wait({?MODULE, Ref, '_'}), + ?TL("reconnect(connect) -> connect"), CRef = ?CONNECT(SvcName, tcp, LRef, [{connect_timer, 2000}, {watchdog_timer, 6000}]), %% Tell partner to kill transport after seeing that there are no %% reconnection attempts. + ?TL("reconnect(connect) -> abort (kill transport)"), abort(SvcName, Pid, Ref), %% Transport goes down and is reestablished. + ?TL("reconnect(connect) -> await transport down"), ?RECV(#diameter_event{service = SvcName, info = {down, CRef, _, _}}), + ?TL("reconnect(connect) -> await transport reconnect"), ?RECV(#diameter_event{service = SvcName, info = {reconnect, CRef, _}}), + ?TL("reconnect(connect) -> await transport up"), ?RECV(#diameter_event{service = SvcName, info = {up, CRef, _, _, _}}), %% Kill again. + ?TL("reconnect(connect) -> abort (kill transport again)"), abort(SvcName, Pid, Ref), %% Wait for partner to die. + ?TL("reconnect(connect) -> await partner death"), MRef = erlang:monitor(process, Pid), Res = ?RECV({'DOWN', MRef, process, _, _}), From 21b5837a4c26f874da8415da6a8ce09ecdd83886 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 20 May 2024 19:35:43 +0200 Subject: [PATCH 046/422] [esock] Silence compiler warning on Windows Add two pragma-statements (disable + default) to silence a compiler warning. --- erts/emulator/nifs/win32/win_socket_asyncio.c | 2 ++ 1 file changed, 2 insertions(+) diff --git a/erts/emulator/nifs/win32/win_socket_asyncio.c b/erts/emulator/nifs/win32/win_socket_asyncio.c index 7516c0b0c852..504e74543d26 100644 --- a/erts/emulator/nifs/win32/win_socket_asyncio.c +++ b/erts/emulator/nifs/win32/win_socket_asyncio.c @@ -3845,7 +3845,9 @@ void encode_cmsgs(ErlNifEnv* env, /* nifs\win32\win_socket_asyncio.c(3167): * warning C4116: unnamed type definition in parentheses */ +#pragma warning(disable:4116) currentP = ESOCK_CMSG_NXTHDR(msgP, currentP)) { +#pragma warning(default:4116) SSDBG( descP, ("WIN-ESAIO", "encode_cmsgs {%d} -> process cmsg header when" From a9e32d89e3afb5f75cc17a8c7656fd3b56c568d8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 21 May 2024 00:07:43 +0200 Subject: [PATCH 047/422] Make Docs chunk deterministic and compressed --- lib/compiler/src/compile.erl | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index 5bbb84286cc5..1c66f80481cf 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -2411,7 +2411,8 @@ beam_docs(Code, #compile{dir = Dir, options = Options, SourceName = deterministic_filename(St), case beam_doc:main(Dir, SourceName, Code, Options) of {ok, Docs, Ws} -> - MetaDocs = [{?META_DOC_CHUNK, term_to_binary(Docs)} | ExtraChunks], + Binary = term_to_binary(Docs, [deterministic, compressed]), + MetaDocs = [{?META_DOC_CHUNK, Binary} | ExtraChunks], {ok, Code, St#compile{extra_chunks = MetaDocs, warnings = St#compile.warnings ++ Ws}}; {error, no_docs} -> From 788e2ed476e2ace7c59537e759cf38135e0ed3e5 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 22 May 2024 15:45:35 +0200 Subject: [PATCH 048/422] [esock|test|sctp] Add a couple of (sctp) test cases SCTP with type = stream "actually" (already) works... --- lib/kernel/test/socket_SUITE.erl | 113 +++++++++++++++++++++++++------ 1 file changed, 92 insertions(+), 21 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 3f7afef63f44..85d4052c2250 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -124,7 +124,10 @@ api_b_open_and_close_udpL/1, api_b_open_and_close_tcpL/1, api_b_open_and_close_seqpL/1, - api_b_open_and_close_sctp4/1, + api_b_open_and_close_seqp_sctp4/1, + api_b_open_and_close_seqp_sctp6/1, + api_b_open_and_close_stream_sctp4/1, + api_b_open_and_close_stream_sctp6/1, api_b_open_and_maybe_close_raw/1, api_b_sendto_and_recvfrom_udp4/1, api_b_sendto_and_recvfrom_udpL/1, @@ -137,7 +140,7 @@ api_b_sendmsg_and_recvmsg_tcp4/1, api_b_sendmsg_and_recvmsg_tcpL/1, api_b_sendmsg_and_recvmsg_seqpL/1, - api_b_sendmsg_and_recvmsg_sctp4/1, + api_b_sendmsg_and_recvmsg_stream_sctp4/1, api_b_sendmsg_iov_dgram_inet/1, api_b_sendmsg_iov_dgram_inet6/1, api_b_sendmsg_iov_dgram_local/1, @@ -1008,7 +1011,10 @@ api_basic_cases() -> api_b_open_and_close_udpL, api_b_open_and_close_tcpL, api_b_open_and_close_seqpL, - api_b_open_and_close_sctp4, + api_b_open_and_close_seqp_sctp4, + api_b_open_and_close_seqp_sctp6, + api_b_open_and_close_stream_sctp4, + api_b_open_and_close_stream_sctp6, api_b_open_and_maybe_close_raw, api_b_sendto_and_recvfrom_udp4, api_b_sendto_and_recvfrom_udpL, @@ -1021,7 +1027,7 @@ api_basic_cases() -> api_b_sendmsg_and_recvmsg_tcp4, api_b_sendmsg_and_recvmsg_tcpL, api_b_sendmsg_and_recvmsg_seqpL, - api_b_sendmsg_and_recvmsg_sctp4, + api_b_sendmsg_and_recvmsg_stream_sctp4, api_b_sendmsg_iov_dgram_inet, api_b_sendmsg_iov_dgram_inet6, api_b_sendmsg_iov_dgram_local, @@ -3108,9 +3114,9 @@ api_b_open_and_close_seqpL(_Config) when is_list(_Config) -> %% Basically open (create) and close an IPv4 SCTP (seqpacket) socket. %% With some extra checks... -api_b_open_and_close_sctp4(_Config) when is_list(_Config) -> +api_b_open_and_close_seqp_sctp4(_Config) when is_list(_Config) -> ?TT(?SECS(5)), - tc_try(api_b_open_and_close_sctp4, + tc_try(?FUNCTION_NAME, fun() -> has_support_sctp() end, fun() -> InitState = #{domain => inet, @@ -3120,6 +3126,60 @@ api_b_open_and_close_sctp4(_Config) when is_list(_Config) -> end). +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% Basically open (create) and close an IPv6 SCTP (seqpacket) socket. +%% With some extra checks... +api_b_open_and_close_seqp_sctp6(_Config) when is_list(_Config) -> + ?TT(?SECS(5)), + tc_try(?FUNCTION_NAME, + fun() -> + has_support_sctp(), + has_support_ipv6() + end, + fun() -> + InitState = #{domain => inet6, + type => seqpacket, + protocol => sctp}, + ok = api_b_open_and_close(InitState) + end). + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% Basically open (create) and close an IPv4 SCTP (stream) socket. +%% With some extra checks... +api_b_open_and_close_stream_sctp4(_Config) when is_list(_Config) -> + ?TT(?SECS(5)), + tc_try(?FUNCTION_NAME, + fun() -> has_support_sctp() end, + fun() -> + InitState = #{domain => inet, + type => stream, + protocol => sctp}, + ok = api_b_open_and_close(InitState) + end). + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% Basically open (create) and close an IPv6 SCTP (stream) socket. +%% With some extra checks... +api_b_open_and_close_stream_sctp6(_Config) when is_list(_Config) -> + ?TT(?SECS(5)), + tc_try(?FUNCTION_NAME, + fun() -> + has_support_sctp(), + has_support_ipv6() + end, + fun() -> + InitState = #{domain => inet6, + type => stream, + protocol => sctp}, + ok = api_b_open_and_close(InitState) + end). + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% api_b_open_and_close(InitState) -> @@ -3152,6 +3212,7 @@ api_b_open_and_close(InitState) -> end}, #{desc => "validate domain (maybe)", cmd => fun({#{domain := Domain} = S, {ok, Domain}}) -> + ?SEV_IPRINT("expected domain: ~p", [Domain]), {ok, S}; ({#{domain := ExpDomain}, {ok, Domain}}) -> {error, {unexpected_domain, ExpDomain, Domain}}; @@ -3177,6 +3238,7 @@ api_b_open_and_close(InitState) -> end}, #{desc => "validate type", cmd => fun({#{type := Type} = State, {ok, Type}}) -> + ?SEV_IPRINT("expected type: ~p", [Type]), {ok, State}; ({#{type := ExpType}, {ok, Type}}) -> {error, {unexpected_type, ExpType, Type}}; @@ -3190,14 +3252,15 @@ api_b_open_and_close(InitState) -> end}, #{desc => "validate protocol", cmd => fun({#{protocol := Protocol} = State, {ok, Protocol}}) -> + ?SEV_IPRINT("expected protocol: ~p", [Protocol]), {ok, State}; ({#{domain := Domain, protocol := ExpProtocol}, {ok, Protocol}}) -> %% On OpenBSD (at least 6.6) something screwy happens %% when domain = local. - %% It will report a completely different protocol (icmp) - %% but everything still works. So we skip if this happens - %% on OpenBSD... + %% It will report a completely different protocol + %% (icmp) but everything still works. + %% So we skip if this happens on OpenBSD... case os:type() of {unix, openbsd} when (Domain =:= local) -> {skip, ?F("Unexpected protocol: ~p instead of ~p", @@ -3710,7 +3773,8 @@ api_b_sendmsg_and_recvmsg_tcp4(_Config) when is_list(_Config) -> end, fun() -> Send = fun(Sock, Data) -> - Msg = #{iov => [Data]}, + Msg = #{%% ctrl => CMsgs, + iov => [Data]}, socket:sendmsg(Sock, Msg) end, Recv = fun(Sock) -> @@ -4807,14 +4871,15 @@ api_b_sendv(InitState) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% Basically send and receive on an IPv4 SCTP (seqpacket) socket +%% Basically send and receive on an IPv4 SCTP (stream) socket %% using sendmsg and recvmsg. -api_b_sendmsg_and_recvmsg_sctp4(_Config) when is_list(_Config) -> +api_b_sendmsg_and_recvmsg_stream_sctp4(_Config) when is_list(_Config) -> ?TT(?SECS(5)), - tc_try(api_b_sendmsg_and_recvmsg_sctp4, + tc_try(?FUNCTION_NAME, fun() -> has_support_sctp(), - not_yet_implemented() + has_support_ipv4()%% , + %% not_yet_implemented() end, fun() -> Send = fun(Sock, Data) -> @@ -4823,26 +4888,31 @@ api_b_sendmsg_and_recvmsg_sctp4(_Config) when is_list(_Config) -> %% data => reliability}, %% CMsgs = [CMsg], Msg = #{%% ctrl => CMsgs, - iov => [Data]}, + iov => [Data]}, socket:sendmsg(Sock, Msg) end, Recv = fun(Sock) -> - %% We have some issues on old darwing... - %% socket:setopt(Sock, otp, debug, true), case socket:recvmsg(Sock) of - {ok, #{addr := Source, + {ok, #{flags := [eor], + addr := _, iov := [Data]}} -> - %% socket:setopt(Sock, otp, debug, false), - {ok, {Source, Data}}; + {ok, Data}; + {ok, Msg} -> + {error, {msg, Msg}}; + %% {ok, #{addr := Source, + %% iov := [Data]}} -> + %% {ok, {Source, Data}}; {error, _} = ERROR -> ERROR end end, InitState = #{domain => inet, + type => stream, proto => sctp, send => Send, recv => Recv}, - ok = api_b_send_and_recv_sctp(InitState) + %% ok = api_b_send_and_recv_sctp(InitState) + ok = api_b_send_and_recv_conn(InitState) end). @@ -5338,6 +5408,7 @@ api_b_send_and_recv_sctp(_InitState) -> ok. + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% %% From 4b9c193648980560309dc310a9fef616e608f4eb Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Thu, 23 May 2024 07:31:45 +0200 Subject: [PATCH 049/422] [esock|test|sctp] Add another (stream) SCTP test case --- lib/kernel/test/socket_SUITE.erl | 29 +++++++++++++++++++++++++++++ 1 file changed, 29 insertions(+) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 85d4052c2250..c7e200fb6b91 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -134,6 +134,7 @@ api_b_sendmsg_and_recvmsg_udp4/1, api_b_sendmsg_and_recvmsg_udpL/1, api_b_send_and_recv_tcp4/1, + api_b_send_and_recv_stream_sctp4/1, api_b_sendv_and_recv_tcp4/1, api_b_send_and_recv_tcpL/1, api_b_send_and_recv_seqpL/1, @@ -1021,6 +1022,7 @@ api_basic_cases() -> api_b_sendmsg_and_recvmsg_udp4, api_b_sendmsg_and_recvmsg_udpL, api_b_send_and_recv_tcp4, + api_b_send_and_recv_stream_sctp4, api_b_sendv_and_recv_tcp4, api_b_send_and_recv_tcpL, api_b_send_and_recv_seqpL, @@ -3680,6 +3682,33 @@ api_b_send_and_recv_tcp4(_Config) when is_list(_Config) -> end). +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% Basically send and receive using the "common" functions (send and recv) +%% on an IPv4 SCTP (stream) socket. +api_b_send_and_recv_stream_sctp4(_Config) when is_list(_Config) -> + ?TT(?SECS(10)), + tc_try(?FUNCTION_NAME, + fun() -> + has_support_sctp(), + has_support_ipv4() + end, + fun() -> + Send = fun(Sock, Data) -> + socket:send(Sock, Data) + end, + Recv = fun(Sock) -> + socket:recv(Sock) + end, + InitState = #{domain => inet, + type => stream, + proto => sctp, + send => Send, + recv => Recv}, + ok = api_b_send_and_recv_conn(InitState) + end). + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Basically send and receive using the sendv and recv functions From 0ba653028a0aa27c693600c4dadfba349cb7f7d3 Mon Sep 17 00:00:00 2001 From: Ingela Anderton Andin Date: Tue, 21 May 2024 11:14:54 +0200 Subject: [PATCH 050/422] ssl: Enhance ALERT logs to help understand what causes the alert. --- lib/ssl/src/ssl_handshake.erl | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 0f9039a9f4ac..428e71d9b682 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -2157,25 +2157,24 @@ maybe_check_hostname(_, valid, _, _) -> path_validation_alert({bad_cert, cert_expired}) -> ?ALERT_REC(?FATAL, ?CERTIFICATE_EXPIRED); path_validation_alert({bad_cert, invalid_issuer}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, invalid_issuer); path_validation_alert({bad_cert, invalid_signature}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, invalid_signature); path_validation_alert({bad_cert, name_not_permitted}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, name_not_permitted); path_validation_alert({bad_cert, unknown_critical_extension}) -> - ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE); + ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE, unknown_critical_extension); path_validation_alert({bad_cert, {revoked, _}}) -> ?ALERT_REC(?FATAL, ?CERTIFICATE_REVOKED); path_validation_alert({bad_cert, {revocation_status_undetermined, Details}}) -> ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, Details); path_validation_alert({bad_cert, selfsigned_peer}) -> - ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE); + ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE, selfsigned_peer); path_validation_alert({bad_cert, unknown_ca}) -> ?ALERT_REC(?FATAL, ?UNKNOWN_CA); path_validation_alert(Reason) -> ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason). - digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) -> try do_digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) catch From fb0573999ad3343990715f1d3f633ea0d7dfd926 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Thu, 23 May 2024 10:23:30 +0200 Subject: [PATCH 051/422] [esock|test|sctp] Add another (stream) SCTP test case Add a API async test case --- lib/kernel/test/socket_SUITE.erl | 104 ++++++++++++++++++++++--------- 1 file changed, 74 insertions(+), 30 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index c7e200fb6b91..05d023409170 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -189,6 +189,7 @@ api_a_sendmsg_and_recvmsg_udp6/1, api_a_send_and_recv_tcp4/1, api_a_send_and_recv_tcp6/1, + api_a_send_and_recv_sctp4/1, api_a_sendmsg_and_recvmsg_tcp4/1, api_a_sendmsg_and_recvmsg_tcp6/1, api_a_recvfrom_cancel_udp4/1, @@ -1082,6 +1083,7 @@ api_async_cases() -> api_a_sendmsg_and_recvmsg_udp6, api_a_send_and_recv_tcp4, api_a_send_and_recv_tcp6, + api_a_send_and_recv_sctp4, api_a_sendmsg_and_recvmsg_tcp4, api_a_sendmsg_and_recvmsg_tcp6, api_a_recvfrom_cancel_udp4, @@ -4948,7 +4950,7 @@ api_b_sendmsg_and_recvmsg_stream_sctp4(_Config) when is_list(_Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -api_b_send_and_recv_sctp(_InitState) -> +%% api_b_send_and_recv_sctp(_InitState) -> %% Seq = %% [ %% #{desc => "local address", @@ -5435,7 +5437,7 @@ api_b_send_and_recv_sctp(_InitState) -> %% ok = ?SEV_AWAIT_FINISH([Server, Client, Tester]). - ok. +%% ok. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -9170,7 +9172,7 @@ api_a_send_and_recv_udp(InitState) -> api_a_send_and_recv_tcp4(Config) when is_list(Config) -> ?TT(?SECS(10)), Nowait = nowait(Config), - tc_try(api_a_send_and_recv_tcp4, + tc_try(?FUNCTION_NAME, fun() -> has_support_ipv4() end, fun() -> Send = fun(Sock, Data) -> @@ -9179,11 +9181,12 @@ api_a_send_and_recv_tcp4(Config) when is_list(Config) -> Recv = fun(Sock) -> socket:recv(Sock, 0, Nowait) end, - InitState = #{domain => inet, - send => Send, - recv => Recv, + InitState = #{domain => inet, + proto => tcp, + send => Send, + recv => Recv, recv_sref => Nowait}, - ok = api_a_send_and_recv_tcp(Config, InitState) + ok = api_a_send_and_recv_stream(Config, InitState) end). @@ -9199,7 +9202,7 @@ api_a_send_and_recv_tcp4(Config) when is_list(Config) -> api_a_send_and_recv_tcp6(Config) when is_list(Config) -> ?TT(?SECS(10)), Nowait = nowait(Config), - tc_try(api_a_send_and_recv_tcp6, + tc_try(?FUNCTION_NAME, fun() -> has_support_ipv6() end, fun() -> Send = fun(Sock, Data) -> @@ -9208,11 +9211,45 @@ api_a_send_and_recv_tcp6(Config) when is_list(Config) -> Recv = fun(Sock) -> socket:recv(Sock, 0, Nowait) end, - InitState = #{domain => inet6, - send => Send, - recv => Recv, + InitState = #{domain => inet6, + proto => tcp, + send => Send, + recv => Recv, recv_sref => Nowait}, - ok = api_a_send_and_recv_tcp(Config, InitState) + ok = api_a_send_and_recv_stream(Config, InitState) + end). + + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% Basically send and receive using the "common" functions (send and recv) +%% on an IPv4 SCTP (stream) socket. But we try to be async. That is, we use +%% the 'nowait' value for the Timeout argument (and await the eventual +%% select message). Note that we only do this for the recv, +%% since its much more difficult to "arrange" for send. +%% We *also* test async for accept. +api_a_send_and_recv_sctp4(Config) when is_list(Config) -> + ?TT(?SECS(10)), + Nowait = nowait(Config), + tc_try(?FUNCTION_NAME, + fun() -> + has_support_sctp(), + has_support_ipv4() + end, + fun() -> + Send = fun(Sock, Data) -> + socket:send(Sock, Data) + end, + Recv = fun(Sock) -> + socket:recv(Sock, 0, Nowait) + end, + InitState = #{domain => inet, + proto => sctp, + send => Send, + recv => Recv, + recv_sref => Nowait}, + ok = api_a_send_and_recv_stream(Config, InitState) end). @@ -9228,7 +9265,7 @@ api_a_send_and_recv_tcp6(Config) when is_list(Config) -> api_a_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) -> ?TT(?SECS(10)), Nowait = nowait(Config), - tc_try(api_a_sendmsg_and_recvmsg_tcp4, + tc_try(?FUNCTION_NAME, fun() -> is_not_windows(), has_support_ipv4() @@ -9240,7 +9277,7 @@ api_a_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) -> end, Recv = fun(Sock) -> case socket:recvmsg(Sock, Nowait) of - {ok, #{iov := [Data]}} -> + {ok, #{iov := [Data]}} -> {ok, Data}; {select, _} = SELECT -> SELECT; @@ -9248,11 +9285,12 @@ api_a_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) -> ERROR end end, - InitState = #{domain => inet, - send => Send, - recv => Recv, + InitState = #{domain => inet, + proto => tcp, + send => Send, + recv => Recv, recv_sref => Nowait}, - ok = api_a_send_and_recv_tcp(Config, InitState) + ok = api_a_send_and_recv_stream(Config, InitState) end). @@ -9268,7 +9306,7 @@ api_a_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) -> api_a_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) -> ?TT(?SECS(10)), Nowait = nowait(Config), - tc_try(api_a_sendmsg_and_recvmsg_tcp6, + tc_try(?FUNCTION_NAME, fun() -> has_support_ipv6() end, fun() -> Send = fun(Sock, Data) -> @@ -9277,7 +9315,7 @@ api_a_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) -> end, Recv = fun(Sock) -> case socket:recvmsg(Sock, Nowait) of - {ok, #{iov := [Data]}} -> + {ok, #{iov := [Data]}} -> {ok, Data}; {select, _} = SELECT -> SELECT; @@ -9285,18 +9323,19 @@ api_a_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) -> ERROR end end, - InitState = #{domain => inet6, - send => Send, - recv => Recv, + InitState = #{domain => inet6, + proto => tcp, + send => Send, + recv => Recv, recv_sref => Nowait}, - ok = api_a_send_and_recv_tcp(Config, InitState) + ok = api_a_send_and_recv_stream(Config, InitState) end). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -api_a_send_and_recv_tcp(Config, InitState) -> +api_a_send_and_recv_stream(Config, InitState) -> process_flag(trap_exit, true), ServerSeq = [ @@ -9319,8 +9358,10 @@ api_a_send_and_recv_tcp(Config, InitState) -> {ok, State#{lsa => LSA}} end}, #{desc => "create listen socket", - cmd => fun(#{domain := Domain} = State) -> - case socket:open(Domain, stream, tcp) of + cmd => fun(#{domain := Domain, proto := Proto} = State) -> + ?SEV_IPRINT("try create (open) ~w (~w) socket", + [Proto, Domain]), + case socket:open(Domain, stream, Proto) of {ok, Sock} -> {ok, State#{lsock => Sock}}; {error, _} = ERROR -> @@ -9598,8 +9639,10 @@ api_a_send_and_recv_tcp(Config, InitState) -> {ok, State#{local_sa => LSA, server_sa => SSA}} end}, #{desc => "create socket", - cmd => fun(#{domain := Domain} = State) -> - case socket:open(Domain, stream, tcp) of + cmd => fun(#{domain := Domain, proto := Proto} = State) -> + ?SEV_IPRINT("try create (open) ~w (~w) socket", + [Proto, Domain]), + case socket:open(Domain, stream, Proto) of {ok, Sock} -> {ok, State#{sock => Sock}}; {error, _} = ERROR -> @@ -13074,6 +13117,7 @@ api_opt_simple_otp_options() -> i("await udp evaluator"), ok = ?SEV_AWAIT_FINISH([Tester2]). + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Perform some simple getopt and setopt otp meta option @@ -13199,7 +13243,7 @@ api_opt_simple_otp_meta_option() -> cmd => fun(#{main := Main}) -> _ = erlang:monitor(process, Main), ok - end} + end}, #{desc => "get value", cmd => fun(#{sock := Sock, value := Value}) -> From 90f84cefdf413b8dda8febde9ad71ff8ff0a4c8f Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Thu, 23 May 2024 10:26:30 +0200 Subject: [PATCH 052/422] [esock|test|sctp] Add another (stream) SCTP test case Add a PRELLIMINARY IPv6 API async test case --- lib/kernel/test/socket_SUITE.erl | 35 ++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 05d023409170..6407fa63f3d2 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -190,6 +190,7 @@ api_a_send_and_recv_tcp4/1, api_a_send_and_recv_tcp6/1, api_a_send_and_recv_sctp4/1, + api_a_send_and_recv_sctp6/1, api_a_sendmsg_and_recvmsg_tcp4/1, api_a_sendmsg_and_recvmsg_tcp6/1, api_a_recvfrom_cancel_udp4/1, @@ -1084,6 +1085,7 @@ api_async_cases() -> api_a_send_and_recv_tcp4, api_a_send_and_recv_tcp6, api_a_send_and_recv_sctp4, + api_a_send_and_recv_sctp6, api_a_sendmsg_and_recvmsg_tcp4, api_a_sendmsg_and_recvmsg_tcp6, api_a_recvfrom_cancel_udp4, @@ -9254,6 +9256,39 @@ api_a_send_and_recv_sctp4(Config) when is_list(Config) -> +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% Basically send and receive using the "common" functions (send and recv) +%% on an IPv4 SCTP (stream) socket. But we try to be async. That is, we use +%% the 'nowait' value for the Timeout argument (and await the eventual +%% select message). Note that we only do this for the recv, +%% since its much more difficult to "arrange" for send. +%% We *also* test async for accept. +api_a_send_and_recv_sctp6(Config) when is_list(Config) -> + ?TT(?SECS(10)), + Nowait = nowait(Config), + tc_try(?FUNCTION_NAME, + fun() -> + has_support_sctp(), + has_support_ipv6() + end, + fun() -> + Send = fun(Sock, Data) -> + socket:send(Sock, Data) + end, + Recv = fun(Sock) -> + socket:recv(Sock, 0, Nowait) + end, + InitState = #{domain => inet6, + proto => sctp, + send => Send, + recv => Recv, + recv_sref => Nowait}, + ok = api_a_send_and_recv_stream(Config, InitState) + end). + + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Basically send and receive using the msg functions (sendmsg and recvmsg) From 07f80c62c12750d03b1f3bb2c651965d55e4968e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?D=C3=A1niel=20Szoboszlay?= Date: Wed, 22 May 2024 22:43:38 +0200 Subject: [PATCH 053/422] Fix assertion in prim_tty The reader updates the Unicode state right before checking the input's encoding, but the assertion that encoding errors are only possible when using utf8 was done against the original state. --- lib/kernel/src/prim_tty.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl index 0fe13b84b8cb..5267822bd9bb 100644 --- a/lib/kernel/src/prim_tty.erl +++ b/lib/kernel/src/prim_tty.erl @@ -544,7 +544,7 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) -> {error, B, Error} -> %% We should only be able to get incorrect encoded data when %% using utf8 - FromEnc = utf8, + UpdatedFromEnc = utf8, Parent ! {self(), set_unicode_state, false}, receive {set_unicode_state, false} -> From 79d9d1ffc44fd00799f33945f8d8b94b4be31449 Mon Sep 17 00:00:00 2001 From: Lukas Larsson Date: Fri, 24 May 2024 08:26:23 +0200 Subject: [PATCH 054/422] Automatically update copyright year in docs --- make/ex_doc.exs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/make/ex_doc.exs b/make/ex_doc.exs index 8a480941d35f..d73c6a5efe6e 100644 --- a/make/ex_doc.exs +++ b/make/ex_doc.exs @@ -146,6 +146,8 @@ extras = annotations = Access.get(local_config, :annotations_for_docs, fn _ -> [] end) +current_datetime = System.os_time() |> DateTime.from_unix!(:native) + config = [ proglang: :erlang, source_url_pattern: source_url_pattern, @@ -153,7 +155,7 @@ config = [ logo: Path.join(:code.root_dir(), "system/doc/assets/erlang-logo.png"), before_closing_head_tag: fn _ -> "" end, before_closing_footer_tag: fn _ -> - ~S'

Copyright © 1996-2023 Ericsson AB

' + ~s'

Copyright © 1996-#{current_datetime.year} Ericsson AB

' end, annotations_for_docs: fn md -> if Map.has_key?(md, :exported) && not md.exported do From e0346098120ad35f42753b91d8e089932c153a27 Mon Sep 17 00:00:00 2001 From: Lukas Larsson Date: Fri, 24 May 2024 08:26:44 +0200 Subject: [PATCH 055/422] Updated ex_doc version to v0.33.0 --- make/ex_doc.sha1sum | 2 +- make/ex_doc.sha256sum | 2 +- make/ex_doc_link | 2 +- make/ex_doc_vsn | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/make/ex_doc.sha1sum b/make/ex_doc.sha1sum index ccc6c7397246..6baca94e8497 100644 --- a/make/ex_doc.sha1sum +++ b/make/ex_doc.sha1sum @@ -1 +1 @@ -6b589e856c359b1706bf3348bbd99fbba339ccee ../bin/ex_doc +880948d1508989e3a7f25a4b1520bf1adc642661 ../bin/ex_doc diff --git a/make/ex_doc.sha256sum b/make/ex_doc.sha256sum index 4cae93f2459b..7be185412dab 100644 --- a/make/ex_doc.sha256sum +++ b/make/ex_doc.sha256sum @@ -1 +1 @@ -1f2b549c62b856a0769b9dc9b3f4e904d5865987e510491c2234f9ea48066340 ../bin/ex_doc +e2e867f6207453c34f91c322fd92a26d1b1c41fe50a54be7e8cf9a71fb1ecd4c ../bin/ex_doc diff --git a/make/ex_doc_link b/make/ex_doc_link index 44aaa04b7eb3..6c154c9facf1 100644 --- a/make/ex_doc_link +++ b/make/ex_doc_link @@ -1 +1 @@ -https://github.com/elixir-lang/ex_doc/releases/download/v0.32.2/ex_doc_otp_26 +https://github.com/elixir-lang/ex_doc/releases/download/v0.33.0/ex_doc_otp_26 diff --git a/make/ex_doc_vsn b/make/ex_doc_vsn index c6a2605c482f..7fdbfd64bbdc 100644 --- a/make/ex_doc_vsn +++ b/make/ex_doc_vsn @@ -1 +1 @@ -v0.32.2 +v0.33.0 From 361565eaeccf59d2da42958debd3c392106a11ec Mon Sep 17 00:00:00 2001 From: Lukas Larsson Date: Fri, 24 May 2024 08:39:56 +0200 Subject: [PATCH 056/422] gh: Fix build-base-image when BASE_BRANCH does not exist --- .github/scripts/build-base-image.sh | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/.github/scripts/build-base-image.sh b/.github/scripts/build-base-image.sh index f4b05e1216ed..f432705b47fb 100755 --- a/.github/scripts/build-base-image.sh +++ b/.github/scripts/build-base-image.sh @@ -47,9 +47,10 @@ elif [ -f "otp_docker_base/otp_docker_base.tar" ]; then echo "BASE_BUILD=loaded" >> $GITHUB_OUTPUT else if [ "${BASE_USE_CACHE}" != "false" ]; then - docker pull "${BASE_TAG}:${BASE_BRANCH}" - docker tag "${BASE_TAG}:${BASE_BRANCH}" "${BASE_TAG}:latest" - BASE_CACHE="--cache-from ${BASE_TAG}" + if docker pull "${BASE_TAG}:${BASE_BRANCH}"; then + docker tag "${BASE_TAG}:${BASE_BRANCH}" "${BASE_TAG}:latest" + BASE_CACHE="--cache-from ${BASE_TAG}" + fi fi BASE_IMAGE_ID=$(docker images -q "${BASE_TAG}:latest") From 2a2d72d56f76308b0490058654ec53b1ab2071a9 Mon Sep 17 00:00:00 2001 From: Lukas Larsson Date: Fri, 24 May 2024 08:41:03 +0200 Subject: [PATCH 057/422] gh: Bump base updater to build maint-27 base branch --- .github/workflows/update-base.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.github/workflows/update-base.yaml b/.github/workflows/update-base.yaml index d7f305692396..dc97a42d8760 100644 --- a/.github/workflows/update-base.yaml +++ b/.github/workflows/update-base.yaml @@ -22,7 +22,7 @@ jobs: strategy: matrix: type: [debian-base,ubuntu-base,i386-debian-base] - branch: [master, maint, maint-26] + branch: [master, maint, maint-26, maint-27] fail-fast: false steps: From 55c88a95835df941b7dead1df57eaeaada4cccca Mon Sep 17 00:00:00 2001 From: Lukas Larsson Date: Fri, 24 May 2024 09:02:38 +0200 Subject: [PATCH 058/422] re: Fix spelling in documentation --- lib/stdlib/doc/src/re.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/stdlib/doc/src/re.md b/lib/stdlib/doc/src/re.md index fec3e1475b86..e8ecdc9d7e58 100644 --- a/lib/stdlib/doc/src/re.md +++ b/lib/stdlib/doc/src/re.md @@ -17,7 +17,7 @@ included here. > your code and in the shell, with an extra backslash, that is, `"\\\\"` or > `<<"\\\\">>`. > -> Since Erlang/OTP 27 you can use [verbaim sigils](`e:system:data_types.md#sigil`) +> Since Erlang/OTP 27 you can use [verbatim sigils](`e:system:data_types.md#sigil`) > to write literal strings. The example above would be written as `~S"\"` or `~B"\"`. ## Perl-Like Regular Expression Syntax From d8d7b9c4fbf54e6e337dc3ce4eeec4a20d941dfe Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 21 May 2024 12:29:58 +0200 Subject: [PATCH 059/422] Add class annotation to HTML from fenced blocks This can be used, for example, to discard Mermaid diagrams when printing documentation in the shell. --- lib/stdlib/src/shell_docs_markdown.erl | 40 ++++++++------- lib/stdlib/test/shell_docs_markdown_SUITE.erl | 50 +++++++++++++++---- 2 files changed, 62 insertions(+), 28 deletions(-) diff --git a/lib/stdlib/src/shell_docs_markdown.erl b/lib/stdlib/src/shell_docs_markdown.erl index c0307f3e9a1b..e9b3a9545294 100644 --- a/lib/stdlib/src/shell_docs_markdown.erl +++ b/lib/stdlib/src/shell_docs_markdown.erl @@ -73,12 +73,12 @@ format_line(Ls) -> OmissionSet :: sets:set(atom()). format_line([], _BlockSet0) -> []; -format_line([{Tag, [], List} | Rest], BlockSet0) -> +format_line([{Tag, Attrs, List} | Rest], BlockSet0) -> case format_line(List, sets:add_element(Tag, BlockSet0)) of [] -> format_line(Rest, BlockSet0); Ls -> - [{Tag, [], Ls}] ++ format_line(Rest, BlockSet0) + [{Tag, Attrs, Ls}] ++ format_line(Rest, BlockSet0) end; format_line([Bin | Rest], BlockSet0) when is_binary(Bin) -> %% Ignores formatting these elements @@ -365,8 +365,8 @@ process_kind_block([<<">", _/binary>>=Line | Rest], Block) -> %% %% process block code %% -process_kind_block([<<"```", _Line/binary>> | Rest], Block) -> - Block ++ process_fence_code(Rest, []); +process_kind_block([<<"```", Line/binary>> | Rest], Block) -> + Block ++ process_fence_code(Rest, [], Line); %% %% New line %% @@ -459,8 +459,9 @@ strip_spaces(Rest, Acc, _) -> ol | li | dl | dt | dd | h1 | h2 | h3 | h4 | h5 | h6. -type chunk_element_attrs() :: []. --type quote() :: {blockquote,[], shell_docs:chunk_elements()}. --type code() :: {pre, chunk_element_attrs(), [{code,[], shell_docs:chunk_elements()}]}. +-type code_element_attrs() :: [{class,unicode:chardata()}]. +-type quote() :: {blockquote, chunk_element_attrs(), shell_docs:chunk_elements()}. +-type code() :: {pre, chunk_element_attrs(), [{code, code_element_attrs(), shell_docs:chunk_elements()}]}. -type p() :: {p, chunk_element_attrs(), shell_docs:chunk_elements()}. -type i() :: {i, chunk_element_attrs(), shell_docs:chunk_elements()}. -type em() :: {em, chunk_element_attrs(), shell_docs:chunk_elements()}. @@ -803,27 +804,30 @@ format(Format, Line0) when is_list(Line0)-> PrevLines :: [binary()], %% Represent unprocessed lines. HtmlErlang :: shell_docs:chunk_elements(). process_code([], Block) -> - [create_code(Block)]; + [create_code(Block, [])]; process_code([<<" ", Line/binary>> | Rest], Block) -> %% process blank line followed by code process_code(Rest, [Line | Block]); process_code(Rest, Block) -> process_code([], Block) ++ parse_md(Rest, []). -process_fence_code([], Block) -> - [create_code(Block)]; -process_fence_code([<<"```">> | Rest], Block) -> +process_fence_code([], Block, Leading) -> + case string:trim(hd(binary:split(Leading, [~"\t", ~" "]))) of + <<>> -> [create_code(Block, [])]; + Trimmed -> [create_code(Block, [{class, <<"language-", Trimmed/binary>>}])] + end; +process_fence_code([<<"```">> | Rest], Block, Leading) -> %% close block - process_fence_code([], Block) ++ parse_md(Rest, []); -process_fence_code([Line | Rest], Block) -> + process_fence_code([], Block, Leading) ++ parse_md(Rest, []); +process_fence_code([Line | Rest], Block, Leading) -> {Stripped, _} = strip_spaces(Line, 0, infinity), maybe <<"```", RestLine/binary>> ?= Stripped, {<<>>, _} ?= strip_spaces(RestLine, 0, infinity), - process_fence_code([<<"```">> | Rest], Block) + process_fence_code([<<"```">> | Rest], Block, Leading) else _ -> - process_fence_code(Rest, [Line | Block]) + process_fence_code(Rest, [Line | Block], Leading) end. -spec process_comment(Line :: [binary()]) -> [binary()]. @@ -853,14 +857,14 @@ create_paragraph(<<$\s, Line/binary>>) -> create_paragraph(Line) when is_binary(Line) -> p(Line). --spec create_code(Lines :: [binary()]) -> code(). -create_code(CodeBlocks) when is_list(CodeBlocks) -> +-spec create_code(Lines :: [binary()], code_element_attrs()) -> code(). +create_code(CodeBlocks, CodeAttrs) when is_list(CodeBlocks) -> %% assumes that the code block is in reverse order Bin = trim_and_add_new_line(CodeBlocks), - {pre,[], [{code,[], [Bin]}]}. + {pre, [], [{code, CodeAttrs, [Bin]}]}. create_table(Table) when is_list(Table) -> - {pre,[], [{code,[], Table}]}. + {pre, [], [{code, [{class, ~"table"}], Table}]}. -spec quote(Quote :: list()) -> quote(). diff --git a/lib/stdlib/test/shell_docs_markdown_SUITE.erl b/lib/stdlib/test/shell_docs_markdown_SUITE.erl index 116c4ba6ccc0..def3d0b56a1e 100644 --- a/lib/stdlib/test/shell_docs_markdown_SUITE.erl +++ b/lib/stdlib/test/shell_docs_markdown_SUITE.erl @@ -48,8 +48,9 @@ %% fence code -export([single_line_fence_code_test/1, multiple_line_fence_code_test/1, + single_line_fence_code_no_language_test/1, single_line_fence_code_no_language_spaces_test/1, paragraph_between_fence_code_test/1, fence_code_ignores_link_format_test/1, - fence_code_with_spaces/1]). + fence_code_with_spaces/1, fence_code_with_tabs/1]). %% br -export([start_with_br_test/1, multiple_br_followed_by_paragraph_test/1, @@ -188,9 +189,11 @@ code_tests() -> fence_code_tests() -> [single_line_fence_code_test, multiple_line_fence_code_test, + single_line_fence_code_no_language_test, + single_line_fence_code_no_language_spaces_test, paragraph_between_fence_code_test, fence_code_ignores_link_format_test, - fence_code_with_spaces + fence_code_with_spaces, fence_code_with_tabs ]. br_tests() -> @@ -492,7 +495,7 @@ single_line_fence_code_test(_Conf) -> ```erlang test() -> ok. ```", - Result = [ code(~"test() -> ok.\n")], + Result = [ code(~"test() -> ok.\n", [{class, ~"language-erlang"}])], compile_and_compare(Input, Result). multiple_line_fence_code_test(_Conf) -> @@ -501,9 +504,24 @@ multiple_line_fence_code_test(_Conf) -> test() -> ok. ```", - Result = [ code(~"test() ->\n ok.\n")], + Result = [ code(~"test() ->\n ok.\n", [{class, ~"language-erlang"}])], compile_and_compare(Input, Result). +single_line_fence_code_no_language_test(_Conf) -> + Input = ~" +``` +test() -> ok. +```", + Result = [ code(~"test() -> ok.\n")], + compile_and_compare(Input, Result). + +single_line_fence_code_no_language_spaces_test(_Conf) -> + Input = ~" +```\s\s +test() -> ok. +```", + Result = [ code(~"test() -> ok.\n")], + compile_and_compare(Input, Result). paragraph_between_fence_code_test(_Conf) -> Input = ~"This is a test: @@ -512,7 +530,7 @@ test() -> ok. ```", Result = [p(~"This is a test:"), - code(~"test() ->\n ok.\n")], + code(~"test() ->\n ok.\n", [{class, ~"language-erlang"}])], compile_and_compare(Input, Result). fence_code_ignores_link_format_test(_Conf) -> @@ -521,15 +539,23 @@ fence_code_ignores_link_format_test(_Conf) -> [foo](bar) ```", Result = [p(~"This is a test:"), - code(~"[foo](bar)\n")], + code(~"[foo](bar)\n", [{class, ~"language-erlang"}])], compile_and_compare(Input, Result). fence_code_with_spaces(_Config) -> Input = -~" ```erlang +~" ```erlang\s\s + [foo](bar) +```", + Result = [code(~" [foo](bar)\n", [{class, ~"language-erlang"}])], + compile_and_compare(Input, Result). + +fence_code_with_tabs(_Config) -> + Input = +~" ```erlang\ttrailing [foo](bar) ```", - Result = [code(~" [foo](bar)\n")], + Result = [code(~" [foo](bar)\n", [{class, ~"language-erlang"}])], compile_and_compare(Input, Result). start_with_br_test(_Conf) -> @@ -1019,10 +1045,14 @@ header(Level, Text) when is_integer(Level) -> {HeadingLevelAtom, [], [Text]}. code(X) -> - {pre,[],[inline_code(X)]}. + code(X, []). +code(X, Attrs) when is_list(X) -> + {pre,[],[{code,Attrs,X}]}; +code(X, Attrs) -> + {pre,[],[{code,Attrs,[X]}]}. table(Table) when is_list(Table) -> - {pre,[], [inline_code(Table)]}. + {pre,[], [{code, [{class, ~"table"}], Table}]}. inline_code(X) when is_list(X) -> {code,[],X}; From 5de1dc369f30c7a52b3963aa52967d137aae2d4d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 24 May 2024 10:46:15 +0200 Subject: [PATCH 060/422] [diameter|test|app] Calculating timeouts --- lib/diameter/test/diameter_app_SUITE.erl | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 896dca711947..0cdf42ebf62c 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -74,7 +74,7 @@ %% =========================================================================== suite() -> - [{timetrap, {seconds, 20}}]. + [{timetrap, {seconds, 120}}]. all() -> [keys, @@ -108,10 +108,21 @@ run(List) -> end. run(Config, List) -> + Timeout = factor2timeout(Config, 10000), [{application, diameter, App}] = ?CONSULT(diameter, app), - ?RUN([{{?MODULE, F, [{App, Config}]}, 10000} || F <- List]). + ?RUN([{{?MODULE, F, [{App, Config}]}, Timeout} || F <- List]). +factor2timeout(Config, BaseTime) -> + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 0) -> + BaseTime + (((Factor-1)*BaseTime) div 10); + _ -> + BaseTime + end. + + %% =========================================================================== %% # keys/1 %% From 40857b07dfe17e68a913b2f78904550572e301ae Mon Sep 17 00:00:00 2001 From: Ingela Anderton Andin Date: Fri, 24 May 2024 10:44:15 +0200 Subject: [PATCH 061/422] public_key: Correct match_name function for dnsNames closes #8482 --- lib/public_key/src/pubkey_cert.erl | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) diff --git a/lib/public_key/src/pubkey_cert.erl b/lib/public_key/src/pubkey_cert.erl index 4a91335e0c73..c8b001eea005 100644 --- a/lib/public_key/src/pubkey_cert.erl +++ b/lib/public_key/src/pubkey_cert.erl @@ -517,10 +517,21 @@ match_name(emailAddress, Name, [PermittedName | Rest]) -> match_name(dNSName, Name, [PermittedName | Rest]) -> Fun = fun(Domain, [$.|Domain]) -> true; - (Name1,Name2) -> - is_suffix(Name2, Name1) + (Name1, [$. | _] = Name2) -> + is_suffix(Name2, Name1); + (Name1, Name2) -> + StrLen1 = string:len(Name1), + StrLen2 = string:len(Name2), + case StrLen1 > StrLen2 of + true -> + is_suffix([$. | Name2], Name1); + false when StrLen1 == StrLen2 -> + string:casefold(Name1) == string:casefold(Name2); + false -> + false + end end, - match_name(Fun, Name, [$.|PermittedName], Rest); + match_name(Fun, Name, PermittedName, Rest); match_name(x400Address, OrAddress, [PermittedAddr | Rest]) -> match_name(fun is_or_address/2, OrAddress, PermittedAddr, Rest); From add67e972f9e9ec0567c7ae980a7fae319ef1e1a Mon Sep 17 00:00:00 2001 From: Louis Pilfold Date: Thu, 23 May 2024 18:38:57 +0100 Subject: [PATCH 062/422] Correct typo in docs: invalid_sequence -> unexpected_sequence --- lib/stdlib/src/json.erl | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/stdlib/src/json.erl b/lib/stdlib/src/json.erl index 34d39fa12833..4caf8210e4ba 100644 --- a/lib/stdlib/src/json.erl +++ b/lib/stdlib/src/json.erl @@ -608,7 +608,7 @@ Supports basic data mapping: * `error(unexpected_end)` if `Binary` contains incomplete JSON value * `error({invalid_byte, Byte})` if `Binary` contains unexpected byte or invalid UTF-8 byte -* `error({invalid_sequence, Bytes})` if `Binary` contains invalid UTF-8 escape +* `error({unexpected_sequence, Bytes})` if `Binary` contains invalid UTF-8 escape ## Example @@ -662,7 +662,7 @@ implementations used by the `decode/1` function: ## Errors * `error({invalid_byte, Byte})` if `Binary` contains unexpected byte or invalid UTF-8 byte -* `error({invalid_sequence, Bytes})` if `Binary` contains invalid UTF-8 escape +* `error({unexpected_sequence, Bytes})` if `Binary` contains invalid UTF-8 escape * `error(unexpected_end)` if `Binary` contains incomplete JSON value ## Example From a93eefd8f8321cbc9d4249c446048fe0a497df84 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 24 May 2024 14:38:51 +0200 Subject: [PATCH 063/422] [esock|test|sctp] Add another sctp test case Add another sctp test case and tweak the test case to handle skip cases (detect eprotonosupport). --- lib/kernel/test/socket_SUITE.erl | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl index 6407fa63f3d2..b80f999f68ed 100644 --- a/lib/kernel/test/socket_SUITE.erl +++ b/lib/kernel/test/socket_SUITE.erl @@ -4025,15 +4025,12 @@ api_b_send_and_recv_conn(InitState) -> end}, #{desc => "await connection", cmd => fun(#{lsock := LSock} = State) -> - %% _ = socket:setopt(LSock, otp, debug, true), ?SEV_IPRINT("try accept"), case socket:accept(LSock) of {ok, Sock} -> - %% _ = socket:setopt(LSock, otp, debug, false), ?SEV_IPRINT("accepted: ~n ~p", [Sock]), {ok, State#{csock => Sock}}; {error, Reason} = ERROR -> - %% _ = socket:setopt(LSock, otp, debug, false), ?SEV_EPRINT("accept failed: " "~n ~p", [Reason]), ERROR @@ -9399,6 +9396,8 @@ api_a_send_and_recv_stream(Config, InitState) -> case socket:open(Domain, stream, Proto) of {ok, Sock} -> {ok, State#{lsock => Sock}}; + {error, eprotonosupport = Reason} -> + {skip, Reason}; {error, _} = ERROR -> ERROR end From ae44d0a24cb36c03d68e398226aea3ae1457e254 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 27 May 2024 10:29:14 +0200 Subject: [PATCH 064/422] [diameter|test] Skip xref test case if factor too large --- lib/diameter/test/diameter_app_SUITE.erl | 28 +++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 0cdf42ebf62c..0d7bae2ede92 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -34,7 +34,9 @@ suite/0, all/0, init_per_suite/1, - end_per_suite/1 + end_per_suite/1, + init_per_testcase/2, + end_per_testcase/2 ]). %% testcases @@ -94,6 +96,29 @@ end_per_suite(Config) -> ?DUTIL:end_per_suite(Config). +%% This test case can take a *long* time, so if the machine is too slow, skip +init_per_testcase(xref = Case, Config) when is_list(Config) -> + ?AL("init_per_testcase(~w) -> check factor", [Case]), + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 10) -> + ?AL("init_per_testcase(~w) -> Too slow (~w) => SKIP", + [Case, Factor]), + {skip, {machine_too_slow, Factor}}; + _ -> + ?AL("init_per_testcase(~w) -> run test", [Case]), + Config + end; +init_per_testcase(Case, Config) -> + ?AL("init_per_testcase(~w) -> entry", [Case]), + Config. + + +end_per_testcase(Case, Config) when is_list(Config) -> + ?AL("end_per_testcase(~w) -> entry", [Case]), + Config. + + %% =========================================================================== run() -> @@ -109,6 +134,7 @@ run(List) -> run(Config, List) -> Timeout = factor2timeout(Config, 10000), + ?AL("run -> use Timeout: ~w", [Timeout]), [{application, diameter, App}] = ?CONSULT(diameter, app), ?RUN([{{?MODULE, F, [{App, Config}]}, Timeout} || F <- List]). From f355302a4acfc866f37b865face697e14ee586f5 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 15 Apr 2024 16:35:42 +0200 Subject: [PATCH 065/422] [preloaded|net] Add net:getservbyname --- erts/preloaded/ebin/prim_net.beam | Bin 2596 -> 2696 bytes erts/preloaded/src/prim_net.erl | 14 ++++++++++++++ 2 files changed, 14 insertions(+) diff --git a/erts/preloaded/ebin/prim_net.beam b/erts/preloaded/ebin/prim_net.beam index 17fa7069a09e777e459551a1269266b1116dc85e..84d1a7d84cfebe9f37e1ffce0a6d96d0977d0750 100644 GIT binary patch delta 1086 zcmZA0O=uHo7zglqGHLfAI5;NO`qeh=G;QCuX_8K~^`n~BP4!XR#9EcTRiUT{i@J*+ zphP@*P*4Yi7wZRAmlb7qbrct6mx^9Q#DjR*^}MG&dhoKa{~5=_I`A;>{D1HB&XbVb zUVN^hHd>h|7)IjENO^c{`@xxM!!S;vzFdP?6oUtKK+UKl>bN?sE~`0pOUXmx0 z{#Ku4iDaZG8>Avraztk3n%t0^GAFm>j{GP;$z8c8_vL5#MIOjQc_feJiTox{<(Vw{ zUH*`Hc`h&HrFyI0sMnXyx7580-umFzQChHn`iJkQj~?51a%S%#?<4*5|KQKqg@#~a zJD3ockJ^oD^-h_kmK+_{)mZYVO=tXi+bYmSJrzryHRz^aZ&=?(wr$cMxwT?$z87t0fc7 z25~kRSBU#GFTvIpL^;2dNSm4)$L&0EUh`5w8_p<1uq=dr&C3A}I@}0WgizGH63~u0 zS4Gei!fMUUfDBF@@N1u6(h|y`<}{=OFIf|{w1%)&a~q%&ur2~8g!P)+0bPKh2r?mT z(A)t~fQ=D!hEUSn1?UD018TuXRH2M$?uPVW;7w6WPYB;??gjLsr5r&vgi+0XfGl8h z1i28lXwC!r@TEuug%GxC19=YlHoufK$L(5)c>CuNr;Pa}GZp0ND)G3U$KC?QsSH{Z z=CJ9Qv(_$Wft|nKXveQx)jdwWF`ejlXRXOp@R-7*>ke8~cg}S+_g}4ZoKm=>sXWr|7I$mI6R5_2UHT33o_JLw8qWYhH4HLxU#4w6nS}Wq?o^jKhS@$ Ck<j$&+?Pp(6pt+ zRF#jzdS1L56&}UDdxn0wCOF>;?tl^KEGp%#=*3h{%&T%Ne%2Bf{Y{qHEf&>WEPhE7 zEB+?UEO@{5v~az&aZL1i=Z#h|?yVYG(eHgUPIV0mvenO6yt>{Jl=hcRTgMhdf|?as zh_@ql5H|<$Zf~xtwz5x9Mo}Et2+aEZW+uR4L2Zf>h?9t=pEKKnctlXUqHTzqG(jD~ zjY@(#71bcxfhgw}t5dq7+9@k9s7p~DAdM}$Bd8A{uV_1s0q-5ZTlkF5yDPIDL^X@>5sq;VL(wDkO2%v&>X@pMGhbfsO*lUC6qmiS|M$a zp$IY|>{XNnNWi`b+CnHQl7M!=a0Klk>{rwQ=m3mF&>6x3ML9qxUaRC+{ytY%D5FXP zUP&9DpmMLiM3c3IGvTF26Eywdo9Ii(Nlj=pTpI9sgzlRC?|Yfc<> z@^yA~-d#4!iQqGVPuCqVC)|6ktEl^SmE#oa>_b>mbc`W$QqTk%L6d6Tu+4GHwn~Ps z$E}2*sa|th$2@K2tu-Cn7I3#YL1jhxG2}Cf3f_;+rHYMTu|VmluK)U2l=lRA>D>Hb r%wJGjQMn*Panxhd4x*ZZ2BQO&LZ(L6@R3+v?2ZgcG +%% =========================================================================== +%% +%% getservbyname - Get service by name +%% + +getservbyname(Name, Proto) when is_list(Name) andalso is_list(Proto) -> + nif_getservbyname(Name, Proto). + + + %% =========================================================================== %% %% if_name2index - Mappings between network interface names and indexes: @@ -684,6 +695,9 @@ nif_get_interface_info(_Args) -> nif_get_ip_address_table(_Args) -> erlang:nif_error(notsup). +nif_getservbyname(_Name, _Proto) -> + erlang:nif_error(notsup). + nif_if_name2index(_Name) -> erlang:nif_error(notsup). From 7f86a1e5c57ac47a368b092d766465fc44f07a96 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 15 Apr 2024 16:55:18 +0200 Subject: [PATCH 066/422] [enet] Add net:getservbyname --- erts/emulator/nifs/common/prim_net_nif.c | 111 ++++++++++++++++++++++- lib/kernel/src/net.erl | 47 +++++++++- 2 files changed, 150 insertions(+), 8 deletions(-) diff --git a/erts/emulator/nifs/common/prim_net_nif.c b/erts/emulator/nifs/common/prim_net_nif.c index 8655c561e394..ed088aaed68e 100644 --- a/erts/emulator/nifs/common/prim_net_nif.c +++ b/erts/emulator/nifs/common/prim_net_nif.c @@ -1,7 +1,7 @@ /* * %CopyrightBegin% * - * Copyright Ericsson AB 2018-2023. All Rights Reserved. + * Copyright Ericsson AB 2018-2024. All Rights Reserved. * * Licensed under the Apache License, Version 2.0 (the "License"); * you may not use this file except in compliance with the License. @@ -203,9 +203,23 @@ ERL_NIF_INIT(prim_net, net_funcs, on_load, NULL, NULL, NULL) #ifdef __WIN32__ -#define net_gethostname(__buf__, __bufSz__) gethostname((__buf__), (__bufSz__)) + +#define net_gethostname(__buf__, __bufSz__) \ + gethostname((__buf__), (__bufSz__)) +#define net_getservbyname(__name__, __proto__) \ + getservbyname((__name__), (__proto__)) +#define net_ntohs(x) \ + ntohs((x)) + #else -#define net_gethostname(__buf__, __bufSz__) gethostname((__buf__), (__bufSz__)) + +#define net_gethostname(__buf__, __bufSz__) \ + gethostname((__buf__), (__bufSz__)) +#define net_getservbyname(__name__, __proto__) \ + getservbyname((__name__), (__proto__)) +#define net_ntohs(x) \ + ntohs((x)) + #endif // __WIN32__ @@ -266,7 +280,7 @@ static NetData data; * ---------------------------------------------------------------------- */ -/* THIS IS JUST TEMPORARY */ +/* THIS IS JUST TEMPORARY...maybe */ extern char* erl_errno_id(int error); /* All the nif "callback" functions for the net API has @@ -292,6 +306,7 @@ extern char* erl_errno_id(int error); ENET_NIF_FUNC_DEF(get_if_entry); \ ENET_NIF_FUNC_DEF(get_interface_info); \ ENET_NIF_FUNC_DEF(get_ip_address_table); \ + ENET_NIF_FUNC_DEF(getservbyname); \ ENET_NIF_FUNC_DEF(if_name2index); \ ENET_NIF_FUNC_DEF(if_index2name); \ ENET_NIF_FUNC_DEF(if_names); @@ -467,7 +482,11 @@ static void make_ip_address_row(ErlNifEnv* env, ERL_NIF_TERM eReasmSize, ERL_NIF_TERM* iar); -#endif +#endif // defined(__WIN32__) + +static ERL_NIF_TERM enet_getservbyname(ErlNifEnv* env, + ERL_NIF_TERM ename, + ERL_NIF_TERM eproto); #if defined(HAVE_IF_NAMETOINDEX) static ERL_NIF_TERM enet_if_name2index(ErlNifEnv* env, @@ -791,6 +810,7 @@ static ErlNifResourceTypeInit netInit = { * nif_get_if_entry/1 * nif_get_interface_info/1 * nif_get_ip_address_table/1 + * nif_getservbyname/2 * nif_if_name2index/1 * nif_if_index2name/1 * nif_if_names/0 @@ -3932,6 +3952,86 @@ void make_ip_address_row(ErlNifEnv* env, +/* ---------------------------------------------------------------------- + * nif_getservbyname + * + * Description: + * Get service by name. + * This is a lookup function that translates a service name to its + * registered port number. + * + * Arguments: + * Name - The name of the service. + * Protocol - The name of the service. + * + * Returns: + * {ok, PortNumber :: port_number()} | {error, Reason :: term()} + */ + +static +ERL_NIF_TERM nif_getservbyname(ErlNifEnv* env, + int argc, + const ERL_NIF_TERM argv[]) +{ + ERL_NIF_TERM result, ename, eproto; + BOOLEAN_T dbg = FALSE; + + NDBG( ("NET", "nif_get_ip_address_table -> entry (%d)\r\n", argc) ); + + if (argc != 2) + return enif_make_badarg(env); + + ename = argv[0]; + eproto = argv[1]; + + NDBG2( dbg, + ("NET", + "nif_getservbyname -> args: " + "\r\n ename: %T" + "\r\n eproto: %T" + "\r\n", ename, eproto) ); + + result = enet_getservbyname(env, ename, eproto); + + NDBG2( dbg, + ("NET", + "nif_getservbyname -> done when result: " + "\r\n %T\r\n", result) ); + + return result; +} + + +static +ERL_NIF_TERM enet_getservbyname(ErlNifEnv* env, + ERL_NIF_TERM ename, + ERL_NIF_TERM eproto) +{ + char name[256]; + char proto[256]; + struct servent* srv; + short port; + + if (0 >= GET_STR(env, ename, name, sizeof(name))) + return esock_make_error(env, esock_atom_einval); + + if (0 >= GET_STR(env, eproto, proto, sizeof(proto))) + return esock_make_error(env, esock_atom_einval); + + if ( strcmp(proto, "any") == 0 ) + srv = net_getservbyname(name, NULL); + else + srv = net_getservbyname(name, proto); + + if (srv == NULL) + return esock_make_error(env, esock_atom_einval); + + port = net_ntohs(srv->s_port); + + return esock_make_ok2(env, MKI(env, port)); +} + + /* ---------------------------------------------------------------------- * nif_if_name2index @@ -4697,6 +4797,7 @@ ErlNifFunc net_funcs[] = {"nif_get_if_entry", 1, nif_get_if_entry, ERL_NIF_DIRTY_JOB_IO_BOUND}, {"nif_get_interface_info", 1, nif_get_interface_info, ERL_NIF_DIRTY_JOB_IO_BOUND}, {"nif_get_ip_address_table", 1, nif_get_ip_address_table, ERL_NIF_DIRTY_JOB_IO_BOUND}, + {"nif_getservbyname", 2, nif_getservbyname, ERL_NIF_DIRTY_JOB_IO_BOUND}, /* Network interface (name and/or index) functions */ {"nif_if_name2index", 1, nif_if_name2index, 0}, diff --git a/lib/kernel/src/net.erl b/lib/kernel/src/net.erl index e642b89d5a5a..f51f4fb51ab6 100644 --- a/lib/kernel/src/net.erl +++ b/lib/kernel/src/net.erl @@ -34,9 +34,10 @@ This module provides an API for the network interface. -export([ gethostname/0, - getnameinfo/1, getnameinfo/2, - getaddrinfo/1, getaddrinfo/2, - getifaddrs/0, getifaddrs/1, getifaddrs/2, + getnameinfo/1, getnameinfo/2, + getaddrinfo/1, getaddrinfo/2, + getifaddrs/0, getifaddrs/1, getifaddrs/2, + getservbyname/1, getservbyname/2, if_name2index/1, if_index2name/1, @@ -320,6 +321,7 @@ getaddrinfo(Host, Service) (not ((Service =:= undefined) andalso (Host =:= undefined))) -> prim_net:getaddrinfo(Host, Service). + %% =========================================================================== %% %% getifaddrs - Get interface addresses @@ -893,6 +895,45 @@ iat_broadaddr({A1, A2, A3, A4}, {M1, M2, M3, M4}) -> addr => {BA1, BA2, BA3, BA4}, port => 0}. + +%% =========================================================================== +%% +%% getservbyname - Get service by name +%% +%% Get the port number for the named service. +%% + +-doc(#{equiv => getservbyname(Name, any)}). +-doc(#{since => <<"OTP FOOBAR">>}). +-spec getservbyname(Name) -> + {ok, PortNumber} | {error, Reason} when + Name :: atom() | string(), + PortNumber :: socket:port_number(), + Reason :: term(). +getservbyname(Name) -> + getservbyname(Name, any). + +-doc """ +Get service by name. + +This function is used to get the port number of the specified protocol +for the named service. +""". +-doc(#{since => <<"OTP FOOBAR">>}). +-spec getservbyname(Name, Protocol) -> + {ok, PortNumber} | {error, Reason} when + Name :: atom() | string(), + PortNumber :: socket:port_number(), + Protocol :: any | socket:protocol(), + Reason :: term(). +getservbyname(Name, Protocol) + when is_atom(Name) -> + getservbyname(atom_to_list(Name), Protocol); +getservbyname(Name, Protocol) + when is_list(Name) andalso is_atom(Protocol) -> + prim_net:getservbyname(Name, atom_to_list(Protocol)). + + %% =========================================================================== %% %% if_name2index - Mappings between network interface names and indexes: From 8be3148602a9e7ca7405b18c0a908a2294528463 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 15 Apr 2024 17:37:51 +0200 Subject: [PATCH 067/422] [preloaded|enet] Add net:getservbyport --- erts/preloaded/ebin/prim_net.beam | Bin 2696 -> 2800 bytes erts/preloaded/src/prim_net.erl | 15 +++++++++++++++ 2 files changed, 15 insertions(+) diff --git a/erts/preloaded/ebin/prim_net.beam b/erts/preloaded/ebin/prim_net.beam index 84d1a7d84cfebe9f37e1ffce0a6d96d0977d0750..3c78ee94c56ea4163fab5ebaa88296b45207c997 100644 GIT binary patch delta 1134 zcmZA1O-~a+7zgm3Zowywn`~MUUx02|DIK7tWm^g&Qoy34@*-3by$};(NQ@FR24l3w zlLrryJxwGAm3Z=E)(?OOH4=P@CVl`fdNL-SJQ)4&I$qf1$;|$LGf!um?B1#SQCArm zpUi1mJPN5yI_qs%BJDF$i)aW8G8Kq;RN zGisBx1JsC??by}kw-k&zB-J5qLY&5q4nID|C?jbn;<(1B(|?XpMp;Sqp=vZ@AXNh@i*5996zmBgFKI7eA9fTJGz8EssS(hEa~2ge1<)fY4oISFuL3K8 z{gM)ZYAb%EPf2qi2PD~$6rf+hz5otNY5{P-fP!QIB}uJ-Ho%~QQ~*PgIG`Octe`D` zLz3D79afc5SxHAABa+gPG@j(Jf=mEMBy|EZ=p__n12`%v2j~PGQ_vN_aY+s!i+^iW zK|X*nsUgoHAFq0)s6J+v7)|^O(dC3!(qn#XO)#32>sagHI8!~wDSc44^%Y~r-fm`} z)|=r6MrGR0)?1Ohvtpc%`L{9LI!=#KaUMC2q{96g+b#twN_M#4ILWAj38Ry8J!~1d zDbq5`VO@`!F-E8I#wpm7}C3PP~J|n5_EaS_WUt3^5dYrrDktImqm4* zDr$a|%aI&xin_;tSA%Vk}z!k zQr1HwfVw#G_wtqUbUScKV3;65%MQ5^aiAnnC+MY3hFyp{ za9LmvL6Ts^g_r|Z1jY$c1kF)b5{`@s>?L6&<1Qo}C<{yxqzNi6Fb5_CrV0A!ypt~U zIdD~Ah9E;TsxD+5m=f4ekR_P5ny0TT=g2jId6Is5kKCP7a9~DAl;-Y`mP-8e7|fdenRu~^x8q#RR5)kVNMHGqraNYT}rrfXG2mi<})aH*&+%QP-) zdF_= +%% =========================================================================== +%% +%% getservbyport - Get service by name +%% + +getservbyport(PortNumber, Proto) + when is_integer(PortNumber) andalso is_list(Proto) -> + nif_getservbyport(PortNumber, Proto). + + + %% =========================================================================== %% %% if_name2index - Mappings between network interface names and indexes: @@ -698,6 +710,9 @@ nif_get_ip_address_table(_Args) -> nif_getservbyname(_Name, _Proto) -> erlang:nif_error(notsup). +nif_getservbyport(_PortNumber, _Proto) -> + erlang:nif_error(notsup). + nif_if_name2index(_Name) -> erlang:nif_error(notsup). From 11687229df4f6aeb9d6e6a0da917924294f2ef18 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 15 Apr 2024 18:58:20 +0200 Subject: [PATCH 068/422] [enet] Add getservbyport --- erts/emulator/nifs/common/prim_net_nif.c | 99 +++++++++++++++++++++++- lib/kernel/src/net.erl | 36 +++++++++ 2 files changed, 134 insertions(+), 1 deletion(-) diff --git a/erts/emulator/nifs/common/prim_net_nif.c b/erts/emulator/nifs/common/prim_net_nif.c index ed088aaed68e..77f1d881e1c9 100644 --- a/erts/emulator/nifs/common/prim_net_nif.c +++ b/erts/emulator/nifs/common/prim_net_nif.c @@ -208,8 +208,12 @@ ERL_NIF_INIT(prim_net, net_funcs, on_load, NULL, NULL, NULL) gethostname((__buf__), (__bufSz__)) #define net_getservbyname(__name__, __proto__) \ getservbyname((__name__), (__proto__)) +#define net_getservbyport(__port__, __proto__) \ + getservbyport((__port__), (__proto__)) #define net_ntohs(x) \ ntohs((x)) +#define net_htons(x) \ + htons((x)) #else @@ -217,8 +221,12 @@ ERL_NIF_INIT(prim_net, net_funcs, on_load, NULL, NULL, NULL) gethostname((__buf__), (__bufSz__)) #define net_getservbyname(__name__, __proto__) \ getservbyname((__name__), (__proto__)) +#define net_getservbyport(__port__, __proto__) \ + getservbyport((__port__), (__proto__)) #define net_ntohs(x) \ ntohs((x)) +#define net_htons(x) \ + htons((x)) #endif // __WIN32__ @@ -307,6 +315,7 @@ extern char* erl_errno_id(int error); ENET_NIF_FUNC_DEF(get_interface_info); \ ENET_NIF_FUNC_DEF(get_ip_address_table); \ ENET_NIF_FUNC_DEF(getservbyname); \ + ENET_NIF_FUNC_DEF(getservbyport); \ ENET_NIF_FUNC_DEF(if_name2index); \ ENET_NIF_FUNC_DEF(if_index2name); \ ENET_NIF_FUNC_DEF(if_names); @@ -487,6 +496,9 @@ static void make_ip_address_row(ErlNifEnv* env, static ERL_NIF_TERM enet_getservbyname(ErlNifEnv* env, ERL_NIF_TERM ename, ERL_NIF_TERM eproto); +static ERL_NIF_TERM enet_getservbyport(ErlNifEnv* env, + ERL_NIF_TERM eport, + ERL_NIF_TERM eproto); #if defined(HAVE_IF_NAMETOINDEX) static ERL_NIF_TERM enet_if_name2index(ErlNifEnv* env, @@ -811,6 +823,7 @@ static ErlNifResourceTypeInit netInit = { * nif_get_interface_info/1 * nif_get_ip_address_table/1 * nif_getservbyname/2 + * nif_getservbyport/2 * nif_if_name2index/1 * nif_if_index2name/1 * nif_if_names/0 @@ -3976,7 +3989,7 @@ ERL_NIF_TERM nif_getservbyname(ErlNifEnv* env, ERL_NIF_TERM result, ename, eproto; BOOLEAN_T dbg = FALSE; - NDBG( ("NET", "nif_get_ip_address_table -> entry (%d)\r\n", argc) ); + NDBG( ("NET", "nif_getservbyname -> entry (%d)\r\n", argc) ); if (argc != 2) return enif_make_badarg(env); @@ -4033,6 +4046,89 @@ ERL_NIF_TERM enet_getservbyname(ErlNifEnv* env, +/* ---------------------------------------------------------------------- + * nif_getservbyport + * + * Description: + * Get service by name. + * This is a lookup function that translates a port number to its + * (registered) service name. + * + * Arguments: + * PortNumber - Port number for which we want to know the service name + * Protocol - The the protocol for which we want to service name + * + * Returns: + * {ok, Name :: string()} | {error, Reason :: term()} + */ + +static +ERL_NIF_TERM nif_getservbyport(ErlNifEnv* env, + int argc, + const ERL_NIF_TERM argv[]) +{ + ERL_NIF_TERM result, eport, eproto; + BOOLEAN_T dbg = FALSE; + + NDBG( ("NET", "nif_getservbyport -> entry (%d)\r\n", argc) ); + + if (argc != 2) + return enif_make_badarg(env); + + eport = argv[0]; + eproto = argv[1]; + + NDBG2( dbg, + ("NET", + "nif_getservbyport -> args: " + "\r\n eport: %T" + "\r\n eproto: %T" + "\r\n", eport, eproto) ); + + result = enet_getservbyport(env, eport, eproto); + + NDBG2( dbg, + ("NET", + "nif_getservbyport -> done when result: " + "\r\n %T\r\n", result) ); + + return result; +} + + +static +ERL_NIF_TERM enet_getservbyport(ErlNifEnv* env, + ERL_NIF_TERM eport, + ERL_NIF_TERM eproto) +{ + char proto[256]; + struct servent* srv; + unsigned short port; + unsigned int len; + + if (0 >= GET_UINT(env, eport, &port)) + return esock_make_error(env, esock_atom_einval); + + if (0 >= GET_STR(env, eproto, proto, sizeof(proto))) + return esock_make_error(env, esock_atom_einval); + + port = net_htons(port); + + if ( strcmp(proto, "any") == 0 ) + srv = net_getservbyport(port, NULL); + else + srv = net_getservbyport(port, proto); + + if (srv == NULL) + return esock_make_error(env, esock_atom_einval); + + len = strlen(srv->s_name); + + return esock_make_ok2(env, MKSL(env, srv->s_name, len)); +} + + + /* ---------------------------------------------------------------------- * nif_if_name2index * @@ -4798,6 +4894,7 @@ ErlNifFunc net_funcs[] = {"nif_get_interface_info", 1, nif_get_interface_info, ERL_NIF_DIRTY_JOB_IO_BOUND}, {"nif_get_ip_address_table", 1, nif_get_ip_address_table, ERL_NIF_DIRTY_JOB_IO_BOUND}, {"nif_getservbyname", 2, nif_getservbyname, ERL_NIF_DIRTY_JOB_IO_BOUND}, + {"nif_getservbyport", 2, nif_getservbyport, ERL_NIF_DIRTY_JOB_IO_BOUND}, /* Network interface (name and/or index) functions */ {"nif_if_name2index", 1, nif_if_name2index, 0}, diff --git a/lib/kernel/src/net.erl b/lib/kernel/src/net.erl index f51f4fb51ab6..dc04cee4af1b 100644 --- a/lib/kernel/src/net.erl +++ b/lib/kernel/src/net.erl @@ -38,6 +38,7 @@ This module provides an API for the network interface. getaddrinfo/1, getaddrinfo/2, getifaddrs/0, getifaddrs/1, getifaddrs/2, getservbyname/1, getservbyname/2, + getservbyport/1, getservbyport/2, if_name2index/1, if_index2name/1, @@ -934,6 +935,41 @@ getservbyname(Name, Protocol) prim_net:getservbyname(Name, atom_to_list(Protocol)). +%% =========================================================================== +%% +%% getservbyport - Get service by name +%% +%% Get service name for the given port number. +%% + +-doc(#{equiv => getservbyport(PortNumber, any)}). +-doc(#{since => <<"OTP FOOBAR">>}). +-spec getservbyport(PortNumber) -> + {ok, Name} | {error, Reason} when + PortNumber :: socket:port_number(), + Name :: atom() | string(), + Reason :: term(). +getservbyport(PortNumber) -> + getservbyport(PortNumber, any). + +-doc """ +Get service by name. + +This function is used to get the service name of the specified protocol +for the given port number. +""". +-doc(#{since => <<"OTP FOOBAR">>}). +-spec getservbyport(PortNumber, Protocol) -> + {ok, Name} | {error, Reason} when + PortNumber :: socket:port_number(), + Protocol :: any | socket:protocol(), + Name :: atom() | string(), + Reason :: term(). +getservbyport(PortNumber, Protocol) + when is_integer(PortNumber) andalso is_atom(Protocol) -> + prim_net:getservbyport(PortNumber, atom_to_list(Protocol)). + + %% =========================================================================== %% %% if_name2index - Mappings between network interface names and indexes: From afd189ec97b6c49060bef9277c5666f92a2f8383 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 16 Apr 2024 11:04:02 +0200 Subject: [PATCH 069/422] [kernel|net|test] Add simple test cases Add a couple of simple getservby[name|port] test cases. --- lib/kernel/test/net_SUITE.erl | 115 ++++++++++++++++++++++++++++++++-- 1 file changed, 111 insertions(+), 4 deletions(-) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index 9c18b3f2614b..bef17f0476d0 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2019-2022. All Rights Reserved. +%% Copyright Ericsson AB 2019-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -50,8 +50,9 @@ %% *** API Basic *** api_b_gethostname/1, api_b_getifaddrs/1, + api_b_getservbyname/1, + api_b_getservbyport/1, api_b_name_and_addr_info/1, - api_b_name_and_index/1, %% *** API Misc *** @@ -63,7 +64,9 @@ api_m_getnameinfo_v4/0, api_m_getnameinfo_v4/1, api_m_getnameinfo_v6/0, - api_m_getnameinfo_v6/1 + api_m_getnameinfo_v6/1, + + api_m_getservbyname_overflow/1 %% Tickets ]). @@ -121,6 +124,8 @@ api_basic_cases() -> [ api_b_gethostname, api_b_getifaddrs, + api_b_getservbyname, + api_b_getservbyport, api_b_name_and_addr_info, api_b_name_and_index ]. @@ -130,7 +135,8 @@ api_misc_cases() -> api_m_getaddrinfo_v4, api_m_getaddrinfo_v6, api_m_getnameinfo_v4, - api_m_getnameinfo_v6 + api_m_getnameinfo_v6, + api_m_getservbyname_overflow ]. %% ticket_cases() -> @@ -330,6 +336,78 @@ merge([H|T], L) -> end. +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% This is a *very* basic test. It simply calls the function with +%% a a couple of diifferent arguments... +api_b_getservbyname(suite) -> + []; +api_b_getservbyname(doc) -> + []; +api_b_getservbyname(_Config) when is_list(_Config) -> + ?TT(?SECS(5)), + tc_try(?FUNCTION_NAME, + fun() -> + ok = api_b_getservbyname() + end). + + +api_b_getservbyname() -> + ?P("A couple of (expected) successes"), + {ok, 80} = net:getservbyname("http"), + {ok, 80} = net:getservbyname("http", any), + {ok, 80} = net:getservbyname("http", tcp), + {ok, 80} = net:getservbyname("www", udp), + {ok, 161} = net:getservbyname("snmp", udp), + {ok, 161} = net:getservbyname("snmp", tcp), + {ok, 4369} = net:getservbyname("epmd", tcp), + {ok, 5672} = net:getservbyname("amqp", tcp), + {ok, 5672} = net:getservbyname("amqp", sctp), + + ?P("A couple of (expected) failures"), + {error, einval} = net:getservbyname("gurka", tcp), + {error, einval} = net:getservbyname("http", gurka), + + ?P("done"), + ok. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +%% This is a *very* basic test. It simply calls the function and expect +%% it to succeed... +api_b_getservbyport(suite) -> + []; +api_b_getservbyport(doc) -> + []; +api_b_getservbyport(_Config) when is_list(_Config) -> + ?TT(?SECS(5)), + tc_try(?FUNCTION_NAME, + fun() -> + ok = api_b_getservbyport() + end). + + +api_b_getservbyport() -> + ?P("A couple of (expected) successes"), + {ok, "http"} = net:getservbyport(80), + {ok, "http"} = net:getservbyport(80, any), + {ok, "http"} = net:getservbyport(80, tcp), + {ok, "www"} = net:getservbyport(80, udp), + {ok, "snmp"} = net:getservbyport(161, udp), + {ok, "snmp"} = net:getservbyport(161, tcp), + {ok, "epmd"} = net:getservbyport(4369, tcp), + {ok, "amqp"} = net:getservbyport(5672, tcp), + {ok, "amqp"} = net:getservbyport(5672, sctp), + + ?P("A couple of (expected) failures"), + {error, einval} = net:getservbyport(11111, tcp), + {error, einval} = net:getservbyport(80, gurka), + + ?P("done"), + ok. + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Get name and address info. @@ -720,6 +798,35 @@ api_m_getnameinfo_verify(NameInfo, Name, FName, _IP) -> ?FAIL({not_found, NameInfo, Name, FName}). +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +api_m_getservbyname_overflow(suite) -> + []; +api_m_getservbyname_overflow(doc) -> + []; +api_m_getservbyname_overflow(Config) when is_list(Config) -> + ?TT(?SECS(5)), + Pre = fun() -> + #{} + end, + Case = fun(_Info) -> + ?P("try name as large atom"), + {error, einval} = + net:getservbyname( + list_to_atom(lists:flatten(lists:duplicate(128, "x"))), + tcp), + ?P("try name as too large string"), + {error, einval} = + net:getservbyname( + lists:flatten(lists:duplicate(257, "x")), + tcp), + ok + end, + Post = fun(_) -> ok end, + tc_try(?FUNCTION_NAME, + Pre, Case, Post). + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% This gets the local address (not 127.0...) From bb399793ec1426ca9dbd5d3f956631bcd00318a8 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 16 Apr 2024 11:18:43 +0200 Subject: [PATCH 070/422] [kernel|net|test] Extend getifaddrs test case --- lib/kernel/test/net_SUITE.erl | 33 +++++++++++++++++++++++++++++++++ 1 file changed, 33 insertions(+) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index bef17f0476d0..c9f649a8dabf 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -263,6 +263,8 @@ api_b_getifaddrs() -> {ok, IfAddrs} -> i("IfAddrs: " "~n ~p", [IfAddrs]), + verify_broadcast(IfAddrs), + verify_loopback(IfAddrs), ok; {error, enotsup = Reason} -> i("getifaddrs not supported - skipping"), @@ -302,6 +304,37 @@ api_b_getifaddrs() -> skip(CReason) end. + +verify_broadcast([]) -> + ok; +verify_broadcast([#{flags := Flags, + broadaddr := _} = IfAddr|IfAddrs]) -> + %% Must have the 'broadcast' flag + case lists:member(broadcast, Flags) of + true -> + verify_broadcast(IfAddrs); + false -> + ?FAIL({missing_broadcast_flag, IfAddr}) + end; +verify_broadcast([_|IfAddrs]) -> + verify_broadcast(IfAddrs). + +verify_loopback([]) -> + ok; +verify_loopback([#{name := "lo", + flags := Flags, + addr := _Addr} = IfAddr|IfAddrs]) -> + %% Must have the 'broadcast' flag + case lists:member(loopback, Flags) of + true -> + verify_loopback(IfAddrs); + false -> + ?FAIL({missing_loopback_flag, IfAddr}) + end; +verify_loopback([_|IfAddrs]) -> + verify_loopback(IfAddrs). + + win_getifaddrs_ife({ok, II}, {ok, AT}) -> IDX1 = [IDX || #{index := IDX} <- II], IDX2 = [IDX || #{index := IDX} <- AT], From 0849b05ec4fd58a7337e11daf2c6d336f5d9c939 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 16 Apr 2024 12:47:39 +0200 Subject: [PATCH 071/422] [kernel|net|test] Tweaked for Windows --- lib/kernel/test/net_SUITE.erl | 39 ++++++++++++++++++++++++++--------- 1 file changed, 29 insertions(+), 10 deletions(-) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index c9f649a8dabf..fcc6e6dc9827 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -390,12 +390,12 @@ api_b_getservbyname() -> {ok, 80} = net:getservbyname("http"), {ok, 80} = net:getservbyname("http", any), {ok, 80} = net:getservbyname("http", tcp), - {ok, 80} = net:getservbyname("www", udp), + not_on_windows(fun() -> {ok, 80} = net:getservbyname("www", udp) end), {ok, 161} = net:getservbyname("snmp", udp), - {ok, 161} = net:getservbyname("snmp", tcp), - {ok, 4369} = net:getservbyname("epmd", tcp), - {ok, 5672} = net:getservbyname("amqp", tcp), - {ok, 5672} = net:getservbyname("amqp", sctp), + not_on_windows(fun() -> {ok, 161} = net:getservbyname("snmp", tcp) end), + not_on_windows(fun() -> {ok, 4369} = net:getservbyname("epmd", tcp) end), + not_on_windows(fun() -> {ok, 5672} = net:getservbyname("amqp", tcp) end), + not_on_windows(fun() -> {ok, 5672} = net:getservbyname("amqp", sctp) end), ?P("A couple of (expected) failures"), {error, einval} = net:getservbyname("gurka", tcp), @@ -426,12 +426,12 @@ api_b_getservbyport() -> {ok, "http"} = net:getservbyport(80), {ok, "http"} = net:getservbyport(80, any), {ok, "http"} = net:getservbyport(80, tcp), - {ok, "www"} = net:getservbyport(80, udp), + not_on_windows(fun() -> {ok, "www"} = net:getservbyport(80, udp) end), {ok, "snmp"} = net:getservbyport(161, udp), - {ok, "snmp"} = net:getservbyport(161, tcp), - {ok, "epmd"} = net:getservbyport(4369, tcp), - {ok, "amqp"} = net:getservbyport(5672, tcp), - {ok, "amqp"} = net:getservbyport(5672, sctp), + not_on_windows(fun() -> {ok, "snmp"} = net:getservbyport(161, tcp) end), + not_on_windows(fun() -> {ok, "epmd"} = net:getservbyport(4369, tcp) end), + not_on_windows(fun() -> {ok, "amqp"} = net:getservbyport(5672, tcp) end), + not_on_windows(fun() -> {ok, "amqp"} = net:getservbyport(5672, sctp) end), ?P("A couple of (expected) failures"), {error, einval} = net:getservbyport(11111, tcp), @@ -441,6 +441,25 @@ api_b_getservbyport() -> ok. +not_on_windows(F) -> + Cond = fun() -> case os:type() of + {win32, nt} -> + skip; + _ -> + run + end + end, + maybe_run(Cond, F). + +maybe_run(Cond, F) -> + case Cond() of + run -> + F(); + skip -> + ok + end. + + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Get name and address info. From 4115e96bb57b61225efbca007a353e8aa6676f84 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 17 Apr 2024 11:32:48 +0200 Subject: [PATCH 072/422] [enet] Fixed for FreeBSD --- erts/emulator/nifs/common/prim_net_nif.c | 50 ++++++++++++++++++------ 1 file changed, 38 insertions(+), 12 deletions(-) diff --git a/erts/emulator/nifs/common/prim_net_nif.c b/erts/emulator/nifs/common/prim_net_nif.c index 77f1d881e1c9..a4ef12a8d134 100644 --- a/erts/emulator/nifs/common/prim_net_nif.c +++ b/erts/emulator/nifs/common/prim_net_nif.c @@ -497,6 +497,7 @@ static ERL_NIF_TERM enet_getservbyname(ErlNifEnv* env, ERL_NIF_TERM ename, ERL_NIF_TERM eproto); static ERL_NIF_TERM enet_getservbyport(ErlNifEnv* env, + BOOLEAN_T dbg, ERL_NIF_TERM eport, ERL_NIF_TERM eproto); @@ -4070,7 +4071,7 @@ ERL_NIF_TERM nif_getservbyport(ErlNifEnv* env, ERL_NIF_TERM result, eport, eproto; BOOLEAN_T dbg = FALSE; - NDBG( ("NET", "nif_getservbyport -> entry (%d)\r\n", argc) ); + NDBG2( dbg, ("NET", "nif_getservbyport -> entry (%d)\r\n", argc) ); if (argc != 2) return enif_make_badarg(env); @@ -4085,7 +4086,7 @@ ERL_NIF_TERM nif_getservbyport(ErlNifEnv* env, "\r\n eproto: %T" "\r\n", eport, eproto) ); - result = enet_getservbyport(env, eport, eproto); + result = enet_getservbyport(env, dbg, eport, eproto); NDBG2( dbg, ("NET", @@ -4098,33 +4099,58 @@ ERL_NIF_TERM nif_getservbyport(ErlNifEnv* env, static ERL_NIF_TERM enet_getservbyport(ErlNifEnv* env, + BOOLEAN_T dbg, ERL_NIF_TERM eport, ERL_NIF_TERM eproto) { char proto[256]; struct servent* srv; - unsigned short port; - unsigned int len; + unsigned int port; + ERL_NIF_TERM ename, result; + NDBG2( dbg, ("NET", "enet_getservbyport -> try 'get' port\r\n") ); if (0 >= GET_UINT(env, eport, &port)) return esock_make_error(env, esock_atom_einval); + NDBG2( dbg, ("NET", "enet_getservbyport -> (pre htons) port: %u\r\n", port) ); + port = net_htons(port); + NDBG2( dbg, ("NET", "enet_getservbyport -> (post htons) port: %u\r\n", port) ); + + NDBG2( dbg, ("NET", "enet_getservbyport -> try 'get' proto\r\n") ); if (0 >= GET_STR(env, eproto, proto, sizeof(proto))) return esock_make_error(env, esock_atom_einval); + NDBG2( dbg, ("NET", "enet_getservbyport -> proto: %s\r\n", proto) ); - port = net_htons(port); - - if ( strcmp(proto, "any") == 0 ) + NDBG2( dbg, ("NET", "enet_getservbyport -> check proto\r\n") ); + if ( strcmp(proto, "any") == 0 ) { srv = net_getservbyport(port, NULL); - else + } else { srv = net_getservbyport(port, proto); + } - if (srv == NULL) - return esock_make_error(env, esock_atom_einval); + if (srv == NULL) { + + NDBG2( dbg, ("NET", "enet_getservbyport -> failed get servent\r\n") ); - len = strlen(srv->s_name); + result = esock_make_error(env, esock_atom_einval); + + } else { + + unsigned int len = strlen(srv->s_name); + + NDBG2( dbg, ("NET", "enet_getservbyport -> make string (term) with length %d\r\n", len) ); + + ename = MKSL(env, srv->s_name, len); - return esock_make_ok2(env, MKSL(env, srv->s_name, len)); + result = esock_make_ok2(env, ename); + + } + + NDBG2( dbg, ("NET", "enet_getservbyport -> done with" + "\r\n result: %T" + "\r\n", result) ); + + return result; } From 479f29f1a6de953d150463b2184509fa061a549d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 17 Apr 2024 11:33:51 +0200 Subject: [PATCH 073/422] [kernel|net|test] Tweaked for FreeBSD --- lib/kernel/test/net_SUITE.erl | 25 ++++++++++++++++++++++--- 1 file changed, 22 insertions(+), 3 deletions(-) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index fcc6e6dc9827..2f339b4900b5 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -24,8 +24,12 @@ %% not even reside here). %% +%% Starting a VM to run tests with ct: +%% ( cd $LOCAL_TESTS/27/kernel_test/ && $ERL_TOP/bin/erl -sname kernel-27-tester -pa $LOCAL_TESTS/27/test_server ) +%% %% Run the entire test suite: %% ts:run(emulator, net_SUITE, [batch]). +%% S = fun(SUITE) -> ct:run_test([{suite, SUITE}]) end, S(net_SUITE). %% %% Run a specific group: %% ts:run(emulator, net_SUITE, {group, foo}, [batch]). @@ -414,7 +418,7 @@ api_b_getservbyport(suite) -> api_b_getservbyport(doc) -> []; api_b_getservbyport(_Config) when is_list(_Config) -> - ?TT(?SECS(5)), + ?TT(?SECS(30)), tc_try(?FUNCTION_NAME, fun() -> ok = api_b_getservbyport() @@ -424,9 +428,13 @@ api_b_getservbyport(_Config) when is_list(_Config) -> api_b_getservbyport() -> ?P("A couple of (expected) successes"), {ok, "http"} = net:getservbyport(80), - {ok, "http"} = net:getservbyport(80, any), + not_freebsd(fun() -> {ok, "http"} = net:getservbyport(80, any) end), {ok, "http"} = net:getservbyport(80, tcp), - not_on_windows(fun() -> {ok, "www"} = net:getservbyport(80, udp) end), + not_on_windows(fun() -> case net:getservbyport(80, udp) of + {ok, STR} when (STR =:= "http") orelse (STR =:= "WWW") -> ok; + {error, Reason} -> ?P("Unexpected failure: ~p", [Reason]), ?FAIL({80, udp, Reason}) + end + end), {ok, "snmp"} = net:getservbyport(161, udp), not_on_windows(fun() -> {ok, "snmp"} = net:getservbyport(161, tcp) end), not_on_windows(fun() -> {ok, "epmd"} = net:getservbyport(4369, tcp) end), @@ -441,6 +449,17 @@ api_b_getservbyport() -> ok. +not_freebsd(F) -> + Cond = fun() -> case os:type() of + {unix, freebsd} -> + skip; + _ -> + run + end + end, + maybe_run(Cond, F). + + not_on_windows(F) -> Cond = fun() -> case os:type() of {win32, nt} -> From 665174369d766371ed56b5ed41130ddd2722c12e Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 17 Apr 2024 11:44:32 +0200 Subject: [PATCH 074/422] [kernel|net|test] Tweaked for FreeBSD --- lib/kernel/test/net_SUITE.erl | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index 2f339b4900b5..f49fc77a1c4d 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -428,7 +428,7 @@ api_b_getservbyport(_Config) when is_list(_Config) -> api_b_getservbyport() -> ?P("A couple of (expected) successes"), {ok, "http"} = net:getservbyport(80), - not_freebsd(fun() -> {ok, "http"} = net:getservbyport(80, any) end), + {ok, "http"} = net:getservbyport(80, any), {ok, "http"} = net:getservbyport(80, tcp), not_on_windows(fun() -> case net:getservbyport(80, udp) of {ok, STR} when (STR =:= "http") orelse (STR =:= "WWW") -> ok; @@ -449,16 +449,16 @@ api_b_getservbyport() -> ok. -not_freebsd(F) -> - Cond = fun() -> case os:type() of - {unix, freebsd} -> - skip; - _ -> - run - end - end, - maybe_run(Cond, F). - +%% not_freebsd(F) -> +%% Cond = fun() -> case os:type() of +%% {unix, freebsd} -> +%% skip; +%% _ -> +%% run +%% end +%% end, +%% maybe_run(Cond, F). +%% not_on_windows(F) -> Cond = fun() -> case os:type() of From c71544e3c18a23108f8aa32d77a3882d65f7718a Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 17 Apr 2024 12:53:18 +0200 Subject: [PATCH 075/422] [kernel|net|test] Tweaked tests for ubuntu on vm --- lib/kernel/test/net_SUITE.erl | 40 +++++++++++++++++++++++++++++------ 1 file changed, 34 insertions(+), 6 deletions(-) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index f49fc77a1c4d..32e089532bf8 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -394,7 +394,23 @@ api_b_getservbyname() -> {ok, 80} = net:getservbyname("http"), {ok, 80} = net:getservbyname("http", any), {ok, 80} = net:getservbyname("http", tcp), - not_on_windows(fun() -> {ok, 80} = net:getservbyname("www", udp) end), + not_on_windows(fun() -> + case net:getservbyname("www", udp) of + {ok, 80} -> + ok; + {error, Reason} -> + case os:type() of + {unix, linux} -> + %% This happens on some linux + %% (Ubuntu 22 on Parallels ARM VM) + ok; + _ -> + ?P("Unexpected failure: ~p", + [Reason]), + ?FAIL({"www", udp, Reason}) + end + end + end), {ok, 161} = net:getservbyname("snmp", udp), not_on_windows(fun() -> {ok, 161} = net:getservbyname("snmp", tcp) end), not_on_windows(fun() -> {ok, 4369} = net:getservbyname("epmd", tcp) end), @@ -430,11 +446,23 @@ api_b_getservbyport() -> {ok, "http"} = net:getservbyport(80), {ok, "http"} = net:getservbyport(80, any), {ok, "http"} = net:getservbyport(80, tcp), - not_on_windows(fun() -> case net:getservbyport(80, udp) of - {ok, STR} when (STR =:= "http") orelse (STR =:= "WWW") -> ok; - {error, Reason} -> ?P("Unexpected failure: ~p", [Reason]), ?FAIL({80, udp, Reason}) - end - end), + not_on_windows(fun() -> + case net:getservbyport(80, udp) of + {ok, STR} when (STR =:= "http") orelse + (STR =:= "WWW") -> ok; + {error, Reason} -> + case os:type() of + {unix, linux} -> + %% This happens on some linux + %% (Ubuntu 22 on Parallels ARM VM) + ok; + _ -> + ?P("Unexpected failure: ~p", + [Reason]), + ?FAIL({80, udp, Reason}) + end + end + end), {ok, "snmp"} = net:getservbyport(161, udp), not_on_windows(fun() -> {ok, "snmp"} = net:getservbyport(161, tcp) end), not_on_windows(fun() -> {ok, "epmd"} = net:getservbyport(4369, tcp) end), From e4d5c24e496805b9c2b7ee66b2bd9fcf82d7d790 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 17 Apr 2024 14:34:54 +0200 Subject: [PATCH 076/422] [kernel|net|test] Tweaked for Darwin --- lib/kernel/test/net_SUITE.erl | 60 +++++++++++++++++++++++++++++++---- 1 file changed, 53 insertions(+), 7 deletions(-) diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index 32e089532bf8..eea9283fecc2 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -400,7 +400,8 @@ api_b_getservbyname() -> ok; {error, Reason} -> case os:type() of - {unix, linux} -> + {unix, linux} + when (Reason =:= einval) -> %% This happens on some linux %% (Ubuntu 22 on Parallels ARM VM) ok; @@ -415,11 +416,39 @@ api_b_getservbyname() -> not_on_windows(fun() -> {ok, 161} = net:getservbyname("snmp", tcp) end), not_on_windows(fun() -> {ok, 4369} = net:getservbyname("epmd", tcp) end), not_on_windows(fun() -> {ok, 5672} = net:getservbyname("amqp", tcp) end), - not_on_windows(fun() -> {ok, 5672} = net:getservbyname("amqp", sctp) end), + not_on_windows(fun() -> + case net:getservbyname("amqp", sctp) of + {ok, 5672} -> + ok; + {error, Reason} -> + case os:type() of + {unix, darwin} + when (Reason =:= einval) -> + ok; + _ -> + ?P("Unexpected failure: ~p", + [Reason]), + ?FAIL({"amap", udp, Reason}) + end + end + end), ?P("A couple of (expected) failures"), {error, einval} = net:getservbyname("gurka", tcp), - {error, einval} = net:getservbyname("http", gurka), + case net:getservbyname("http", gurka) of + {error, einval} -> + ok; + {ok, 80} -> + case os:type() of + {unix, darwin} -> + %% Darwin seems to ignore the clearly invalid protocol + %% and just looks at the Service... + ok; + _ -> + ?P("Unexpected success"), + ?FAIL({"http", gurka}) + end + end, ?P("done"), ok. @@ -449,10 +478,12 @@ api_b_getservbyport() -> not_on_windows(fun() -> case net:getservbyport(80, udp) of {ok, STR} when (STR =:= "http") orelse + (STR =:= "www") orelse (STR =:= "WWW") -> ok; {error, Reason} -> case os:type() of - {unix, linux} -> + {unix, linux} + when (Reason =:= einval) -> %% This happens on some linux %% (Ubuntu 22 on Parallels ARM VM) ok; @@ -467,11 +498,26 @@ api_b_getservbyport() -> not_on_windows(fun() -> {ok, "snmp"} = net:getservbyport(161, tcp) end), not_on_windows(fun() -> {ok, "epmd"} = net:getservbyport(4369, tcp) end), not_on_windows(fun() -> {ok, "amqp"} = net:getservbyport(5672, tcp) end), - not_on_windows(fun() -> {ok, "amqp"} = net:getservbyport(5672, sctp) end), + not_on_windows(fun() -> + case net:getservbyport(5672, sctp) of + {ok, "amqp"} -> + ok; + {error, Reason} -> + case os:type() of + {unix, darwin} + when (Reason =:= einval) -> + ok; + _ -> + ?P("Unexpected failure: ~p", + [Reason]), + ?FAIL({"amap", sctp, Reason}) + end + end + end), ?P("A couple of (expected) failures"), - {error, einval} = net:getservbyport(11111, tcp), - {error, einval} = net:getservbyport(80, gurka), + {error, einval} = net:getservbyport(16#FFFF, tcp), + {error, einval} = net:getservbyport(80, gurka), ?P("done"), ok. From bc780565ad59161ee8a9e739cd240cd3bef25688 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 17 Apr 2024 16:04:11 +0200 Subject: [PATCH 077/422] [kernel|esock] Use 'net' instead of 'inet' when possible --- lib/kernel/src/socket.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/kernel/src/socket.erl b/lib/kernel/src/socket.erl index aea6690f45f8..57e319f907bd 100644 --- a/lib/kernel/src/socket.erl +++ b/lib/kernel/src/socket.erl @@ -2286,7 +2286,7 @@ fmt_sockaddr(#{family := local, fmt_port(N, Proto) -> - case inet:getservbyport(N, Proto) of + case net:getservbyport(N, Proto) of {ok, Name} -> f("~s (~w)", [Name, N]); _ -> integer_to_list(N) end. From 75a460d2d0a445372a8d6eb078a0bf8c5f49810c Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Tue, 14 May 2024 19:34:31 +0200 Subject: [PATCH 078/422] erts: Fix bug in return_to trace Generate a 'return_to' trace regardless how far up an exception is caught. The old behavior was to only generate return_to trace if the exception was caught by the nearest stack frame. According to this old comment it seemed to be by-design. But why? /* The stackframe closest to the catch contained an * return_to_trace entry, so since the execution now * continues after the catch, a return_to trace message * would be appropriate. */ --- erts/emulator/beam/beam_common.c | 15 +-- erts/emulator/test/trace_session_SUITE.erl | 133 ++++++++++++++++++++- lib/kernel/src/trace.erl | 24 ++-- 3 files changed, 151 insertions(+), 21 deletions(-) diff --git a/erts/emulator/beam/beam_common.c b/erts/emulator/beam/beam_common.c index afc7cb710037..5dc090db6199 100644 --- a/erts/emulator/beam/beam_common.c +++ b/erts/emulator/beam/beam_common.c @@ -614,22 +614,18 @@ next_catch(Process* c_p, Eterm *reg) { } else if (BeamIsReturnCallAccTrace(return_address)) { ptr += CP_SIZE + BEAM_RETURN_CALL_ACC_TRACE_FRAME_SZ; } else if (BeamIsReturnToTrace(return_address)) { - have_return_to_trace = 1; /* Record next cp */ + have_return_to_trace = 1; session_weak_id = frame[0]; return_to_trace_address = NULL; ptr += CP_SIZE + BEAM_RETURN_TO_TRACE_FRAME_SZ; } else { - /* This is an ordinary call frame: if the previous frame was a + /* This is an ordinary call frame: If a previous frame was a * return_to trace we should record this CP as a return_to * candidate. */ if (have_return_to_trace) { return_to_trace_address = return_address; - have_return_to_trace = 0; - } else { - return_to_trace_address = NULL; } - ptr += CP_SIZE; } } else { @@ -647,10 +643,9 @@ next_catch(Process* c_p, Eterm *reg) { ErtsTracerRef *ref = get_tracer_ref_from_weak_id(&c_p->common, session_weak_id); if (ref && IS_SESSION_TRACED_FL(ref, F_TRACE_RETURN_TO)) { - /* The stackframe closest to the catch contained an - * return_to_trace entry, so since the execution now - * continues after the catch, a return_to trace message - * would be appropriate. + /* + * Execution now continues after catching exception from + * return_to traced function(s). */ erts_trace_return_to(c_p, return_to_trace_address, session_weak_id); } diff --git a/erts/emulator/test/trace_session_SUITE.erl b/erts/emulator/test/trace_session_SUITE.erl index 73fc834971f0..e7d218b63760 100644 --- a/erts/emulator/test/trace_session_SUITE.erl +++ b/erts/emulator/test/trace_session_SUITE.erl @@ -32,6 +32,7 @@ basic/1, call/1, meta/1, + return_to/1, destroy/1, negative/1, error_info/1, @@ -47,7 +48,7 @@ -define(line,void). -endif. --export([foo/0, exported/1]). +-export([foo/0, exported/1, middle/1, bottom/1]). suite() -> [{ct_hooks,[ts_install_cth]}, @@ -65,6 +66,7 @@ all() -> test_set_on_first_spawn, test_set_on_link, test_set_on_first_link, + return_to, destroy, negative, error_info, @@ -1174,6 +1176,130 @@ meta(_Config) -> ok. +return_to(_Config) -> + Tester = self(), + Tracer1 = spawn_link(fun() -> tracer("Tracer1",Tester) end), + Tracer2 = spawn_link(fun() -> tracer("Tracer2",Tester) end), + + Tracee = self(), + S1 = trace:session_create(session1, Tracer1, []), + S2 = trace:session_create(session2, Tracer2, []), + + 1 = trace:process(S1, Tracee, true, [call, return_to, arity]), + 1 = trace:process(S2, Tracee, true, [call, return_to, arity]), + + TracedList = [[{S1, Tracer1, [bottom]}, + {S2, Tracer2, []}], + [{S1, Tracer1, [middle]}], + [{S1, Tracer1, [middle,bottom]}]], + + [begin + %% Set up tracing for all sessions + [begin + trace:function(Session, {?MODULE,'_','_'}, false, [local]), + [1 = trace:function(S1, {?MODULE,Func,'_'}, true, [local]) + || Func <- TracedFuncs] + end + || {Session, _Tracer, TracedFuncs} <- Traced], + + %% Execute test with both local and external calls + [return_to_do(MiddleCall, BottomCall, Traced) + || MiddleCall <- [local, extern], + BottomCall <- [local, extern]] + end + || Traced <- TracedList], + + true = trace:session_destroy(S1), + ok. + +return_to_do(MiddleCall, BottomCall, Traced) -> + Tracee = self(), + Script = [{[{'catch',MiddleCall}, {body,BottomCall}, exception], + #{[bottom] => [{call, bottom}, {return_to, top}], + [middle] => [{call, middle}, {return_to, top}], + [middle,bottom] => [{call, middle}, {call, bottom}, {return_to,top}] + }}, + + {[{'catch',MiddleCall}, {'catch',BottomCall}, exception], + #{[bottom] => [{call, bottom}, {return_to, middle}], + [middle] => [{call, middle}, {return_to, top}], + [middle,bottom] => [{call, middle}, {call, bottom}, {return_to,middle}, {return_to,top}] + }}, + + {[{'catch',MiddleCall}, {tail,BottomCall}, exception], + #{[bottom] => [{call, bottom}, {return_to, top}], + [middle] => [{call, middle}, {return_to, top}], + [middle,bottom] => [{call, middle}, {call, bottom}, {return_to,top}] + }}, + + {[{'catch',MiddleCall}, {body,BottomCall}, return], + #{[bottom] => [{call, bottom}, {return_to, middle}], + [middle] => [{call, middle}, {return_to, top}], + [middle,bottom] => [{call, middle}, {call, bottom}, {return_to,middle}, {return_to,top}] + }}, + + {[{'catch',MiddleCall}, {'catch',BottomCall}, return], + #{[bottom] => [{call,bottom}, {return_to,middle}], + [middle] => [{call, middle}, {return_to, top}], + [middle,bottom] => [{call, middle}, {call, bottom}, {return_to,middle}, {return_to,top}] + }}, + + {[{'catch',MiddleCall}, {tail,BottomCall}, return], + #{[bottom] => [{call,bottom}, {return_to,top}], + [middle] => [{call, middle}, {return_to, top}], + [middle,bottom] => [{call, middle}, {call, bottom}, {return_to,top}] + }} + ], + + [begin + %% Make the call sequence + top(CallSequence), + + %% Construct expected trace messages + Exp = [[{Tracer, {trace, Tracee, CallOrReturnTo, {?MODULE, Func, 1}}} + || {CallOrReturnTo, Func} <- maps:get(TracedFuncs, TraceMap, [])] + || {_Session, Tracer, TracedFuncs} <- Traced], + + + receive_parallel_list(Exp) + end + || {CallSequence, TraceMap} <- Script], + ok. + +top([{'catch',local} | T]) -> + erlang:display("top(catch local)"), + [(catch middle(T)) | 1]; +top([{'catch',extern} | T]) -> + erlang:display("top(catch extern)"), + [(catch ?MODULE:middle(T)) | 1]. + +middle([{body,local} | T]) -> + erlang:display("middle(local)"), + [bottom(T) | 1]; +middle([{body,extern} | T]) -> + erlang:display("middle(extern)"), + [?MODULE:bottom(T) | 1]; +middle([{'catch',local} | T]) -> + erlang:display("middle(catch local)"), + [(catch bottom(T)) | 1]; +middle([{'catch',extern} | T]) -> + erlang:display("middle(catch extern)"), + [(catch ?MODULE:bottom(T)) | 1]; +middle([{tail,local} | T]) -> + erlang:display("middle(tail local)"), + bottom(T); +middle([{tail,extern} | T]) -> + erlang:display("middle(tail extern)"), + ?MODULE:bottom(T). + +bottom([return | T]) -> + erlang:display("bottom(return)"), + T; +bottom([exception]) -> + erlang:display("bottom(exception)"), + error(exception). + + destroy(_Config) -> Name = ?MODULE, {_,SName1}=S1 = trace:session_create(Name, self(), []), @@ -1415,6 +1541,11 @@ receive_parallel(M, Tuple, 0) -> io:format("Got message:\n~p\n", [M]), ct:fail("Unexpected messages: ~p", [M]). +%% Same as receive_parallel/1 but accepts a *list* of message lists +%% and the message lists are allowed to be empty meaning no expected messages. +receive_parallel_list(List0) -> + List1 = lists:filter(fun(E) -> E =/= [] end, List0), + receive_parallel(list_to_tuple(List1)). receive_unsorted(Expect) -> receive_unsorted(Expect, length(Expect)). diff --git a/lib/kernel/src/trace.erl b/lib/kernel/src/trace.erl index 20262ffa17ff..05a63ccd1ee7 100644 --- a/lib/kernel/src/trace.erl +++ b/lib/kernel/src/trace.erl @@ -278,16 +278,20 @@ tags" refers to the list of [`trace messages`](#process_trace_messages)): [`return_to`](#process_trace_messages_return_to). Or rather, the absence of. -- **`return_to`** - Used with the `call` trace flag. Traces the return from a - traced function back to its caller. Only works for functions traced with - option `local` to `function/4`. - - The semantics is that a trace message is sent when a call traced function - returns, that is, when a chain of tail recursive calls ends. Only one trace - message is sent per chain of tail recursive calls, so the properties of tail - recursiveness for function calls are kept while tracing with this flag. Using - `call` and `return_to` trace together makes it possible to know exactly in - which function a process executes at any time. +- **`return_to`** - Used with the `call` trace flag. Traces the exit from + call traced functions back to where the execution resumes. Only works for + functions traced with option `local` to `function/4`. + + The semantics is that a `return_to` trace message is sent when a call traced + function returns or throws and exception that is caught. For tail calls, only + one trace message is sent per chain of tail calls, so the properties of tail + recursiveness for function calls are kept while tracing with this + flag. Similar for exceptions, only one `return_to` trace message is sent, even + if the exception passed more than one call traced function before it was + caught. + + Using `call` and `return_to` trace together makes it possible to know exactly + in which function a process executes at any time. To get trace messages containing return values from functions, use the `{return_trace}` match specification action instead. From d90146606fe1a0ed251732f7a17425b27b5d7e08 Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Wed, 15 May 2024 19:26:37 +0200 Subject: [PATCH 079/422] erts: Fix multiple return_to trace sessions --- erts/emulator/beam/beam_bp.c | 10 +-- erts/emulator/beam/beam_common.c | 56 +++++++++------- erts/emulator/beam/emu/trace_instrs.tab | 9 ++- erts/emulator/beam/erl_process.h | 3 +- erts/emulator/beam/erl_trace.c | 14 ++-- erts/emulator/beam/erl_trace.h | 2 +- erts/emulator/beam/jit/beam_jit_common.cpp | 8 ++- erts/emulator/test/trace_session_SUITE.erl | 77 +++++++++++++++------- 8 files changed, 116 insertions(+), 63 deletions(-) diff --git a/erts/emulator/beam/beam_bp.c b/erts/emulator/beam/beam_bp.c index 74be1ca76f63..aa6027e59eeb 100644 --- a/erts/emulator/beam/beam_bp.c +++ b/erts/emulator/beam/beam_bp.c @@ -877,6 +877,7 @@ erts_clear_all_export_break(Module* modp, Export *ep) */ static void fixup_cp_before_trace(Process *c_p, Eterm cp_save[2], + ErtsTraceSession* session, int *return_to_trace) { const ErtsFrameLayout frame_layout = erts_frame_layout; @@ -892,15 +893,16 @@ static void fixup_cp_before_trace(Process *c_p, for (;;) { ErtsCodePtr w; - - erts_inspect_frame(cpp, &w); + const Eterm *frame = erts_inspect_frame(cpp, &w); if (BeamIsReturnTrace(w)) { cpp += CP_SIZE + BEAM_RETURN_TRACE_FRAME_SZ; } else if (BeamIsReturnCallAccTrace(w)) { cpp += CP_SIZE + BEAM_RETURN_CALL_ACC_TRACE_FRAME_SZ; } else if (BeamIsReturnToTrace(w)) { - *return_to_trace = 1; + if (frame[0] == session->weak_id) { + *return_to_trace = 1; + } cpp += CP_SIZE + BEAM_RETURN_TO_TRACE_FRAME_SZ; } else { if (frame_layout == ERTS_FRAME_LAYOUT_FP_RA) { @@ -1108,7 +1110,7 @@ do_call_trace(Process* c_p, ErtsCodeInfo* info, Eterm* reg, Uint need = 0; Eterm* E; - fixup_cp_before_trace(c_p, cp_save, &return_to_trace); + fixup_cp_before_trace(c_p, cp_save, session, &return_to_trace); ERTS_UNREQ_PROC_MAIN_LOCK(c_p); flags = erts_call_trace(c_p, info, ms, reg, local, ref, &tracer); diff --git a/erts/emulator/beam/beam_common.c b/erts/emulator/beam/beam_common.c index 5dc090db6199..a4e4e42eb1d1 100644 --- a/erts/emulator/beam/beam_common.c +++ b/erts/emulator/beam/beam_common.c @@ -573,11 +573,13 @@ handle_error(Process* c_p, ErtsCodePtr pc, Eterm* reg, static ErtsCodePtr next_catch(Process* c_p, Eterm *reg) { int active_catches = c_p->catches > 0; - ErtsCodePtr return_to_trace_address = NULL; + ErtsCodePtr return_address = NULL; int have_return_to_trace = 0; - Eterm session_weak_id = NIL; Eterm *ptr, *prev; ErtsCodePtr handler; +#ifdef DEBUG + ErtsCodePtr dbg_return_to_trace_address = NULL; +#endif ptr = prev = c_p->stop; ASSERT(ptr < STACK_START(c_p)); @@ -592,7 +594,6 @@ next_catch(Process* c_p, Eterm *reg) { ptr++; } else if (is_CP(val)) { - ErtsCodePtr return_address; const Eterm *frame; prev = ptr; @@ -614,40 +615,49 @@ next_catch(Process* c_p, Eterm *reg) { } else if (BeamIsReturnCallAccTrace(return_address)) { ptr += CP_SIZE + BEAM_RETURN_CALL_ACC_TRACE_FRAME_SZ; } else if (BeamIsReturnToTrace(return_address)) { - have_return_to_trace = 1; - session_weak_id = frame[0]; - return_to_trace_address = NULL; - + ErtsTracerRef *ref = get_tracer_ref_from_weak_id(&c_p->common, + frame[0]); + if (ref && IS_SESSION_TRACED_FL(ref, F_TRACE_RETURN_TO)) { + ref->flags |= F_TRACE_RETURN_TO_MARK; + have_return_to_trace = 1; + } ptr += CP_SIZE + BEAM_RETURN_TO_TRACE_FRAME_SZ; } else { - /* This is an ordinary call frame: If a previous frame was a - * return_to trace we should record this CP as a return_to - * candidate. */ - if (have_return_to_trace) { - return_to_trace_address = return_address; - } + #ifdef DEBUG + dbg_return_to_trace_address = return_address; + #endif ptr += CP_SIZE; } } else { ptr++; } } - + if (have_return_to_trace) { + ErtsTracerRef *ref; + for (ref = c_p->common.tracee.first_ref; ref; ref = ref->next) { + ref->flags &= ~F_TRACE_RETURN_TO_MARK; + } + } return NULL; found_catch: ASSERT(ptr < STACK_START(c_p)); c_p->stop = prev; - if (return_to_trace_address) { - ErtsTracerRef *ref = get_tracer_ref_from_weak_id(&c_p->common, - session_weak_id); - if (ref && IS_SESSION_TRACED_FL(ref, F_TRACE_RETURN_TO)) { - /* - * Execution now continues after catching exception from - * return_to traced function(s). - */ - erts_trace_return_to(c_p, return_to_trace_address, session_weak_id); + if (have_return_to_trace) { + ErtsTracerRef *ref; + /* + * Execution now continues after catching exception from + * return_to traced function(s). + */ + ASSERT(return_address == dbg_return_to_trace_address); + + for (ref = c_p->common.tracee.first_ref; ref; ref = ref->next) { + if (ref->flags & F_TRACE_RETURN_TO_MARK) { + ASSERT(IS_SESSION_TRACED_FL(ref, F_TRACE_RETURN_TO)); + erts_trace_return_to(c_p, return_address, ref); + ref->flags &= ~F_TRACE_RETURN_TO_MARK; + } } } diff --git a/erts/emulator/beam/emu/trace_instrs.tab b/erts/emulator/beam/emu/trace_instrs.tab index 048619e35191..4f1b4cef913a 100644 --- a/erts/emulator/beam/emu/trace_instrs.tab +++ b/erts/emulator/beam/emu/trace_instrs.tab @@ -69,8 +69,11 @@ i_call_trace_return() { } i_return_to_trace() { - if (ERTS_IS_P_TRACED_FL(c_p, F_TRACE_RETURN_TO)) { - Eterm session_id = E[1]; + ErtsTracerRef *ref = get_tracer_ref_from_weak_id(&c_p->common, E[1]); + + if (!ERTS_IS_PROC_SENSITIVE(c_p) + && ref && IS_SESSION_TRACED_FL(ref, F_TRACE_RETURN_TO)) { + Uint *cpp = (Uint*) E + 1; while (is_not_CP(*cpp)) { @@ -92,7 +95,7 @@ i_return_to_trace() { } SWAPOUT; /* Needed for shared heap */ ERTS_UNREQ_PROC_MAIN_LOCK(c_p); - erts_trace_return_to(c_p, cp_val(*cpp), session_id); + erts_trace_return_to(c_p, cp_val(*cpp), ref); ERTS_REQ_PROC_MAIN_LOCK(c_p); SWAPIN; } diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h index b3eae36e7089..5ded94ac4cca 100644 --- a/erts/emulator/beam/erl_process.h +++ b/erts/emulator/beam/erl_process.h @@ -1689,9 +1689,10 @@ extern int erts_system_profile_ts_type; #define F_TRACE_PORTS F_TRACE_FLAG(19) /* Ports equivalent to F_TRACE_PROCS */ #define F_TRACE_SCHED_NO F_TRACE_FLAG(20) /* Trace with scheduler id */ #define F_TRACE_SCHED_EXIT F_TRACE_FLAG(21) +#define F_TRACE_RETURN_TO_MARK F_TRACE_FLAG(22) /* temporary marker */ -#define F_NUM_FLAGS (ERTS_TRACE_TS_TYPE_BITS + 22) +#define F_NUM_FLAGS (ERTS_TRACE_TS_TYPE_BITS + 23) #ifdef DEBUG // Was there a point with this high 5? # define F_INITIAL_TRACE_FLAGS 0 //(5 << F_NUM_FLAGS) diff --git a/erts/emulator/beam/erl_trace.c b/erts/emulator/beam/erl_trace.c index 2be1830c21a4..6e0301fe1e3e 100644 --- a/erts/emulator/beam/erl_trace.c +++ b/erts/emulator/beam/erl_trace.c @@ -991,15 +991,10 @@ seq_trace_output_generic(Eterm token, Eterm msg, Uint type, * or {trace, Pid, return_to, {Mod, Func, Arity}} */ void -erts_trace_return_to(Process *p, ErtsCodePtr pc, Eterm session_weak_id) +erts_trace_return_to(Process *p, ErtsCodePtr pc, ErtsTracerRef *ref) { const ErtsCodeMFA *cmfa; Eterm mfa; - ErtsTracerRef *ref; - - ref = get_tracer_ref_from_weak_id(&p->common, session_weak_id); - if (!ref) - return; cmfa = erts_find_function_from_pc(pc); @@ -3326,7 +3321,12 @@ ErtsTracerRef* get_tracer_ref_from_weak_id(ErtsPTabElementCommon* t_p, { ErtsTracerRef* ref; - ASSERT(t_p->tracee.all_trace_flags == erts_sum_all_trace_flags(t_p)); +#ifdef DEBUG + { + Uint32 all = erts_sum_all_trace_flags(t_p) & ~F_TRACE_RETURN_TO_MARK; + ASSERT(all == t_p->tracee.all_trace_flags); + } +#endif for (ref = t_p->tracee.first_ref; ref; ref = ref->next) if (ref->session->weak_id == weak_id) diff --git a/erts/emulator/beam/erl_trace.h b/erts/emulator/beam/erl_trace.h index 23d7f81bc1ef..212bda587829 100644 --- a/erts/emulator/beam/erl_trace.h +++ b/erts/emulator/beam/erl_trace.h @@ -184,7 +184,7 @@ void erts_trace_return(Process* p, ErtsCodeMFA *mfa, Eterm retval, ErtsTracer tracer, Eterm session_weak_id); void erts_trace_exception(Process* p, ErtsCodeMFA *mfa, Eterm class_, Eterm value, ErtsTracer tracer, Eterm session_weak_id); -void erts_trace_return_to(Process *p, ErtsCodePtr pc, Eterm session_weak_id); +void erts_trace_return_to(Process *p, ErtsCodePtr pc, ErtsTracerRef *ref); void trace_sched(Process*, ErtsProcLocks, Eterm, Uint32 trace_flag); void trace_sched_session(Process*, ErtsProcLocks, Eterm what, ErtsTracerRef*); void trace_proc(Process*, ErtsProcLocks, Process*, Eterm, Eterm); diff --git a/erts/emulator/beam/jit/beam_jit_common.cpp b/erts/emulator/beam/jit/beam_jit_common.cpp index 1f2957addbab..c0c304e87d52 100644 --- a/erts/emulator/beam/jit/beam_jit_common.cpp +++ b/erts/emulator/beam/jit/beam_jit_common.cpp @@ -1235,7 +1235,11 @@ void beam_jit_timeout_locked(Process *c_p) { void beam_jit_return_to_trace(Process *c_p, Eterm session_weak_id, Eterm *frame) { - if (ERTS_IS_P_TRACED_FL(c_p, F_TRACE_RETURN_TO)) { + ErtsTracerRef *ref = + get_tracer_ref_from_weak_id(&c_p->common, session_weak_id); + + if (!ERTS_IS_PROC_SENSITIVE(c_p) && ref && + IS_SESSION_TRACED_FL(ref, F_TRACE_RETURN_TO)) { ErtsCodePtr return_to_address; Uint *cpp; @@ -1257,7 +1261,7 @@ void beam_jit_return_to_trace(Process *c_p, } ERTS_UNREQ_PROC_MAIN_LOCK(c_p); - erts_trace_return_to(c_p, return_to_address, session_weak_id); + erts_trace_return_to(c_p, return_to_address, ref); ERTS_REQ_PROC_MAIN_LOCK(c_p); } } diff --git a/erts/emulator/test/trace_session_SUITE.erl b/erts/emulator/test/trace_session_SUITE.erl index e7d218b63760..37afa99be9c6 100644 --- a/erts/emulator/test/trace_session_SUITE.erl +++ b/erts/emulator/test/trace_session_SUITE.erl @@ -1177,9 +1177,11 @@ meta(_Config) -> ok. return_to(_Config) -> + %%put(display, true), %% To get some usable debug printouts + Tester = self(), - Tracer1 = spawn_link(fun() -> tracer("Tracer1",Tester) end), - Tracer2 = spawn_link(fun() -> tracer("Tracer2",Tester) end), + Tracer1 = spawn_link(fun() -> tracer("Tracer1",Tester,get(display)) end), + Tracer2 = spawn_link(fun() -> tracer("Tracer2",Tester,get(display)) end), Tracee = self(), S1 = trace:session_create(session1, Tracer1, []), @@ -1188,26 +1190,29 @@ return_to(_Config) -> 1 = trace:process(S1, Tracee, true, [call, return_to, arity]), 1 = trace:process(S2, Tracee, true, [call, return_to, arity]), - TracedList = [[{S1, Tracer1, [bottom]}, - {S2, Tracer2, []}], - [{S1, Tracer1, [middle]}], - [{S1, Tracer1, [middle,bottom]}]], - [begin + Traced = [{S1, Tracer1, Funcs1}, + {S2, Tracer2, Funcs2}], + %% Set up tracing for all sessions [begin trace:function(Session, {?MODULE,'_','_'}, false, [local]), - [1 = trace:function(S1, {?MODULE,Func,'_'}, true, [local]) + [begin + io_format("trace:function(~p) for tracer ~p\n", [Func, Tracer]), + 1 = trace:function(Session, {?MODULE,Func,'_'}, true, [local]) + end || Func <- TracedFuncs] end - || {Session, _Tracer, TracedFuncs} <- Traced], + || {Session, Tracer, TracedFuncs} <- Traced], %% Execute test with both local and external calls [return_to_do(MiddleCall, BottomCall, Traced) || MiddleCall <- [local, extern], BottomCall <- [local, extern]] end - || Traced <- TracedList], + || Funcs1 <- [[bottom], [middle], [middle,bottom]], + Funcs2 <- [[bottom], [middle], [middle,bottom]] + ], true = trace:session_destroy(S1), ok. @@ -1253,6 +1258,7 @@ return_to_do(MiddleCall, BottomCall, Traced) -> [begin %% Make the call sequence + io_format("CallSequence = ~p\n", [CallSequence]), top(CallSequence), %% Construct expected trace messages @@ -1261,44 +1267,60 @@ return_to_do(MiddleCall, BottomCall, Traced) -> || {_Session, Tracer, TracedFuncs} <- Traced], + io_format("Exp = ~p\n", [Exp]), receive_parallel_list(Exp) end || {CallSequence, TraceMap} <- Script], ok. top([{'catch',local} | T]) -> - erlang:display("top(catch local)"), + display("top(catch local)"), [(catch middle(T)) | 1]; top([{'catch',extern} | T]) -> - erlang:display("top(catch extern)"), + display("top(catch extern)"), [(catch ?MODULE:middle(T)) | 1]. middle([{body,local} | T]) -> - erlang:display("middle(local)"), + display("middle(local)"), [bottom(T) | 1]; middle([{body,extern} | T]) -> - erlang:display("middle(extern)"), + display("middle(extern)"), [?MODULE:bottom(T) | 1]; middle([{'catch',local} | T]) -> - erlang:display("middle(catch local)"), + display("middle(catch local)"), [(catch bottom(T)) | 1]; middle([{'catch',extern} | T]) -> - erlang:display("middle(catch extern)"), + display("middle(catch extern)"), [(catch ?MODULE:bottom(T)) | 1]; middle([{tail,local} | T]) -> - erlang:display("middle(tail local)"), + display("middle(tail local)"), bottom(T); middle([{tail,extern} | T]) -> - erlang:display("middle(tail extern)"), + display("middle(tail extern)"), ?MODULE:bottom(T). bottom([return | T]) -> - erlang:display("bottom(return)"), + display("bottom(return)"), T; bottom([exception]) -> - erlang:display("bottom(exception)"), + display("bottom(exception)"), error(exception). +display(Term) -> + case get(display) of + true -> + erlang:display(Term); + _ -> + true + end. + +io_format(Frmt, List) -> + case get(display) of + true -> + io:format(Frmt, List); + _ -> + ok + end. destroy(_Config) -> Name = ?MODULE, @@ -1497,11 +1519,22 @@ local(_) -> ok. tracer(Name, Tester) -> + tracer(Name, Tester, true). + +tracer(Name, Tester, Display) -> + case Display of + true -> put(display,true); + _ -> ok + end, + tracer_loop(Name, Tester). + + +tracer_loop(Name, Tester) -> receive M -> - io:format("~p ~p got message: ~p\n", [Name, self(), M]), + io_format("~p ~p got message: ~p\n", [Name, self(), M]), Tester ! {self(), M} end, - tracer(Name, Tester). + tracer_loop(Name, Tester). receive_any() -> From 96f08b9897734145f3288ea48c8fd5238a4407bb Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Tue, 21 May 2024 17:00:35 +0200 Subject: [PATCH 080/422] kernel: Fix typos on trace.erl docs --- lib/kernel/src/trace.erl | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/lib/kernel/src/trace.erl b/lib/kernel/src/trace.erl index 05a63ccd1ee7..087bf005e4f3 100644 --- a/lib/kernel/src/trace.erl +++ b/lib/kernel/src/trace.erl @@ -95,6 +95,7 @@ on the same local node as the call is made. To trace remote nodes use `m:dbg` or > | [`erlang:trace(processes, ...)`][1] | [`process(S, all, ...)`][p] | > | [`erlang:trace(existing_processes, ...)`][1] | [`process(S, existing, ...)`][p] | > | [`erlang:trace(new_processes, ...)`][1] | [`process(S, new, ...)`][p] | +> | [`erlang:trace(Port, ...)`][1] | [`port(S, Port, ...)`][o] | > | [`erlang:trace(ports, ...)`][1] | [`port(S, all, ...)`][o] | > | [`erlang:trace(existing_ports, ...)`][1] | [`port(S, existing, ...)`][o] | > | [`erlang:trace(new_ports, ...)`][1] | [`port(S, new, ...)`][o] | @@ -226,7 +227,7 @@ Turn on or off trace flags for one or more processes. Argument `Session` is the trace session to operate on as returned by `session_create/3`. -Argument `PidSpec` is either a process identifier (pid) for a local process or +Argument `Procs` is either a process identifier (pid) for a local process or one of the following atoms: - **`all`** - All currently existing processes and all that will be @@ -343,7 +344,7 @@ tags" refers to the list of [`trace messages`](#process_trace_messages)): - **`cpu_timestamp`** - A global trace flag for the Erlang node that makes all trace time stamps using flag `timestamp` to be in CPU time, not wall clock time. That is, `cpu_timestamp` is not be used if `monotonic_timestamp` or - `strict_monotonic_timestamp` is enabled. Only allowed with `PidPortSpec==all`. + `strict_monotonic_timestamp` is enabled. Only allowed with `Procs==all`. If the host machine OS does not support high-resolution CPU time measurements, `process/4` exits with `badarg`. Notice that most OS do not synchronize this value across cores, so be prepared that time can seem to go @@ -574,10 +575,10 @@ Trace messages: If the tracing process dies or the tracer module returns `remove`, the flags are silently removed. -Returns a number indicating the number of processes that matched `PidSpec`. -If `PidSpec` is a process identifier, the return value is `1`. If -`PidSpec` is `all` or `existing`, the return value is the number of -processes running. If `PidSpec` is `new`, the return value is `0`. +Returns a number indicating the number of processes that matched `Procs`. +If `Procs` is a process identifier, the return value is `1`. If +`Procs` is `all` or `existing`, the return value is the number of +processes running. If `Procs` is `new`, the return value is `0`. Failure: `badarg` if the specified arguments are not supported. For example, `cpu_timestamp` is not supported on all platforms. @@ -614,7 +615,7 @@ Turn on or off trace flags for one or more ports. Argument `Session` is the trace session to operate on as returned by `session_create/3`. -`PortSpec` is either a port identifier for a local port or one of the following atoms: +`Ports` is either a port identifier for a local port or one of the following atoms: - **`all`** - All currently existing ports and all that will be created in the future. @@ -729,10 +730,10 @@ Trace messages: If the tracing process/port dies or the tracer module returns `remove`, the flags are silently removed. -Returns a number indicating the number of ports that matched `PortSpec`. -If `PortSpec` is a port identifier, the return value is `1`. If -`PortSpec` is `all` or `existing`, the return value is the number of -existing ports. If `PortSpec` is `new`, the return value is `0`. +Returns a number indicating the number of ports that matched `Ports`. +If `Ports` is a port identifier, the return value is `1`. If +`Ports` is `all` or `existing`, the return value is the number of +existing ports. If `Ports` is `new`, the return value is `0`. Failure: `badarg` if the specified arguments are not supported. For example, `cpu_timestamp` is not supported on all platforms. From f9b4b53bac233c5d27401f19e21917d80c20208a Mon Sep 17 00:00:00 2001 From: Sverker Eriksson Date: Wed, 22 May 2024 17:16:44 +0200 Subject: [PATCH 081/422] erts: Fix test treatment of trace flag cpu_timestmap --- erts/emulator/test/trace_sessions.erl | 68 ++++++++++++++++++--------- 1 file changed, 45 insertions(+), 23 deletions(-) diff --git a/erts/emulator/test/trace_sessions.erl b/erts/emulator/test/trace_sessions.erl index 365bad08023c..ea3e6e00a98c 100644 --- a/erts/emulator/test/trace_sessions.erl +++ b/erts/emulator/test/trace_sessions.erl @@ -146,35 +146,57 @@ erlang_trace_pattern(MFA, MS, FlagList) -> end. %% Wrap erlang:trace/3 -erlang_trace(PidPortSpec, How, FlagList) -> +erlang_trace(PidPortSpec, How, FlagList0) -> case ets:lookup(?MODULE, dynamic_session) of [] -> - erlang:trace(PidPortSpec, How, FlagList); + erlang:trace(PidPortSpec, How, FlagList0); [{dynamic_session, S}] -> - if is_pid(PidPortSpec); - PidPortSpec =:= processes; - PidPortSpec =:= existing_processes; - PidPortSpec =:= new_processes -> - trace:process(S, PidPortSpec, How, FlagList); - - is_port(PidPortSpec); - PidPortSpec =:= ports; - PidPortSpec =:= existing_ports; - PidPortSpec =:= new_ports -> - trace:port(S, PidPortSpec, How, FlagList); - - PidPortSpec =:= all; - PidPortSpec =:= existing; - PidPortSpec =:= new -> - trace:process(S, PidPortSpec, How, FlagList), - trace:port(S, PidPortSpec, How, FlagList); - - true -> - %% Must be negative testing - trace:process(S, PidPortSpec, How, FlagList) + case handle_cpu_timestamp(PidPortSpec, How, FlagList0) of + {true, Ret, []} -> + Ret; + {_, _, FlagList1} -> + if is_pid(PidPortSpec); + PidPortSpec =:= processes; + PidPortSpec =:= existing_processes; + PidPortSpec =:= new_processes -> + trace:process(S, PidPortSpec, How, FlagList1); + + is_port(PidPortSpec); + PidPortSpec =:= ports; + PidPortSpec =:= existing_ports; + PidPortSpec =:= new_ports -> + trace:port(S, PidPortSpec, How, FlagList1); + + PidPortSpec =:= all; + PidPortSpec =:= existing; + PidPortSpec =:= new -> + trace:process(S, PidPortSpec, How, FlagList1), + trace:port(S, PidPortSpec, How, FlagList1); + + true -> + %% Must be negative testing + trace:process(S, PidPortSpec, How, FlagList1) + end end end. +handle_cpu_timestamp(all, How, FlagList) -> + case lists:member(cpu_timestamp, FlagList) of + true -> + %% Do special call for ugly duckling 'cpu_timestamp' + %% not (yet) supported by module 'trace'. + Ret = erlang:trace(all, How, [cpu_timestamp]), + FlagListRest = lists:filter(fun(E) -> E =/= cpu_timestamp end, + FlagList), + {true, Ret, FlagListRest}; + + false -> + {false, void, FlagList} + end; +handle_cpu_timestamp(_, _, FlagList) -> + {false, void, FlagList}. + + %% Wrap erlang:trace_info/2 erlang_trace_info(PidPortFuncEvent, Item) -> From 0ac6bc969a347d4a99bc27214ac2cb0f6442d639 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 27 May 2024 16:24:42 +0200 Subject: [PATCH 082/422] [net] Tweaked the since attributes Tweaked the since attributes of the getservby[name|port] functions. OTP-19101 --- lib/kernel/src/net.erl | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/lib/kernel/src/net.erl b/lib/kernel/src/net.erl index dc04cee4af1b..783e847b8446 100644 --- a/lib/kernel/src/net.erl +++ b/lib/kernel/src/net.erl @@ -905,7 +905,7 @@ iat_broadaddr({A1, A2, A3, A4}, {M1, M2, M3, M4}) -> %% -doc(#{equiv => getservbyname(Name, any)}). --doc(#{since => <<"OTP FOOBAR">>}). +-doc(#{since => <<"OTP @OTP-19101@">>}). -spec getservbyname(Name) -> {ok, PortNumber} | {error, Reason} when Name :: atom() | string(), @@ -920,7 +920,7 @@ Get service by name. This function is used to get the port number of the specified protocol for the named service. """. --doc(#{since => <<"OTP FOOBAR">>}). +-doc(#{since => <<"OTP @OTP-19101@">>}). -spec getservbyname(Name, Protocol) -> {ok, PortNumber} | {error, Reason} when Name :: atom() | string(), @@ -943,7 +943,7 @@ getservbyname(Name, Protocol) %% -doc(#{equiv => getservbyport(PortNumber, any)}). --doc(#{since => <<"OTP FOOBAR">>}). +-doc(#{since => <<"OTP @OTP-19101@">>}). -spec getservbyport(PortNumber) -> {ok, Name} | {error, Reason} when PortNumber :: socket:port_number(), @@ -958,7 +958,7 @@ Get service by name. This function is used to get the service name of the specified protocol for the given port number. """. --doc(#{since => <<"OTP FOOBAR">>}). +-doc(#{since => <<"OTP @OTP-19101@">>}). -spec getservbyport(PortNumber, Protocol) -> {ok, Name} | {error, Reason} when PortNumber :: socket:port_number(), From 73ab1309ab6fe5859599fcbd44714d0f6f005e3d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Mon, 20 May 2024 08:46:12 +0200 Subject: [PATCH 083/422] erl_syntax: Polish documentation after migration to Markdown --- lib/syntax_tools/src/erl_syntax.erl | 5552 +++++++-------------------- 1 file changed, 1418 insertions(+), 4134 deletions(-) diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl index 79f67aa45fc5..a6fd397fda07 100644 --- a/lib/syntax_tools/src/erl_syntax.erl +++ b/lib/syntax_tools/src/erl_syntax.erl @@ -24,67 +24,13 @@ %% @end %% ===================================================================== -%% @doc Abstract Erlang syntax trees. -%% -%% This module defines an abstract data type for representing Erlang -%% source code as syntax trees, in a way that is backwards compatible -%% with the data structures created by the Erlang standard library -%% parser module `erl_parse' (often referred to as "parse -%% trees", which is a bit of a misnomer). This means that all -%% `erl_parse' trees are valid abstract syntax trees, but the -%% reverse is not true: abstract syntax trees can in general not be used -%% as input to functions expecting an `erl_parse' tree. -%% However, as long as an abstract syntax tree represents a correct -%% Erlang program, the function {@link revert/1} should be able to -%% transform it to the corresponding `erl_parse' -%% representation. -%% -%% A recommended starting point for the first-time user is the documentation -%% of the {@link syntaxTree()} data type, and the function {@link type/1}. -%% -%% == NOTES: == -%% -%% This module deals with the composition and decomposition of -%% syntactic entities (as opposed to semantic ones); its -%% purpose is to hide all direct references to the data structures used -%% to represent these entities. With few exceptions, the functions in -%% this module perform no semantic interpretation of their inputs, and -%% in general, the user is assumed to pass type-correct arguments - if -%% this is not done, the effects are not defined. -%% -%% With the exception of the {@link erl_parse()} data structures, -%% the internal representations of abstract syntax trees are subject to -%% change without notice, and should not be documented outside this -%% module. Furthermore, we do not give any guarantees on how an abstract -%% syntax tree may or may not be represented, with the following -%% exceptions: no syntax tree is represented by a single atom, such -%% as `none', by a list constructor `[X | Y]', or -%% by the empty list `[]'. This can be relied on when writing -%% functions that operate on syntax trees. - -%% @type syntaxTree(). An abstract syntax tree. The {@link erl_parse()} -%% "parse tree" representation is a proper subset of the `syntaxTree()' -%% representation. -%% -%% Every abstract syntax tree node has a type, given by the -%% function {@link type/1}. Each node also has associated -%% attributes; see {@link get_attrs/1} for details. The functions -%% {@link make_tree/2} and {@link subtrees/1} are generic -%% constructor/decomposition functions for abstract syntax trees. The -%% functions {@link abstract/1} and {@link concrete/1} convert between -%% constant Erlang terms and their syntactic representations. The set of -%% syntax tree nodes is extensible through the {@link tree/2} function. -%% -%% A syntax tree can be transformed to the {@link erl_parse()} -%% representation with the {@link revert/1} function. - -module(erl_syntax). -moduledoc """ Abstract Erlang syntax trees. This module defines an abstract data type for representing Erlang source code as syntax trees, in a way that is backwards compatible with the data structures -created by the Erlang standard library parser module `erl_parse` (often referred +created by the Erlang standard library parser module `m:erl_parse` (often referred to as "parse trees", which is a bit of a misnomer). This means that all `erl_parse` trees are valid abstract syntax trees, but the reverse is not true: abstract syntax trees can in general not be used as input to functions expecting @@ -95,14 +41,14 @@ to the corresponding `erl_parse` representation. A recommended starting point for the first-time user is the documentation of the [`syntaxTree()`](`t:syntaxTree/0`) data type, and the function `type/1`. -### NOTES: - -This module deals with the composition and decomposition of _syntactic_ entities -(as opposed to semantic ones); its purpose is to hide all direct references to -the data structures used to represent these entities. With few exceptions, the -functions in this module perform no semantic interpretation of their inputs, and -in general, the user is assumed to pass type-correct arguments - if this is not -done, the effects are not defined. +> #### Note {: .info } +> +> This module deals with the composition and decomposition of _syntactic_ entities +> (as opposed to semantic ones); its purpose is to hide all direct references to +> the data structures used to represent these entities. With few exceptions, the +> functions in this module perform no semantic interpretation of their inputs, and +> in general, the user is assumed to pass type-correct arguments — if this is not +> done, the effects are not defined. With the exception of the [`erl_parse()`](`t:erl_parse/0`) data structures, the internal representations of abstract syntax trees are subject to change without @@ -523,197 +469,86 @@ trees. %% %% ===================================================================== - -%% ===================================================================== -%% @doc Returns the type tag of `Node'. If `Node' -%% does not represent a syntax tree, evaluation fails with reason -%% `badarg'. Node types currently defined by this module are: -%% -%%
-%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%%
applicationannotated_typearity_qualifieratom
attributebinarybinary_fieldbitstring_type
block_exprcase_exprcatch_exprchar
class_qualifierclausecommentconjunction
constrained_function_typeconstraintdisjunction
else_expreof_markererror_marker
floatform_listfun_exprfun_typefunctionfunction_typegenerator
if_exprimplicit_funinfix_exprinteger
integer_range_typelistlist_compmacro
map_exprmap_field_assocmap_field_exactmap_type
map_type_assocmap_type_exactmatch_expr
maybe_exprmaybe_match_exprmodule_qualifier
named_fun_exprniloperatorparentheses
prefix_exprreceive_exprrecord_accessrecord_expr
record_fieldrecord_index_exprrecord_typerecord_type_field
size_qualifierstringtexttry_expr
tupletuple_typetyped_record_fieldtype_application
type_unionunderscoreuser_type_applicationvariable
warning_marker
-%% -%% The user may (for special purposes) create additional nodes -%% with other type tags, using the {@link tree/2} function. -%% -%% Note: The primary constructor functions for a node type should -%% always have the same name as the node type itself. -%% -%% @see tree/2 -%% @see annotated_type/2 -%% @see application/3 -%% @see arity_qualifier/2 -%% @see atom/1 -%% @see attribute/2 -%% @see binary/1 -%% @see binary_field/2 -%% @see bitstring_type/2 -%% @see block_expr/1 -%% @see case_expr/2 -%% @see catch_expr/1 -%% @see char/1 -%% @see class_qualifier/2 -%% @see clause/3 -%% @see comment/2 -%% @see conjunction/1 -%% @see constrained_function_type/2 -%% @see constraint/2 -%% @see disjunction/1 -%% @see else_expr/1 -%% @see eof_marker/0 -%% @see error_marker/1 -%% @see float/1 -%% @see form_list/1 -%% @see fun_expr/1 -%% @see fun_type/0 -%% @see function/2 -%% @see function_type/1 -%% @see function_type/2 -%% @see generator/2 -%% @see if_expr/1 -%% @see implicit_fun/2 -%% @see infix_expr/3 -%% @see integer/1 -%% @see integer_range_type/2 -%% @see list/2 -%% @see list_comp/2 -%% @see macro/2 -%% @see map_expr/2 -%% @see map_field_assoc/2 -%% @see map_field_exact/2 -%% @see map_type/0 -%% @see map_type/1 -%% @see map_type_assoc/2 -%% @see map_type_exact/2 -%% @see match_expr/2 -%% @see maybe_expr/1 -%% @see maybe_expr/2 -%% @see maybe_match_expr/2 -%% @see module_qualifier/2 -%% @see named_fun_expr/2 -%% @see nil/0 -%% @see operator/1 -%% @see parentheses/1 -%% @see prefix_expr/2 -%% @see receive_expr/3 -%% @see record_access/3 -%% @see record_expr/2 -%% @see record_field/2 -%% @see record_index_expr/2 -%% @see record_type/2 -%% @see record_type_field/2 -%% @see size_qualifier/2 -%% @see string/1 -%% @see text/1 -%% @see try_expr/3 -%% @see tuple/1 -%% @see tuple_type/0 -%% @see tuple_type/1 -%% @see typed_record_field/2 -%% @see type_application/2 -%% @see type_union/1 -%% @see underscore/0 -%% @see user_type_application/2 -%% @see variable/1 -%% @see warning_marker/1 - --doc """ -Returns the type tag of `Node`. If `Node` does not represent a syntax tree, -evaluation fails with reason `badarg`. Node types currently defined by this -module are: - -
applicationannotated_typearity_qualifieratom
attributebinarybinary_fieldbitstring_type
block_exprcase_exprcatch_exprchar
class_qualifierclausecommentconjunction
constrained_function_typeconstraintdisjunction
else_expreof_markererror_marker
floatform_listfun_exprfun_typefunctionfunction_typegenerator
if_exprimplicit_funinfix_exprinteger
integer_range_typelistlist_compmacro
map_exprmap_field_assocmap_field_exactmap_type
map_type_assocmap_type_exactmatch_expr
maybe_exprmaybe_match_exprmodule_qualifier
named_fun_exprniloperatorparentheses
prefix_exprreceive_exprrecord_accessrecord_expr
record_fieldrecord_index_exprrecord_typerecord_type_field
size_qualifierstringtexttry_expr
tupletuple_typetyped_record_fieldtype_application
type_unionunderscoreuser_type_applicationvariable
warning_marker
+-doc """ +type(Node) + +Returns the type tag of `Node`. + +If `Node` does not represent a syntax tree, evaluation fails with +reason `badarg`. Node types currently defined by this module are: + +* `application` +* `annotated_type` +* `arity_qualifier` +* `atom` +* `attribute` +* `binary` +* `binary_field` +* `bitstring_type` +* `block_expr` +* `case_expr` +* `catch_expr` +* `char` +* `class_qualifier` +* `clause` +* `comment` +* `conjunction` +* `constrained_function_type` +* `constraint` +* `disjunction` +* `else_expr` +* `eof_marker` +* `error_marker` +* `float` +* `form_list` +* `fun_expr` +* `fun_type` +* `function` +* `function_type` +* `generator` +* `if_expr` +* `implicit_fun` +* `infix_expr` +* `integer` +* `integer_range_type` +* `list` +* `list_comp` +* `macro` +* `map_expr` +* `map_field_assoc` +* `map_field_exact` +* `map_type` +* `map_type_assoc` +* `map_type_exact` +* `match_expr` +* `maybe_expr` +* `maybe_match_expr` +* `module_qualifier` +* `named_fun_expr` +* `nil` +* `operator` +* `parentheses` +* `prefix_expr` +* `receive_expr` +* `record_access` +* `record_expr` +* `record_field` +* `record_index_expr` +* `record_type` +* `record_type_field` +* `size_qualifier` +* `string` +* `text` +* `try_expr` +* `tuple` +* `tuple_type` +* `typed_record_field` +* `type_application` +* `type_union` +* `underscore` +* `user_type_application` +* `variable` +* `warning_marker` The user may (for special purposes) create additional nodes with other type tags, using the `tree/2` function. @@ -830,54 +665,26 @@ type(Node) -> end. -%% ===================================================================== -%% @doc Returns `true' if `Node' is a leaf node, -%% otherwise `false'. The currently recognised leaf node -%% types are: -%% -%%
-%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%%
`atom'`char'`comment'`eof_marker'`error_marker'
`float'`fun_type'`integer'`nil'`operator'`string'
`text'`underscore'`variable'`warning_marker'
-%% -%% A node of type `map_expr' is a leaf node if and only if it has no -%% argument and no fields. -%% A node of type `map_type' is a leaf node if and only if it has no -%% fields (`any_size'). -%% A node of type `tuple' is a leaf node if and only if its arity is zero. -%% A node of type `tuple_type' is a leaf node if and only if it has no -%% elements (`any_size'). -%% -%% Note: not all literals are leaf nodes, and vice versa. E.g., -%% tuples with nonzero arity and nonempty lists may be literals, but are -%% not leaf nodes. Variables, on the other hand, are leaf nodes but not -%% literals. -%% -%% @see type/1 -%% @see is_literal/1 - --doc """ -Returns `true` if `Node` is a leaf node, otherwise `false`. The currently -recognised leaf node types are: - -
`atom``char``comment``eof_marker``error_marker`
`float``fun_type``integer``nil``operator``string`
`text``underscore``variable``warning_marker`
+-doc """ +Returns `true` if `Node` is a leaf node, otherwise `false`. + +The currently recognised leaf node types are: + +* `atom` +* `char` +* `comment` +* `eof_marker` +* `error_marker` +* `float` +* `fun_type` +* `integer` +* `nil` +* `operator` +* `string` +* `text` +* `underscore` +* `variable` +* `warning_marker` A node of type `map_expr` is a leaf node if and only if it has no argument and no fields. A node of type `map_type` is a leaf node if and only if it has no @@ -885,9 +692,10 @@ fields (`any_size`). A node of type `tuple` is a leaf node if and only if its arity is zero. A node of type `tuple_type` is a leaf node if and only if it has no elements (`any_size`). -Note: not all literals are leaf nodes, and vice versa. E.g., tuples with nonzero -arity and nonempty lists may be literals, but are not leaf nodes. Variables, on -the other hand, are leaf nodes but not literals. +Note: not all literals are leaf nodes, and vice versa. For example, +tuples with nonzero arity and nonempty lists may be literals, but are +not leaf nodes. Variables, on the other hand, are leaf nodes but not +literals. _See also: _`is_literal/1`, `type/1`. """. @@ -920,42 +728,22 @@ is_leaf(Node) -> end. -%% ===================================================================== -%% @doc Returns `true' if `Node' is a syntax tree -%% representing a so-called "source code form", otherwise -%% `false'. Forms are the Erlang source code units which, -%% placed in sequence, constitute an Erlang program. Current form types -%% are: -%% -%%
-%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%% -%%
`attribute'`comment'`error_marker'`eof_marker'
`form_list'`function'`warning_marker'`text'
-%% -%% @see type/1 -%% @see attribute/2 -%% @see comment/2 -%% @see eof_marker/0 -%% @see error_marker/1 -%% @see form_list/1 -%% @see function/2 -%% @see warning_marker/1 - -doc """ Returns `true` if `Node` is a syntax tree representing a so-called "source code -form", otherwise `false`. Forms are the Erlang source code units which, placed -in sequence, constitute an Erlang program. Current form types are: +form", otherwise `false`. + +Forms are the Erlang source code units which, placed in sequence, +constitute an Erlang program. Current form types are: + +* `attribute` +* `comment` +* `error_marker` +* `eof_marker` +* `form_list` +* `function` +* `warning_marker` +* `text` -
`attribute``comment``error_marker``eof_marker`
`form_list``function``warning_marker``text`
_See also: _`attribute/2`, `comment/2`, `eof_marker/0`, `error_marker/1`, `form_list/1`, `function/2`, `type/1`, `warning_marker/1`. @@ -978,27 +766,22 @@ is_form(Node) -> %% ===================================================================== -%% @doc Returns the annotation (see {@link //stdlib/erl_anno}) -%% associated with `Node'. By default, all new tree nodes have their -%% associated position information set to the integer zero. Use {@link -%% //stdlib/erl_anno:location/1} or {@link //stdlib/erl_anno:line/1} -%% to get the position information. -%% -%% @see set_pos/2 -%% @see get_attrs/1 - %% All `erl_parse' tree nodes are represented by tuples whose second %% field is the annotation, *with the %% exceptions of* `{error, ...}' (type `error_marker') and `{warning, %% ...}' (type `warning_marker'), which only contain the associated location %% *of the error descriptor*; this is all handled transparently -%% by `get_pos' and `set_pos'. +%% by `get_pos/1' and `set_pos/2'. -type annotation_or_location() :: erl_anno:anno() | erl_anno:location(). -doc """ +get_pos(Node) + Returns the annotation (see [`//stdlib/erl_anno`](`m:erl_anno`)) associated with -`Node`. By default, all new tree nodes have their associated position +`Node`. + +By default, all new tree nodes have their associated position information set to the integer zero. Use [`//stdlib/erl_anno:location/1`](`erl_anno:location/1`) or [`//stdlib/erl_anno:line/1`](`erl_anno:line/1`) to get the position information. @@ -1021,12 +804,6 @@ get_pos(Node) -> element(2, Node). -%% ===================================================================== -%% @doc Sets the position information of `Node' to `Pos'. -%% -%% @see get_pos/1 -%% @see copy_pos/2 - -doc """ Sets the position information of `Node` to `Pos`. @@ -1051,15 +828,6 @@ set_pos(Node, Pos) -> end. -%% ===================================================================== -%% @doc Copies the annotation from `Source' to `Target'. -%% -%% This is equivalent to `set_pos(Target, -%% get_pos(Source))', but potentially more efficient. -%% -%% @see get_pos/1 -%% @see set_pos/2 - -doc """ Copies the annotation from `Source` to `Target`. @@ -1092,45 +860,28 @@ set_com(Node, Com) -> end. -%% ===================================================================== -%% @doc Returns the associated pre-comments of a node. This is a -%% possibly empty list of abstract comments, in top-down textual order. -%% When the code is formatted, pre-comments are typically displayed -%% directly above the node. For example: -%% ```% Pre-comment of function -%% foo(X) -> {bar, X}.''' -%% -%% If possible, the comment should be moved before any preceding -%% separator characters on the same line. E.g.: -%% ```foo([X | Xs]) -> -%% % Pre-comment of 'bar(X)' node -%% [bar(X) | foo(Xs)]; -%% ...''' -%% (where the comment is moved before the "`['"). -%% -%% @see comment/2 -%% @see set_precomments/2 -%% @see get_postcomments/1 -%% @see get_attrs/1 - --doc """ -Returns the associated pre-comments of a node. This is a possibly empty list of -abstract comments, in top-down textual order. When the code is formatted, -pre-comments are typically displayed directly above the node. For example: +-doc """ +get_precomments(Node) -```text - % Pre-comment of function - foo(X) -> {bar, X}. +Returns the associated pre-comments of a node. + +This is a possibly empty list of abstract comments, in top-down +textual order. When the code is formatted, pre-comments are typically +displayed directly above the node. For example: + +```erlang +% Pre-comment of function +foo(X) -> {bar, X}. ``` If possible, the comment should be moved before any preceding separator -characters on the same line. E.g.: +characters on the same line. For example: -```text - foo([X | Xs]) -> - % Pre-comment of 'bar(X)' node - [bar(X) | foo(Xs)]; - ... +```erlang +foo([X | Xs]) -> + % Pre-comment of 'bar(X)' node + [bar(X) | foo(Xs)]; +... ``` (where the comment is moved before the "`[`"). @@ -1148,22 +899,13 @@ get_precomments_1(#attr{com = none}) -> []; get_precomments_1(#attr{com = #com{pre = Cs}}) -> Cs. -%% ===================================================================== -%% @doc Sets the pre-comments of `Node' to -%% `Comments'. `Comments' should be a possibly -%% empty list of abstract comments, in top-down textual order. -%% -%% @see comment/2 -%% @see get_precomments/1 -%% @see add_precomments/2 -%% @see set_postcomments/2 -%% @see copy_comments/2 -%% @see remove_comments/1 -%% @see join_comments/2 - -doc """ -Sets the pre-comments of `Node` to `Comments`. `Comments` should be a possibly -empty list of abstract comments, in top-down textual order. +set_precomments(Node, Comments) + +Sets the pre-comments of `Node` to `Comments`. + +`Comments` should be a possibly empty list of abstract comments, in +top-down textual order. _See also: _`add_precomments/2`, `comment/2`, `copy_comments/2`, `get_precomments/1`, `join_comments/2`, `remove_comments/1`, @@ -1187,20 +929,9 @@ set_precomments_1(#attr{com = Com} = Attr, Cs) -> Attr#attr{com = Com#com{pre = Cs}}. -%% ===================================================================== -%% @doc Appends `Comments' to the pre-comments of `Node'. -%% -%% Note: This is equivalent to `set_precomments(Node, -%% get_precomments(Node) ++ Comments)', but potentially more -%% efficient. -%% -%% @see comment/2 -%% @see get_precomments/1 -%% @see set_precomments/2 -%% @see add_postcomments/2 -%% @see join_comments/2 - -doc """ +add_precomments(Comments, Node) + Appends `Comments` to the pre-comments of `Node`. Note: This is equivalent to @@ -1228,45 +959,27 @@ add_precomments_1(Cs, #attr{com = Com} = Attr) -> Attr#attr{com = Com#com{pre = Com#com.pre ++ Cs}}. -%% ===================================================================== -%% @doc Returns the associated post-comments of a node. This is a -%% possibly empty list of abstract comments, in top-down textual order. -%% When the code is formatted, post-comments are typically displayed to -%% the right of and/or below the node. For example: -%% ```{foo, X, Y} % Post-comment of tuple''' -%% -%% If possible, the comment should be moved past any following -%% separator characters on the same line, rather than placing the -%% separators on the following line. E.g.: -%% ```foo([X | Xs], Y) -> -%% foo(Xs, bar(X)); % Post-comment of 'bar(X)' node -%% ...''' -%% (where the comment is moved past the rightmost "`)'" and -%% the "`;'"). -%% -%% @see comment/2 -%% @see set_postcomments/2 -%% @see get_precomments/1 -%% @see get_attrs/1 - --doc """ -Returns the associated post-comments of a node. This is a possibly empty list of -abstract comments, in top-down textual order. When the code is formatted, -post-comments are typically displayed to the right of and/or below the node. For -example: +-doc """ +get_postcomments(Node) -```text - {foo, X, Y} % Post-comment of tuple +Returns the associated post-comments of a node. + +This is a possibly empty list of abstract comments, in top-down +textual order. When the code is formatted, post-comments are typically +displayed to the right of and/or below the node. For example: + +```erlang +{foo, X, Y} % Post-comment of tuple ``` If possible, the comment should be moved past any following separator characters on the same line, rather than placing the separators on the following line. -E.g.: +For example: -```text - foo([X | Xs], Y) -> - foo(Xs, bar(X)); % Post-comment of 'bar(X)' node - ... +```erlang +foo([X | Xs], Y) -> + foo(Xs, bar(X)); % Post-comment of 'bar(X)' node + ... ``` (where the comment is moved past the rightmost "`)`" and the "`;`"). @@ -1284,22 +997,13 @@ get_postcomments_1(#attr{com = none}) -> []; get_postcomments_1(#attr{com = #com{post = Cs}}) -> Cs. -%% ===================================================================== -%% @doc Sets the post-comments of `Node' to -%% `Comments'. `Comments' should be a possibly -%% empty list of abstract comments, in top-down textual order -%% -%% @see comment/2 -%% @see get_postcomments/1 -%% @see add_postcomments/2 -%% @see set_precomments/2 -%% @see copy_comments/2 -%% @see remove_comments/1 -%% @see join_comments/2 - -doc """ -Sets the post-comments of `Node` to `Comments`. `Comments` should be a possibly -empty list of abstract comments, in top-down textual order +set_postcomments(Node, Comments) + +Sets the post-comments of `Node` to `Comments`. + +`Comments` should be a possibly empty list of abstract comments, in +top-down textual order _See also: _`add_postcomments/2`, `comment/2`, `copy_comments/2`, `get_postcomments/1`, `join_comments/2`, `remove_comments/1`, @@ -1323,20 +1027,9 @@ set_postcomments_1(#attr{com = Com} = Attr, Cs) -> Attr#attr{com = Com#com{post = Cs}}. -%% ===================================================================== -%% @doc Appends `Comments' to the post-comments of `Node'. -%% -%% Note: This is equivalent to `set_postcomments(Node, -%% get_postcomments(Node) ++ Comments)', but potentially more -%% efficient. -%% -%% @see comment/2 -%% @see get_postcomments/1 -%% @see set_postcomments/2 -%% @see add_precomments/2 -%% @see join_comments/2 - -doc """ +add_postcomments(Comments, Node) + Appends `Comments` to the post-comments of `Node`. Note: This is equivalent to @@ -1364,19 +1057,9 @@ add_postcomments_1(Cs, #attr{com = Com} = Attr) -> Attr#attr{com = Com#com{post = Com#com.post ++ Cs}}. -%% ===================================================================== -%% @doc Yields `false' if the node has no associated -%% comments, and `true' otherwise. -%% -%% Note: This is equivalent to `(get_precomments(Node) == []) -%% and (get_postcomments(Node) == [])', but potentially more -%% efficient. -%% -%% @see get_precomments/1 -%% @see get_postcomments/1 -%% @see remove_comments/1 - -doc """ +has_comments(Node) + Yields `false` if the node has no associated comments, and `true` otherwise. Note: This is equivalent to @@ -1402,16 +1085,6 @@ has_comments(#wrapper{attr = Attr}) -> has_comments(_) -> false. -%% ===================================================================== -%% @doc Clears the associated comments of `Node'. -%% -%% Note: This is equivalent to -%% `set_precomments(set_postcomments(Node, []), [])', but -%% potentially more efficient. -%% -%% @see set_precomments/2 -%% @see set_postcomments/2 - -doc """ Clears the associated comments of `Node`. @@ -1434,20 +1107,6 @@ remove_comments(Node) -> end. -%% ===================================================================== -%% @doc Copies the pre- and postcomments from `Source' to `Target'. -%% -%% Note: This is equivalent to -%% `set_postcomments(set_precomments(Target, -%% get_precomments(Source)), get_postcomments(Source))', but -%% potentially more efficient. -%% -%% @see comment/2 -%% @see get_precomments/1 -%% @see get_postcomments/1 -%% @see set_precomments/2 -%% @see set_postcomments/2 - -doc """ Copies the pre- and postcomments from `Source` to `Target`. @@ -1464,21 +1123,6 @@ copy_comments(Source, Target) -> set_com(Target, get_com(Source)). -%% ===================================================================== -%% @doc Appends the comments of `Source' to the current -%% comments of `Target'. -%% -%% Note: This is equivalent to -%% `add_postcomments(get_postcomments(Source), -%% add_precomments(get_precomments(Source), Target))', but -%% potentially more efficient. -%% -%% @see comment/2 -%% @see get_precomments/1 -%% @see get_postcomments/1 -%% @see add_precomments/2 -%% @see add_postcomments/2 - -doc """ Appends the comments of `Source` to the current comments of `Target`. @@ -1497,17 +1141,13 @@ join_comments(Source, Target) -> add_precomments(get_precomments(Source), Target)). -%% ===================================================================== -%% @doc Returns the list of user annotations associated with a syntax -%% tree node. For a newly created node, this is the empty list. The -%% annotations may be any terms. -%% -%% @see set_ann/2 -%% @see get_attrs/1 - -doc """ -Returns the list of user annotations associated with a syntax tree node. For a -newly created node, this is the empty list. The annotations may be any terms. +get_ann(Node) + +Returns the list of user annotations associated with a syntax tree. + +For a newly created node, this is the empty list. The annotations may +be any terms. _See also: _`get_attrs/1`, `set_ann/2`. """. @@ -1518,14 +1158,9 @@ get_ann(#wrapper{attr = Attr}) -> Attr#attr.ann; get_ann(_) -> []. -%% ===================================================================== -%% @doc Sets the list of user annotations of `Node' to `Annotations'. -%% -%% @see get_ann/1 -%% @see add_ann/2 -%% @see copy_ann/2 - -doc """ +set_ann(Node, Annotations) + Sets the list of user annotations of `Node` to `Annotations`. _See also: _`add_ann/2`, `copy_ann/2`, `get_ann/1`. @@ -1545,17 +1180,9 @@ set_ann(Node, As) -> end. -%% ===================================================================== -%% @doc Appends the term `Annotation' to the list of user -%% annotations of `Node'. -%% -%% Note: this is equivalent to `set_ann(Node, [Annotation | -%% get_ann(Node)])', but potentially more efficient. -%% -%% @see get_ann/1 -%% @see set_ann/2 - -doc """ +add_ann(Annotation, Node) + Appends the term `Annotation` to the list of user annotations of `Node`. Note: this is equivalent to @@ -1579,15 +1206,6 @@ add_ann(A, Node) -> end. -%% ===================================================================== -%% @doc Copies the list of user annotations from `Source' to `Target'. -%% -%% Note: this is equivalent to `set_ann(Target, -%% get_ann(Source))', but potentially more efficient. -%% -%% @see get_ann/1 -%% @see set_ann/2 - -doc """ Copies the list of user annotations from `Source` to `Target`. @@ -1602,29 +1220,11 @@ copy_ann(Source, Target) -> set_ann(Target, get_ann(Source)). -%% ===================================================================== -%% @doc Returns a representation of the attributes associated with a -%% syntax tree node. The attributes are all the extra information that -%% can be attached to a node. Currently, this includes position -%% information, source code comments, and user annotations. The result -%% of this function cannot be inspected directly; only attached to -%% another node (see {@link set_attrs/2}). -%% -%% For accessing individual attributes, see {@link get_pos/1}, -%% {@link get_ann/1}, {@link get_precomments/1} and -%% {@link get_postcomments/1}. -%% -%% @type syntaxTreeAttributes(). This is an abstract representation of -%% syntax tree node attributes; see the function {@link get_attrs/1}. -%% -%% @see set_attrs/2 -%% @see get_pos/1 -%% @see get_ann/1 -%% @see get_precomments/1 -%% @see get_postcomments/1 - -doc """ +get_attrs(Node) + Returns a representation of the attributes associated with a syntax tree node. + The attributes are all the extra information that can be attached to a node. Currently, this includes position information, source code comments, and user annotations. The result of this function cannot be inspected directly; only @@ -1645,13 +1245,9 @@ get_attrs(Node) -> #attr{pos = get_pos(Node), com = get_com(Node)}. -%% ===================================================================== -%% @doc Sets the attributes of `Node' to `Attributes'. -%% -%% @see get_attrs/1 -%% @see copy_attrs/2 - -doc """ +set_attrs(Node, Attributes) + Sets the attributes of `Node` to `Attributes`. _See also: _`copy_attrs/2`, `get_attrs/1`. @@ -1669,16 +1265,9 @@ set_attrs(Node, Attr) -> end. -%% ===================================================================== -%% @doc Copies the attributes from `Source' to `Target'. -%% -%% Note: this is equivalent to `set_attrs(Target, -%% get_attrs(Source))', but potentially more efficient. -%% -%% @see get_attrs/1 -%% @see set_attrs/2 - -doc """ +copy_attrs(Source, Target) + Copies the attributes from `Source` to `Target`. Note: this is equivalent to @@ -1694,54 +1283,28 @@ copy_attrs(S, T) -> %% ===================================================================== -%% @equiv comment(none, Strings) --doc "Equivalent to [comment(none, Strings)](`comment/2`).". +-doc #{equiv => comment(none, Strings)}. -spec comment([string()]) -> syntaxTree(). comment(Strings) -> comment(none, Strings). -%% ===================================================================== -%% @doc Creates an abstract comment with the given padding and text. If -%% `Strings' is a (possibly empty) list -%% ["Txt1", ..., "TxtN"], the result -%% represents the source code text -%%
-%%    %Txt1
-%%    ...
-%%    %TxtN
-%% `Padding' states the number of empty character positions -%% to the left of the comment separating it horizontally from -%% source code on the same line (if any). If `Padding' is -%% `none', a default positive number is used. If -%% `Padding' is an integer less than 1, there should be no -%% separating space. Comments are in themselves regarded as source -%% program forms. -%% -%% @see comment/1 -%% @see is_form/1 - -type padding() :: 'none' | integer(). -record(comment, {pad :: padding(), text :: [string()]}). -%% type(Node) = comment -%% data(Node) = #comment{pad :: Padding, text :: Strings} -%% -%% Padding = none | integer() -%% Strings = [string()] - -doc """ -Creates an abstract comment with the given padding and text. If `Strings` is a -(possibly empty) list `["*Txt1*", ..., "*TxtN*"]`, the result represents the -source code text +Creates an abstract comment with the given padding and text. + +If `Strings` is a (possibly empty) list `["Txt1", ..., "TxtN"]`, +the result represents the source code text ```text - %Txt1 + Txt1 ... - %TxtN + TxtN ``` `Padding` states the number of empty character positions to the left of the @@ -1758,11 +1321,6 @@ comment(Pad, Strings) -> tree(comment, #comment{pad = Pad, text = Strings}). -%% ===================================================================== -%% @doc Returns the lines of text of the abstract comment. -%% -%% @see comment/2 - -doc """ Returns the lines of text of the abstract comment. @@ -1774,15 +1332,10 @@ comment_text(Node) -> (data(Node))#comment.text. -%% ===================================================================== -%% @doc Returns the amount of padding before the comment, or -%% `none'. The latter means that a default padding may be used. -%% -%% @see comment/2 - -doc """ -Returns the amount of padding before the comment, or `none`. The latter means -that a default padding may be used. +Returns the amount of padding before the comment, or `none`. + +`none` means that a default padding may be used. _See also: _`comment/2`. """. @@ -1792,49 +1345,25 @@ comment_padding(Node) -> (data(Node))#comment.pad. -%% ===================================================================== -%% @doc Creates an abstract sequence of "source code forms". If -%% `Forms' is `[F1, ..., Fn]', where each -%% `Fi' is a form (see {@link is_form/1}, the result -%% represents -%%
-%%    F1
-%%    ...
-%%    Fn
-%% where the `Fi' are separated by one or more line breaks. A -%% node of type `form_list' is itself regarded as a source -%% code form; see {@link flatten_form_list/1}. -%% -%% Note: this is simply a way of grouping source code forms as a -%% single syntax tree, usually in order to form an Erlang module -%% definition. -%% -%% @see form_list_elements/1 -%% @see is_form/1 -%% @see flatten_form_list/1 - -%% type(Node) = form_list -%% data(Node) = [Form] -%% -%% Form = syntaxTree() -%% is_form(Form) = true - -doc """ -Creates an abstract sequence of "source code forms". If `Forms` is -`[F1, ..., Fn]`, where each `Fi` is a form (see `is_form/1`, the result -represents +Creates an abstract sequence of "source code forms". + +If `Forms` is `[F1, ..., Fn]`, where each `Fi` is a form (see +`is_form/1`), the result represents: ```text F1 - ... - Fn +... +Fn ``` where the `Fi` are separated by one or more line breaks. A node of type `form_list` is itself regarded as a source code form; see `flatten_form_list/1`. -Note: this is simply a way of grouping source code forms as a single syntax -tree, usually in order to form an Erlang module definition. +> #### Note {: .info } +> +> This is simply a way of grouping source code forms into a single syntax +tree, usually to form an Erlang module definition. _See also: _`flatten_form_list/1`, `form_list_elements/1`, `is_form/1`. """. @@ -1844,11 +1373,6 @@ form_list(Forms) -> tree(form_list, Forms). -%% ===================================================================== -%% @doc Returns the list of subnodes of a `form_list' node. -%% -%% @see form_list/1 - -doc """ Returns the list of subnodes of a `form_list` node. @@ -1860,18 +1384,11 @@ form_list_elements(Node) -> data(Node). -%% ===================================================================== -%% @doc Flattens sublists of a `form_list' node. Returns -%% `Node' with all subtrees of type `form_list' -%% recursively expanded, yielding a single "flat" abstract form -%% sequence. -%% -%% @see form_list/1 - -doc """ -Flattens sublists of a `form_list` node. Returns `Node` with all subtrees of -type `form_list` recursively expanded, yielding a single "flat" abstract form -sequence. +Flattens sublists of a `form_list` node. + +Returns `Node` with all subtrees of type `form_list` recursively +expanded, yielding a single "flat" abstract form sequence. _See also: _`form_list/1`. """. @@ -1894,23 +1411,13 @@ flatten_form_list_1([], As) -> As. -%% ===================================================================== -%% @doc Creates an abstract piece of source code text. The result -%% represents exactly the sequence of characters in `String'. -%% This is useful in cases when one wants full control of the resulting -%% output, e.g., for the appearance of floating-point numbers or macro -%% definitions. -%% -%% @see text_string/1 - -%% type(Node) = text -%% data(Node) = string() - -doc """ -Creates an abstract piece of source code text. The result represents exactly the -sequence of characters in `String`. This is useful in cases when one wants full -control of the resulting output, e.g., for the appearance of floating-point -numbers or macro definitions. +Creates an abstract piece of source code text. + +The result represents exactly the sequence of characters in +`String`. This is useful in cases where one wants full control of the +resulting output, such as the appearance of floating-point numbers or +macro definitions. _See also: _`text_string/1`. """. @@ -1920,11 +1427,6 @@ text(String) -> tree(text, String). -%% ===================================================================== -%% @doc Returns the character sequence represented by a `text' node. -%% -%% @see text/1 - -doc """ Returns the character sequence represented by a `text` node. @@ -1936,38 +1438,21 @@ text_string(Node) -> data(Node). -%% ===================================================================== -%% @doc Creates an abstract variable with the given name. -%% `Name' may be any atom or string that represents a -%% lexically valid variable name, but not a single underscore -%% character; see {@link underscore/0}. -%% -%% Note: no checking is done whether the character sequence -%% represents a proper variable name, i.e., whether or not its first -%% character is an uppercase Erlang character, or whether it does not -%% contain control characters, whitespace, etc. -%% -%% @see variable_name/1 -%% @see variable_literal/1 -%% @see underscore/0 +-doc """ +variable(Name) -%% type(Node) = variable -%% data(Node) = atom() -%% -%% `erl_parse' representation: -%% -%% {var, Pos, Name} -%% -%% Name = atom() \ '_' +Creates an abstract variable with the given name. --doc """ -Creates an abstract variable with the given name. `Name` may be any atom or -string that represents a lexically valid variable name, but _not_ a single -underscore character; see `underscore/0`. +`Name` may be any atom or string that represents a lexically valid +variable name, but _not_ a single underscore character; see +`underscore/0`. -Note: no checking is done whether the character sequence represents a proper -variable name, i.e., whether or not its first character is an uppercase Erlang -character, or whether it does not contain control characters, whitespace, etc. +> #### Note {: .info } +> +> No check is performed to verify whether the character sequence +> represents a proper variable name, that is, whether its first character +> is an uppercase Erlang character, or whether it contains illegal characters +> such as control characters or whitespace. _See also: _`underscore/0`, `variable_literal/1`, `variable_name/1`. """. @@ -1984,11 +1469,6 @@ revert_variable(Node) -> {var, Pos, Name}. -%% ===================================================================== -%% @doc Returns the name of a `variable' node as an atom. -%% -%% @see variable/1 - -doc """ Returns the name of a `variable` node as an atom. @@ -2005,11 +1485,6 @@ variable_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the name of a `variable' node as a string. -%% -%% @see variable/1 - -doc """ Returns the name of a `variable` node as a string. @@ -2026,29 +1501,20 @@ variable_literal(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract universal pattern ("`_'"). The -%% lexical representation is a single underscore character. Note that -%% this is not a variable, lexically speaking. -%% -%% @see variable/1 - -%% type(Node) = underscore -%% data(Node) = [] -%% -%% `erl_parse' representation: -%% -%% {var, Pos, '_'} - -doc """ -Creates an abstract universal pattern ("`_`"). The lexical representation is a -single underscore character. Note that this is _not_ a variable, lexically -speaking. +Creates an abstract universal pattern ("`_`"). + +The lexical representation is a single underscore character. Note that +this is _not_ a variable, lexically speaking. _See also: _`variable/1`. """. -spec underscore() -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {var, Pos, '_'} + underscore() -> tree(underscore, []). @@ -2057,31 +1523,21 @@ revert_underscore(Node) -> {var, Pos, '_'}. -%% ===================================================================== -%% @doc Creates an abstract integer literal. The lexical representation -%% is the canonical decimal numeral of `Value'. -%% -%% @see integer_value/1 -%% @see integer_literal/1 -%% @see is_integer/2 +-doc """ +Creates an abstract integer literal. + +The lexical representation is the canonical decimal numeral of `Value`. + +_See also: _`integer_literal/1`, `integer_value/1`, `is_integer/2`. +""". +-spec integer(integer()) -> syntaxTree(). -%% type(Node) = integer -%% data(Node) = integer() -%% %% `erl_parse' representation: %% %% {integer, Pos, Value} %% %% Value = integer() --doc """ -Creates an abstract integer literal. The lexical representation is the canonical -decimal numeral of `Value`. - -_See also: _`integer_literal/1`, `integer_value/1`, `is_integer/2`. -""". --spec integer(integer()) -> syntaxTree(). - integer(Value) -> tree(integer, Value). @@ -2090,12 +1546,6 @@ revert_integer(Node) -> {integer, Pos, integer_value(Node)}. -%% ===================================================================== -%% @doc Returns `true' if `Node' has type -%% `integer' and represents `Value', otherwise `false'. -%% -%% @see integer/1 - -doc """ Returns `true` if `Node` has type `integer` and represents `Value`, otherwise `false`. @@ -2115,11 +1565,6 @@ is_integer(Node, Value) -> end. -%% ===================================================================== -%% @doc Returns the value represented by an `integer' node. -%% -%% @see integer/1 - -doc """ Returns the value represented by an `integer` node. @@ -2136,11 +1581,6 @@ integer_value(Node) -> end. -%% ===================================================================== -%% @doc Returns the numeral string represented by an `integer' node. -%% -%% @see integer/1 - -doc """ Returns the numeral string represented by an `integer` node. @@ -2152,37 +1592,27 @@ integer_literal(Node) -> integer_to_list(integer_value(Node)). -%% ===================================================================== -%% @doc Creates an abstract floating-point literal. The lexical -%% representation is the decimal floating-point numeral of `Value'. -%% -%% @see float_value/1 -%% @see float_literal/1 - -%% type(Node) = float -%% data(Node) = Value -%% -%% Value = float() -%% -%% `erl_parse' representation: -%% -%% {float, Pos, Value} -%% -%% Value = float() - %% Note that under current versions of Erlang, the name `float/1' cannot %% be used for local calls (i.e., within the module) - it will be %% overridden by the type conversion BIF of the same name, so always use %% `make_float/1' for local calls. -doc """ -Creates an abstract floating-point literal. The lexical representation is the -decimal floating-point numeral of `Value`. +Creates an abstract floating-point literal. + +The lexical representation is the decimal floating-point numeral of +`Value`. _See also: _`float_literal/1`, `float_value/1`. """. -spec float(float()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {float, Pos, Value} +%% +%% Value = float() + float(Value) -> make_float(Value). @@ -2194,16 +1624,11 @@ revert_float(Node) -> {float, Pos, float_value(Node)}. -%% ===================================================================== -%% @doc Returns the value represented by a `float' node. Note -%% that floating-point values should usually not be compared for -%% equality. -%% -%% @see float/1 - -doc """ -Returns the value represented by a `float` node. Note that floating-point values -should usually not be compared for equality. +Returns the value represented by a `float` node. + +Note that floating-point values should usually not be compared for +equality. _See also: _`float/1`. """. @@ -2218,11 +1643,6 @@ float_value(Node) -> end. -%% ===================================================================== -%% @doc Returns the numeral string represented by a `float' node. -%% -%% @see float/1 - -doc """ Returns the numeral string represented by a `float` node. @@ -2234,43 +1654,30 @@ float_literal(Node) -> float_to_list(float_value(Node)). -%% ===================================================================== -%% @doc Creates an abstract character literal. The result represents -%% "$Name", where `Name' corresponds to -%% `Value'. -%% -%% Note: the literal corresponding to a particular character value is -%% not uniquely defined. E.g., the character "`a'" can be -%% written both as "`$a'" and "`$\141'", and a Tab -%% character can be written as "`$\11'", "`$\011'" -%% or "`$\t'". -%% -%% @see char_value/1 -%% @see char_literal/1 -%% @see char_literal/2 -%% @see is_char/2 +-doc """ +char(Value) -%% type(Node) = char -%% data(Node) = char() -%% -%% `erl_parse' representation: -%% -%% {char, Pos, Code} -%% -%% Code = integer() +Creates an abstract character literal. --doc """ -Creates an abstract character literal. The result represents "`$*Name*`", where -`Name` corresponds to `Value`. +The result represents "`$Name`", where `Name` corresponds to `Value`. + +> #### Note {: .info } -Note: the literal corresponding to a particular character value is not uniquely -defined. E.g., the character "`a`" can be written both as "`$a`" and "`$\141`", -and a Tab character can be written as "`$\11`", "`$\011`" or "`$\t`". +The literal corresponding to a particular character value is not +uniquely defined. For example, the character "`a`" can be written both +as "`$a`" and "`$\141`", and a Tab character can be written as +"`$\11`", "`$\011`", or "`$\t`". _See also: _`char_literal/1`, `char_literal/2`, `char_value/1`, `is_char/2`. """. -spec char(char()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {char, Pos, Code} +%% +%% Code = integer() + char(Char) -> tree(char, Char). @@ -2279,12 +1686,6 @@ revert_char(Node) -> {char, Pos, char_value(Node)}. -%% ===================================================================== -%% @doc Returns `true' if `Node' has type -%% `char' and represents `Value', otherwise `false'. -%% -%% @see char/1 - -doc """ Returns `true` if `Node` has type `char` and represents `Value`, otherwise `false`. @@ -2304,11 +1705,6 @@ is_char(Node, Value) -> end. -%% ===================================================================== -%% @doc Returns the value represented by a `char' node. -%% -%% @see char/1 - -doc """ Returns the value represented by a `char` node. @@ -2325,16 +1721,11 @@ char_value(Node) -> end. -%% ===================================================================== -%% @doc Returns the literal string represented by a `char' -%% node. This includes the leading "`$'" character. -%% Characters beyond 255 will be escaped. -%% -%% @see char/1 - -doc """ -Returns the literal string represented by a `char` node. This includes the -leading "`$`" character. Characters beyond 255 will be escaped. +Returns the literal string represented by a `char` node. + +This includes the leading "`$`" character. Characters beyond 255 will +be escaped. _See also: _`char/1`. """. @@ -2344,20 +1735,16 @@ char_literal(Node) -> char_literal(Node, latin1). -%% ===================================================================== -%% @doc Returns the literal string represented by a `char' -%% node. This includes the leading "`$'" character. -%% Depending on the encoding a character beyond 255 will be escaped -%% (`latin1') or copied as is (`utf8'). -%% -%% @see char/1 - -type encoding() :: 'utf8' | 'unicode' | 'latin1'. -doc """ -Returns the literal string represented by a `char` node. This includes the -leading "`$`" character. Depending on the encoding a character beyond 255 will -be escaped (`latin1`) or copied as is (`utf8`). +char_literal(Node, Encoding) + +Returns the literal string represented by a `char` node. + +This includes the leading "`$`" character. Depending on the encoding a +character beyond 255 will be escaped (`latin1`) or copied as is +(`utf8`). _See also: _`char/1`. """. @@ -2371,35 +1758,12 @@ char_literal(Node, latin1) -> io_lib:write_char_as_latin1(char_value(Node)). -%% ===================================================================== -%% @doc Creates an abstract string literal. The result represents -%% "Text" (including the surrounding -%% double-quotes), where `Text' corresponds to the sequence -%% of characters in `Value', but not representing a -%% specific string literal. -%% -%% For example, the result of `string("x\ny")' represents any and all of -%% `"x\ny"', `"x\12y"', `"x\012y"' and `"x\^Jy"'; see {@link char/1}. -%% -%% @see string_value/1 -%% @see string_literal/1 -%% @see string_literal/2 -%% @see is_string/2 -%% @see char/1 - -%% type(Node) = string -%% data(Node) = string() -%% -%% `erl_parse' representation: -%% -%% {string, Pos, Chars} -%% -%% Chars = string() - -doc """ -Creates an abstract string literal. The result represents `"*Text*"` (including -the surrounding double-quotes), where `Text` corresponds to the sequence of -characters in `Value`, but not representing a _specific_ string literal. +Creates an abstract string literal. + +The result represents `"Text"` (including the surrounding +double-quotes), where `Text` corresponds to the sequence of characters +in `Value`, but not representing a _specific_ string literal. For example, the result of [`string("x\ny")`](`string/1`) represents any and all of `"x\ny"`, `"x\12y"`, `"x\012y"` and `"x\^Jy"`; see `char/1`. @@ -2409,6 +1773,12 @@ _See also: _`char/1`, `is_string/2`, `string_literal/1`, `string_literal/2`, """. -spec string(string()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {string, Pos, Chars} +%% +%% Chars = string() + string(String) -> tree(string, String). @@ -2417,12 +1787,6 @@ revert_string(Node) -> {string, Pos, string_value(Node)}. -%% ===================================================================== -%% @doc Returns `true' if `Node' has type -%% `string' and represents `Value', otherwise `false'. -%% -%% @see string/1 - -doc """ Returns `true` if `Node` has type `string` and represents `Value`, otherwise `false`. @@ -2442,11 +1806,6 @@ is_string(Node, Value) -> end. -%% ===================================================================== -%% @doc Returns the value represented by a `string' node. -%% -%% @see string/1 - -doc """ Returns the value represented by a `string` node. @@ -2463,16 +1822,11 @@ string_value(Node) -> end. -%% ===================================================================== -%% @doc Returns the literal string represented by a `string' -%% node. This includes surrounding double-quote characters. -%% Characters beyond 255 will be escaped. -%% -%% @see string/1 - -doc """ -Returns the literal string represented by a `string` node. This includes -surrounding double-quote characters. Characters beyond 255 will be escaped. +Returns the literal string represented by a `string` node. + +This includes surrounding double-quote characters. Characters beyond +255 will be escaped. _See also: _`string/1`. """. @@ -2482,18 +1836,14 @@ string_literal(Node) -> string_literal(Node, latin1). -%% ===================================================================== -%% @doc Returns the literal string represented by a `string' -%% node. This includes surrounding double-quote characters. -%% Depending on the encoding characters beyond 255 will be escaped -%% (`latin1') or copied as is (`utf8'). -%% -%% @see string/1 - -doc """ -Returns the literal string represented by a `string` node. This includes -surrounding double-quote characters. Depending on the encoding characters beyond -255 will be escaped (`latin1`) or copied as is (`utf8`). +string_literal(Node, Encoding) + +Returns the literal string represented by a `string` node. + +This includes surrounding double-quote characters. Depending on the +encoding characters beyond 255 will be escaped (`latin1`) or copied as +is (`utf8`). _See also: _`string/1`. """. @@ -2507,34 +1857,25 @@ string_literal(Node, latin1) -> io_lib:write_string_as_latin1(string_value(Node)). -%% ===================================================================== -%% @doc Creates an abstract atom literal. The print name of the atom is -%% the character sequence represented by `Name'. -%% -%% @see atom_value/1 -%% @see atom_name/1 -%% @see atom_literal/1 -%% @see atom_literal/2 -%% @see is_atom/2 +-doc """ +atom(Name) -%% type(Node) = atom -%% data(Node) = atom() -%% -%% `erl_parse' representation: -%% -%% {atom, Pos, Value} -%% -%% Value = atom() +Creates an abstract atom literal. --doc """ -Creates an abstract atom literal. The print name of the atom is the character -sequence represented by `Name`. +The print name of the atom is the character sequence represented by +`Name`. _See also: _`atom_literal/1`, `atom_literal/2`, `atom_name/1`, `atom_value/1`, `is_atom/2`. """. -spec atom(atom() | string()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {atom, Pos, Value} +%% +%% Value = atom() + atom(Name) when is_atom(Name) -> tree(atom, Name); atom(Name) -> @@ -2545,12 +1886,6 @@ revert_atom(Node) -> {atom, Pos, atom_value(Node)}. -%% ===================================================================== -%% @doc Returns `true' if `Node' has type -%% `atom' and represents `Value', otherwise `false'. -%% -%% @see atom/1 - -doc """ Returns `true` if `Node` has type `atom` and represents `Value`, otherwise `false`. @@ -2570,11 +1905,6 @@ is_atom(Node, Value) -> end. -%% ===================================================================== -%% @doc Returns the value represented by an `atom' node. -%% -%% @see atom/1 - -doc """ Returns the value represented by an `atom` node. @@ -2591,11 +1921,6 @@ atom_value(Node) -> end. -%% ===================================================================== -%% @doc Returns the printname of an `atom' node. -%% -%% @see atom/1 - -doc """ Returns the printname of an `atom` node. @@ -2607,25 +1932,15 @@ atom_name(Node) -> atom_to_list(atom_value(Node)). -%% ===================================================================== -%% @doc Returns the literal string represented by an `atom' -%% node. This includes surrounding single-quote characters if necessary. -%% Characters beyond 255 will be escaped. -%% -%% Note that e.g. the result of `atom("x\ny")' represents -%% any and all of `'x\ny'', `'x\12y'', -%% `'x\012y'' and `'x\^Jy\''; see {@link string/1}. -%% -%% @see atom/1 -%% @see string/1 - -doc """ -Returns the literal string represented by an `atom` node. This includes -surrounding single-quote characters if necessary. Characters beyond 255 will be -escaped. +Returns the literal string represented by an `atom` node. + +This includes surrounding single-quote characters if +necessary. Characters beyond 255 will be escaped. -Note that e.g. the result of [`atom("x\ny")`](`atom/1`) represents any and all -of \`x\\ny'', \`x\\12y'', \`x\\012y'' and \`x\\^Jy\\''; see `string/1`. +Note that, for example, the result of [`atom("x\ny")`](`atom/1`) +represents any and all of `'x\ny'`, `'x\12y'`, `'x\012y'`, and +`'x\^Jy'`; see `string/1`. _See also: _`atom/1`, `string/1`. """. @@ -2634,20 +1949,14 @@ _See also: _`atom/1`, `string/1`. atom_literal(Node) -> atom_literal(Node, latin1). -%% ===================================================================== -%% @doc Returns the literal string represented by an `atom' -%% node. This includes surrounding single-quote characters if necessary. -%% Depending on the encoding a character beyond 255 will be escaped -%% (`latin1') or copied as is (`utf8'). -%% -%% @see atom/1 -%% @see atom_literal/1 -%% @see string/1 - -doc """ -Returns the literal string represented by an `atom` node. This includes -surrounding single-quote characters if necessary. Depending on the encoding a -character beyond 255 will be escaped (`latin1`) or copied as is (`utf8`). +atom_literal(Node, Encoding) + +Returns the literal string represented by an `atom` node. + +This includes surrounding single-quote characters if +necessary. Depending on the encoding a character beyond 255 will be +escaped (`latin1`) or copied as is (`utf8`). _See also: _`atom/1`, `atom_literal/1`, `string/1`. """. @@ -2661,46 +1970,34 @@ atom_literal(Node, latin1) -> io_lib:write_atom_as_latin1(atom_value(Node)). %% ===================================================================== -%% @equiv map_expr(none, Fields) --doc "Equivalent to [map_expr(none, Fields)](`map_expr/2`).". +-doc #{equiv => map_expr(none, Fields)}. -spec map_expr([syntaxTree()]) -> syntaxTree(). map_expr(Fields) -> map_expr(none, Fields). -%% ===================================================================== -%% @doc Creates an abstract map expression. If `Fields' is -%% `[F1, ..., Fn]', then if `Argument' is `none', the result represents -%% "#{F1, ..., Fn}", -%% otherwise it represents -%% "Argument#{F1, ..., Fn}". -%% -%% @see map_expr/1 -%% @see map_expr_argument/1 -%% @see map_expr_fields/1 -%% @see map_field_assoc/2 -%% @see map_field_exact/2 - -record(map_expr, {argument :: 'none' | syntaxTree(), fields :: [syntaxTree()]}). -%% `erl_parse' representation: -%% -%% {map, Pos, Fields} -%% {map, Pos, Argument, Fields} - -doc """ -Creates an abstract map expression. If `Fields` is `[F1, ..., Fn]`, then if -`Argument` is `none`, the result represents "`#{*F1*, ..., *Fn*}`", otherwise it -represents "`*Argument*#{*F1*, ..., *Fn*}`". +Creates an abstract map expression. + +If `Fields` is `[F1, ..., Fn]`, then if `Argument` is `none`, the +result represents "`#{F1, ..., Fn}`", otherwise it represents +"`Argument#{F1, ..., Fn}`". _See also: _`map_expr/1`, `map_expr_argument/1`, `map_expr_fields/1`, `map_field_assoc/2`, `map_field_exact/2`. """. -spec map_expr('none' | syntaxTree(), [syntaxTree()]) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {map, Pos, Fields} +%% {map, Pos, Argument, Fields} + map_expr(Argument, Fields) -> tree(map_expr, #map_expr{argument = Argument, fields = Fields}). @@ -2716,18 +2013,11 @@ revert_map_expr(Node) -> end. -%% ===================================================================== -%% @doc Returns the argument subtree of a `map_expr' node, if any. If `Node' -%% represents "#{...}", `none' is returned. -%% Otherwise, if `Node' represents "Argument#{...}", -%% `Argument' is returned. -%% -%% @see map_expr/2 - -doc """ -Returns the argument subtree of a `map_expr` node, if any. If `Node` represents -"`#{...}`", `none` is returned. Otherwise, if `Node` represents -"`*Argument*#{...}`", `Argument` is returned. +Returns the argument subtree of a `map_expr` node, if any. + +If `Node` represents "`#{...}`", `none` is returned. Otherwise, if +`Node` represents "`Argument#{...}`", `Argument` is returned. _See also: _`map_expr/2`. """. @@ -2744,11 +2034,6 @@ map_expr_argument(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of field subtrees of a `map_expr' node. -%% -%% @see map_expr/2 - -doc """ Returns the list of field subtrees of a `map_expr` node. @@ -2767,28 +2052,21 @@ map_expr_fields(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract map assoc field. The result represents -%% "Name => Value". -%% -%% @see map_field_assoc_name/1 -%% @see map_field_assoc_value/1 -%% @see map_expr/2 - -record(map_field_assoc, {name :: syntaxTree(), value :: syntaxTree()}). -%% `erl_parse' representation: -%% -%% {map_field_assoc, Pos, Name, Value} - -doc """ -Creates an abstract map assoc field. The result represents -"`*Name* => *Value*`". +Creates an abstract map assoc field. + +The result represents "`Name => Value`". _See also: _`map_expr/2`, `map_field_assoc_name/1`, `map_field_assoc_value/1`. """. -spec map_field_assoc(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {map_field_assoc, Pos, Name, Value} + map_field_assoc(Name, Value) -> tree(map_field_assoc, #map_field_assoc{name = Name, value = Value}). @@ -2799,11 +2077,6 @@ revert_map_field_assoc(Node) -> {map_field_assoc, Pos, Name, Value}. -%% ===================================================================== -%% @doc Returns the name subtree of a `map_field_assoc' node. -%% -%% @see map_field_assoc/2 - -doc """ Returns the name subtree of a `map_field_assoc` node. @@ -2820,11 +2093,6 @@ map_field_assoc_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the value subtree of a `map_field_assoc' node. -%% -%% @see map_field_assoc/2 - -doc """ Returns the value subtree of a `map_field_assoc` node. @@ -2841,28 +2109,21 @@ map_field_assoc_value(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract map exact field. The result represents -%% "Name := Value". -%% -%% @see map_field_exact_name/1 -%% @see map_field_exact_value/1 -%% @see map_expr/2 - -record(map_field_exact, {name :: syntaxTree(), value :: syntaxTree()}). -%% `erl_parse' representation: -%% -%% {map_field_exact, Pos, Name, Value} - -doc """ -Creates an abstract map exact field. The result represents -"`*Name* := *Value*`". +Creates an abstract map exact field. + +The result represents "`Name := Value`". _See also: _`map_expr/2`, `map_field_exact_name/1`, `map_field_exact_value/1`. """. -spec map_field_exact(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {map_field_exact, Pos, Name, Value} + map_field_exact(Name, Value) -> tree(map_field_exact, #map_field_exact{name = Name, value = Value}). @@ -2873,11 +2134,6 @@ revert_map_field_exact(Node) -> {map_field_exact, Pos, Name, Value}. -%% ===================================================================== -%% @doc Returns the name subtree of a `map_field_exact' node. -%% -%% @see map_field_exact/2 - -doc """ Returns the name subtree of a `map_field_exact` node. @@ -2894,11 +2150,6 @@ map_field_exact_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the value subtree of a `map_field_exact' node. -%% -%% @see map_field_exact/2 - -doc """ Returns the value subtree of a `map_field_exact` node. @@ -2915,39 +2166,27 @@ map_field_exact_value(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract tuple. If `Elements' is -%% `[X1, ..., Xn]', the result represents -%% "{X1, ..., Xn}". -%% -%% Note: The Erlang language has distinct 1-tuples, i.e., -%% `{X}' is always distinct from `X' itself. -%% -%% @see tuple_elements/1 -%% @see tuple_size/1 - -%% type(Node) = tuple -%% data(Node) = Elements -%% -%% Elements = [syntaxTree()] -%% -%% `erl_parse' representation: -%% -%% {tuple, Pos, Elements} -%% -%% Elements = [erl_parse()] - -doc """ -Creates an abstract tuple. If `Elements` is `[X1, ..., Xn]`, the result -represents "`{*X1*, ..., *Xn*}`". +Creates an abstract tuple. + +If `Elements` is `[X1, ..., Xn]`, the result represents "`{X1, ..., +Xn}`". -Note: The Erlang language has distinct 1-tuples, i.e., `{X}` is always distinct -from `X` itself. +> #### Note {: .info } +> +> The Erlang language has distinct 1-tuples, meaning `{X}` is always distinct +> from `X` itself. _See also: _`tuple_elements/1`, `tuple_size/1`. """. -spec tuple([syntaxTree()]) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {tuple, Pos, Elements} +%% +%% Elements = [erl_parse()] + tuple(List) -> tree(tuple, List). @@ -2956,11 +2195,6 @@ revert_tuple(Node) -> {tuple, Pos, tuple_elements(Node)}. -%% ===================================================================== -%% @doc Returns the list of element subtrees of a `tuple' node. -%% -%% @see tuple/1 - -doc """ Returns the list of element subtrees of a `tuple` node. @@ -2977,21 +2211,13 @@ tuple_elements(Node) -> end. -%% ===================================================================== -%% @doc Returns the number of elements of a `tuple' node. -%% -%% Note: this is equivalent to -%% `length(tuple_elements(Node))', but potentially more -%% efficient. -%% -%% @see tuple/1 -%% @see tuple_elements/1 - -doc """ Returns the number of elements of a `tuple` node. -Note: this is equivalent to [`length(tuple_elements(Node))`](`length/1`), but -potentially more efficient. +> #### Note {: .info } +> +> This is equivalent to [`length(tuple_elements(Node))`](`length/1`), +> but potentially more efficient. _See also: _`tuple/1`, `tuple_elements/1`. """. @@ -3004,79 +2230,25 @@ tuple_size(Node) -> %% ===================================================================== %% @equiv list(List, none) --doc "Equivalent to [list(List, none)](`list/2`).". +-doc #{equiv => list(List, none)}. -spec list([syntaxTree()]) -> syntaxTree(). list(List) -> list(List, none). -%% ===================================================================== -%% @doc Constructs an abstract list skeleton. The result has type -%% `list' or `nil'. If `List' is a -%% nonempty list `[E1, ..., En]', the result has type -%% `list' and represents either "[E1, ..., -%% En]", if `Tail' is `none', or -%% otherwise "[E1, ..., En | -%% Tail]". If `List' is the empty list, -%% `Tail' must be `none', and in that -%% case the result has type `nil' and represents -%% "`[]'" (see {@link nil/0}). -%% -%% The difference between lists as semantic objects (built up of -%% individual "cons" and "nil" terms) and the various syntactic forms -%% for denoting lists may be bewildering at first. This module provides -%% functions both for exact control of the syntactic representation as -%% well as for the simple composition and deconstruction in terms of -%% cons and head/tail operations. -%% -%% Note: in `list(Elements, none)', the "nil" list -%% terminator is implicit and has no associated information (see -%% {@link get_attrs/1}), while in the seemingly equivalent -%% `list(Elements, Tail)' when `Tail' has type -%% `nil', the list terminator subtree `Tail' may -%% have attached attributes such as position, comments, and annotations, -%% which will be preserved in the result. -%% -%% @see nil/0 -%% @see list/1 -%% @see list_prefix/1 -%% @see list_suffix/1 -%% @see cons/2 -%% @see list_head/1 -%% @see list_tail/1 -%% @see is_list_skeleton/1 -%% @see is_proper_list/1 -%% @see list_elements/1 -%% @see list_length/1 -%% @see normalize_list/1 -%% @see compact_list/1 -%% @see get_attrs/1 - -record(list, {prefix :: [syntaxTree()], suffix :: 'none' | syntaxTree()}). -%% type(Node) = list -%% data(Node) = #list{prefix :: Elements, suffix :: Tail} -%% -%% Elements = [syntaxTree()] -%% Tail = none | syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {cons, Pos, Head, Tail} -%% -%% Head = Tail = [erl_parse()] -%% -%% This represents `[ | ]', or more generally `[ -%% ]' where the form of can depend on the -%% structure of ; there is no fixed printed form. - -doc """ -Constructs an abstract list skeleton. The result has type `list` or `nil`. If -`List` is a nonempty list `[E1, ..., En]`, the result has type `list` and -represents either "`[*E1*, ..., *En*]`", if `Tail` is `none`, or otherwise -"`[*E1*, ..., *En* | *Tail*]`". If `List` is the empty list, `Tail`_must_ be -`none`, and in that case the result has type `nil` and represents "`[]`" (see +list(List, Tail) + +Constructs an abstract list skeleton. + +The result has type `list` or `nil`. If `List` is a nonempty list +`[E1, ..., En]`, the result has type `list` and represents either +"`[E1, ..., En]`" if `Tail` is `none`, or otherwise "`[E1, ..., +En | Tail]`". If `List` is the empty list, `Tail` _must_ be `none`, +and in that case the result has type `nil` and represents "`[]`" (see `nil/0`). The difference between lists as semantic objects (built up of individual "cons" @@ -3085,11 +2257,14 @@ bewildering at first. This module provides functions both for exact control of the syntactic representation as well as for the simple composition and deconstruction in terms of cons and head/tail operations. -Note: in [`list(Elements, none)`](`list/2`), the "nil" list terminator is -implicit and has no associated information (see `get_attrs/1`), while in the -seemingly equivalent [`list(Elements, Tail)`](`list/2`) when `Tail` has type -`nil`, the list terminator subtree `Tail` may have attached attributes such as -position, comments, and annotations, which will be preserved in the result. +> #### Note {: .info } +> +> In [`list(Elements, none)`](`list/2`), the "nil" list terminator is +> implicit and has no associated information (see `get_attrs/1`). However, +> in the seemingly equivalent [`list(Elements, Tail)`](`list/2`) where +> `Tail` has the type `nil`, the list terminator subtree `Tail` may have +> attached attributes such as position, comments, and annotations, which +> will be preserved in the result. _See also: _`compact_list/1`, `cons/2`, `get_attrs/1`, `is_list_skeleton/1`, `is_proper_list/1`, `list/1`, `list_elements/1`, `list_head/1`, `list_length/1`, @@ -3097,6 +2272,16 @@ _See also: _`compact_list/1`, `cons/2`, `get_attrs/1`, `is_list_skeleton/1`, """. -spec list([syntaxTree()], 'none' | syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {cons, Pos, Head, Tail} +%% +%% Head = Tail = [erl_parse()] +%% +%% This represents `[ | ]', or more generally `[ +%% ]' where the form of can depend on the +%% structure of ; there is no fixed printed form. + list([], none) -> nil(); list(Elements, Tail) when Elements =/= [] -> @@ -3122,28 +2307,21 @@ revert_list(Node) -> {cons, erl_anno:set_location(HeadLocation, Pos), Head, Tail} end, Suffix, Prefix). -%% ===================================================================== -%% @doc Creates an abstract empty list. The result represents -%% "`[]'". The empty list is traditionally called "nil". -%% -%% @see list/2 -%% @see is_list_skeleton/1 - -%% type(Node) = nil -%% data(Node) = term() -%% -%% `erl_parse' representation: -%% -%% {nil, Pos} -doc """ -Creates an abstract empty list. The result represents "`[]`". The empty list is -traditionally called "nil". +Creates an abstract empty list. + +The result represents "`[]`". The empty list is traditionally called +"nil". _See also: _`is_list_skeleton/1`, `list/2`. """. -spec nil() -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {nil, Pos} + nil() -> tree(nil). @@ -3152,19 +2330,11 @@ revert_nil(Node) -> {nil, Pos}. -%% ===================================================================== -%% @doc Returns the prefix element subtrees of a `list' node. -%% If `Node' represents "[E1, ..., -%% En]" or "[E1, ..., En | -%% Tail]", the returned value is `[E1, ..., -%% En]'. -%% -%% @see list/2 - -doc """ -Returns the prefix element subtrees of a `list` node. If `Node` represents -"`[*E1*, ..., *En*]`" or "`[*E1*, ..., *En* | *Tail*]`", the returned value is -`[E1, ..., En]`. +Returns the prefix element subtrees of a `list` node. + +If `Node` represents "`[E1, ..., En]`" or "`[E1, ..., En | +Tail]`", the returned value is `[E1, ..., En]`. _See also: _`list/2`. """. @@ -3185,31 +2355,18 @@ cons_prefix(_) -> []. -%% ===================================================================== -%% @doc Returns the suffix subtree of a `list' node, if one -%% exists. If `Node' represents "[E1, ..., -%% En | Tail]", the returned value is -%% `Tail', otherwise, i.e., if `Node' represents -%% "[E1, ..., En]", `none' is -%% returned. -%% -%% Note that even if this function returns some `Tail' -%% that is not `none', the type of `Tail' can be -%% `nil', if the tail has been given explicitly, and the list -%% skeleton has not been compacted (see {@link compact_list/1}). -%% -%% @see list/2 -%% @see nil/0 -%% @see compact_list/1 - -doc """ -Returns the suffix subtree of a `list` node, if one exists. If `Node` represents -"`[*E1*, ..., *En* | *Tail*]`", the returned value is `Tail`, otherwise, i.e., -if `Node` represents "`[*E1*, ..., *En*]`", `none` is returned. +Returns the suffix subtree of a `list` node, if one exists. -Note that even if this function returns some `Tail` that is not `none`, the type -of `Tail` can be `nil`, if the tail has been given explicitly, and the list -skeleton has not been compacted (see `compact_list/1`). +If `Node` represents "`[E1, ..., En | Tail]`", the returned value is +`Tail`. Otherwise, if `Node` represents "`[E1, ..., En]`", `none` is +returned. + +> #### Note {: .info } +> +> Even if this function returns a `Tail` that is not `none`, the type +> of `Tail` can be `nil` if the tail has been given explicitly and the +> list skeleton has not been compacted (see `compact_list/1`). _See also: _`compact_list/1`, `list/2`, `nil/0`. """. @@ -3235,34 +2392,19 @@ cons_suffix(Tail) -> Tail. -%% ===================================================================== -%% @doc "Optimising" list skeleton cons operation. Creates an abstract -%% list skeleton whose first element is `Head' and whose tail -%% corresponds to `Tail'. This is similar to -%% `list([Head], Tail)', except that `Tail' may -%% not be `none', and that the result does not necessarily -%% represent exactly "[Head | Tail]", but -%% may depend on the `Tail' subtree. E.g., if -%% `Tail' represents `[X, Y]', the result may -%% represent "[Head, X, Y]", rather than -%% "[Head | [X, Y]]". Annotations on -%% `Tail' itself may be lost if `Tail' represents -%% a list skeleton, but comments on `Tail' are propagated to -%% the result. -%% -%% @see list/2 -%% @see list_head/1 -%% @see list_tail/1 - --doc """ -"Optimising" list skeleton cons operation. Creates an abstract list skeleton -whose first element is `Head` and whose tail corresponds to `Tail`. This is -similar to [`list([Head], Tail)`](`list/2`), except that `Tail` may not be -`none`, and that the result does not necessarily represent exactly -"`[*Head* | *Tail*]`", but may depend on the `Tail` subtree. E.g., if `Tail` -represents `[X, Y]`, the result may represent "`[*Head*, X, Y]`", rather than -"`[*Head* | [X, Y]]`". Annotations on `Tail` itself may be lost if `Tail` -represents a list skeleton, but comments on `Tail` are propagated to the result. +-doc """ +"Optimizing" list skeleton cons operation. + +Creates an abstract list skeleton whose first element is `Head` and +whose tail corresponds to `Tail`. This is similar to [`list([Head], +Tail)`](`list/2`), except that `Tail` must not be `none`, +and the result does not necessarily represent exactly "`[Head | Tail]`", but +may depend on the `Tail` subtree. + +For example, if `Tail` represents `[X, Y]`, the result may represent +"`[Head, X, Y]`", rather than "`[Head | [X, Y]]`". Annotations on +`Tail` itself may be lost if `Tail` represents a list skeleton, but +comments on `Tail` are propagated to the result. _See also: _`list/2`, `list_head/1`, `list_tail/1`. """. @@ -3280,18 +2422,10 @@ cons(Head, Tail) -> end. -%% ===================================================================== -%% @doc Returns the head element subtree of a `list' node. If -%% `Node' represents "[Head ...]", the -%% result will represent "Head". -%% -%% @see list/2 -%% @see list_tail/1 -%% @see cons/2 - -doc """ -Returns the head element subtree of a `list` node. If `Node` represents -"`[*Head* ...]`", the result will represent "`*Head*`". +Returns the head element subtree of a `list` node. + +If `Node` represents "`[Head ...]`", the result will represent "`Head`". _See also: _`cons/2`, `list/2`, `list_tail/1`. """. @@ -3301,27 +2435,14 @@ list_head(Node) -> hd(list_prefix(Node)). -%% ===================================================================== -%% @doc Returns the tail of a `list' node. If -%% `Node' represents a single-element list -%% "[E]", then the result has type -%% `nil', representing "`[]'". If -%% `Node' represents "[E1, E2 -%% ...]", the result will represent "[E2 -%% ...]", and if `Node' represents -%% "[Head | Tail]", the result will -%% represent "Tail". -%% -%% @see list/2 -%% @see list_head/1 -%% @see cons/2 - --doc """ -Returns the tail of a `list` node. If `Node` represents a single-element list -"`[*E*]`", then the result has type `nil`, representing "`[]`". If `Node` -represents "`[*E1*, *E2* ...]`", the result will represent "`[*E2* ...]`", and -if `Node` represents "`[*Head* | *Tail*]`", the result will represent -"`*Tail*`". +-doc """ +Returns the tail of a `list` node. + +If `Node` represents a single-element list "`[E]`", then the result +has type `nil`, representing "`[]`". If `Node` represents "`[E1, +E2 ...]`", the result will represent "`[E2 ...]`", and if `Node` +represents "`[Head | Tail]`", the result will represent +"`Tail`". _See also: _`cons/2`, `list/2`, `list_head/1`. """. @@ -3341,13 +2462,6 @@ list_tail(Node) -> end. -%% ===================================================================== -%% @doc Returns `true' if `Node' has type -%% `list' or `nil', otherwise `false'. -%% -%% @see list/2 -%% @see nil/0 - -doc """ Returns `true` if `Node` has type `list` or `nil`, otherwise `false`. @@ -3363,38 +2477,22 @@ is_list_skeleton(Node) -> end. -%% ===================================================================== -%% @doc Returns `true' if `Node' represents a -%% proper list, and `false' otherwise. A proper list is a -%% list skeleton either on the form "`[]'" or -%% "[E1, ..., En]", or "[... | -%% Tail]" where recursively `Tail' also -%% represents a proper list. -%% -%% Note: Since `Node' is a syntax tree, the actual -%% run-time values corresponding to its subtrees may often be partially -%% or completely unknown. Thus, if `Node' represents e.g. -%% "`[... | Ns]'" (where `Ns' is a variable), then -%% the function will return `false', because it is not known -%% whether `Ns' will be bound to a list at run-time. If -%% `Node' instead represents e.g. "`[1, 2, 3]'" or -%% "`[A | []]'", then the function will return -%% `true'. -%% -%% @see list/2 - --doc """ -Returns `true` if `Node` represents a proper list, and `false` otherwise. A -proper list is a list skeleton either on the form "`[]`" or -"`[*E1*, ..., *En*]`", or "`[... | *Tail*]`" where recursively `Tail` also +-doc """ +Returns `true` if `Node` represents a proper list, and `false` otherwise. + +A proper list is a list skeleton either on the form "`[]`" or "`[E1, +..., En]`", or "`[... | Tail]`" where recursively `Tail` also represents a proper list. -Note: Since `Node` is a syntax tree, the actual run-time values corresponding to -its subtrees may often be partially or completely unknown. Thus, if `Node` -represents e.g. "`[... | Ns]`" (where `Ns` is a variable), then the function -will return `false`, because it is not known whether `Ns` will be bound to a -list at run-time. If `Node` instead represents e.g. "`[1, 2, 3]`" or -"`[A | []]`", then the function will return `true`. +> #### Note {: .info } +> +> Since `Node` is a syntax tree, the actual run-time values +> corresponding to its subtrees can often be partially or completely +> unknown. For example, if `Node` represents "`[... | Ns]`" +> (where `Ns` is a variable), the function will return `false` +> because it is not known whether `Ns` will be bound to a list at +> run-time. Conversely, if `Node` represents, for example, "`[1, 2, 3]`" or +> "`[A | []]`", the function will return `true`. _See also: _`list/2`. """. @@ -3416,21 +2514,13 @@ is_proper_list(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of element subtrees of a list skeleton. -%% `Node' must represent a proper list. E.g., if -%% `Node' represents "[X1, X2 | -%% [X3, X4 | []]", then -%% `list_elements(Node)' yields the list `[X1, X2, X3, X4]'. -%% -%% @see list/2 -%% @see is_proper_list/1 - -doc """ -Returns the list of element subtrees of a list skeleton. `Node` must represent a -proper list. E.g., if `Node` represents "`[*X1*, *X2* | [*X3*, *X4* | []]`", -then [`list_elements(Node)`](`list_elements/1`) yields the list -`[X1, X2, X3, X4]`. +Returns the list of element subtrees of a list skeleton. + +`Node` must represent a proper list. For example, if `Node` represents +"`[X1, X2 | [X3, X4 | []]`", then +[`list_elements(Node)`](`list_elements/1`) yields the list `[X1, X2, +X3, X4]`. _See also: _`is_proper_list/1`, `list/2`. """. @@ -3454,28 +2544,17 @@ list_elements(Node, As) -> end. -%% ===================================================================== -%% @doc Returns the number of element subtrees of a list skeleton. -%% `Node' must represent a proper list. E.g., if -%% `Node' represents "`[X1 | [X2, X3 | [X4, X5, -%% X6]]]'", then `list_length(Node)' returns the -%% integer 6. -%% -%% Note: this is equivalent to -%% `length(list_elements(Node))', but potentially more -%% efficient. -%% -%% @see list/2 -%% @see is_proper_list/1 -%% @see list_elements/1 - -doc """ -Returns the number of element subtrees of a list skeleton. `Node` must represent -a proper list. E.g., if `Node` represents "`[X1 | [X2, X3 | [X4, X5, X6]]]`", -then [`list_length(Node)`](`list_length/1`) returns the integer 6. +Returns the number of element subtrees of a list skeleton. -Note: this is equivalent to [`length(list_elements(Node))`](`length/1`), but -potentially more efficient. +`Node` must represent a proper list. For example, if `Node` represents +"`[X1 | [X2, X3 | [X4, X5, X6]]]`", then +[`list_length(Node)`](`list_length/1`) returns the integer 6. + +> #### Note {: .info } +> +> This is equivalent to [`length(list_elements(Node))`](`length/1`), but +> potentially more efficient. _See also: _`is_proper_list/1`, `list/2`, `list_elements/1`. """. @@ -3499,29 +2578,15 @@ list_length(Node, A) -> end. -%% ===================================================================== -%% @doc Expands an abstract list skeleton to its most explicit form. If -%% `Node' represents "[E1, ..., En | -%% Tail]", the result represents "[E1 | -%% ... [En | Tail1] ... ]", where -%% `Tail1' is the result of -%% `normalize_list(Tail)'. If `Node' represents -%% "[E1, ..., En]", the result simply -%% represents "[E1 | ... [En | []] ... -%% ]". If `Node' does not represent a list skeleton, -%% `Node' itself is returned. -%% -%% @see list/2 -%% @see compact_list/1 - --doc """ -Expands an abstract list skeleton to its most explicit form. If `Node` -represents "`[*E1*, ..., *En* | *Tail*]`", the result represents -"`[*E1* | ... [*En* | *Tail1*] ... ]`", where `Tail1` is the result of -[`normalize_list(Tail)`](`normalize_list/1`). If `Node` represents -"`[*E1*, ..., *En*]`", the result simply represents -"`[*E1* | ... [*En* | []] ... ]`". If `Node` does not represent a list skeleton, -`Node` itself is returned. +-doc """ +Expands an abstract list skeleton to its most explicit form. + +If `Node` represents "`[E1, ..., En | Tail]`", the result +represents "`[E1 | ... [En | Tail1] ... ]`", where `Tail1` is +the result of [`normalize_list(Tail)`](`normalize_list/1`). If `Node` +represents "`[E1, ..., En]`", the result simply represents "`[E1 +| ... [En | []] ... ]`". If `Node` does not represent a list +skeleton, `Node` itself is returned. _See also: _`compact_list/1`, `list/2`. """. @@ -3549,25 +2614,15 @@ normalize_list_1(Es, Tail) -> Tail, Es). -%% ===================================================================== -%% @doc Yields the most compact form for an abstract list skeleton. The -%% result either represents "[E1, ..., En | -%% Tail]", where `Tail' is not a list -%% skeleton, or otherwise simply "[E1, ..., -%% En]". Annotations on subtrees of `Node' -%% that represent list skeletons may be lost, but comments will be -%% propagated to the result. Returns `Node' itself if -%% `Node' does not represent a list skeleton. -%% -%% @see list/2 -%% @see normalize_list/1 - -doc """ -Yields the most compact form for an abstract list skeleton. The result either -represents "`[*E1*, ..., *En* | *Tail*]`", where `Tail` is not a list skeleton, -or otherwise simply "`[*E1*, ..., *En*]`". Annotations on subtrees of `Node` -that represent list skeletons may be lost, but comments will be propagated to -the result. Returns `Node` itself if `Node` does not represent a list skeleton. +Yields the most compact form for an abstract list skeleton. + +The result either represents "`[E1, ..., En | Tail]`", where +`Tail` is not a list skeleton, or otherwise simply "`[E1, ..., +En]`". Annotations on subtrees of `Node` that represent list +skeletons may be lost, but comments will be propagated to the +result. Returns `Node` itself if `Node` does not represent a list +skeleton. _See also: _`list/2`, `normalize_list/1`. """. @@ -3603,20 +2658,16 @@ compact_list(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract binary-object template. If -%% `Fields' is `[F1, ..., Fn]', the result -%% represents "<<F1, ..., -%% Fn>>". -%% -%% @see binary_fields/1 -%% @see binary_field/2 +-doc """ +Creates an abstract binary-object template. + +If `Fields` is `[F1, ..., Fn]`, the result represents "`<>`". + +_See also: _`binary_field/2`, `binary_fields/1`. +""". +-spec binary([syntaxTree()]) -> syntaxTree(). -%% type(Node) = binary -%% data(Node) = Fields -%% -%% Fields = [syntaxTree()] -%% %% `erl_parse' representation: %% %% {bin, Pos, Fields} @@ -3627,14 +2678,6 @@ compact_list(Node) -> %% See `binary_field' for documentation on `erl_parse' binary %% fields (or "elements"). --doc """ -Creates an abstract binary-object template. If `Fields` is `[F1, ..., Fn]`, the -result represents "`<<*F1*, ..., *Fn*>>`". - -_See also: _`binary_field/2`, `binary_fields/1`. -""". --spec binary([syntaxTree()]) -> syntaxTree(). - binary(List) -> tree(binary, List). @@ -3643,12 +2686,6 @@ revert_binary(Node) -> {bin, Pos, binary_fields(Node)}. -%% ===================================================================== -%% @doc Returns the list of field subtrees of a `binary' node. -%% -%% @see binary/1 -%% @see binary_field/2 - -doc """ Returns the list of field subtrees of a `binary` node. @@ -3666,33 +2703,23 @@ binary_fields(Node) -> %% ===================================================================== -%% @equiv binary_field(Body, []) --doc "Equivalent to [binary_field(Body, [])](`binary_field/2`).". +-doc #{equiv => binary_field(Body, [])}. -spec binary_field(syntaxTree()) -> syntaxTree(). binary_field(Body) -> binary_field(Body, []). -%% ===================================================================== -%% @doc Creates an abstract binary template field. -%% If `Size' is `none', this is equivalent to -%% "`binary_field(Body, Types)'", otherwise it is -%% equivalent to "`binary_field(size_qualifier(Body, Size), -%% Types)'". -%% -%% (This is a utility function.) -%% -%% @see binary/1 -%% @see binary_field/2 -%% @see size_qualifier/2 - -doc """ -Creates an abstract binary template field. If `Size` is `none`, this is -equivalent to "[`binary_field(Body, Types)`](`binary_field/2`)", otherwise it is -equivalent to -"[`binary_field(size_qualifier(Body, Size), Types)`](`binary_field/2`)". +binary_field(Body, Size, Types) + +Creates an abstract binary template field. + +If `Size` is `none`, this is equivalent to "[`binary_field(Body, +Types)`](`binary_field/2`)", otherwise it is equivalent to +"[`binary_field(size_qualifier(Body, Size), +Types)`](`binary_field/2`)". (This is a utility function.) @@ -3707,28 +2734,20 @@ binary_field(Body, Size, Types) -> binary_field(size_qualifier(Body, Size), Types). -%% ===================================================================== -%% @doc Creates an abstract binary template field. If -%% `Types' is the empty list, the result simply represents -%% "Body", otherwise, if `Types' is -%% `[T1, ..., Tn]', the result represents -%% "Body/T1-...-Tn". -%% -%% @see binary/1 -%% @see binary_field/1 -%% @see binary_field/3 -%% @see binary_field_body/1 -%% @see binary_field_types/1 -%% @see binary_field_size/1 - -record(binary_field, {body :: syntaxTree(), types :: [syntaxTree()]}). -%% type(Node) = binary_field -%% data(Node) = #binary_field{body :: Body, types :: Types} -%% -%% Body = syntaxTree() -%% Types = [syntaxTree()] -%% +-doc """ +Creates an abstract binary template field. + +If `Types` is the empty list, the result simply represents +"`Body`", otherwise, if `Types` is `[T1, ..., Tn]`, the result +represents "`Body/T1-...-Tn`". + +_See also: _`binary/1`, `binary_field/1`, `binary_field/3`, +`binary_field_body/1`, `binary_field_size/1`, `binary_field_types/1`. +""". +-spec binary_field(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {bin_element, Pos, Expr, Size, TypeList} @@ -3738,16 +2757,6 @@ binary_field(Body, Size, Types) -> %% TypeList = default | [Type] \ [] %% Type = atom() | {atom(), integer()} --doc """ -Creates an abstract binary template field. If `Types` is the empty list, the -result simply represents "`*Body*`", otherwise, if `Types` is `[T1, ..., Tn]`, -the result represents "`*Body*/*T1*-...-*Tn*`". - -_See also: _`binary/1`, `binary_field/1`, `binary_field/3`, -`binary_field_body/1`, `binary_field_size/1`, `binary_field_types/1`. -""". --spec binary_field(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - binary_field(Body, Types) -> tree(binary_field, #binary_field{body = Body, types = Types}). @@ -3772,11 +2781,6 @@ revert_binary_field(Node) -> {bin_element, Pos, Expr, Size, Types}. -%% ===================================================================== -%% @doc Returns the body subtree of a `binary_field'. -%% -%% @see binary_field/2 - -doc """ Returns the body subtree of a `binary_field`. @@ -3797,18 +2801,11 @@ binary_field_body(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of type-specifier subtrees of a -%% `binary_field' node. If `Node' represents -%% ".../T1, ..., Tn", the result is -%% `[T1, ..., Tn]', otherwise the result is the empty list. -%% -%% @see binary_field/2 - -doc """ -Returns the list of type-specifier subtrees of a `binary_field` node. If `Node` -represents "`.../*T1*, ..., *Tn*`", the result is `[T1, ..., Tn]`, otherwise the -result is the empty list. +Returns the list of type-specifier subtrees of a `binary_field` node. + +If `Node` represents "`.../T1, ..., Tn`", the result is `[T1, +..., Tn]`, otherwise the result is the empty list. _See also: _`binary_field/2`. """. @@ -3827,23 +2824,11 @@ binary_field_types(Node) -> end. -%% ===================================================================== -%% @doc Returns the size specifier subtree of a -%% `binary_field' node, if any. If `Node' -%% represents "Body:Size" or -%% "Body:Size/T1, ..., -%% Tn", the result is `Size', otherwise -%% `none' is returned. -%% -%% (This is a utility function.) -%% -%% @see binary_field/2 -%% @see binary_field/3 - -doc """ -Returns the size specifier subtree of a `binary_field` node, if any. If `Node` -represents "`*Body*:*Size*`" or "`*Body*:*Size*/*T1*, ..., *Tn*`", the result is -`Size`, otherwise `none` is returned. +Returns the size specifier subtree of a `binary_field` node, if any. + +If `Node` represents "`Body:Size`" or "`Body:Size/T1, ..., +Tn`", the result is `Size`, otherwise `none` is returned. (This is a utility function.) @@ -3870,22 +2855,12 @@ binary_field_size(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract size qualifier. The result represents -%% "Body:Size". -%% -%% @see size_qualifier_body/1 -%% @see size_qualifier_argument/1 - -record(size_qualifier, {body :: syntaxTree(), size :: syntaxTree()}). -%% type(Node) = size_qualifier -%% data(Node) = #size_qualifier{body :: Body, size :: Size} -%% -%% Body = Size = syntaxTree() - -doc """ -Creates an abstract size qualifier. The result represents "`*Body*:*Size*`". +Creates an abstract size qualifier. + +The result represents "`Body:Size`". _See also: _`size_qualifier_argument/1`, `size_qualifier_body/1`. """. @@ -3896,11 +2871,6 @@ size_qualifier(Body, Size) -> #size_qualifier{body = Body, size = Size}). -%% ===================================================================== -%% @doc Returns the body subtree of a `size_qualifier' node. -%% -%% @see size_qualifier/2 - -doc """ Returns the body subtree of a `size_qualifier` node. @@ -3912,12 +2882,6 @@ size_qualifier_body(Node) -> (data(Node))#size_qualifier.body. -%% ===================================================================== -%% @doc Returns the argument subtree (the size) of a -%% `size_qualifier' node. -%% -%% @see size_qualifier/2 - -doc """ Returns the argument subtree (the size) of a `size_qualifier` node. @@ -3929,24 +2893,24 @@ size_qualifier_argument(Node) -> (data(Node))#size_qualifier.size. -%% ===================================================================== -%% @doc Creates an abstract error marker. The result represents an -%% occurrence of an error in the source code, with an associated Erlang -%% I/O ErrorInfo structure given by `Error' (see module -%% {@link //stdlib/io} for details). Error markers are regarded as source -%% code forms, but have no defined lexical form. -%% -%% Note: this is supported only for backwards compatibility with -%% existing parsers and tools. -%% -%% @see error_marker_info/1 -%% @see warning_marker/1 -%% @see eof_marker/0 -%% @see is_form/1 +-doc """ +Creates an abstract error marker. + +The result represents an occurrence of an error in the source code, +with an associated Erlang I/O ErrorInfo structure given by `Error` +(see module [`//stdlib/io`](`m:io`) for details). Error markers are +regarded as source code forms, but have no defined lexical form. + +> #### Note {: .info } +> +> This is supported only for backwards compatibility with existing parsers +> and tools. + +_See also: _`eof_marker/0`, `error_marker_info/1`, `is_form/1`, +`warning_marker/1`. +""". +-spec error_marker(term()) -> syntaxTree(). -%% type(Node) = error_marker -%% data(Node) = term() -%% %% `erl_parse' representation: %% %% {error, Error} @@ -3956,20 +2920,6 @@ size_qualifier_argument(Node) -> %% Note that there is no position information for the node %% itself: `get_pos' and `set_pos' handle this as a special case. --doc """ -Creates an abstract error marker. The result represents an occurrence of an -error in the source code, with an associated Erlang I/O ErrorInfo structure -given by `Error` (see module [`//stdlib/io`](`m:io`) for details). Error markers -are regarded as source code forms, but have no defined lexical form. - -Note: this is supported only for backwards compatibility with existing parsers -and tools. - -_See also: _`eof_marker/0`, `error_marker_info/1`, `is_form/1`, -`warning_marker/1`. -""". --spec error_marker(term()) -> syntaxTree(). - error_marker(Error) -> tree(error_marker, Error). @@ -3979,11 +2929,6 @@ revert_error_marker(Node) -> {error, error_marker_info(Node)}. -%% ===================================================================== -%% @doc Returns the ErrorInfo structure of an `error_marker' node. -%% -%% @see error_marker/1 - -doc """ Returns the ErrorInfo structure of an `error_marker` node. @@ -4000,24 +2945,25 @@ error_marker_info(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract warning marker. The result represents an -%% occurrence of a possible problem in the source code, with an -%% associated Erlang I/O ErrorInfo structure given by `Error' -%% (see module {@link //stdlib/io} for details). Warning markers are -%% regarded as source code forms, but have no defined lexical form. -%% -%% Note: this is supported only for backwards compatibility with -%% existing parsers and tools. -%% -%% @see warning_marker_info/1 -%% @see error_marker/1 -%% @see eof_marker/0 -%% @see is_form/1 +-doc """ +Creates an abstract warning marker. + +The result represents an occurrence of a possible problem in the +source code, with an associated Erlang I/O ErrorInfo structure given +by `Error` (see module [`//stdlib/io`](`m:io`) for details). Warning +markers are regarded as source code forms, but have no defined lexical +form. + +> #### Note {: .info } +> +> This is supported only for backwards compatibility with existing parsers +> and tools. + +_See also: _`eof_marker/0`, `error_marker/1`, `is_form/1`, +`warning_marker_info/1`. +""". +-spec warning_marker(term()) -> syntaxTree(). -%% type(Node) = warning_marker -%% data(Node) = term() -%% %% `erl_parse' representation: %% %% {warning, Error} @@ -4027,21 +2973,6 @@ error_marker_info(Node) -> %% Note that there is no position information for the node %% itself: `get_pos' and `set_pos' handle this as a special case. --doc """ -Creates an abstract warning marker. The result represents an occurrence of a -possible problem in the source code, with an associated Erlang I/O ErrorInfo -structure given by `Error` (see module [`//stdlib/io`](`m:io`) for details). -Warning markers are regarded as source code forms, but have no defined lexical -form. - -Note: this is supported only for backwards compatibility with existing parsers -and tools. - -_See also: _`eof_marker/0`, `error_marker/1`, `is_form/1`, -`warning_marker_info/1`. -""". --spec warning_marker(term()) -> syntaxTree(). - warning_marker(Warning) -> tree(warning_marker, Warning). @@ -4051,11 +2982,6 @@ revert_warning_marker(Node) -> {warning, warning_marker_info(Node)}. -%% ===================================================================== -%% @doc Returns the ErrorInfo structure of a `warning_marker' node. -%% -%% @see warning_marker/1 - -doc """ Returns the ErrorInfo structure of a `warning_marker` node. @@ -4072,40 +2998,27 @@ warning_marker_info(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract end-of-file marker. This represents the -%% end of input when reading a sequence of source code forms. An -%% end-of-file marker is itself regarded as a source code form -%% (namely, the last in any sequence in which it occurs). It has no -%% defined lexical form. -%% -%% Note: this is retained only for backwards compatibility with -%% existing parsers and tools. -%% -%% @see error_marker/1 -%% @see warning_marker/1 -%% @see is_form/1 - -%% type(Node) = eof_marker -%% data(Node) = term() -%% -%% `erl_parse' representation: -%% -%% {eof, Pos} - -doc """ -Creates an abstract end-of-file marker. This represents the end of input when -reading a sequence of source code forms. An end-of-file marker is itself -regarded as a source code form (namely, the last in any sequence in which it -occurs). It has no defined lexical form. +Creates an abstract end-of-file marker. -Note: this is retained only for backwards compatibility with existing parsers -and tools. +This represents the end of input when reading a sequence of source +code forms. An end-of-file marker is itself regarded as a source code +form (namely, the last in any sequence in which it occurs). It has no +defined lexical form. + +> #### Note {: .info } +> +> This is retained only for backwards compatibility with existing parsers +> and tools. _See also: _`error_marker/1`, `is_form/1`, `warning_marker/1`. """. -spec eof_marker() -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {eof, Pos} + eof_marker() -> tree(eof_marker). @@ -4117,43 +3030,36 @@ revert_eof_marker(Node) -> %% ===================================================================== %% @equiv attribute(Name, none) --doc "Equivalent to [attribute(Name, none)](`attribute/2`).". +-doc #{equiv => attribute(Name, none)}. -spec attribute(syntaxTree()) -> syntaxTree(). attribute(Name) -> attribute(Name, none). -%% ===================================================================== -%% @doc Creates an abstract program attribute. If -%% `Arguments' is `[A1, ..., An]', the result -%% represents "-Name(A1, ..., -%% An).". Otherwise, if `Arguments' is -%% `none', the result represents -%% "-Name.". The latter form makes it possible -%% to represent preprocessor directives such as -%% "`-endif.'". Attributes are source code forms. -%% -%% Note: The preprocessor macro definition directive -%% "-define(Name, Body)." has relatively -%% few requirements on the syntactical form of `Body' (viewed -%% as a sequence of tokens). The `text' node type can be used -%% for a `Body' that is not a normal Erlang construct. -%% -%% @see attribute/1 -%% @see attribute_name/1 -%% @see attribute_arguments/1 -%% @see text/1 -%% @see is_form/1 - -record(attribute, {name :: syntaxTree(), args :: 'none' | [syntaxTree()]}). -%% type(Node) = attribute -%% data(Node) = #attribute{name :: Name, args :: Arguments} -%% -%% Name = syntaxTree() -%% Arguments = none | [syntaxTree()] -%% +-doc """ +Creates an abstract program attribute. + +If `Arguments` is `[A1, ..., An]`, the result represents +"`-Name(A1, ..., An).`". Otherwise, if `Arguments` is `none`, +the result represents "`-Name.`". The latter form makes it possible +to represent preprocessor directives such as "`-endif.`". Attributes +are source code forms. + +> #### Note {: .info } +> +> The preprocessor macro definition directive "`-define(Name, Body).`" +> has relatively few requirements on the syntactical form of `Body` +> (viewed as a sequence of tokens). The `text` node type can be used for +> a `Body` that is not a normal Erlang construct. + +_See also: _`attribute/1`, `attribute_arguments/1`, `attribute_name/1`, +`is_form/1`, `text/1`. +""". +-spec attribute(syntaxTree(), 'none' | [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {attribute, Pos, module, {Name,Vars}} @@ -4248,23 +3154,6 @@ attribute(Name) -> %% %% Representing `-Name(Term).'. --doc """ -Creates an abstract program attribute. If `Arguments` is `[A1, ..., An]`, the -result represents "`-*Name*(*A1*, ..., *An*).`". Otherwise, if `Arguments` is -`none`, the result represents "`-*Name*.`". The latter form makes it possible to -represent preprocessor directives such as "`-endif.`". Attributes are source -code forms. - -Note: The preprocessor macro definition directive "`-define(*Name*, *Body*).`" -has relatively few requirements on the syntactical form of `Body` (viewed as a -sequence of tokens). The `text` node type can be used for a `Body` that is not a -normal Erlang construct. - -_See also: _`attribute/1`, `attribute_arguments/1`, `attribute_name/1`, -`is_form/1`, `text/1`. -""". --spec attribute(syntaxTree(), 'none' | [syntaxTree()]) -> syntaxTree(). - attribute(Name, Args) -> tree(attribute, #attribute{name = Name, args = Args}). @@ -4382,11 +3271,6 @@ revert_module_name(A) -> end. -%% ===================================================================== -%% @doc Returns the name subtree of an `attribute' node. -%% -%% @see attribute/1 - -doc """ Returns the name subtree of an `attribute` node. @@ -4403,20 +3287,12 @@ attribute_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of argument subtrees of an -%% `attribute' node, if any. If `Node' -%% represents "-Name.", the result is -%% `none'. Otherwise, if `Node' represents -%% "-Name(E1, ..., En).", -%% `[E1, ..., E1]' is returned. -%% -%% @see attribute/1 - -doc """ -Returns the list of argument subtrees of an `attribute` node, if any. If `Node` -represents "`-*Name*.`", the result is `none`. Otherwise, if `Node` represents -"`-*Name*(*E1*, ..., *En*).`", `[E1, ..., E1]` is returned. +Returns the list of argument subtrees of an `attribute` node, if any. + +If `Node` represents "`-Name.`", the result is `none`. Otherwise, if +`Node` represents "`-Name(E1, ..., En).`", `[E1, ..., E1]` is +returned. _See also: _`attribute/1`. """. @@ -4469,22 +3345,12 @@ attribute_arguments(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract arity qualifier. The result represents -%% "Body/Arity". -%% -%% @see arity_qualifier_body/1 -%% @see arity_qualifier_argument/1 - -record(arity_qualifier, {body :: syntaxTree(), arity :: syntaxTree()}). -%% type(Node) = arity_qualifier -%% data(Node) = #arity_qualifier{body :: Body, arity :: Arity} -%% -%% Body = Arity = syntaxTree() - -doc """ -Creates an abstract arity qualifier. The result represents "`*Body*/*Arity*`". +Creates an abstract arity qualifier. + +The result represents "`Body/Arity`". _See also: _`arity_qualifier_argument/1`, `arity_qualifier_body/1`. """. @@ -4495,11 +3361,6 @@ arity_qualifier(Body, Arity) -> #arity_qualifier{body = Body, arity = Arity}). -%% ===================================================================== -%% @doc Returns the body subtree of an `arity_qualifier' node. -%% -%% @see arity_qualifier/2 - -doc """ Returns the body subtree of an `arity_qualifier` node. @@ -4511,12 +3372,6 @@ arity_qualifier_body(Node) -> (data(Node))#arity_qualifier.body. -%% ===================================================================== -%% @doc Returns the argument (the arity) subtree of an -%% `arity_qualifier' node. -%% -%% @see arity_qualifier/2 - -doc """ Returns the argument (the arity) subtree of an `arity_qualifier` node. @@ -4528,33 +3383,23 @@ arity_qualifier_argument(Node) -> (data(Node))#arity_qualifier.arity. -%% ===================================================================== -%% @doc Creates an abstract module qualifier. The result represents -%% "Module:Body". -%% -%% @see module_qualifier_argument/1 -%% @see module_qualifier_body/1 - -record(module_qualifier, {module :: syntaxTree(), body :: syntaxTree()}). -%% type(Node) = module_qualifier -%% data(Node) = #module_qualifier{module :: Module, body :: Body} -%% -%% Module = Body = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {remote, Pos, Module, Arg} -%% -%% Module = Arg = erl_parse() - -doc """ -Creates an abstract module qualifier. The result represents "`*Module*:*Body*`". +Creates an abstract module qualifier. + +The result represents "`Module:Body`". _See also: _`module_qualifier_argument/1`, `module_qualifier_body/1`. """. -spec module_qualifier(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {remote, Pos, Module, Arg} +%% +%% Module = Arg = erl_parse() + module_qualifier(Module, Body) -> tree(module_qualifier, #module_qualifier{module = Module, body = Body}). @@ -4566,12 +3411,6 @@ revert_module_qualifier(Node) -> {remote, Pos, Module, Body}. -%% ===================================================================== -%% @doc Returns the argument (the module) subtree of a -%% `module_qualifier' node. -%% -%% @see module_qualifier/2 - -doc """ Returns the argument (the module) subtree of a `module_qualifier` node. @@ -4588,11 +3427,6 @@ module_qualifier_argument(Node) -> end. -%% ===================================================================== -%% @doc Returns the body subtree of a `module_qualifier' node. -%% -%% @see module_qualifier/2 - -doc """ Returns the body subtree of a `module_qualifier` node. @@ -4609,39 +3443,31 @@ module_qualifier_body(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract function definition. If `Clauses' -%% is `[C1, ..., Cn]', the result represents -%% "Name C1; ...; Name -%% Cn.". More exactly, if each `Ci' -%% represents "(Pi1, ..., Pim) Gi -> -%% Bi", then the result represents -%% "Name(P11, ..., P1m) G1 -> -%% B1; ...; Name(Pn1, ..., Pnm) -%% Gn -> Bn.". Function definitions are source -%% code forms. -%% -%% @see function_name/1 -%% @see function_clauses/1 -%% @see function_arity/1 -%% @see is_form/1 - %% Don't use the name 'function' for this record, to avoid confusion with %% the tuples on the form {function,Name,Arity} used by erl_parse. +%% +%% (There's no real point in precomputing and storing the arity, +%% and passing it as a constructor argument makes it possible to +%% end up with an inconsistent value. Besides, some people might +%% want to check all clauses, and not just the first, so the +%% computation is not obvious.) + -record(func, {name :: syntaxTree(), clauses :: [syntaxTree()]}). -%% type(Node) = function -%% data(Node) = #func{name :: Name, clauses :: Clauses} -%% -%% Name = syntaxTree() -%% Clauses = [syntaxTree()] -%% -%% (There's no real point in precomputing and storing the arity, -%% and passing it as a constructor argument makes it possible to -%% end up with an inconsistent value. Besides, some people might -%% want to check all clauses, and not just the first, so the -%% computation is not obvious.) -%% +-doc """ +Creates an abstract function definition. + +If `Clauses` is `[C1, ..., Cn]`, the result represents "`Name C1; +...; Name Cn.`". More exactly, if each `Ci` represents "`(Pi1, ..., +Pim) Gi -> Bi`", then the result represents "`Name(P11, ..., +P1m) G1 -> B1; ...; Name(Pn1, ..., Pnm) Gn -> Bn.`". +Function definitions are source code forms. + +_See also: _`function_arity/1`, `function_clauses/1`, `function_name/1`, +`is_form/1`. +""". +-spec function(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {function, Pos, Name, Arity, Clauses} @@ -4655,18 +3481,6 @@ module_qualifier_body(Node) -> %% the integer `Arity'; see `clause' for documentation on %% `erl_parse' clauses. --doc """ -Creates an abstract function definition. If `Clauses` is `[C1, ..., Cn]`, the -result represents "`*Name**C1*; ...; *Name**Cn*.`". More exactly, if each `Ci` -represents "`(*Pi1*, ..., *Pim*) *Gi* -> *Bi*`", then the result represents -"`*Name*(*P11*, ..., *P1m*) *G1* -> *B1*; ...; *Name*(*Pn1*, ..., *Pnm*) *Gn* -> *Bn*.`". -Function definitions are source code forms. - -_See also: _`function_arity/1`, `function_clauses/1`, `function_name/1`, -`is_form/1`. -""". --spec function(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - function(Name, Clauses) -> tree(function, #func{name = Name, clauses = Clauses}). @@ -4683,11 +3497,6 @@ revert_function(Node) -> end. -%% ===================================================================== -%% @doc Returns the name subtree of a `function' node. -%% -%% @see function/2 - -doc """ Returns the name subtree of a `function` node. @@ -4704,11 +3513,6 @@ function_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of clause subtrees of a `function' node. -%% -%% @see function/2 - -doc """ Returns the list of clause subtrees of a `function` node. @@ -4725,24 +3529,11 @@ function_clauses(Node) -> end. -%% ===================================================================== -%% @doc Returns the arity of a `function' node. The result -%% is the number of parameter patterns in the first clause of the -%% function; subsequent clauses are ignored. -%% -%% An exception is thrown if `function_clauses(Node)' -%% returns an empty list, or if the first element of that list is not -%% a syntax tree `C' of type `clause' such that -%% `clause_patterns(C)' is a nonempty list. -%% -%% @see function/2 -%% @see function_clauses/1 -%% @see clause/3 -%% @see clause_patterns/1 - -doc """ -Returns the arity of a `function` node. The result is the number of parameter -patterns in the first clause of the function; subsequent clauses are ignored. +Returns the arity of a `function` node. + +The result is the number of parameter patterns in the first clause of +the function; subsequent clauses are ignored. An exception is thrown if [`function_clauses(Node)`](`function_clauses/1`) returns an empty list, or if the first element of that list is not a syntax tree @@ -4760,58 +3551,42 @@ function_arity(Node) -> %% ===================================================================== -%% @equiv clause([], Guard, Body) -type guard() :: 'none' | syntaxTree() | [syntaxTree()] | [[syntaxTree()]]. --doc "Equivalent to [clause([], Guard, Body)](`clause/3`).". +-doc #{equiv => clause([], Guard, Body)}. -spec clause(guard(), [syntaxTree()]) -> syntaxTree(). clause(Guard, Body) -> clause([], Guard, Body). -%% ===================================================================== -%% @doc Creates an abstract clause. If `Patterns' is -%% `[P1, ..., Pn]' and `Body' is `[B1, ..., -%% Bm]', then if `Guard' is `none', the -%% result represents "(P1, ..., Pn) -> -%% B1, ..., Bm", otherwise, unless -%% `Guard' is a list, the result represents -%% "(P1, ..., Pn) when Guard -> -%% B1, ..., Bm". -%% -%% For simplicity, the `Guard' argument may also be any -%% of the following: -%%
    -%%
  • An empty list `[]'. This is equivalent to passing -%% `none'.
  • -%%
  • A nonempty list `[E1, ..., Ej]' of syntax trees. -%% This is equivalent to passing `conjunction([E1, ..., -%% Ej])'.
  • -%%
  • A nonempty list of lists of syntax trees `[[E1_1, ..., -%% E1_k1], ..., [Ej_1, ..., Ej_kj]]', which is equivalent -%% to passing `disjunction([conjunction([E1_1, ..., -%% E1_k1]), ..., conjunction([Ej_1, ..., Ej_kj])])'.
  • -%%
-%% -%% @see clause/2 -%% @see clause_patterns/1 -%% @see clause_guard/1 -%% @see clause_body/1 - -record(clause, {patterns :: [syntaxTree()], guard :: guard(), body :: [syntaxTree()]}). -%% type(Node) = clause -%% data(Node) = #clause{patterns :: Patterns, guard :: Guard, -%% body :: Body} -%% -%% Patterns = [syntaxTree()] -%% Guard = syntaxTree() | none -%% Body = [syntaxTree()] -%% +-doc """ +Creates an abstract clause. + +If `Patterns` is `[P1, ..., Pn]` and `Body` is `[B1, ..., Bm]`, then +if `Guard` is `none`, the result represents "`(P1, ..., Pn) -> +B1, ..., Bm`", otherwise, unless `Guard` is a list, the result +represents "`(P1, ..., Pn) when Guard -> B1, ..., Bm`". + +For simplicity, the `Guard` argument may also be any of the following: + +- An empty list `[]`. This is equivalent to passing `none`. +- A nonempty list `[E1, ..., Ej]` of syntax trees. This is equivalent to passing + `conjunction([E1, ..., Ej])`. +- A nonempty list of lists of syntax trees + `[[E1_1, ..., E1_k1], ..., [Ej_1, ..., Ej_kj]]`, which is equivalent to + passing + `disjunction([conjunction([E1_1, ..., E1_k1]), ..., conjunction([Ej_1, ..., Ej_kj])])`. + +_See also: _`clause/2`, `clause_body/1`, `clause_guard/1`, `clause_patterns/1`. +""". +-spec clause([syntaxTree()], guard(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {clause, Pos, Patterns, Guard, Body} @@ -4829,26 +3604,6 @@ clause(Guard, Body) -> %% versions, `Guard' was simply a list `[E1, ..., En]' of parse %% trees, which is equivalent to the new form `[[E1, ..., En]]'. --doc """ -Creates an abstract clause. If `Patterns` is `[P1, ..., Pn]` and `Body` is -`[B1, ..., Bm]`, then if `Guard` is `none`, the result represents -"`(*P1*, ..., *Pn*) -> *B1*, ..., *Bm*`", otherwise, unless `Guard` is a list, -the result represents "`(*P1*, ..., *Pn*) when *Guard* -> *B1*, ..., *Bm*`". - -For simplicity, the `Guard` argument may also be any of the following: - -- An empty list `[]`. This is equivalent to passing `none`. -- A nonempty list `[E1, ..., Ej]` of syntax trees. This is equivalent to passing - `conjunction([E1, ..., Ej])`. -- A nonempty list of lists of syntax trees - `[[E1_1, ..., E1_k1], ..., [Ej_1, ..., Ej_kj]]`, which is equivalent to - passing - `disjunction([conjunction([E1_1, ..., E1_k1]), ..., conjunction([Ej_1, ..., Ej_kj])])`. - -_See also: _`clause/2`, `clause_body/1`, `clause_guard/1`, `clause_patterns/1`. -""". --spec clause([syntaxTree()], guard(), [syntaxTree()]) -> syntaxTree(). - clause(Patterns, Guard, Body) -> Guard1 = case Guard of [] -> @@ -4928,11 +3683,6 @@ unfold_try_clause({clause, Pos, [{tuple, _, [C, V, Stacktrace]}], {clause, Pos, [class_qualifier(C, V, Stacktrace)], Guard, Body}. -%% ===================================================================== -%% @doc Returns the list of pattern subtrees of a `clause' node. -%% -%% @see clause/3 - -doc """ Returns the list of pattern subtrees of a `clause` node. @@ -4949,19 +3699,11 @@ clause_patterns(Node) -> end. -%% ===================================================================== -%% @doc Returns the guard subtree of a `clause' node, if -%% any. If `Node' represents "(P1, ..., -%% Pn) when Guard -> B1, ..., -%% Bm", `Guard' is returned. Otherwise, the -%% result is `none'. -%% -%% @see clause/3 - -doc """ -Returns the guard subtree of a `clause` node, if any. If `Node` represents -"`(*P1*, ..., *Pn*) when *Guard* -> *B1*, ..., *Bm*`", `Guard` is returned. -Otherwise, the result is `none`. +Returns the guard subtree of a `clause` node, if any. + +If `Node` represents "`(P1, ..., Pn) when Guard -> B1, ..., +Bm`", `Guard` is returned. Otherwise, the result is `none`. _See also: _`clause/3`. """. @@ -4982,11 +3724,6 @@ clause_guard(Node) -> end. -%% ===================================================================== -%% @doc Return the list of body subtrees of a `clause' node. -%% -%% @see clause/3 - -doc """ Return the list of body subtrees of a `clause` node. @@ -5003,20 +3740,10 @@ clause_body(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract disjunction. If `List' is -%% `[E1, ..., En]', the result represents -%% "E1; ...; En". -%% -%% @see disjunction_body/1 -%% @see conjunction/1 - -%% type(Node) = disjunction -%% data(Node) = [syntaxTree()] - -doc """ -Creates an abstract disjunction. If `List` is `[E1, ..., En]`, the result -represents "`*E1*; ...; *En*`". +Creates an abstract disjunction. + +If `List` is `[E1, ..., En]`, the result represents "`E1; ...; En`". _See also: _`conjunction/1`, `disjunction_body/1`. """. @@ -5026,12 +3753,6 @@ disjunction(Tests) -> tree(disjunction, Tests). -%% ===================================================================== -%% @doc Returns the list of body subtrees of a -%% `disjunction' node. -%% -%% @see disjunction/1 - -doc """ Returns the list of body subtrees of a `disjunction` node. @@ -5043,20 +3764,10 @@ disjunction_body(Node) -> data(Node). -%% ===================================================================== -%% @doc Creates an abstract conjunction. If `List' is -%% `[E1, ..., En]', the result represents -%% "E1, ..., En". -%% -%% @see conjunction_body/1 -%% @see disjunction/1 - -%% type(Node) = conjunction -%% data(Node) = [syntaxTree()] - -doc """ -Creates an abstract conjunction. If `List` is `[E1, ..., En]`, the result -represents "`*E1*, ..., *En*`". +Creates an abstract conjunction. + +If `List` is `[E1, ..., En]`, the result represents "`E1, ..., En`". _See also: _`conjunction_body/1`, `disjunction/1`. """. @@ -5066,12 +3777,6 @@ conjunction(Tests) -> tree(conjunction, Tests). -%% ===================================================================== -%% @doc Returns the list of body subtrees of a -%% `conjunction' node. -%% -%% @see conjunction/1 - -doc """ Returns the list of body subtrees of a `conjunction` node. @@ -5083,28 +3788,21 @@ conjunction_body(Node) -> data(Node). -%% ===================================================================== -%% @doc Creates an abstract catch-expression. The result represents -%% "catch Expr". -%% -%% @see catch_expr_body/1 +-doc """ +Creates an abstract catch-expression. + +The result represents "`catch Expr`". + +_See also: _`catch_expr_body/1`. +""". +-spec catch_expr(syntaxTree()) -> syntaxTree(). -%% type(Node) = catch_expr -%% data(Node) = syntaxTree() -%% %% `erl_parse' representation: %% %% {'catch', Pos, Expr} %% %% Expr = erl_parse() --doc """ -Creates an abstract catch-expression. The result represents "`catch *Expr*`". - -_See also: _`catch_expr_body/1`. -""". --spec catch_expr(syntaxTree()) -> syntaxTree(). - catch_expr(Expr) -> tree(catch_expr, Expr). @@ -5114,11 +3812,6 @@ revert_catch_expr(Node) -> {'catch', Pos, Expr}. -%% ===================================================================== -%% @doc Returns the body subtree of a `catch_expr' node. -%% -%% @see catch_expr/1 - -doc """ Returns the body subtree of a `catch_expr` node. @@ -5135,34 +3828,23 @@ catch_expr_body(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract match-expression. The result represents -%% "Pattern = Body". -%% -%% @see match_expr_pattern/1 -%% @see match_expr_body/1 - -record(match_expr, {pattern :: syntaxTree(), body :: syntaxTree()}). -%% type(Node) = match_expr -%% data(Node) = #match_expr{pattern :: Pattern, body :: Body} -%% -%% Pattern = Body = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {match, Pos, Pattern, Body} -%% -%% Pattern = Body = erl_parse() - -doc """ -Creates an abstract match-expression. The result represents -"`*Pattern* = *Body*`". +Creates an abstract match-expression. + +The result represents "`Pattern = Body`". _See also: _`match_expr_body/1`, `match_expr_pattern/1`. """. -spec match_expr(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {match, Pos, Pattern, Body} +%% +%% Pattern = Body = erl_parse() + match_expr(Pattern, Body) -> tree(match_expr, #match_expr{pattern = Pattern, body = Body}). @@ -5173,11 +3855,6 @@ revert_match_expr(Node) -> {match, Pos, Pattern, Body}. -%% ===================================================================== -%% @doc Returns the pattern subtree of a `match_expr' node. -%% -%% @see match_expr/2 - -doc """ Returns the pattern subtree of a `match_expr` node. @@ -5194,11 +3871,6 @@ match_expr_pattern(Node) -> end. -%% ===================================================================== -%% @doc Returns the body subtree of a `match_expr' node. -%% -%% @see match_expr/2 - -doc """ Returns the body subtree of a `match_expr` node. @@ -5215,38 +3887,25 @@ match_expr_body(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract maybe-expression, as used in maybe -%% blocks. The result represents -%% "Pattern ?= Body". -%% -%% @see maybe_match_expr_pattern/1 -%% @see maybe_match_expr_body/1 -%% @see maybe_expr/2 - -record(maybe_match_expr, {pattern :: syntaxTree(), body :: syntaxTree()}). -%% type(Node) = maybe_expr -%% data(Node) = #maybe_expr{pattern :: Pattern, body :: Body} -%% -%% Pattern = Body = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {maybe_match, Pos, Pattern, Body} -%% -%% Pattern = Body = erl_parse() -%% - -doc """ -Creates an abstract maybe-expression, as used in `maybe` blocks. The result -represents "`*Pattern* ?= *Body*`". +Creates an abstract maybe-expression, as used in `maybe` blocks. + +The result represents "`Pattern ?= Body`". _See also: _`maybe_expr/2`, `maybe_match_expr_body/1`, `maybe_match_expr_pattern/1`. """. -spec maybe_match_expr(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {maybe_match, Pos, Pattern, Body} +%% +%% Pattern = Body = erl_parse() +%% + maybe_match_expr(Pattern, Body) -> tree(maybe_match_expr, #maybe_match_expr{pattern = Pattern, body = Body}). @@ -5256,11 +3915,6 @@ revert_maybe_match_expr(Node) -> Body = maybe_match_expr_body(Node), {maybe_match, Pos, Pattern, Body}. -%% ===================================================================== -%% @doc Returns the pattern subtree of a `maybe_expr' node. -%% -%% @see maybe_match_expr/2 - -doc """ Returns the pattern subtree of a `maybe_expr` node. @@ -5277,11 +3931,6 @@ maybe_match_expr_pattern(Node) -> end. -%% ===================================================================== -%% @doc Returns the body subtree of a `maybe_expr' node. -%% -%% @see maybe_match_expr/2 - -doc """ Returns the body subtree of a `maybe_expr` node. @@ -5297,26 +3946,16 @@ maybe_match_expr_body(Node) -> (data(Node1))#maybe_match_expr.body end. -%% ===================================================================== -%% @doc Creates an abstract operator. The name of the operator is the -%% character sequence represented by `Name'. This is -%% analogous to the print name of an atom, but an operator is never -%% written within single-quotes; e.g., the result of -%% operator('++') represents "++" rather -%% than "'++'". -%% -%% @see operator_name/1 -%% @see operator_literal/1 -%% @see atom/1 +-doc """ +operator(Name) -%% type(Node) = operator -%% data(Node) = atom() +Creates an abstract operator. --doc """ -Creates an abstract operator. The name of the operator is the character sequence -represented by `Name`. This is analogous to the print name of an atom, but an -operator is never written within single-quotes; e.g., the result of -[`operator('++')`](`operator/1`) represents "`++`" rather than "`'++'`". +The name of the operator is the character sequence represented by +`Name`. This is analogous to the print name of an atom, but an +operator is never written within single-quotes; for example, the +result of [`operator('++')`](`operator/1`) represents "`++`" rather +than "`'++'`". _See also: _`atom/1`, `operator_literal/1`, `operator_name/1`. """. @@ -5328,15 +3967,10 @@ operator(Name) -> tree(operator, list_to_atom(Name)). -%% ===================================================================== -%% @doc Returns the name of an `operator' node. Note that -%% the name is returned as an atom. -%% -%% @see operator/1 - -doc """ -Returns the name of an `operator` node. Note that the name is returned as an -atom. +Returns the name of an `operator` node. + +Note that the name is returned as an atom. _See also: _`operator/1`. """. @@ -5346,15 +3980,10 @@ operator_name(Node) -> data(Node). -%% ===================================================================== -%% @doc Returns the literal string represented by an -%% `operator' node. This is simply the operator name as a string. -%% -%% @see operator/1 - -doc """ -Returns the literal string represented by an `operator` node. This is simply the -operator name as a string. +Returns the literal string represented by an `operator` node. + +This is simply the operator name as a string. _See also: _`operator/1`. """. @@ -5364,42 +3993,27 @@ operator_literal(Node) -> atom_to_list(operator_name(Node)). -%% ===================================================================== -%% @doc Creates an abstract infix operator expression. The result -%% represents "Left Operator -%% Right". -%% -%% @see infix_expr_left/1 -%% @see infix_expr_right/1 -%% @see infix_expr_operator/1 -%% @see prefix_expr/2 - -record(infix_expr, {operator :: syntaxTree(), left :: syntaxTree(), right :: syntaxTree()}). -%% type(Node) = infix_expr -%% data(Node) = #infix_expr{left :: Left, operator :: Operator, -%% right :: Right} -%% -%% Left = Operator = Right = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {op, Pos, Operator, Left, Right} -%% -%% Operator = atom() -%% Left = Right = erl_parse() - -doc """ -Creates an abstract infix operator expression. The result represents -"`*Left**Operator**Right*`". +Creates an abstract infix operator expression. + +The result represents "`Left Operator Right`". _See also: _`infix_expr_left/1`, `infix_expr_operator/1`, `infix_expr_right/1`, `prefix_expr/2`. """. -spec infix_expr(syntaxTree(), syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {op, Pos, Operator, Left, Right} +%% +%% Operator = atom() +%% Left = Right = erl_parse() + infix_expr(Left, Operator, Right) -> tree(infix_expr, #infix_expr{operator = Operator, left = Left, right = Right}). @@ -5419,12 +4033,6 @@ revert_infix_expr(Node) -> end. -%% ===================================================================== -%% @doc Returns the left argument subtree of an -%% `infix_expr' node. -%% -%% @see infix_expr/3 - -doc """ Returns the left argument subtree of an `infix_expr` node. @@ -5441,11 +4049,6 @@ infix_expr_left(Node) -> end. -%% ===================================================================== -%% @doc Returns the operator subtree of an `infix_expr' node. -%% -%% @see infix_expr/3 - -doc """ Returns the operator subtree of an `infix_expr` node. @@ -5462,12 +4065,6 @@ infix_expr_operator(Node) -> end. -%% ===================================================================== -%% @doc Returns the right argument subtree of an -%% `infix_expr' node. -%% -%% @see infix_expr/3 - -doc """ Returns the right argument subtree of an `infix_expr` node. @@ -5484,22 +4081,17 @@ infix_expr_right(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract prefix operator expression. The result -%% represents "Operator Argument". -%% -%% @see prefix_expr_argument/1 -%% @see prefix_expr_operator/1 -%% @see infix_expr/3 - -record(prefix_expr, {operator :: syntaxTree(), argument :: syntaxTree()}). -%% type(Node) = prefix_expr -%% data(Node) = #prefix_expr{operator :: Operator, -%% argument :: Argument} -%% -%% Operator = Argument = syntaxTree() -%% +-doc """ +Creates an abstract prefix operator expression. + +The result represents "`Operator Argument`". + +_See also: _`infix_expr/3`, `prefix_expr_argument/1`, `prefix_expr_operator/1`. +""". +-spec prefix_expr(syntaxTree(), syntaxTree()) -> syntaxTree(). + %% `erl_parse' representation: %% %% {op, Pos, Operator, Arg} @@ -5507,14 +4099,6 @@ infix_expr_right(Node) -> %% Operator = atom() %% Argument = erl_parse() --doc """ -Creates an abstract prefix operator expression. The result represents -"`*Operator**Argument*`". - -_See also: _`infix_expr/3`, `prefix_expr_argument/1`, `prefix_expr_operator/1`. -""". --spec prefix_expr(syntaxTree(), syntaxTree()) -> syntaxTree(). - prefix_expr(Operator, Argument) -> tree(prefix_expr, #prefix_expr{operator = Operator, argument = Argument}). @@ -5533,11 +4117,6 @@ revert_prefix_expr(Node) -> end. -%% ===================================================================== -%% @doc Returns the operator subtree of a `prefix_expr' node. -%% -%% @see prefix_expr/2 - -doc """ Returns the operator subtree of a `prefix_expr` node. @@ -5554,11 +4133,6 @@ prefix_expr_operator(Node) -> end. -%% ===================================================================== -%% @doc Returns the argument subtree of a `prefix_expr' node. -%% -%% @see prefix_expr/2 - -doc """ Returns the argument subtree of a `prefix_expr` node. @@ -5576,36 +4150,21 @@ prefix_expr_argument(Node) -> %% ===================================================================== -%% @equiv record_field(Name, none) --doc "Equivalent to [record_field(Name, none)](`record_field/2`).". +-doc #{equiv => record_field(Name, none)}. -spec record_field(syntaxTree()) -> syntaxTree(). record_field(Name) -> record_field(Name, none). -%% ===================================================================== -%% @doc Creates an abstract record field specification. If -%% `Value' is `none', the result represents -%% simply "Name", otherwise it represents -%% "Name = Value". -%% -%% @see record_field_name/1 -%% @see record_field_value/1 -%% @see record_expr/3 - -record(record_field, {name :: syntaxTree(), value :: 'none' | syntaxTree()}). -%% type(Node) = record_field -%% data(Node) = #record_field{name :: Name, value :: Value} -%% -%% Name = syntaxTree() -%% Value = none | syntaxTree() - -doc """ -Creates an abstract record field specification. If `Value` is `none`, the result -represents simply "`*Name*`", otherwise it represents "`*Name* = *Value*`". +Creates an abstract record field specification. + +If `Value` is `none`, the result represents simply "`Name`", +otherwise it represents "`Name = Value`". _See also: _`record_expr/3`, `record_field_name/1`, `record_field_value/1`. """. @@ -5615,11 +4174,6 @@ record_field(Name, Value) -> tree(record_field, #record_field{name = Name, value = Value}). -%% ===================================================================== -%% @doc Returns the name subtree of a `record_field' node. -%% -%% @see record_field/2 - -doc """ Returns the name subtree of a `record_field` node. @@ -5631,20 +4185,11 @@ record_field_name(Node) -> (data(Node))#record_field.name. -%% ===================================================================== -%% @doc Returns the value subtree of a `record_field' node, -%% if any. If `Node' represents -%% "Name", `none' is -%% returned. Otherwise, if `Node' represents -%% "Name = Value", `Value' -%% is returned. -%% -%% @see record_field/2 - -doc """ -Returns the value subtree of a `record_field` node, if any. If `Node` represents -"`*Name*`", `none` is returned. Otherwise, if `Node` represents -"`*Name* = *Value*`", `Value` is returned. +Returns the value subtree of a `record_field` node, if any. + +If `Node` represents "`Name`", `none` is returned. Otherwise, if +`Node` represents "`Name = Value`", `Value` is returned. _See also: _`record_field/2`. """. @@ -5654,44 +4199,29 @@ record_field_value(Node) -> (data(Node))#record_field.value. -%% ===================================================================== -%% @doc Creates an abstract record field index expression. The result -%% represents "#Type.Field". -%% -%% (Note: the function name `record_index/2' is reserved -%% by the Erlang compiler, which is why that name could not be used -%% for this constructor.) -%% -%% @see record_index_expr_type/1 -%% @see record_index_expr_field/1 -%% @see record_expr/3 - -record(record_index_expr, {type :: syntaxTree(), field :: syntaxTree()}). -%% type(Node) = record_index_expr -%% data(Node) = #record_index_expr{type :: Type, field :: Field} -%% -%% Type = Field = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {record_index, Pos, Type, Field} -%% -%% Type = atom() -%% Field = erl_parse() - -doc """ Creates an abstract record field index expression. The result represents -"`#*Type*.*Field*`". +"`#Type.Field`". -(Note: the function name `record_index/2` is reserved by the Erlang compiler, -which is why that name could not be used for this constructor.) +> #### Note {: .info } +> +> The function name `record_index/2` is reserved by the Erlang compiler, +> which is why that name could not be used for this constructor. _See also: _`record_expr/3`, `record_index_expr_field/1`, `record_index_expr_type/1`. """. -spec record_index_expr(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {record_index, Pos, Type, Field} +%% +%% Type = atom() +%% Field = erl_parse() + record_index_expr(Type, Field) -> tree(record_index_expr, #record_index_expr{type = Type, field = Field}). @@ -5708,11 +4238,6 @@ revert_record_index_expr(Node) -> end. -%% ===================================================================== -%% @doc Returns the type subtree of a `record_index_expr' node. -%% -%% @see record_index_expr/2 - -doc """ Returns the type subtree of a `record_index_expr` node. @@ -5729,11 +4254,6 @@ record_index_expr_type(Node) -> end. -%% ===================================================================== -%% @doc Returns the field subtree of a `record_index_expr' node. -%% -%% @see record_index_expr/2 - -doc """ Returns the field subtree of a `record_index_expr` node. @@ -5750,35 +4270,14 @@ record_index_expr_field(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract record field access expression. The result -%% represents "Argument#Type.Field". -%% -%% @see record_access_argument/1 -%% @see record_access_type/1 -%% @see record_access_field/1 -%% @see record_expr/3 - -record(record_access, {argument :: syntaxTree(), type :: syntaxTree(), field :: syntaxTree()}). -%% type(Node) = record_access -%% data(Node) = #record_access{argument :: Argument, type :: Type, -%% field :: Field} -%% -%% Argument = Type = Field = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {record_field, Pos, Argument, Type, Field} -%% -%% Argument = Field = erl_parse() -%% Type = atom() - -doc """ -Creates an abstract record field access expression. The result represents -"`*Argument*#*Type*.*Field*`". +Creates an abstract record field access expression. + +The result represents "`Argument#Type.Field`". _See also: _`record_access_argument/1`, `record_access_field/1`, `record_access_type/1`, `record_expr/3`. @@ -5786,6 +4285,13 @@ _See also: _`record_access_argument/1`, `record_access_field/1`, -spec record_access(syntaxTree(), syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {record_field, Pos, Argument, Type, Field} +%% +%% Argument = Field = erl_parse() +%% Type = atom() + record_access(Argument, Type, Field) -> tree(record_access,#record_access{argument = Argument, type = Type, @@ -5804,11 +4310,6 @@ revert_record_access(Node) -> end. -%% ===================================================================== -%% @doc Returns the argument subtree of a `record_access' node. -%% -%% @see record_access/3 - -doc """ Returns the argument subtree of a `record_access` node. @@ -5825,11 +4326,6 @@ record_access_argument(Node) -> end. -%% ===================================================================== -%% @doc Returns the type subtree of a `record_access' node. -%% -%% @see record_access/3 - -doc """ Returns the type subtree of a `record_access` node. @@ -5846,11 +4342,6 @@ record_access_type(Node) -> end. -%% ===================================================================== -%% @doc Returns the field subtree of a `record_access' node. -%% -%% @see record_access/3 - -doc """ Returns the field subtree of a `record_access` node. @@ -5868,44 +4359,32 @@ record_access_field(Node) -> %% ===================================================================== -%% @equiv record_expr(none, Type, Fields) --doc "Equivalent to [record_expr(none, Type, Fields)](`record_expr/3`).". +-doc #{equiv => record_expr(none, Type, Fields)}. -spec record_expr(syntaxTree(), [syntaxTree()]) -> syntaxTree(). record_expr(Type, Fields) -> record_expr(none, Type, Fields). -%% ===================================================================== -%% @doc Creates an abstract record expression. If `Fields' is -%% `[F1, ..., Fn]', then if `Argument' is -%% `none', the result represents -%% "#Type{F1, ..., Fn}", -%% otherwise it represents -%% "Argument#Type{F1, ..., -%% Fn}". -%% -%% @see record_expr/2 -%% @see record_expr_argument/1 -%% @see record_expr_fields/1 -%% @see record_expr_type/1 -%% @see record_field/2 -%% @see record_index_expr/2 -%% @see record_access/3 - -record(record_expr, {argument :: 'none' | syntaxTree(), type :: syntaxTree(), fields :: [syntaxTree()]}). -%% type(Node) = record_expr -%% data(Node) = #record_expr{argument :: Argument, type :: Type, -%% fields :: Fields} -%% -%% Argument = none | syntaxTree() -%% Type = syntaxTree -%% Fields = [syntaxTree()] -%% +-doc """ +Creates an abstract record expression. + +If `Fields` is `[F1, ..., Fn]`, then if `Argument` is `none`, the +result represents "`#Type{F1, ..., Fn}`", otherwise it +represents "`Argument#Type{F1, ..., Fn}`". + +_See also: _`record_access/3`, `record_expr/2`, `record_expr_argument/1`, +`record_expr_fields/1`, `record_expr_type/1`, `record_field/2`, +`record_index_expr/2`. +""". +-spec record_expr('none' | syntaxTree(), syntaxTree(), [syntaxTree()]) -> + syntaxTree(). + %% `erl_parse' representation: %% %% {record, Pos, Type, Fields} @@ -5918,18 +4397,6 @@ record_expr(Type, Fields) -> %% | {record_field, Pos, Field} %% Field = Value = erl_parse() --doc """ -Creates an abstract record expression. If `Fields` is `[F1, ..., Fn]`, then if -`Argument` is `none`, the result represents "`#*Type*{*F1*, ..., *Fn*}`", -otherwise it represents "`*Argument*#*Type*{*F1*, ..., *Fn*}`". - -_See also: _`record_access/3`, `record_expr/2`, `record_expr_argument/1`, -`record_expr_fields/1`, `record_expr_type/1`, `record_field/2`, -`record_index_expr/2`. -""". --spec record_expr('none' | syntaxTree(), syntaxTree(), [syntaxTree()]) -> - syntaxTree(). - record_expr(Argument, Type, Fields) -> tree(record_expr, #record_expr{argument = Argument, type = Type, fields = Fields}). @@ -5954,20 +4421,12 @@ revert_record_expr(Node) -> end. -%% ===================================================================== -%% @doc Returns the argument subtree of a `record_expr' node, -%% if any. If `Node' represents -%% "#Type{...}", `none' is returned. -%% Otherwise, if `Node' represents -%% "Argument#Type{...}", -%% `Argument' is returned. -%% -%% @see record_expr/3 - -doc """ -Returns the argument subtree of a `record_expr` node, if any. If `Node` -represents "`#*Type*{...}`", `none` is returned. Otherwise, if `Node` represents -"`*Argument*#*Type*{...}`", `Argument` is returned. +Returns the argument subtree of a `record_expr` node, if any. + +If `Node` represents "`#Type{...}`", `none` is returned. Otherwise, +if `Node` represents "`Argument#Type{...}`", `Argument` is +returned. _See also: _`record_expr/3`. """. @@ -5984,11 +4443,6 @@ record_expr_argument(Node) -> end. -%% ===================================================================== -%% @doc Returns the type subtree of a `record_expr' node. -%% -%% @see record_expr/3 - -doc """ Returns the type subtree of a `record_expr` node. @@ -6007,12 +4461,6 @@ record_expr_type(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of field subtrees of a -%% `record_expr' node. -%% -%% @see record_expr/3 - -doc """ Returns the list of field subtrees of a `record_expr` node. @@ -6031,23 +4479,15 @@ record_expr_fields(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract function application expression. If -%% `Module' is `none', this is call is equivalent -%% to `application(Function, Arguments)', otherwise it is -%% equivalent to `application(module_qualifier(Module, Function), -%% Arguments)'. -%% -%% (This is a utility function.) -%% -%% @see application/2 -%% @see module_qualifier/2 - -doc """ -Creates an abstract function application expression. If `Module` is `none`, this -is call is equivalent to [`application(Function, Arguments)`](`application/2`), -otherwise it is equivalent to -[`application(module_qualifier(Module, Function), Arguments)`](`application/2`). +application(Module, Name, Arguments) + +Creates an abstract function application expression. + +If `Module` is `none`, this is call is equivalent to +[`application(Function, Arguments)`](`application/2`), otherwise it is +equivalent to [`application(module_qualifier(Module, Function), +Arguments)`](`application/2`). (This is a utility function.) @@ -6062,41 +4502,26 @@ application(Module, Name, Arguments) -> application(module_qualifier(Module, Name), Arguments). -%% ===================================================================== -%% @doc Creates an abstract function application expression. If -%% `Arguments' is `[A1, ..., An]', the result -%% represents "Operator(A1, ..., -%% An)". -%% -%% @see application_operator/1 -%% @see application_arguments/1 -%% @see application/3 - -record(application, {operator :: syntaxTree(), arguments :: [syntaxTree()]}). -%% type(Node) = application -%% data(Node) = #application{operator :: Operator, -%% arguments :: Arguments} -%% -%% Operator = syntaxTree() -%% Arguments = [syntaxTree()] -%% -%% `erl_parse' representation: -%% -%% {call, Pos, Operator, Args} -%% -%% Operator = erl_parse() -%% Arguments = [erl_parse()] - -doc """ -Creates an abstract function application expression. If `Arguments` is -`[A1, ..., An]`, the result represents "`*Operator*(*A1*, ..., *An*)`". +Creates an abstract function application expression. + +If `Arguments` is `[A1, ..., An]`, the result represents +"`Operator(A1, ..., An)`". _See also: _`application/3`, `application_arguments/1`, `application_operator/1`. """. -spec application(syntaxTree(), [syntaxTree()]) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {call, Pos, Operator, Args} +%% +%% Operator = erl_parse() +%% Arguments = [erl_parse()] + application(Operator, Arguments) -> tree(application, #application{operator = Operator, arguments = Arguments}). @@ -6108,21 +4533,11 @@ revert_application(Node) -> {call, Pos, Operator, Arguments}. -%% ===================================================================== -%% @doc Returns the operator subtree of an `application' node. -%% -%% Note: if `Node' represents -%% "M:F(...)", then the result is the -%% subtree representing "M:F". -%% -%% @see application/2 -%% @see module_qualifier/2 - -doc """ Returns the operator subtree of an `application` node. -Note: if `Node` represents "`*M*:*F*(...)`", then the result is the subtree -representing "`*M*:*F*`". +If `Node` represents "`M:F(...)`", then the result is the subtree +representing "`M:F`". _See also: _`application/2`, `module_qualifier/2`. """. @@ -6137,12 +4552,6 @@ application_operator(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of argument subtrees of an -%% `application' node. -%% -%% @see application/2 - -doc """ Returns the list of argument subtrees of an `application` node. @@ -6158,22 +4567,17 @@ application_arguments(Node) -> (data(Node1))#application.arguments end. -%% ===================================================================== -%% @doc Creates an abstract annotated type expression. The result -%% represents "Name :: Type". -%% -%% @see annotated_type_name/1 -%% @see annotated_type_body/1 - -record(annotated_type, {name :: syntaxTree(), body :: syntaxTree()}). -%% type(Node) = annotated_type -%% data(Node) = #annotated_type{name :: Name, -%% body :: Type} -%% -%% Name = syntaxTree() -%% Type = syntaxTree() -%% +-doc """ +Creates an abstract annotated type expression. + +The result represents "`Name :: Type`". + +_See also: _`annotated_type_body/1`, `annotated_type_name/1`. +""". +-spec annotated_type(syntaxTree(), syntaxTree()) -> syntaxTree(). + %% `erl_parse' representation: %% %% {ann_type, Pos, [Name, Type]} @@ -6181,14 +4585,6 @@ application_arguments(Node) -> %% Name = erl_parse() %% Type = erl_parse() --doc """ -Creates an abstract annotated type expression. The result represents -"`*Name* :: *Type*`". - -_See also: _`annotated_type_body/1`, `annotated_type_name/1`. -""". --spec annotated_type(syntaxTree(), syntaxTree()) -> syntaxTree(). - annotated_type(Name, Type) -> tree(annotated_type, #annotated_type{name = Name, body = Type}). @@ -6199,11 +4595,6 @@ revert_annotated_type(Node) -> {ann_type, Pos, [Name, Type]}. -%% ===================================================================== -%% @doc Returns the name subtree of an `annotated_type' node. -%% -%% @see annotated_type/2 - -doc """ Returns the name subtree of an `annotated_type` node. @@ -6220,11 +4611,6 @@ annotated_type_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the type subtrees of an `annotated_type' node. -%% -%% @see annotated_type/2 - -doc """ Returns the type subtrees of an `annotated_type` node. @@ -6241,21 +4627,17 @@ annotated_type_body(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract fun of any type. The result represents -%% "fun()". +-doc """ +Creates an abstract fun of any type. + +The result represents "`fun()`". +""". +-spec fun_type() -> syntaxTree(). -%% type(Node) = fun_type -%% %% `erl_parse' representation: %% %% {type, Pos, 'fun', []} --doc """ -Creates an abstract fun of any type. The result represents "`fun()`". -""". --spec fun_type() -> syntaxTree(). - fun_type() -> tree(fun_type). @@ -6264,24 +4646,16 @@ revert_fun_type(Node) -> {type, Pos, 'fun', []}. -%% ===================================================================== -%% @doc Creates an abstract type application expression. If -%% `Module' is `none', this is call is equivalent -%% to `type_application(TypeName, Arguments)', otherwise it is -%% equivalent to `type_application(module_qualifier(Module, TypeName), -%% Arguments)'. -%% -%% (This is a utility function.) -%% -%% @see type_application/2 -%% @see module_qualifier/2 - -doc """ -Creates an abstract type application expression. If `Module` is `none`, this is -call is equivalent to -[`type_application(TypeName, Arguments)`](`type_application/2`), otherwise it is -equivalent to -[`type_application(module_qualifier(Module, TypeName), Arguments)`](`type_application/2`). +type_application(Module, TypeName, Arguments) + +Creates an abstract type application expression. + +If `Module` is `none`, this is call is equivalent to +[`type_application(TypeName, Arguments)`](`type_application/2`), +otherwise it is equivalent to +[`type_application(module_qualifier(Module, TypeName), +Arguments)`](`type_application/2`). (This is a utility function.) @@ -6296,26 +4670,20 @@ type_application(Module, TypeName, Arguments) -> type_application(module_qualifier(Module, TypeName), Arguments). -%% ===================================================================== -%% @doc Creates an abstract type application expression. If `Arguments' is -%% `[T1, ..., Tn]', the result represents -%% "TypeName(T1, ...Tn)". -%% -%% @see user_type_application/2 -%% @see type_application/3 -%% @see type_application_name/1 -%% @see type_application_arguments/1 - -record(type_application, {type_name :: syntaxTree(), arguments :: [syntaxTree()]}). -%% type(Node) = type_application -%% data(Node) = #type_application{type_name :: TypeName, -%% arguments :: Arguments} -%% -%% TypeName = syntaxTree() -%% Arguments = [syntaxTree()] -%% +-doc """ +Creates an abstract type application expression. + +If `Arguments` is `[T1, ..., Tn]`, the result represents +"`TypeName(T1, ...Tn)`". + +_See also: _`type_application/3`, `type_application_arguments/1`, +`type_application_name/1`, `user_type_application/2`. +""". +-spec type_application(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {remote, Pos, [Module, Name, Arguments]} | @@ -6325,15 +4693,6 @@ type_application(Module, TypeName, Arguments) -> %% Name = atom() %% Arguments = [erl_parse()] --doc """ -Creates an abstract type application expression. If `Arguments` is -`[T1, ..., Tn]`, the result represents "`*TypeName*(*T1*, ...*Tn*)`". - -_See also: _`type_application/3`, `type_application_arguments/1`, -`type_application_name/1`, `user_type_application/2`. -""". --spec type_application(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - type_application(TypeName, Arguments) -> tree(type_application, #type_application{type_name = TypeName, arguments = Arguments}). @@ -6352,11 +4711,6 @@ revert_type_application(Node) -> end. -%% ===================================================================== -%% @doc Returns the type name subtree of a `type_application' node. -%% -%% @see type_application/2 - -doc """ Returns the type name subtree of a `type_application` node. @@ -6375,11 +4729,6 @@ type_application_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the arguments subtrees of a `type_application' node. -%% -%% @see type_application/2 - -doc """ Returns the arguments subtrees of a `type_application` node. @@ -6398,24 +4747,12 @@ type_application_arguments(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract bitstring type. The result represents -%% "<<_:M, _:_*N>>". -%% -%% @see bitstring_type_m/1 -%% @see bitstring_type_n/1 - -record(bitstring_type, {m :: syntaxTree(), n :: syntaxTree()}). -%% type(Node) = bitstring_type -%% data(Node) = #bitstring_type{m :: M, n :: N} -%% -%% M = syntaxTree() -%% N = syntaxTree() -%% - -doc """ -Creates an abstract bitstring type. The result represents "`*<<_:M, _:_*N>>*`". +Creates an abstract bitstring type. + +The result represents "`<<_:M, _:_N>>`". _See also: _`bitstring_type_m/1`, `bitstring_type_n/1`. """. @@ -6430,11 +4767,6 @@ revert_bitstring_type(Node) -> N = bitstring_type_n(Node), {type, Pos, binary, [M, N]}. -%% ===================================================================== -%% @doc Returns the number of start bits, `M', of a `bitstring_type' node. -%% -%% @see bitstring_type/2 - -doc """ Returns the number of start bits, `M`, of a `bitstring_type` node. @@ -6450,11 +4782,6 @@ bitstring_type_m(Node) -> (data(Node1))#bitstring_type.m end. -%% ===================================================================== -%% @doc Returns the segment size, `N', of a `bitstring_type' node. -%% -%% @see bitstring_type/2 - -doc """ Returns the segment size, `N`, of a `bitstring_type` node. @@ -6471,40 +4798,27 @@ bitstring_type_n(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract constrained function type. -%% If `FunctionConstraint' is `[C1, ..., Cn]', the result represents -%% "FunctionType when C1, ...Cn". -%% -%% @see constrained_function_type_body/1 -%% @see constrained_function_type_argument/1 - -record(constrained_function_type, {body :: syntaxTree(), argument :: syntaxTree()}). -%% type(Node) = constrained_function_type -%% data(Node) = #constrained_function_type{body :: FunctionType, -%% argument :: FunctionConstraint} -%% -%% FunctionType = syntaxTree() -%% FunctionConstraint = syntaxTree() -%% -%% `erl_parse' representation: -%% -%% {type, Pos, bounded_fun, [FunctionType, FunctionConstraint]} -%% -%% FunctionType = erl_parse() -%% FunctionConstraint = [erl_parse()] - -doc """ -Creates an abstract constrained function type. If `FunctionConstraint` is -`[C1, ..., Cn]`, the result represents "`*FunctionType* when *C1*, ...*Cn*`". +Creates an abstract constrained function type. + +If `FunctionConstraint` is `[C1, ..., Cn]`, the result represents +"`FunctionType when C1, ...Cn`". _See also: _`constrained_function_type_argument/1`, `constrained_function_type_body/1`. """. -spec constrained_function_type(syntaxTree(), [syntaxTree()]) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {type, Pos, bounded_fun, [FunctionType, FunctionConstraint]} +%% +%% FunctionType = erl_parse() +%% FunctionConstraint = [erl_parse()] + constrained_function_type(FunctionType, FunctionConstraint) -> Conj = conjunction(FunctionConstraint), tree(constrained_function_type, @@ -6519,12 +4833,6 @@ revert_constrained_function_type(Node) -> {type, Pos, bounded_fun, [FunctionType, FunctionConstraint]}. -%% ===================================================================== -%% @doc Returns the function type subtree of a -%% `constrained_function_type' node. -%% -%% @see constrained_function_type/2 - -doc """ Returns the function type subtree of a `constrained_function_type` node. @@ -6540,12 +4848,6 @@ constrained_function_type_body(Node) -> (data(Node1))#constrained_function_type.body end. -%% ===================================================================== -%% @doc Returns the function constraint subtree of a -%% `constrained_function_type' node. -%% -%% @see constrained_function_type/2 - -doc """ Returns the function constraint subtree of a `constrained_function_type` node. @@ -6563,41 +4865,31 @@ constrained_function_type_argument(Node) -> %% ===================================================================== -%% @equiv function_type(any_arity, Type) --doc "Equivalent to [function_type(any_arity, Type)](`function_type/2`).". +-doc #{equiv => function_type(any_arity, Type)}. -spec function_type(syntaxTree()) -> syntaxTree(). function_type(Type) -> function_type(any_arity, Type). -%% ===================================================================== -%% @doc Creates an abstract function type. If `Arguments' is -%% `[T1, ..., Tn]', then if it occurs within a function -%% specification, the result represents -%% "(T1, ...Tn) -> Return"; otherwise -%% it represents -%% "fun((T1, ...Tn) -> Return)". -%% If `Arguments' is `any_arity', it represents -%% "fun((...) -> Return)". -%% -%% Note that the `erl_parse' representation is identical for -%% "FunctionType" and -%% "fun(FunctionType)". -%% -%% @see function_type_arguments/1 -%% @see function_type_return/1 - -record(function_type, {arguments :: any_arity | [syntaxTree()], return :: syntaxTree()}). -%% type(Node) = function_type -%% data(Node) = #function_type{arguments :: any | Arguments, -%% return :: Type} -%% -%% Arguments = [syntaxTree()] -%% Type = syntaxTree() -%% +-doc """ +Creates an abstract function type. + +If `Arguments` is `[T1, ..., Tn]` *and* it occurs within a function +specification, the result represents "`(T1, ...Tn) -> Return`"; +otherwise it represents "`fun((T1, ...Tn) -> Return)`". If +`Arguments` is `any_arity`, it represents "`fun((...) -> Return)`". + +Note that the `m:erl_parse` representation is identical for +"`FunctionType`" and "`fun(FunctionType)`". + +_See also: _`function_type_arguments/1`, `function_type_return/1`. +""". +-spec function_type('any_arity' | [syntaxTree()], syntaxTree()) -> syntaxTree(). + %% `erl_parse' representation: %% %% {type, Pos, 'fun', [{type, Pos, product, Arguments}, Type]} @@ -6606,20 +4898,6 @@ function_type(Type) -> %% Arguments = [erl_parse()] %% Type = erl_parse() --doc """ -Creates an abstract function type. If `Arguments` is `[T1, ..., Tn]`, then if it -occurs within a function specification, the result represents -"`(*T1*, ...*Tn*) -> *Return*`"; otherwise it represents -"`fun((*T1*, ...*Tn*) -> *Return*)`". If `Arguments` is `any_arity`, it -represents "`fun((...) -> *Return*)`". - -Note that the `erl_parse` representation is identical for "`*FunctionType*`" and -"`fun(*FunctionType*)`". - -_See also: _`function_type_arguments/1`, `function_type_return/1`. -""". --spec function_type('any_arity' | [syntaxTree()], syntaxTree()) -> syntaxTree(). - function_type(Arguments, Return) -> tree(function_type, #function_type{arguments = Arguments, return = Return}). @@ -6635,23 +4913,13 @@ revert_function_type(Node) -> end. -%% ===================================================================== -%% @doc Returns the argument types subtrees of a `function_type' node. -%% If `Node' represents "fun((...) -> Return)", -%% `any_arity' is returned; otherwise, if `Node' represents -%% "(T1, ...Tn) -> Return" or -%% "fun((T1, ...Tn) -> Return)", -%% `[T1, ..., Tn]' is returned. - -%% -%% @see function_type/1 -%% @see function_type/2 - -doc """ -Returns the argument types subtrees of a `function_type` node. If `Node` -represents "`fun((...) -> *Return*)`", `any_arity` is returned; otherwise, if -`Node` represents "`(*T1*, ...*Tn*) -> *Return*`" or -"`fun((*T1*, ...*Tn*) -> *Return*)`", `[T1, ..., Tn]` is returned. +Returns the argument types subtrees of a `function_type` node. + +If `Node` represents "`fun((...) -> Return)`", `any_arity` is +returned; otherwise, if `Node` represents "`(T1, ...Tn) -> +Return`" or "`fun((T1, ...Tn) -> Return)`", `[T1, ..., Tn]` is +returned. _See also: _`function_type/1`, `function_type/2`. """. @@ -6667,12 +4935,6 @@ function_type_arguments(Node) -> (data(Node1))#function_type.arguments end. -%% ===================================================================== -%% @doc Returns the return type subtrees of a `function_type' node. -%% -%% @see function_type/1 -%% @see function_type/2 - -doc """ Returns the return type subtrees of a `function_type` node. @@ -6690,22 +4952,19 @@ function_type_return(Node) -> %% ===================================================================== -%% @doc Creates an abstract (subtype) constraint. The result represents -%% "Name :: Type". -%% -%% @see constraint_argument/1 -%% @see constraint_body/1 -record(constraint, {name :: syntaxTree(), types :: [syntaxTree()]}). -%% type(Node) = constraint -%% data(Node) = #constraint{name :: Name, -%% types :: [Type]} -%% -%% Name = syntaxTree() -%% Type = syntaxTree() -%% +-doc """ +Creates an abstract (subtype) constraint. + +The result represents "`Name :: Type`". + +_See also: _`constraint_argument/1`, `constraint_body/1`. +""". +-spec constraint(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {type, Pos, constraint, [Name, [Var, Type]]} @@ -6714,14 +4973,6 @@ function_type_return(Node) -> %% Var = erl_parse() %% Type = erl_parse() --doc """ -Creates an abstract (subtype) constraint. The result represents -"`*Name* :: *Type*`". - -_See also: _`constraint_argument/1`, `constraint_body/1`. -""". --spec constraint(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - constraint(Name, Types) -> tree(constraint, #constraint{name = Name, types = Types}). @@ -6733,11 +4984,6 @@ revert_constraint(Node) -> {type, Pos, constraint, [Name, Types]}. -%% ===================================================================== -%% @doc Returns the name subtree of a `constraint' node. -%% -%% @see constraint/2 - -doc """ Returns the name subtree of a `constraint` node. @@ -6753,11 +4999,6 @@ constraint_argument(Node) -> (data(Node1))#constraint.name end. -%% ===================================================================== -%% @doc Returns the type subtree of a `constraint' node. -%% -%% @see constraint/2 - -doc """ Returns the type subtree of a `constraint` node. @@ -6775,27 +5016,22 @@ constraint_body(Node) -> %% ===================================================================== -%% @doc Creates an abstract map type assoc field. The result represents -%% "Name => Value". -%% -%% @see map_type_assoc_name/1 -%% @see map_type_assoc_value/1 -%% @see map_type/1 -record(map_type_assoc, {name :: syntaxTree(), value :: syntaxTree()}). -%% `erl_parse' representation: -%% -%% {type, Pos, map_field_assoc, [Name, Value]} - -doc """ -Creates an abstract map type assoc field. The result represents -"`*Name* => *Value*`". +Creates an abstract map type assoc field. + +The result represents "`Name => Value`". _See also: _`map_type/1`, `map_type_assoc_name/1`, `map_type_assoc_value/1`. """. -spec map_type_assoc(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {type, Pos, map_field_assoc, [Name, Value]} + map_type_assoc(Name, Value) -> tree(map_type_assoc, #map_type_assoc{name = Name, value = Value}). @@ -6806,11 +5042,6 @@ revert_map_type_assoc(Node) -> {type, Pos, map_field_assoc, [Name, Value]}. -%% ===================================================================== -%% @doc Returns the name subtree of a `map_type_assoc' node. -%% -%% @see map_type_assoc/2 - -doc """ Returns the name subtree of a `map_type_assoc` node. @@ -6827,11 +5058,6 @@ map_type_assoc_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the value subtree of a `map_type_assoc' node. -%% -%% @see map_type_assoc/2 - -doc """ Returns the value subtree of a `map_type_assoc` node. @@ -6849,27 +5075,22 @@ map_type_assoc_value(Node) -> %% ===================================================================== -%% @doc Creates an abstract map type exact field. The result represents -%% "Name := Value". -%% -%% @see map_type_exact_name/1 -%% @see map_type_exact_value/1 -%% @see map_type/1 -record(map_type_exact, {name :: syntaxTree(), value :: syntaxTree()}). -%% `erl_parse' representation: -%% -%% {type, Pos, map_field_exact, [Name, Value]} - -doc """ -Creates an abstract map type exact field. The result represents -"`*Name* := *Value*`". +Creates an abstract map type exact field. + +The result represents "`Name := Value`". _See also: _`map_type/1`, `map_type_exact_name/1`, `map_type_exact_value/1`. """. -spec map_type_exact(syntaxTree(), syntaxTree()) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {type, Pos, map_field_exact, [Name, Value]} + map_type_exact(Name, Value) -> tree(map_type_exact, #map_type_exact{name = Name, value = Value}). @@ -6880,11 +5101,6 @@ revert_map_type_exact(Node) -> {type, Pos, map_field_exact, [Name, Value]}. -%% ===================================================================== -%% @doc Returns the name subtree of a `map_type_exact' node. -%% -%% @see map_type_exact/2 - -doc """ Returns the name subtree of a `map_type_exact` node. @@ -6901,11 +5117,6 @@ map_type_exact_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the value subtree of a `map_type_exact' node. -%% -%% @see map_type_exact/2 - -doc """ Returns the value subtree of a `map_type_exact` node. @@ -6923,28 +5134,24 @@ map_type_exact_value(Node) -> %% ===================================================================== -%% @equiv map_type(any_size) --doc "Equivalent to [map_type(any_size)](`map_type/1`).". +-doc #{equiv => map_type(any_size)}. -spec map_type() -> syntaxTree(). map_type() -> map_type(any_size). -%% ===================================================================== -%% @doc Creates an abstract type map. If `Fields' is -%% `[F1, ..., Fn]', the result represents -%% "#{F1, ..., Fn}"; -%% otherwise, if `Fields' is `any_size', it represents -%% "map()". -%% -%% @see map_type_fields/1 +-doc """ +Creates an abstract type map. + +If `Fields` is `[F1, ..., Fn]`, the result represents "`#{F1, ..., +Fn}`"; otherwise, if `Fields` is `any_size`, it represents +"`t:map/0`". + +_See also: _`map_type_fields/1`. +""". +-spec map_type('any_size' | [syntaxTree()]) -> syntaxTree(). -%% type(Node) = map_type -%% data(Node) = Fields -%% -%% Fields = any_size | [syntaxTree()] -%% %% `erl_parse' representation: %% %% {type, Pos, map, [Field]} @@ -6952,15 +5159,6 @@ map_type() -> %% %% Field = erl_parse() --doc """ -Creates an abstract type map. If `Fields` is `[F1, ..., Fn]`, the result -represents "`#{*F1*, ..., *Fn*}`"; otherwise, if `Fields` is `any_size`, it -represents "`t:map/0`". - -_See also: _`map_type_fields/1`. -""". --spec map_type('any_size' | [syntaxTree()]) -> syntaxTree(). - map_type(Fields) -> tree(map_type, Fields). @@ -6973,20 +5171,12 @@ revert_map_type(Node) -> {type, Pos, map, Fields} end. -%% ===================================================================== -%% @doc Returns the list of field subtrees of a `map_type' node. -%% If `Node' represents "map()", `any_size' is returned; -%% otherwise, if `Node' represents -%% "#{F1, ..., Fn}", -%% `[F1, ..., Fn]' is returned. -%% -%% @see map_type/0 -%% @see map_type/1 - -doc """ -Returns the list of field subtrees of a `map_type` node. If `Node` represents -"`t:map/0`", `any_size` is returned; otherwise, if `Node` represents -"`#{*F1*, ..., *Fn*}`", `[F1, ..., Fn]` is returned. +Returns the list of field subtrees of a `map_type` node. + +If `Node` represents "`t:map/0`", `any_size` is returned; otherwise, +if `Node` represents "`#{F1, ..., Fn}`", `[F1, ..., Fn]` is +returned. _See also: _`map_type/0`, `map_type/1`. """. @@ -7004,21 +5194,19 @@ map_type_fields(Node) -> %% ===================================================================== -%% @doc Creates an abstract range type. The result represents -%% "Low .. High". -%% -%% @see integer_range_type_low/1 -%% @see integer_range_type_high/1 -record(integer_range_type, {low :: syntaxTree(), high :: syntaxTree()}). -%% type(Node) = integer_range_type -%% data(Node) = #integer_range_type{low :: Low, high :: High} -%% -%% Low = syntaxTree() -%% High = syntaxTree() -%% +-doc """ +Creates an abstract range type. + +The result represents "`Low .. High`". + +_See also: _`integer_range_type_high/1`, `integer_range_type_low/1`. +""". +-spec integer_range_type(syntaxTree(), syntaxTree()) -> syntaxTree(). + %% `erl_parse' representation: %% %% {type, Pos, range, [Low, High]} @@ -7026,13 +5214,6 @@ map_type_fields(Node) -> %% Low = erl_parse() %% High = erl_parse() --doc """ -Creates an abstract range type. The result represents "`*Low* .. *High*`". - -_See also: _`integer_range_type_high/1`, `integer_range_type_low/1`. -""". --spec integer_range_type(syntaxTree(), syntaxTree()) -> syntaxTree(). - integer_range_type(Low, High) -> tree(integer_range_type, #integer_range_type{low = Low, high = High}). @@ -7043,11 +5224,6 @@ revert_integer_range_type(Node) -> {type, Pos, range, [Low, High]}. -%% ===================================================================== -%% @doc Returns the low limit of an `integer_range_type' node. -%% -%% @see integer_range_type/2 - -doc """ Returns the low limit of an `integer_range_type` node. @@ -7063,11 +5239,6 @@ integer_range_type_low(Node) -> (data(Node1))#integer_range_type.low end. -%% ===================================================================== -%% @doc Returns the high limit of an `integer_range_type' node. -%% -%% @see integer_range_type/2 - -doc """ Returns the high limit of an `integer_range_type` node. @@ -7085,22 +5256,20 @@ integer_range_type_high(Node) -> %% ===================================================================== -%% @doc Creates an abstract record type. If `Fields' is -%% `[F1, ..., Fn]', the result represents -%% "#Name{F1, ..., Fn}". -%% -%% @see record_type_name/1 -%% @see record_type_fields/1 -record(record_type, {name :: syntaxTree(), fields :: [syntaxTree()]}). -%% type(Node) = record_type -%% data(Node) = #record_type{name = Name, fields = Fields} -%% -%% Name = syntaxTree() -%% Fields = [syntaxTree()] -%% +-doc """ +Creates an abstract record type. + +If `Fields` is `[F1, ..., Fn]`, the result represents "`#Name{F1, +..., Fn}`". + +_See also: _`record_type_fields/1`, `record_type_name/1`. +""". +-spec record_type(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {type, Pos, record, [Name|Fields]} @@ -7108,14 +5277,6 @@ integer_range_type_high(Node) -> %% Name = erl_parse() %% Fields = [erl_parse()] --doc """ -Creates an abstract record type. If `Fields` is `[F1, ..., Fn]`, the result -represents "`#*Name*{*F1*, ..., *Fn*}`". - -_See also: _`record_type_fields/1`, `record_type_name/1`. -""". --spec record_type(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - record_type(Name, Fields) -> tree(record_type, #record_type{name = Name, fields = Fields}). @@ -7126,11 +5287,6 @@ revert_record_type(Node) -> {type, Pos, record, [Name | Fields]}. -%% ===================================================================== -%% @doc Returns the name subtree of a `record_type' node. -%% -%% @see record_type/2 - -doc """ Returns the name subtree of a `record_type` node. @@ -7146,11 +5302,6 @@ record_type_name(Node) -> (data(Node1))#record_type.name end. -%% ===================================================================== -%% @doc Returns the fields subtree of a `record_type' node. -%% -%% @see record_type/2 - -doc """ Returns the fields subtree of a `record_type` node. @@ -7167,22 +5318,18 @@ record_type_fields(Node) -> end. -%% ===================================================================== -%% @doc Creates an abstract record type field. The result represents -%% "Name :: Type". -%% -%% @see record_type_field_name/1 -%% @see record_type_field_type/1 - -record(record_type_field, {name :: syntaxTree(), type :: syntaxTree()}). -%% type(Node) = record_type_field -%% data(Node) = #record_type_field{name = Name, type = Type} -%% -%% Name = syntaxTree() -%% Type = syntaxTree() -%% +-doc """ +Creates an abstract record type field. + +The result represents "`Name :: Type`". + +_See also: _`record_type_field_name/1`, `record_type_field_type/1`. +""". +-spec record_type_field(syntaxTree(), syntaxTree()) -> syntaxTree(). + %% `erl_parse' representation: %% %% {type, Pos, field_type, [Name, Type]} @@ -7190,14 +5337,6 @@ record_type_fields(Node) -> %% Name = erl_parse() %% Type = erl_parse() --doc """ -Creates an abstract record type field. The result represents -"`*Name* :: *Type*`". - -_See also: _`record_type_field_name/1`, `record_type_field_type/1`. -""". --spec record_type_field(syntaxTree(), syntaxTree()) -> syntaxTree(). - record_type_field(Name, Type) -> tree(record_type_field, #record_type_field{name = Name, type = Type}). @@ -7208,11 +5347,6 @@ revert_record_type_field(Node) -> {type, Pos, field_type, [Name, Type]}. -%% ===================================================================== -%% @doc Returns the name subtree of a `record_type_field' node. -%% -%% @see record_type_field/2 - -doc """ Returns the name subtree of a `record_type_field` node. @@ -7228,11 +5362,6 @@ record_type_field_name(Node) -> (data(Node1))#record_type_field.name end. -%% ===================================================================== -%% @doc Returns the type subtree of a `record_type_field' node. -%% -%% @see record_type_field/2 - -doc """ Returns the type subtree of a `record_type_field` node. @@ -7250,28 +5379,24 @@ record_type_field_type(Node) -> %% ===================================================================== -%% @equiv tuple_type(any_size) --doc "Equivalent to [tuple_type(any_size)](`tuple_type/1`).". +-doc #{equiv => tuple_type(any_size)}. -spec tuple_type() -> syntaxTree(). tuple_type() -> tuple_type(any_size). -%% ===================================================================== -%% @doc Creates an abstract type tuple. If `Elements' is -%% `[T1, ..., Tn]', the result represents -%% "{T1, ..., Tn}"; -%% otherwise, if `Elements' is `any_size', it represents -%% "tuple()". -%% -%% @see tuple_type_elements/1 +-doc """ +Creates an abstract type tuple. + +If `Elements` is `[T1, ..., Tn]`, the result represents "`{T1, ..., +Tn}`"; otherwise, if `Elements` is `any_size`, it represents +"`t:tuple/0`". + +_See also: _`tuple_type_elements/1`. +""". +-spec tuple_type(any_size | [syntaxTree()]) -> syntaxTree(). -%% type(Node) = tuple_type -%% data(Node) = Elements -%% -%% Elements = any_size | [syntaxTree()] -%% %% `erl_parse' representation: %% %% {type, Pos, tuple, [Element]} @@ -7279,15 +5404,6 @@ tuple_type() -> %% %% Element = erl_parse() --doc """ -Creates an abstract type tuple. If `Elements` is `[T1, ..., Tn]`, the result -represents "`{*T1*, ..., *Tn*}`"; otherwise, if `Elements` is `any_size`, it -represents "`t:tuple/0`". - -_See also: _`tuple_type_elements/1`. -""". --spec tuple_type(any_size | [syntaxTree()]) -> syntaxTree(). - tuple_type(Elements) -> tree(tuple_type, Elements). @@ -7301,20 +5417,11 @@ revert_tuple_type(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of type element subtrees of a `tuple_type' node. -%% If `Node' represents "tuple()", `any_size' is returned; -%% otherwise, if `Node' represents -%% "{T1, ..., Tn}", -%% `[T1, ..., Tn]' is returned. -%% -%% @see tuple_type/0 -%% @see tuple_type/1 - -doc """ -Returns the list of type element subtrees of a `tuple_type` node. If `Node` -represents "`t:tuple/0`", `any_size` is returned; otherwise, if `Node` -represents "`{*T1*, ..., *Tn*}`", `[T1, ..., Tn]` is returned. +Returns the list of type element subtrees of a `tuple_type` node. + +If `Node` represents "`t:tuple/0`", `any_size` is returned; otherwise, +if `Node` represents "`{T1, ..., Tn}`", `[T1, ..., Tn]` is returned. _See also: _`tuple_type/0`, `tuple_type/1`. """. @@ -7332,31 +5439,23 @@ tuple_type_elements(Node) -> %% ===================================================================== -%% @doc Creates an abstract type union. If `Types' is -%% `[T1, ..., Tn]', the result represents -%% "T1 | ... | Tn". -%% -%% @see type_union_types/1 - -%% type(Node) = type_union -%% data(Node) = Types -%% -%% Types = [syntaxTree()] -%% -%% `erl_parse' representation: -%% -%% {type, Pos, union, Elements} -%% -%% Elements = [erl_parse()] -doc """ -Creates an abstract type union. If `Types` is `[T1, ..., Tn]`, the result -represents "`*T1* | ... | *Tn*`". +Creates an abstract type union. + +If `Types` is `[T1, ..., Tn]`, the result represents "`T1 | ... | +Tn`". _See also: _`type_union_types/1`. """. -spec type_union([syntaxTree()]) -> syntaxTree(). +%% `erl_parse' representation: +%% +%% {type, Pos, union, Elements} +%% +%% Elements = [erl_parse()] + type_union(Types) -> tree(type_union, Types). @@ -7365,11 +5464,6 @@ revert_type_union(Node) -> {type, Pos, union, type_union_types(Node)}. -%% ===================================================================== -%% @doc Returns the list of type subtrees of a `type_union' node. -%% -%% @see type_union/1 - -doc """ Returns the list of type subtrees of a `type_union` node. @@ -7387,24 +5481,21 @@ type_union_types(Node) -> %% ===================================================================== -%% @doc Creates an abstract user type. If `Arguments' is -%% `[T1, ..., Tn]', the result represents -%% "TypeName(T1, ...Tn)". -%% -%% @see type_application/2 -%% @see user_type_application_name/1 -%% @see user_type_application_arguments/1 -record(user_type_application, {type_name :: syntaxTree(), arguments :: [syntaxTree()]}). -%% type(Node) = user_type_application -%% data(Node) = #user_type_application{type_name :: TypeName, -%% arguments :: Arguments} -%% -%% TypeName = syntaxTree() -%% Arguments = [syntaxTree()] -%% +-doc """ +Creates an abstract user type. + +If `Arguments` is `[T1, ..., Tn]`, the result represents +"`TypeName(T1, ...Tn)`". + +_See also: _`type_application/2`, `user_type_application_arguments/1`, +`user_type_application_name/1`. +""". +-spec user_type_application(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {user_type, Pos, Name, Arguments} @@ -7413,15 +5504,6 @@ type_union_types(Node) -> %% Arguments = [Type] %% Type = erl_parse() --doc """ -Creates an abstract user type. If `Arguments` is `[T1, ..., Tn]`, the result -represents "`*TypeName*(*T1*, ...*Tn*)`". - -_See also: _`type_application/2`, `user_type_application_arguments/1`, -`user_type_application_name/1`. -""". --spec user_type_application(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - user_type_application(TypeName, Arguments) -> tree(user_type_application, #user_type_application{type_name = TypeName, arguments = Arguments}). @@ -7433,11 +5515,6 @@ revert_user_type_application(Node) -> {user_type, Pos, atom_value(TypeName), Arguments}. -%% ===================================================================== -%% @doc Returns the type name subtree of a `user_type_application' node. -%% -%% @see user_type_application/2 - -doc """ Returns the type name subtree of a `user_type_application` node. @@ -7454,11 +5531,6 @@ user_type_application_name(Node) -> end. -%% ===================================================================== -%% @doc Returns the arguments subtrees of a `user_type_application' node. -%% -%% @see user_type_application/2 - -doc """ Returns the arguments subtrees of a `user_type_application` node. @@ -7476,25 +5548,14 @@ user_type_application_arguments(Node) -> %% ===================================================================== -%% @doc Creates an abstract typed record field specification. The -%% result represents "Field :: Type". -%% -%% @see typed_record_field_body/1 -%% @see typed_record_field_type/1 -record(typed_record_field, {body :: syntaxTree(), type :: syntaxTree()}). -%% type(Node) = typed_record_field -%% data(Node) = #typed_record_field{body :: Field -%% type = Type} -%% -%% Field = syntaxTree() -%% Type = syntaxTree() - -doc """ -Creates an abstract typed record field specification. The result represents -"`*Field* :: *Type*`". +Creates an abstract typed record field specification. + +The result represents "`Field :: Type`". _See also: _`typed_record_field_body/1`, `typed_record_field_type/1`. """. @@ -7505,11 +5566,6 @@ typed_record_field(Field, Type) -> #typed_record_field{body = Field, type = Type}). -%% ===================================================================== -%% @doc Returns the field subtree of a `typed_record_field' node. -%% -%% @see typed_record_field/2 - -doc """ Returns the field subtree of a `typed_record_field` node. @@ -7521,11 +5577,6 @@ typed_record_field_body(Node) -> (data(Node))#typed_record_field.body. -%% ===================================================================== -%% @doc Returns the type subtree of a `typed_record_field' node. -%% -%% @see typed_record_field/2 - -doc """ Returns the type subtree of a `typed_record_field` node. @@ -7538,22 +5589,19 @@ typed_record_field_type(Node) -> %% ===================================================================== -%% @doc Creates an abstract list comprehension. If `Body' is -%% `[E1, ..., En]', the result represents -%% "[Template || E1, ..., En]". -%% -%% @see list_comp_template/1 -%% @see list_comp_body/1 -%% @see generator/2 -record(list_comp, {template :: syntaxTree(), body :: [syntaxTree()]}). -%% type(Node) = list_comp -%% data(Node) = #list_comp{template :: Template, body :: Body} -%% -%% Template = Node = syntaxTree() -%% Body = [syntaxTree()] -%% +-doc """ +Creates an abstract list comprehension. + +If `Body` is `[E1, ..., En]`, the result represents "`[Template || +E1, ..., En]`". + +_See also: _`generator/2`, `list_comp_body/1`, `list_comp_template/1`. +""". +-spec list_comp(syntaxTree(), [syntaxTree()]) -> syntaxTree(). + %% `erl_parse' representation: %% %% {lc, Pos, Template, Body} @@ -7561,14 +5609,6 @@ typed_record_field_type(Node) -> %% Template = erl_parse() %% Body = [erl_parse()] \ [] --doc """ -Creates an abstract list comprehension. If `Body` is `[E1, ..., En]`, the result -represents "`[*Template* || *E1*, ..., *En*]`". - -_See also: _`generator/2`, `list_comp_body/1`, `list_comp_template/1`. -""". --spec list_comp(syntaxTree(), [syntaxTree()]) -> syntaxTree(). - list_comp(Template, Body) -> tree(list_comp, #list_comp{template = Template, body = Body}). @@ -7579,11 +5619,6 @@ revert_list_comp(Node) -> {lc, Pos, Template, Body}. -%% ===================================================================== -%% @doc Returns the template subtree of a `list_comp' node. -%% -%% @see list_comp/2 - -doc """ Returns the template subtree of a `list_comp` node. @@ -7600,11 +5635,6 @@ list_comp_template(Node) -> end. -%% ===================================================================== -%% @doc Returns the list of body subtrees of a `list_comp' node. -%% -%% @see list_comp/2 - -doc """ Returns the list of body subtrees of a `list_comp` node. @@ -7621,22 +5651,19 @@ list_comp_body(Node) -> end. %% ===================================================================== -%% @doc Creates an abstract binary comprehension. If `Body' is -%% `[E1, ..., En]', the result represents -%% "<<Template || E1, ..., En>>". -%% -%% @see binary_comp_template/1 -%% @see binary_comp_body/1 -%% @see generator/2 -record(binary_comp, {template :: syntaxTree(), body :: [syntaxTree()]}). -%% type(Node) = binary_comp -%% data(Node) = #binary_comp{template :: Template, body :: Body} -%% -%% Template = Node = syntaxTree() -%% Body = [syntaxTree()] -%% +-doc """ +Creates an abstract binary comprehension. + +If `Body` is `[E1, ..., En]`, the result represents "`<