Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
Mikaka27 committed Aug 12, 2024
2 parents 90a48ae + 2ffcb7f commit 3bd5814
Show file tree
Hide file tree
Showing 16 changed files with 133 additions and 119 deletions.
1 change: 0 additions & 1 deletion lib/common_test/doc/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ include $(ERL_TOP)/make/$(TARGET)/otp.mk
include ../vsn.mk
VSN=$(COMMON_TEST_VSN)
APPLICATION=common_test
EX_DOC_WARNINGS_AS_ERRORS=false

# ----------------------------------------------------
# Release Target
Expand Down
16 changes: 7 additions & 9 deletions lib/common_test/src/ct.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@

-module(ct).
-moduledoc """
Main user interface for the Common Test framework.
Main user interface for the `Common Test` framework.
This module implements the command-line interface for running tests and basic
Expand Down Expand Up @@ -506,7 +504,7 @@ require(Name,Required) ->
-doc(#{equiv => get_config(Required, undefined, [])}).
-spec get_config(Required) -> Value
when Required :: KeyOrName | {KeyOrName, SubKey} | {KeyOrName, SubKey, SubKey},
KeyOrName :: atom(),
KeyOrName :: key_or_name(),
SubKey :: atom(),
Value :: term().
get_config(Required) ->
Expand All @@ -515,7 +513,7 @@ get_config(Required) ->
-doc(#{equiv => get_config(Required, Default, [])}).
-spec get_config(Required, Default) -> Value
when Required :: KeyOrName | {KeyOrName, SubKey} | {KeyOrName, SubKey, SubKey},
KeyOrName :: atom(),
KeyOrName :: key_or_name(),
SubKey :: atom(),
Default :: term(),
Value :: term().
Expand Down Expand Up @@ -574,7 +572,7 @@ See also [`ct:get_config/1`](`get_config/1`),
""".
-spec get_config(Required, Default, Opts) -> ValueOrElement
when Required :: KeyOrName | {KeyOrName, SubKey} | {KeyOrName, SubKey, SubKey},
KeyOrName :: atom(),
KeyOrName :: key_or_name(),
SubKey :: atom(),
Default :: term(),
Opts :: [Opt],
Expand All @@ -597,7 +595,7 @@ aliases.
-doc(#{since => <<"OTP R14B">>}).
-spec reload_config(Required) -> ValueOrElement | {error, Reason}
when Required :: KeyOrName | {KeyOrName, SubKey} | {KeyOrName, SubKey, SubKey},
KeyOrName :: atom(),
KeyOrName :: key_or_name(),
SubKey :: atom(),
ValueOrElement :: term(),
Reason :: term().
Expand Down Expand Up @@ -661,7 +659,7 @@ escape_chars(Format, Args) ->
{error,Reason}
end.

-doc(#{equiv => log(default, ?STD_IMPORTANCE, Format, [], [])}).
-doc "Equivalent to [`log(default, ?STD_IMPORTANCE, Format, [], [])`](`log/5`).".
-spec log(Format) -> ok
when Format :: string().
log(Format) ->
Expand Down Expand Up @@ -750,7 +748,7 @@ printed with this function, unless the `esc_chars` option is used.
log(Category,Importance,Format,Args,Opts) ->
ct_logs:tc_log(Category,Importance,Format,Args,Opts).

-doc(#{equiv => print(default, ?STD_IMPORTANCE, Format, [], [])}).
-doc "Equivalent to [`print(default, ?STD_IMPORTANCE, Format, [], [])`](`print/5`).".
-spec print(Format) -> ok
when Format :: string().
print(Format) ->
Expand Down Expand Up @@ -835,7 +833,7 @@ the User's Guide.
print(Category,Importance,Format,Args,Opts) ->
ct_logs:tc_print(Category,Importance,Format,Args,Opts).

-doc(#{equiv => pal(default, ?STD_IMPORTANCE, Format, [], [])}).
-doc "Equivalent to [`pal(default, ?STD_IMPORTANCE, Format, [])`](`pal/4`).".
-spec pal(Format) -> ok
when Format :: string().
pal(Format) ->
Expand Down
2 changes: 0 additions & 2 deletions lib/common_test/src/ct_cover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@

-module(ct_cover).
-moduledoc """
Common Test framework code coverage support module.
`Common Test` framework code coverage support module.
This module exports help functions for performing code coverage analysis.
Expand Down
16 changes: 4 additions & 12 deletions lib/common_test/src/ct_ftp.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@

-module(ct_ftp).
-moduledoc """
FTP client module (based on the FTP application).
FTP client module (based on the `ftp` application).
""".

Expand All @@ -38,7 +36,7 @@ FTP client module (based on the `ftp` application).

-define(DEFAULT_PORT,21).

-doc "For `target_name`, see module `m:ct`.".
-doc "Reference to opened FTP connection associated to either a `handle` or `target_name`.".
-type connection() :: handle() | ct:target_name().
-doc "Handle for a specific FTP connection, see module `m:ct`.".
-type handle() :: ct:handle().
Expand All @@ -52,8 +50,6 @@ Opens an FTP connection and sends a file to the remote host.
`LocalFile` and `RemoteFile` must be absolute paths.
For `target_name`, see module `m:ct`.
If the target host is a "special" node, the FTP address must be specified in the
configuration file as follows:
Expand All @@ -73,7 +69,7 @@ configuration file must also include the username and password (both strings):
See also `ct:require/2`.
""".
-spec put(KeyOrName, LocalFile, RemoteFile) -> 'ok' | {'error', Reason}
when KeyOrName :: atom(),
when KeyOrName :: ct:key_or_name(),
LocalFile :: file:filename(),
RemoteFile :: file:filename(),
Reason :: term().
Expand All @@ -88,12 +84,10 @@ Opens an FTP connection and fetches a file from the remote host.
The configuration file must be as for [`ct_ftp:put/3`](`put/3`).
For `target_name`, see module `m:ct`.
See also `ct:require/2`.
""".
-spec get(KeyOrName, RemoteFile, LocalFile) -> 'ok' | {'error', Reason}
when KeyOrName :: atom(),
when KeyOrName :: ct:key_or_name(),
RemoteFile :: file:filename(),
LocalFile :: file:filename(),
Reason :: term().
Expand All @@ -112,11 +106,9 @@ the target. A connection without an associated target name can only be closed
with the handle value.
For information on how to create a new `Name`, see `ct:require/2`.
For `target_name`, see module `m:ct`.
""".
-spec open(KeyOrName) -> {'ok', Handle} | {'error', Reason}
when KeyOrName :: atom(),
when KeyOrName :: ct:key_or_name(),
Handle :: handle(),
Reason :: term().
open(KeyOrName) ->
Expand Down
4 changes: 2 additions & 2 deletions lib/common_test/src/ct_hooks.erl
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ That is:
- If a test case is skipped, this function is called after
[`post_end_per_testcase`](`c:post_end_per_testcase/5`).
If the skipped test case belongs to a test case group, the first argument is a
If the skipped test case belongs to a test case group, the second argument is a
tuple `{FuncName,GroupName}`, otherwise only the function name.
The data that comes with `Reason` follows the same format as events
Expand Down Expand Up @@ -163,7 +163,7 @@ That is:
- If a test case fails, this function is called after
[`post_end_per_testcase`](`c:post_end_per_testcase/5`).
If the failed test case belongs to a test case group, the first argument is a
If the failed test case belongs to a test case group, the second argument is a
tuple `{FuncName,GroupName}`, otherwise only the function name.
The data that comes with `Reason` follows the same format as
Expand Down
3 changes: 1 addition & 2 deletions lib/common_test/src/ct_master.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@

-module(ct_master).
-moduledoc """
Distributed test execution control for Common Test.
Distributed test execution control for `Common Test`.
This module exports functions for running `Common Test` nodes on multiple hosts
Expand All @@ -43,6 +41,7 @@ in parallel.
-include("ct_event.hrl").
-include("ct_util.hrl").

-doc "Filename of test spec to be executed.".
-type test_spec() :: file:name_all().

-record(state, {node_ctrl_pids=[],
Expand Down
67 changes: 51 additions & 16 deletions lib/common_test/src/ct_property_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -93,9 +93,17 @@ prop_ftp() ->
]).

%% Type declarations
-type arguments() :: [term()].
-type function_name() :: atom().
-type symbolic_var() :: {'var', pos_integer()}.
-type symbolic_call() :: {'call', module(), function_name(), arguments()}.
-type symbolic_state() :: term().
-type dynamic_state() :: term().
-type command() :: term().
-type set_command() :: {'set', symbolic_var(), symbolic_call()}.
-type init_command() :: {'init', symbolic_state()}.
-type command() :: set_command() | init_command().
-type command_list() :: [command()].
-type parallel_testcase() :: {command_list(), [command_list()]}.
-type history() :: [term()].
-type statem_result() :: 'ok' | term().

Expand Down Expand Up @@ -233,7 +241,7 @@ quickcheck(Property, Config) ->
-doc(#{equiv => present_result(Module, Cmds, Triple, Config, []), since => <<"OTP 22.3">>}).
-spec present_result(Module, Cmds, Triple, Config) -> boolean()
when Module :: module(),
Cmds :: command() | command_list(),
Cmds :: command_list() | parallel_testcase(),
Triple :: {H, Sf, Result},
H :: history(),
Sf :: dynamic_state(),
Expand Down Expand Up @@ -315,7 +323,7 @@ The default `StatisticsSpec` is:
-doc(#{since => <<"OTP 22.3">>}).
-spec present_result(Module, Cmds, Triple, Config, Options0) -> boolean()
when Module :: module(),
Cmds :: command() | command_list(),
Cmds :: command_list() | parallel_testcase(),
Triple :: {H, Sf, Result},
H :: history(),
Sf :: dynamic_state(),
Expand Down Expand Up @@ -361,6 +369,7 @@ print_frequency() ->
print_frequency_ranges() ->
print_frequency_ranges([{ngroups,10}]).

-doc false.
print_frequency_ranges(Options0) ->
fun([]) ->
io_lib:format('Empty list!~n',[]);
Expand All @@ -374,6 +383,45 @@ print_frequency_ranges(Options0) ->
end
end.

-doc """
Returns a list of commands (function calls) generated in the `Cmnd` sequence,
without Module, Arguments and other details.
For more information see: `present_result/5`.
""".
-doc #{since => "OTP @OTP-19148@"}.
-spec cmnd_names(Cs) -> Result when
Cs :: command_list() | parallel_testcase(),
Result :: [function_name()].
cmnd_names(Cs) -> traverse_commands(fun cmnd_name/1, Cs).
cmnd_name(L) -> [F || {set,_Var,{call,_Mod,F,_As}} <- L].

-doc """
Returns number of command calls in a test case.
For more information see: `present_result/5`.
""".
-doc #{since => "OTP @OTP-19148@"}.
-spec num_calls(Cs) -> Result when
Cs :: command_list() | parallel_testcase(),
Result :: [non_neg_integer()].
num_calls(Cs) -> traverse_commands(fun num_call/1, Cs).
num_call(L) -> [length(L)].

-doc """
Returns a list with information about sequential and parallel parts.
For more information see: `present_result/5`.
""".
-doc #{since => "OTP @OTP-19148@"}.
-spec sequential_parallel(Cs) -> Result when
Cs :: command_list() | parallel_testcase(),
Result :: [atom()].
sequential_parallel(Cs) ->
traverse_commands(fun(L) -> dup_module(L, sequential) end,
fun(L) -> [dup_module(L1, mkmod("parallel",num(L1,L))) || L1<-L] end,
Cs).

%%%================================================================
%%%
%%% Local functions
Expand Down Expand Up @@ -483,19 +531,6 @@ do_present_result(Module, Cmds, H, Sf, Result, _Config, Options) ->
Result == ok. % Proper dislikes non-boolean results while eqc treats non-true as false.

%%%================================================================
-doc false.
cmnd_names(Cs) -> traverse_commands(fun cmnd_name/1, Cs).
cmnd_name(L) -> [F || {set,_Var,{call,_Mod,F,_As}} <- L].

-doc false.
num_calls(Cs) -> traverse_commands(fun num_call/1, Cs).
num_call(L) -> [length(L)].

-doc false.
sequential_parallel(Cs) ->
traverse_commands(fun(L) -> dup_module(L, sequential) end,
fun(L) -> [dup_module(L1, mkmod("parallel",num(L1,L))) || L1<-L] end,
Cs).
dup_module(L, ModName) -> lists:duplicate(length(L), ModName).
mkmod(PfxStr,N) -> list_to_atom(PfxStr++"_"++integer_to_list(N)).

Expand Down
2 changes: 0 additions & 2 deletions lib/common_test/src/ct_rpc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@

-module(ct_rpc).
-moduledoc """
Common Test specific layer on Erlang/OTP rpc.
`Common Test` specific layer on Erlang/OTP `rpc`.
""".

Expand Down
5 changes: 2 additions & 3 deletions lib/common_test/src/ct_slave.erl
Original file line number Diff line number Diff line change
Expand Up @@ -25,9 +25,6 @@
%%----------------------------------------------------------------------
-module(ct_slave).
-moduledoc """
Common Test framework functions for starting and stopping nodes for Large-Scale
Testing.
`Common Test` framework functions for starting and stopping nodes for
Large-Scale Testing.
Expand All @@ -48,6 +45,7 @@ term in the Test Specification.
kill_if_fail, erl_flags, env, ssh_port, ssh_opts,
stop_timeout}).

-doc "Options used for starting `ct_slave` node.".
-type start_options() :: [{'username', string()}
| {'password', string()}
| {'boot_timeout', non_neg_integer()}
Expand All @@ -61,6 +59,7 @@ term in the Test Specification.
| {'ssh_port', inet:port_number()}
| {'ssh_opts', ssh:client_options()}].

-doc "Options used for stopping `ct_slave` node.".
-type stop_options() :: [{'stop_timeout', non_neg_integer()}].

-export_type([start_options/0, stop_options/0]).
Expand Down
2 changes: 0 additions & 2 deletions lib/common_test/src/ct_snmp.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@

-module(ct_snmp).
-moduledoc """
Common Test user interface module for the SNMP application.
`Common Test` user interface module for the `SNMP` application.
The purpose of this module is to simplify SNMP configuration for the test case
Expand Down
Loading

0 comments on commit 3bd5814

Please sign in to comment.