Skip to content

Commit

Permalink
Merge pull request #2874 from ferd/bump-relx-ec
Browse files Browse the repository at this point in the history
Bump relx and erlware commons
  • Loading branch information
ferd authored Apr 6, 2024
2 parents 7ff5618 + bb596d6 commit 9880ef3
Show file tree
Hide file tree
Showing 25 changed files with 103 additions and 218 deletions.
4 changes: 2 additions & 2 deletions apps/rebar/rebar.config
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 ft=erlang et

{deps, [{erlware_commons, "1.6.0"},
{deps, [{erlware_commons, "1.7.0"},
{ssl_verify_fun, "1.1.6"},
{certifi, "2.11.0"},
{providers, "1.9.0"},
{getopt, "1.0.2"},
{bbmustache, "1.12.2"},
{relx, "4.8.0"},
{relx, "4.9.0"},
{cf, "0.3.1"},
{cth_readable, "1.5.1"},
{eunit_formatters, "0.5.0"}]}.
Expand Down
4 changes: 2 additions & 2 deletions apps/rebar/test/rebar_dialyzer_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -583,14 +583,14 @@ incremental_cli_args(Config) ->
%% Helpers

erts_files() ->
ErtsDir = code:lib_dir(erts, ebin),
ErtsDir = filename:join(code:lib_dir(erts), "ebin"),
ErtsBeams = filelib:wildcard("*.beam", ErtsDir),
ErtsFiles = lists:map(fun(Beam) -> filename:join(ErtsDir, Beam) end,
ErtsBeams),
lists:sort(ErtsFiles).

erts_modules() ->
ErtsDir = code:lib_dir(erts, ebin),
ErtsDir = filename:join(code:lib_dir(erts), "ebin"),
ErtsBeams = filelib:wildcard("*.beam", ErtsDir),
ErtsModules = lists:map(fun(Beam) -> filename:basename(Beam, ".beam") end,
ErtsBeams),
Expand Down
6 changes: 3 additions & 3 deletions vendor/erlware_commons/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -69,15 +69,15 @@ href="http://www.erlang.org/doc/man/lists.html">lists</a>, making most
list operations parallel. It can operate on each element in parallel,
for IO-bound operations, on sublists in parallel, for taking advantage
of multi-core machines with CPU-bound operations, and across erlang
nodes, for parallizing inside a cluster. It handles errors and node
nodes, for parallelizing inside a cluster. It handles errors and node
failures. It can be configured, tuned, and tweaked to get optimal
performance while minimizing overhead.

Almost all the functions are identical to equivalent functions in
lists, returning exactly the same result, and having both a form with
an identical syntax that operates on each element in parallel and a
form which takes an optional "malt", a specification for how to
parallize the operation.
parallelize the operation.

fold is the one exception, parallel fold is different from linear
fold. This module also include a simple mapreduce implementation, and
Expand Down Expand Up @@ -106,7 +106,7 @@ Other languages, have built in support for **Interface** or
**signature** functionality. Java has Interfaces, SML has
Signatures. Erlang, though, doesn't currently support this model, at
least not directly. There are a few ways you can approximate it. We
have defined a mechnism called *signatures* and several modules that
have defined a mechanism called *signatures* and several modules that
to serve as examples and provide a good set of *dictionary*
signatures. More information about signatures can be found at
[signature](https://github.com/erlware/erlware_commons/blob/master/doc/signatures.md).
Expand Down
16 changes: 8 additions & 8 deletions vendor/erlware_commons/hex_metadata.config
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,14 @@
{<<"build_tools">>,[<<"rebar3">>]}.
{<<"description">>,<<"Additional standard library for Erlang">>}.
{<<"files">>,
[<<"README.md">>,<<"include/ec_cmd_log.hrl">>,
[<<"README.md">>,<<"include">>,<<"include/ec_cmd_log.hrl">>,<<"priv">>,
<<"priv/ec_semver_parser.peg">>,<<"rebar.config">>,
<<"rebar.config.script">>,<<"rebar.lock">>,<<"src/ec_assoc_list.erl">>,
<<"src/ec_cmd_log.erl">>,<<"src/ec_cnv.erl">>,<<"src/ec_compile.erl">>,
<<"src/ec_date.erl">>,<<"src/ec_dict.erl">>,<<"src/ec_dictionary.erl">>,
<<"src/ec_file.erl">>,<<"src/ec_gb_trees.erl">>,<<"src/ec_git_vsn.erl">>,
<<"src/ec_lists.erl">>,<<"src/ec_orddict.erl">>,<<"src/ec_plists.erl">>,
<<"src/ec_rbdict.erl">>,<<"src/ec_semver.erl">>,
<<"rebar.config.script">>,<<"rebar.lock">>,<<"src">>,
<<"src/ec_assoc_list.erl">>,<<"src/ec_cmd_log.erl">>,<<"src/ec_cnv.erl">>,
<<"src/ec_compile.erl">>,<<"src/ec_date.erl">>,<<"src/ec_dict.erl">>,
<<"src/ec_dictionary.erl">>,<<"src/ec_file.erl">>,<<"src/ec_gb_trees.erl">>,
<<"src/ec_git_vsn.erl">>,<<"src/ec_lists.erl">>,<<"src/ec_orddict.erl">>,
<<"src/ec_plists.erl">>,<<"src/ec_rbdict.erl">>,<<"src/ec_semver.erl">>,
<<"src/ec_semver_parser.erl">>,<<"src/ec_talk.erl">>,<<"src/ec_vsn.erl">>,
<<"src/erlware_commons.app.src">>]}.
{<<"licenses">>,[<<"Apache">>,<<"MIT">>]}.
Expand All @@ -21,4 +21,4 @@
[{<<"app">>,<<"cf">>},
{<<"optional">>,false},
{<<"requirement">>,<<"~>0.3">>}]}]}.
{<<"version">>,<<"1.6.0">>}.
{<<"version">>,<<"1.7.0">>}.
11 changes: 1 addition & 10 deletions vendor/erlware_commons/rebar.config
Original file line number Diff line number Diff line change
Expand Up @@ -8,16 +8,7 @@
{erl_first_files, ["ec_dictionary", "ec_vsn"]}.

%% Compiler Options ============================================================
{erl_opts,
[{platform_define, "^[0-9]+", namespaced_types},
{platform_define, "^[0-9]+", have_callback_support},
{platform_define, "^R1[4|5]", deprecated_crypto},
{platform_define, "^1[8|9]", rand_module},
{platform_define, "^2", rand_module},
{platform_define, "^2", unicode_str},
{platform_define, "^(R|1|20)", fun_stacktrace},
debug_info,
warnings_as_errors]}.
{erl_opts, [debug_info, warnings_as_errors]}.

%% EUnit =======================================================================
{eunit_opts, [verbose,
Expand Down
11 changes: 9 additions & 2 deletions vendor/erlware_commons/rebar.config.script
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,15 @@ Rebar2Deps = [
{cf, ".*", {git, "https://github.com/project-fifo/cf", {tag, "0.2.2"}}}
],

NoDialWarns = {dialyzer, [{warnings, [no_unknown]}]},
OTPRelease = erlang:list_to_integer(erlang:system_info(otp_release)),
WarnsRemoved = case OTPRelease<26 of
true -> fun(Config) -> Config end;
false -> fun(Config) -> lists:keystore(dialyzer, 1, Config, NoDialWarns) end
end,

case IsRebar3 of
true -> CONFIG;
true -> WarnsRemoved(CONFIG);
false ->
lists:keyreplace(deps, 1, CONFIG, {deps, Rebar2Deps})
lists:keyreplace(deps, 1, WarnsRemoved(CONFIG), {deps, Rebar2Deps})
end.
14 changes: 7 additions & 7 deletions vendor/erlware_commons/src/ec_cmd_log.erl
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@
%%% @copyright (C) 2012 Erlware, LLC.
%%%
%%% @doc This provides simple output functions for command line apps. You should
%%% use this to talk to the users if you are wrting code for the system
%%% use this to talk to the users if you are writing code for the system
-module(ec_cmd_log).

%% Avoid clashing with `error/3` BIF added in Erlang/OTP 24
Expand Down Expand Up @@ -129,7 +129,7 @@ debug(LogState, String) ->
debug(LogState, "~ts~n", [String]).

%% @doc log at the debug level given the current log state with a format string
%% and argements @see io:format/2
%% and arguments @see io:format/2
-spec debug(t(), string(), [any()]) -> ok.
debug(LogState, FormatString, Args) ->
log(LogState, ?EC_DEBUG, colorize(LogState, ?CYAN, false, FormatString), Args).
Expand All @@ -146,7 +146,7 @@ info(LogState, String) ->
info(LogState, "~ts~n", [String]).

%% @doc log at the info level given the current log state with a format string
%% and argements @see io:format/2
%% and arguments @see io:format/2
-spec info(t(), string(), [any()]) -> ok.
info(LogState, FormatString, Args) ->
log(LogState, ?EC_INFO, colorize(LogState, ?GREEN, false, FormatString), Args).
Expand All @@ -163,7 +163,7 @@ error(LogState, String) ->
error(LogState, "~ts~n", [String]).

%% @doc log at the error level given the current log state with a format string
%% and argements @see io:format/2
%% and arguments @see io:format/2
-spec error(t(), string(), [any()]) -> ok.
error(LogState, FormatString, Args) ->
log(LogState, ?EC_ERROR, colorize(LogState, ?RED, false, FormatString), Args).
Expand All @@ -178,7 +178,7 @@ warn(LogState, String) ->
warn(LogState, "~ts~n", [String]).

%% @doc log at the warn level given the current log state with a format string
%% and argements @see io:format/2
%% and arguments @see io:format/2
-spec warn(t(), string(), [any()]) -> ok.
warn(LogState, FormatString, Args) ->
log(LogState, ?EC_WARN, colorize(LogState, ?MAGENTA, false, FormatString), Args).
Expand Down Expand Up @@ -243,12 +243,12 @@ format(Log) ->

colorize(#state_t{intensity=none}, _, _, Msg) ->
Msg;
%% When it is suposed to be bold and we already have a uppercase
%% When it is supposed to be bold and we already have a uppercase
%% (bold color) we don't need to modify the color
colorize(State, Color, true, Msg) when ?VALID_COLOR(Color),
Color >= $A, Color =< $Z ->
colorize(State, Color, false, Msg);
%% We're sneaky we can substract 32 to get the uppercase character if we want
%% We're sneaky we can subtract 32 to get the uppercase character if we want
%% bold but have a non bold color.
colorize(State, Color, true, Msg) when ?VALID_COLOR(Color) ->
colorize(State, Color - 32, false, Msg);
Expand Down
35 changes: 6 additions & 29 deletions vendor/erlware_commons/src/ec_date.erl
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,8 @@
-define( is_tz_offset(H1,H2,M1,M2), (?is_num(H1) andalso ?is_num(H2) andalso ?is_num(M1) andalso ?is_num(M2)) ).

-define(GREGORIAN_SECONDS_1970, 62167219200).
-define(ISO_8601_DATETIME_FORMAT, "Y-m-dTG:i:sZ").
-define(ISO_8601_DATETIME_WITH_MS_FORMAT, "Y-m-dTG:i:s.fZ").
-define(ISO_8601_DATETIME_FORMAT, "Y-m-dTH:i:sZ").
-define(ISO_8601_DATETIME_WITH_MS_FORMAT, "Y-m-dTH:i:s.fZ").

-type year() :: non_neg_integer().
-type month() :: 1..12 | {?MONTH_TAG, 1..12}.
Expand Down Expand Up @@ -101,7 +101,7 @@ parse(Date, Now) ->
do_parse(Date, Now, []).

do_parse(Date, Now, Opts) ->
case filter_hints(parse(tokenise(uppercase(Date), []), Now, Opts)) of
case filter_hints(parse(tokenise(string:uppercase(Date), []), Now, Opts)) of
{error, bad_date} ->
erlang:throw({?MODULE, {bad_date, Date}});
{D1, T1} = {{Y, M, D}, {H, M1, S}}
Expand Down Expand Up @@ -197,17 +197,6 @@ parse([Day,X,Month,X,Year,Hour,$:,Min,$:,Sec,$., Ms | PAM], _Now, _Opts)
andalso ?is_year(Year) ->
{{Year, Month, Day}, {hour(Hour, PAM), Min, Sec}, {Ms}};

parse([Year,X,Month,X,Day,Hour,$:,Min,$:,Sec,$., Ms], _Now, _Opts)
when (?is_us_sep(X) orelse ?is_world_sep(X))
andalso ?is_year(Year) ->
{{Year, Month, Day}, {hour(Hour,[]), Min, Sec}, {Ms}};
parse([Month,X,Day,X,Year,Hour,$:,Min,$:,Sec,$., Ms], _Now, _Opts)
when ?is_us_sep(X) andalso ?is_month(Month) ->
{{Year, Month, Day}, {hour(Hour, []), Min, Sec}, {Ms}};
parse([Day,X,Month,X,Year,Hour,$:,Min,$:,Sec,$., Ms ], _Now, _Opts)
when ?is_world_sep(X) andalso ?is_month(Month) ->
{{Year, Month, Day}, {hour(Hour, []), Min, Sec}, {Ms}};

%% Date/Times Dec 1st, 2012 6:25 PM
parse([Month,Day,Year,Hour,$:,Min,$:,Sec | PAM], _Now, _Opts)
when ?is_meridian(PAM) andalso ?is_hinted_month(Month) andalso ?is_day(Day) ->
Expand All @@ -219,14 +208,6 @@ parse([Month,Day,Year,Hour | PAM], _Now, _Opts)
when ?is_meridian(PAM) andalso ?is_hinted_month(Month) andalso ?is_day(Day) ->
{{Year, Month, Day}, {hour(Hour, PAM), 0, 0}};

%% Date/Times Dec 1st, 2012 18:25:15 (no AM/PM)
parse([Month,Day,Year,Hour,$:,Min,$:,Sec], _Now, _Opts)
when ?is_hinted_month(Month) andalso ?is_day(Day) ->
{{Year, Month, Day}, {hour(Hour, []), Min, Sec}};
parse([Month,Day,Year,Hour,$:,Min], _Now, _Opts)
when ?is_hinted_month(Month) andalso ?is_day(Day) ->
{{Year, Month, Day}, {hour(Hour, []), Min, 0}};

%% Date/Times Fri Nov 21 14:55:26 +0000 2014 (Twitter format)
parse([Month, Day, Hour,$:,Min,$:,Sec, Year], _Now, _Opts)
when ?is_hinted_month(Month), ?is_day(Day), ?is_year(Year) ->
Expand Down Expand Up @@ -522,7 +503,7 @@ format([$g|T], {_,{H,_,_}}=Dt, Acc) when H > 12 ->
format([$g|T], {_,{H,_,_}}=Dt, Acc) ->
format(T, Dt, [itol(H)|Acc]);
format([$G|T], {_,{H,_,_}}=Dt, Acc) ->
format(T, Dt, [pad2(H)|Acc]);
format(T, Dt, [itol(H)|Acc]);
format([$h|T], {_,{H,_,_}}=Dt, Acc) when H > 12 ->
format(T, Dt, [pad2(H-12)|Acc]);
format([$h|T], {_,{H,_,_}}=Dt, Acc) ->
Expand Down Expand Up @@ -728,12 +709,6 @@ pad6(X) when is_integer(X) ->
ltoi(X) ->
list_to_integer(X).

-ifdef(unicode_str).
uppercase(Str) -> string:uppercase(Str).
-else.
uppercase(Str) -> string:to_upper(Str).
-endif.

%%%===================================================================
%%% Tests
%%%===================================================================
Expand Down Expand Up @@ -762,6 +737,8 @@ basic_format_test_() ->
?_assertEqual(format("H:i:s",?DATE), "17:16:17"),
?_assertEqual(format("z",?DATE), "68"),
?_assertEqual(format("D M j G:i:s Y",?DATE), "Sat Mar 10 17:16:17 2001"),
?_assertEqual(format("D M j G:i:s Y", {{2001,3,10},{5,16,17}}), "Sat Mar 10 5:16:17 2001"),
?_assertEqual(format("D M j H:i:s Y", {{2001,3,10},{5,16,17}}), "Sat Mar 10 05:16:17 2001"),
?_assertEqual(format("ga",?DATE_NOON), "12pm"),
?_assertEqual(format("gA",?DATE_NOON), "12PM"),
?_assertEqual(format("ga",?DATE_MIDNIGHT), "12am"),
Expand Down
4 changes: 0 additions & 4 deletions vendor/erlware_commons/src/ec_dict.erl
Original file line number Diff line number Diff line change
Expand Up @@ -34,11 +34,7 @@
%%%===================================================================
%% This should be opaque, but that kills dialyzer so for now we export it
%% however you should not rely on the internal representation here
-ifdef(namespaced_types).
-type dictionary(_K, _V) :: dict:dict().
-else.
-type dictionary(_K, _V) :: dict().
-endif.

%%%===================================================================
%%% API
Expand Down
23 changes: 0 additions & 23 deletions vendor/erlware_commons/src/ec_dictionary.erl
Original file line number Diff line number Diff line change
Expand Up @@ -42,8 +42,6 @@
-type key(T) :: T.
-type value(T) :: T.

-ifdef(have_callback_support).

-callback new() -> any().
-callback has_key(key(any()), any()) -> boolean().
-callback get(key(any()), any()) -> any().
Expand All @@ -55,27 +53,6 @@
-callback from_list([{key(any()), value(any())}]) -> any().
-callback keys(any()) -> [key(any())].

-else.

%% In the case where R14 or lower is being used to compile the system
%% we need to export a behaviour info
-export([behaviour_info/1]).
-spec behaviour_info(atom()) -> [{atom(), arity()}] | undefined.
behaviour_info(callbacks) ->
[{new, 0},
{has_key, 2},
{get, 2},
{add, 3},
{remove, 2},
{has_value, 2},
{size, 1},
{to_list, 1},
{from_list, 1},
{keys, 1}];
behaviour_info(_Other) ->
undefined.
-endif.

%%%===================================================================
%%% API
%%%===================================================================
Expand Down
33 changes: 12 additions & 21 deletions vendor/erlware_commons/src/ec_file.erl
Original file line number Diff line number Diff line change
Expand Up @@ -139,23 +139,20 @@ try_write_owner(To, #file_info{uid=OwnerId}) ->
try_write_group(To, #file_info{gid=OwnerId}) ->
file:write_file_info(To, #file_info{gid=OwnerId}).

%% @doc return an md5 checksum string or a binary. Same as unix utility of
%% same name.
%% @doc return the MD5 digest of a string or a binary,
%% named after the UNIX utility.
-spec md5sum(string() | binary()) -> string().
md5sum(Value) ->
hex(binary_to_list(erlang:md5(Value))).
bin_to_hex(crypto:hash(md5, Value)).

%% @doc return an sha1sum checksum string or a binary. Same as unix utility of
%% same name.
-ifdef(deprecated_crypto).
%% @doc return the SHA-1 digest of a string or a binary,
%% named after the UNIX utility.
-spec sha1sum(string() | binary()) -> string().
sha1sum(Value) ->
hex(binary_to_list(crypto:sha(Value))).
-else.
-spec sha1sum(string() | binary()) -> string().
sha1sum(Value) ->
hex(binary_to_list(crypto:hash(sha, Value))).
-endif.
bin_to_hex(crypto:hash(sha, Value)).

bin_to_hex(Bin) ->
hex(binary_to_list(Bin)).

%% @doc delete a file. Use the recursive option for directories.
%% <pre>
Expand All @@ -174,7 +171,7 @@ remove(Path, Options) ->
remove(Path) ->
remove(Path, []).

%% @doc indicates witha boolean if the path supplied refers to symlink.
%% @doc indicates with a boolean if the path supplied refers to symlink.
-spec is_symlink(file:name()) -> boolean().
is_symlink(Path) ->
case file:read_link_info(Path) of
Expand Down Expand Up @@ -252,7 +249,7 @@ mkdir_path(Path) ->
mkdir_p(Path).


%% @doc read a file from the file system. Provide UEX exeption on failure.
%% @doc read a file from the file system. Provide UEX exception on failure.
-spec read(FilePath::file:filename()) -> {ok, binary()} | {error, Reason::term()}.
read(FilePath) ->
%% Now that we are moving away from exceptions again this becomes
Expand All @@ -261,7 +258,7 @@ read(FilePath) ->
file:read_file(FilePath).


%% @doc write a file to the file system. Provide UEX exeption on failure.
%% @doc write a file to the file system. Provide UEX exception on failure.
-spec write(FileName::file:filename(), Contents::string()) -> ok | {error, Reason::term()}.
write(FileName, Contents) ->
%% Now that we are moving away from exceptions again this becomes
Expand Down Expand Up @@ -379,14 +376,8 @@ sub_files(From) ->
{ok, SubFiles} = file:list_dir(From),
[filename:join(From, SubFile) || SubFile <- SubFiles].

-ifdef(rand_module).
random_uniform() ->
rand:uniform().
-else.
random_uniform() ->
random:seed(os:timestamp()),
random:uniform().
-endif.

%%%===================================================================
%%% Test Functions
Expand Down
Loading

0 comments on commit 9880ef3

Please sign in to comment.