From a073186fd72d5ce2a22f4c1cc8f7c3ec50604bfe Mon Sep 17 00:00:00 2001 From: Fred Hebert Date: Wed, 3 Apr 2024 00:39:47 +0000 Subject: [PATCH 1/3] Bump Relx and Erlware Commons This also required a drive-by fix on the tests for OTP-27. This fails, I'll temporarily add a patch to test further. --- apps/rebar/rebar.config | 4 +- apps/rebar/test/rebar_dialyzer_SUITE.erl | 4 +- vendor/erlware_commons/README.md | 6 +- vendor/erlware_commons/hex_metadata.config | 16 ++--- vendor/erlware_commons/rebar.config | 11 +--- vendor/erlware_commons/rebar.config.script | 19 +++++- vendor/erlware_commons/src/ec_cmd_log.erl | 14 ++--- vendor/erlware_commons/src/ec_date.erl | 35 ++--------- vendor/erlware_commons/src/ec_dict.erl | 4 -- vendor/erlware_commons/src/ec_dictionary.erl | 23 ------- vendor/erlware_commons/src/ec_file.erl | 33 ++++------ vendor/erlware_commons/src/ec_git_vsn.erl | 15 +---- vendor/erlware_commons/src/ec_lists.erl | 2 +- vendor/erlware_commons/src/ec_plists.erl | 60 +++++-------------- vendor/erlware_commons/src/ec_rbdict.erl | 4 +- vendor/erlware_commons/src/ec_semver.erl | 6 +- vendor/erlware_commons/src/ec_talk.erl | 18 ++---- vendor/erlware_commons/src/ec_vsn.erl | 15 ----- .../src/erlware_commons.app.src | 2 +- vendor/relx/hex_metadata.config | 2 +- vendor/relx/priv/templates/vm_args | 5 +- vendor/relx/src/relx.app.src | 4 +- vendor/relx/src/rlx_assemble.erl | 10 ++-- vendor/relx/src/rlx_overlay.erl | 15 ++++- vendor/relx/src/rlx_util.erl | 2 +- 25 files changed, 110 insertions(+), 219 deletions(-) diff --git a/apps/rebar/rebar.config b/apps/rebar/rebar.config index 69fc1e1fb..8b1fe85c5 100644 --- a/apps/rebar/rebar.config +++ b/apps/rebar/rebar.config @@ -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"}]}. diff --git a/apps/rebar/test/rebar_dialyzer_SUITE.erl b/apps/rebar/test/rebar_dialyzer_SUITE.erl index efa08ce69..1548a2259 100644 --- a/apps/rebar/test/rebar_dialyzer_SUITE.erl +++ b/apps/rebar/test/rebar_dialyzer_SUITE.erl @@ -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), diff --git a/vendor/erlware_commons/README.md b/vendor/erlware_commons/README.md index 6ff669cec..f1fbfbaca 100644 --- a/vendor/erlware_commons/README.md +++ b/vendor/erlware_commons/README.md @@ -69,7 +69,7 @@ href="http://www.erlang.org/doc/man/lists.html">lists, 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. @@ -77,7 +77,7 @@ 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 @@ -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). diff --git a/vendor/erlware_commons/hex_metadata.config b/vendor/erlware_commons/hex_metadata.config index 3d0891715..c89af1bfe 100644 --- a/vendor/erlware_commons/hex_metadata.config +++ b/vendor/erlware_commons/hex_metadata.config @@ -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">>]}. @@ -21,4 +21,4 @@ [{<<"app">>,<<"cf">>}, {<<"optional">>,false}, {<<"requirement">>,<<"~>0.3">>}]}]}. -{<<"version">>,<<"1.6.0">>}. +{<<"version">>,<<"1.7.0">>}. diff --git a/vendor/erlware_commons/rebar.config b/vendor/erlware_commons/rebar.config index e26913287..017e3fec8 100644 --- a/vendor/erlware_commons/rebar.config +++ b/vendor/erlware_commons/rebar.config @@ -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, diff --git a/vendor/erlware_commons/rebar.config.script b/vendor/erlware_commons/rebar.config.script index 636b57988..0f7c22b28 100644 --- a/vendor/erlware_commons/rebar.config.script +++ b/vendor/erlware_commons/rebar.config.script @@ -1,11 +1,24 @@ -IsRebar3 = true, +IsRebar3 = case application:get_key(rebar, vsn) of + {ok, Vsn} -> + [MajorVersion|_] = string:tokens(Vsn, "."), + (list_to_integer(MajorVersion) >= 3); + undefined -> + false + end, 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. diff --git a/vendor/erlware_commons/src/ec_cmd_log.erl b/vendor/erlware_commons/src/ec_cmd_log.erl index 56efa5c5b..ba616f47f 100644 --- a/vendor/erlware_commons/src/ec_cmd_log.erl +++ b/vendor/erlware_commons/src/ec_cmd_log.erl @@ -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 @@ -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). @@ -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). @@ -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). @@ -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). @@ -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); diff --git a/vendor/erlware_commons/src/ec_date.erl b/vendor/erlware_commons/src/ec_date.erl index 97bcea391..49266b14d 100644 --- a/vendor/erlware_commons/src/ec_date.erl +++ b/vendor/erlware_commons/src/ec_date.erl @@ -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}. @@ -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}} @@ -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) -> @@ -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) -> @@ -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) -> @@ -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 %%%=================================================================== @@ -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"), diff --git a/vendor/erlware_commons/src/ec_dict.erl b/vendor/erlware_commons/src/ec_dict.erl index 0c0b9981e..3e9418e68 100644 --- a/vendor/erlware_commons/src/ec_dict.erl +++ b/vendor/erlware_commons/src/ec_dict.erl @@ -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 diff --git a/vendor/erlware_commons/src/ec_dictionary.erl b/vendor/erlware_commons/src/ec_dictionary.erl index 423914acd..ea7fdc921 100644 --- a/vendor/erlware_commons/src/ec_dictionary.erl +++ b/vendor/erlware_commons/src/ec_dictionary.erl @@ -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(). @@ -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 %%%=================================================================== diff --git a/vendor/erlware_commons/src/ec_file.erl b/vendor/erlware_commons/src/ec_file.erl index a139e6e60..cc3d1c46c 100644 --- a/vendor/erlware_commons/src/ec_file.erl +++ b/vendor/erlware_commons/src/ec_file.erl @@ -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. %%
@@ -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
@@ -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
@@ -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
@@ -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
diff --git a/vendor/erlware_commons/src/ec_git_vsn.erl b/vendor/erlware_commons/src/ec_git_vsn.erl
index 8c2376feb..d690d1a71 100644
--- a/vendor/erlware_commons/src/ec_git_vsn.erl
+++ b/vendor/erlware_commons/src/ec_git_vsn.erl
@@ -94,22 +94,11 @@ parse_tags(Pattern) ->
         "fatal: " ++ _ ->
             {undefined, ""};
         _ ->
-            Vsn = slice(Tag, len(Pattern)),
-            Vsn1 = trim(trim(Vsn, left, "v"), right, "\n"),
+            Vsn  = string:slice(Tag, string:length(Pattern)),
+            Vsn1 = string:trim(string:trim(Vsn, leading, "v"), trailing, "\n"),
             {Tag, Vsn1}
     end.
 
--ifdef(unicode_str).
-len(Str) -> string:length(Str).
-trim(Str, right, Chars) -> string:trim(Str, trailing, Chars);
-trim(Str, left, Chars) -> string:trim(Str, leading, Chars).
-slice(Str, Len) -> string:slice(Str, Len).
--else.
-len(Str) -> string:len(Str).
-trim(Str, Dir, [Chars|_]) -> string:strip(Str, Dir, Chars).
-slice(Str, Len) -> string:substr(Str, Len + 1).
--endif.
-
 -ifdef(TEST).
 -include_lib("eunit/include/eunit.hrl").
 
diff --git a/vendor/erlware_commons/src/ec_lists.erl b/vendor/erlware_commons/src/ec_lists.erl
index c95078bfb..0ae520498 100644
--- a/vendor/erlware_commons/src/ec_lists.erl
+++ b/vendor/erlware_commons/src/ec_lists.erl
@@ -52,7 +52,7 @@ find(_Fun, []) ->
     error.
 
 %% @doc Fetch a value from the list. If the function returns true the
-%% value is returend. If processing reaches the end of the list and
+%% value is returned. If processing reaches the end of the list and
 %% the function has never returned true an exception not_found is
 %% thrown.
 -spec fetch(fun(), list()) -> term().
diff --git a/vendor/erlware_commons/src/ec_plists.erl b/vendor/erlware_commons/src/ec_plists.erl
index 50f122e46..221075bcc 100644
--- a/vendor/erlware_commons/src/ec_plists.erl
+++ b/vendor/erlware_commons/src/ec_plists.erl
@@ -30,7 +30,7 @@
 %%% 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
+%%% and across erlang 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.
 %%%
@@ -38,7 +38,7 @@
 %%% 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.
+%%% to parallelize the operation.
 %%%
 %%% fold is the one exception, parallel fold is different from linear
 %%% fold.  This module also include a simple mapreduce implementation,
@@ -169,7 +169,7 @@
 %%% processes. If one of them does a non-normal exit, plists receives
 %%% the 'DOWN' message believing it to be from one of its own
 %%% processes. The error propagation system goes into effect, which
-%%% results in the error occuring in the calling process.
+%%% results in the error occurring in the calling process.
 %%%
 -module(ec_plists).
 
@@ -330,14 +330,14 @@ fold(Fun, Fuse, InitAcc, List, Malt) ->
            end,
     runmany(Fun2, Fuse, List, Malt).
 
-%% @doc Similiar to foreach in module
+%% @doc Similar to foreach in module
 %% lists
 %% except it makes no guarantee about the order it processes list elements.
 -spec foreach(fun(), list()) -> ok.
 foreach(Fun, List) ->
     foreach(Fun, List, 1).
 
-%% @doc Similiar to foreach in module
+%% @doc Similar to foreach in module
 %% lists
 %% except it makes no guarantee about the order it processes list elements.
 -spec foreach(fun(), list(), malt()) -> ok.
@@ -432,8 +432,8 @@ sort(Fun, List) ->
 %%
 %% sort splits the list into sublists and sorts them, and it merges the
 %% sorted lists together. These are done in parallel. Each sublist is
-%% sorted in a seperate process, and each merging of results is done in a
-%% seperate process. Malt defaults to 100, causing the list to be split into
+%% sorted in a separate process, and each merging of results is done in a
+%% separate process. Malt defaults to 100, causing the list to be split into
 %% 100-element sublists.
 -spec sort(fun(), list(), malt()) -> list().
 sort(Fun, List, Malt) ->
@@ -464,11 +464,11 @@ usort(Fun, List) ->
 %%
 %% usort splits the list into sublists and sorts them, and it merges the
 %% sorted lists together. These are done in parallel. Each sublist is
-%% sorted in a seperate process, and each merging of results is done in a
-%% seperate process. Malt defaults to 100, causing the list to be split into
+%% sorted in a separate process, and each merging of results is done in a
+%% separate process. Malt defaults to 100, causing the list to be split into
 %% 100-element sublists.
 %%
-%% usort removes duplicate elments while it sorts.
+%% usort removes duplicate elements while it sorts.
 -spec usort(fun(), list(), malt()) -> list().
 usort(Fun, List, Malt) ->
     Fun2 = fun (L) ->
@@ -480,16 +480,9 @@ usort(Fun, List, Malt) ->
     runmany(Fun2, {recursive, Fuse}, List, Malt).
 
 %% @doc Like below, assumes default MapMalt of 1.
--ifdef(namespaced_types).
 -spec mapreduce(MapFunc, list()) -> dict:dict() when
       MapFunc ::  fun((term()) -> DeepListOfKeyValuePairs),
       DeepListOfKeyValuePairs :: [DeepListOfKeyValuePairs] | {Key::term(), Value::term()}.
--else.
--spec mapreduce(MapFunc, list()) -> dict() when
-      MapFunc ::  fun((term()) -> DeepListOfKeyValuePairs),
-      DeepListOfKeyValuePairs :: [DeepListOfKeyValuePairs] | {Key::term(), Value::term()}.
--endif.
-
 
 mapreduce(MapFunc, List) ->
     mapreduce(MapFunc, List, 1).
@@ -514,21 +507,14 @@ mapreduce(MapFunc, List, MapMalt) ->
 %% reducer's final state.
 %%
 %% MapMalt is the malt for the mapping operation, with a default value of 1,
-%% meaning each element of the list is mapped by a seperate process.
+%% meaning each element of the list is mapped by a separate process.
 %%
 %% mapreduce requires OTP R11B, or it may leave monitoring messages in the
 %% message queue.
--ifdef(namespaced_types).
 -spec mapreduce(MapFunc, list(), InitState::term(), ReduceFunc, malt()) -> dict:dict() when
       MapFunc :: fun((term()) -> DeepListOfKeyValuePairs),
       DeepListOfKeyValuePairs :: [DeepListOfKeyValuePairs] | {Key::term(), Value::term()},
       ReduceFunc :: fun((OldState::term(), Key::term(), Value::term()) -> NewState::term()).
--else.
--spec mapreduce(MapFunc, list(), InitState::term(), ReduceFunc, malt()) -> dict() when
-      MapFunc :: fun((term()) -> DeepListOfKeyValuePairs),
-      DeepListOfKeyValuePairs :: [DeepListOfKeyValuePairs] | {Key::term(), Value::term()},
-      ReduceFunc :: fun((OldState::term(), Key::term(), Value::term()) -> NewState::term()).
--endif.
 mapreduce(MapFunc, List, InitState, ReduceFunc, MapMalt) ->
     Parent = self(),
     {Reducer, ReducerRef} =
@@ -586,7 +572,7 @@ add_key(Dict, Key, Value) ->
     end.
 
 %% @doc Like below, but assumes a Malt of 1,
-%% meaning each element of the list is processed by a seperate process.
+%% meaning each element of the list is processed by a separate process.
 -spec runmany(fun(), fuse(), list()) -> term().
 runmany(Fun, Fuse, List) ->
     runmany(Fun, Fuse, List, 1).
@@ -615,7 +601,7 @@ runmany(Fun, Fuse, List) ->
 %% continues fusing pairs of results until it is down to one.
 %%
 %% Recursive fuse is down in parallel with processing the sublists, and a
-%% process is spawned to fuse each pair of results. It is a parallized
+%% process is spawned to fuse each pair of results. It is a parallelized
 %% algorithm. Linear fuse is done after all results of processing sublists
 %% have been collected, and can only run in a single process.
 %%
@@ -691,7 +677,7 @@ runmany(Fun, {recursive, Fuse}, List, local, Split, []) ->
     %% or {nodes, NodeList}. Degenerates recursive fuse into linear fuse.
     runmany(Fun, Fuse, List, local, Split, []);
 runmany(Fun, Fuse, List, Nodes, no_split, []) ->
-    %% by default, operate on each element seperately
+    %% by default, operate on each element separately
     runmany(Fun, Fuse, List, Nodes, 1, []);
 runmany(Fun, Fuse, List, local, Split, []) ->
     List2 = splitmany(List, Split),
@@ -872,24 +858,9 @@ cluster_runmany(_, _, [_Non|_Empty], []=_Nodes, []=_Running, _) ->
 %% We have data, but no nodes either available or occupied
     erlang:exit(allnodescrashed).
 
--ifdef(fun_stacktrace).
-runmany_wrap(Fun, Parent) ->
-    try
-        Fun
-    catch
-        exit:siblingdied ->
-            ok;
-        exit:Reason ->
-            Parent ! {erlang:self(), error, Reason};
-        error:R ->
-            Parent ! {erlang:self(), error, {R, erlang:get_stacktrace()}};
-        throw:R ->
-            Parent ! {erlang:self(), error, {{nocatch, R}, erlang:get_stacktrace()}}
-    end.
--else.
 runmany_wrap(Fun, Parent) ->
     try
-        Fun
+        Fun()
     catch
         exit:siblingdied ->
             ok;
@@ -900,7 +871,6 @@ runmany_wrap(Fun, Parent) ->
         throw:R:Stacktrace ->
             Parent ! {erlang:self(), error, {{nocatch, R}, Stacktrace}}
     end.
--endif.
 
 delete_running(Pid, [{Pid, Node, List}|Running], Acc) ->
     {Running ++ Acc, Node, List};
diff --git a/vendor/erlware_commons/src/ec_rbdict.erl b/vendor/erlware_commons/src/ec_rbdict.erl
index 60e337f14..9f3b61745 100644
--- a/vendor/erlware_commons/src/ec_rbdict.erl
+++ b/vendor/erlware_commons/src/ec_rbdict.erl
@@ -32,7 +32,7 @@
 %%% representation of a dictionary, where a red-black tree is used to
 %%% store the keys and values.
 %%%
-%%% This module implents exactly the same interface as the module
+%%% This module implements exactly the same interface as the module
 %%% ec_dictionary but with a defined representation. One difference is
 %%% that while dict considers two keys as different if they do not
 %%% match (=:=), this module considers two keys as different if and
@@ -296,7 +296,7 @@ to_list(empty, List) -> List;
 to_list({_, A, Xk, Xv, B}, List) ->
     to_list(A, [{Xk, Xv} | to_list(B, List)]).
 
-%% Balance a tree afer (possibly) adding a node to the left/right.
+%% Balance a tree after (possibly) adding a node to the left/right.
 -spec lbalance(color(), dictionary(K, V),
                ec_dictionary:key(K), ec_dictionary:value(V),
                dictionary(K, V)) ->
diff --git a/vendor/erlware_commons/src/ec_semver.erl b/vendor/erlware_commons/src/ec_semver.erl
index 8141065f7..493466fc6 100644
--- a/vendor/erlware_commons/src/ec_semver.erl
+++ b/vendor/erlware_commons/src/ec_semver.erl
@@ -202,13 +202,13 @@ pes(VsnA, VsnB) ->
 %%%===================================================================
 %%% Friend Functions
 %%%===================================================================
-%% @doc helper function for the peg grammer to parse the iolist into a semver
+%% @doc helper function for the peg grammar to parse the iolist into a semver
 -spec internal_parse_version(iolist()) -> semver().
 internal_parse_version([MMP, AlphaPart, BuildPart, _]) ->
     {parse_major_minor_patch_minpatch(MMP), {parse_alpha_part(AlphaPart),
                                              parse_alpha_part(BuildPart)}}.
 
-%% @doc helper function for the peg grammer to parse the iolist into a major_minor_patch
+%% @doc helper function for the peg grammar to parse the iolist into a major_minor_patch
 -spec parse_major_minor_patch_minpatch(iolist()) -> major_minor_patch_minpatch().
 parse_major_minor_patch_minpatch([MajVsn, [], [], []]) ->
     strip_maj_version(MajVsn);
@@ -224,7 +224,7 @@ parse_major_minor_patch_minpatch([MajVsn,
                                   [<<".">>, MinPatch]]) ->
     {strip_maj_version(MajVsn), MinVsn, PatchVsn, MinPatch}.
 
-%% @doc helper function for the peg grammer to parse the iolist into an alpha part
+%% @doc helper function for the peg grammar to parse the iolist into an alpha part
 -spec parse_alpha_part(iolist()) -> [alpha_part()].
 parse_alpha_part([]) ->
     [];
diff --git a/vendor/erlware_commons/src/ec_talk.erl b/vendor/erlware_commons/src/ec_talk.erl
index 454b1f853..9b9a71af0 100644
--- a/vendor/erlware_commons/src/ec_talk.erl
+++ b/vendor/erlware_commons/src/ec_talk.erl
@@ -75,7 +75,7 @@ ask(Prompt) ->
 ask_default(Prompt, Default) ->
     ask_convert(Prompt, fun get_string/1, string, Default).
 
-%% @doc Asks the user to respond to the prompt. Trys to return the
+%% @doc Asks the user to respond to the prompt. Tries to return the
 %% value in the format specified by 'Type'.
 -spec ask(prompt(), type()) ->  supported().
 ask(Prompt, boolean) ->
@@ -85,7 +85,7 @@ ask(Prompt, number) ->
 ask(Prompt, string) ->
     ask_convert(Prompt, fun get_string/1, string, none).
 
-%% @doc Asks the user to respond to the prompt. Trys to return the
+%% @doc Asks the user to respond to the prompt. Tries to return the
 %% value in the format specified by 'Type'.
 -spec ask_default(prompt(), type(), supported()) ->  supported().
 ask_default(Prompt, boolean, Default)  ->
@@ -127,7 +127,7 @@ ask_convert(Prompt, TransFun, Type,  Default) ->
                                                            Default ->
                                                                [" (", io_lib:format("~p", [Default]) , ")"]
                                                        end, "> "])),
-    Data = trim(trim(io:get_line(NewPrompt)), both, [$\n]),
+    Data = string:trim(string:trim(io:get_line(NewPrompt)), both, [$\n]),
     Ret = TransFun(Data),
     case Ret of
         no_data ->
@@ -145,7 +145,7 @@ ask_convert(Prompt, TransFun, Type,  Default) ->
             Ret
     end.
 
-%% @doc Trys to translate the result into a boolean
+%% @doc Tries to translate the result into a boolean
 -spec get_boolean(string()) -> boolean().
 get_boolean([]) ->
     no_data;
@@ -172,7 +172,7 @@ get_boolean([$N | _]) ->
 get_boolean(_) ->
     no_clue.
 
-%% @doc Trys to translate the result into an integer
+%% @doc Tries to translate the result into an integer
 -spec get_integer(string()) -> integer().
 get_integer([]) ->
     no_data;
@@ -197,14 +197,6 @@ get_string(String) ->
             no_clue
     end.
 
--ifdef(unicode_str).
-trim(Str) -> string:trim(Str).
-trim(Str, both, Chars) -> string:trim(Str, both, Chars).
--else.
-trim(Str) -> string:strip(Str).
-trim(Str, Dir, [Chars|_]) -> string:strip(Str, Dir, Chars).
--endif.
-
 %%%====================================================================
 %%% tests
 %%%====================================================================
diff --git a/vendor/erlware_commons/src/ec_vsn.erl b/vendor/erlware_commons/src/ec_vsn.erl
index 2f38090b9..e407b9fc8 100644
--- a/vendor/erlware_commons/src/ec_vsn.erl
+++ b/vendor/erlware_commons/src/ec_vsn.erl
@@ -27,24 +27,9 @@
 %% however you should not rely on the internal representation here
 -type t() :: #t{}.
 
--ifdef(have_callback_support).
-
 -callback new() -> any().
 -callback vsn(any()) -> {ok, string()} | {error, Reason::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},
-     {vsn, 1}];
-behaviour_info(_Other) ->
-    undefined.
--endif.
-
 %%%===================================================================
 %%% API
 %%%===================================================================
diff --git a/vendor/erlware_commons/src/erlware_commons.app.src b/vendor/erlware_commons/src/erlware_commons.app.src
index 9ffca4ae4..de1839f9c 100644
--- a/vendor/erlware_commons/src/erlware_commons.app.src
+++ b/vendor/erlware_commons/src/erlware_commons.app.src
@@ -1,6 +1,6 @@
 {application,erlware_commons,
              [{description,"Additional standard library for Erlang"},
-              {vsn,"1.6.0"},
+              {vsn,"1.7.0"},
               {modules,[]},
               {registered,[]},
               {applications,[kernel,stdlib,cf]},
diff --git a/vendor/relx/hex_metadata.config b/vendor/relx/hex_metadata.config
index a34317d8f..7dd55542d 100644
--- a/vendor/relx/hex_metadata.config
+++ b/vendor/relx/hex_metadata.config
@@ -28,4 +28,4 @@
    [{<<"app">>,<<"bbmustache">>},
     {<<"optional">>,false},
     {<<"requirement">>,<<"~>1.10">>}]}]}.
-{<<"version">>,<<"4.8.0">>}.
+{<<"version">>,<<"4.9.0">>}.
diff --git a/vendor/relx/priv/templates/vm_args b/vendor/relx/priv/templates/vm_args
index babba6208..a9b23da69 100644
--- a/vendor/relx/priv/templates/vm_args
+++ b/vendor/relx/priv/templates/vm_args
@@ -4,6 +4,7 @@
 ## Cookie for distributed erlang
 -setcookie {{ rel_name }}
 
+## This is now the default as of OTP-26
 ## Multi-time warp mode in combination with time correction is the preferred configuration. 
 ## It is only not the default in Erlang itself because it could break older systems.
 +C multi_time_warp 
@@ -15,10 +16,6 @@
 ## (Disabled by default..use with caution!)
 ##-heart
 
-## Enable kernel poll and a few async threads
-##+K true
-##+A 5
-
 ## Increase number of concurrent ports/sockets
 ##-env ERL_MAX_PORTS 4096
 
diff --git a/vendor/relx/src/relx.app.src b/vendor/relx/src/relx.app.src
index efeabe8d9..3114f388a 100644
--- a/vendor/relx/src/relx.app.src
+++ b/vendor/relx/src/relx.app.src
@@ -1,8 +1,8 @@
 {application,relx,
              [{description,"Release assembler for Erlang/OTP Releases"},
-              {vsn,"4.8.0"},
+              {vsn,"4.9.0"},
               {modules,[]},
               {registered,[]},
-              {applications,[kernel,stdlib,bbmustache]},
+              {applications,[kernel,stdlib,bbmustache,sasl,tools]},
               {licenses,["Apache-2.0"]},
               {links,[{"Github","https://github.com/erlware/relx"}]}]}.
diff --git a/vendor/relx/src/rlx_assemble.erl b/vendor/relx/src/rlx_assemble.erl
index 308abb7d6..4763e01ce 100644
--- a/vendor/relx/src/rlx_assemble.erl
+++ b/vendor/relx/src/rlx_assemble.erl
@@ -759,7 +759,7 @@ maybe_check_for_undefined_functions_(State, Release) ->
                     FilterMethod = rlx_state:filter_xref_warning(State),
                     FilteredWarnings = FilterMethod(Warnings),
                     format_xref_warning(FilteredWarnings);
-                {error, _} = Error ->
+                {error, _, _} = Error ->
                     ?log_warn(
                         "Error running xref analyze: ~s", 
                         [xref:format_error(Error)])
@@ -776,13 +776,13 @@ add_project_apps_to_xref(Rf, [AppSpec | Rest], State) ->
     case maps:find(element(1, AppSpec), rlx_state:available_apps(State)) of
         {ok, App=#{app_type := project}} ->
             case xref:add_application(
-                    Rf,
-                    rlx_app_info:dir(App),
-                    [{name, rlx_app_info:name(App)}, {warnings, false}]) 
+                   Rf,
+                   binary_to_list(rlx_app_info:dir(App)),
+                   [{name, rlx_app_info:name(App)}, {warnings, false}])
             of
                 {ok, _} ->
                     ok;
-                {error, _} = Error ->
+                {error, _, _} = Error ->
                     ?log_warn("Error adding application ~s to xref context: ~s",
                               [rlx_app_info:name(App), xref:format_error(Error)])
             end;
diff --git a/vendor/relx/src/rlx_overlay.erl b/vendor/relx/src/rlx_overlay.erl
index 5b7b861c5..43631fc40 100644
--- a/vendor/relx/src/rlx_overlay.erl
+++ b/vendor/relx/src/rlx_overlay.erl
@@ -118,7 +118,9 @@ read_overlay_vars(State, OverlayVars, FileNames) ->
             % definitions should be able to be overwritten by both internal
             % and rendered vars, as not to change behaviour in
             % setups preceding the support for overlays from the caller.
-            OverlayVars ++ NewTerms ++ OverlayVarsValues;
+            % Place NewTerms at the start - the last overlays added should be able
+            % to override those that came before
+            NewTerms ++ OverlayVars ++ OverlayVarsValues;
         Error ->
             Error
     end.
@@ -324,6 +326,17 @@ do_individual_overlay(State, Release, _Files, OverlayVars, {template, From, To})
                                                                  absolute_path_to(State, Release, ToFile))
                                           end)
                    end);
+do_individual_overlay(State, Release, _Files, OverlayVars0, {template, From, To, OverlayFilename}) ->
+    OverlayVars = read_overlay_vars(State, OverlayVars0, [OverlayFilename]),
+    file_render_do(OverlayVars, From,
+                   fun(FromFile) ->
+                           file_render_do(OverlayVars, To,
+                                          fun(ToFile) ->
+                                                  write_template(OverlayVars,
+                                                                 absolute_path_from(State, FromFile),
+                                                                 absolute_path_to(State, Release, ToFile))
+                                          end)
+                   end);
 do_individual_overlay(_State, _Release, _Files, _OverlayVars, Invalid) ->
     ?RLX_ERROR({malformed_overlay, Invalid}).
 
diff --git a/vendor/relx/src/rlx_util.erl b/vendor/relx/src/rlx_util.erl
index 9047b4b59..349aa7bee 100644
--- a/vendor/relx/src/rlx_util.erl
+++ b/vendor/relx/src/rlx_util.erl
@@ -104,7 +104,7 @@ parsed_vsn_lt({MMPA, {AlphaA, PatchA}}, {MMPB, {AlphaB, PatchB}}) ->
            PatchA < PatchB))).
 
 %% @doc Generates the correct set of code paths for the system.
--spec get_code_paths(rlx_release:t(), file:name()) -> [filename:filename_all()].
+-spec get_code_paths(rlx_release:t(), file:name()) -> [file:filename_all()].
 get_code_paths(Release, OutDir) ->
     LibDir = filename:join(OutDir, "lib"),
     [filename:join([LibDir, [rlx_app_info:name(App), "-", rlx_app_info:vsn(App)], "ebin"]) ||

From c3fe89f4f4a81fc66b7f5ae389ed729f126c7c2a Mon Sep 17 00:00:00 2001
From: Fred Hebert 
Date: Wed, 3 Apr 2024 00:40:32 +0000
Subject: [PATCH 2/3] Manual patch to make builds work

---
 vendor/relx/src/rlx_assemble.erl | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/vendor/relx/src/rlx_assemble.erl b/vendor/relx/src/rlx_assemble.erl
index 4763e01ce..b7a6d2cc8 100644
--- a/vendor/relx/src/rlx_assemble.erl
+++ b/vendor/relx/src/rlx_assemble.erl
@@ -777,7 +777,7 @@ add_project_apps_to_xref(Rf, [AppSpec | Rest], State) ->
         {ok, App=#{app_type := project}} ->
             case xref:add_application(
                    Rf,
-                   binary_to_list(rlx_app_info:dir(App)),
+                   unicode:characters_to_list(rlx_app_info:dir(App)),
                    [{name, rlx_app_info:name(App)}, {warnings, false}])
             of
                 {ok, _} ->

From bb596d63102bbf55f578d752e997ef88dfdfdcd1 Mon Sep 17 00:00:00 2001
From: Fred Hebert 
Date: Wed, 3 Apr 2024 11:32:42 +0000
Subject: [PATCH 3/3] bring back erlware_commons version hotfix

---
 vendor/erlware_commons/rebar.config.script | 8 +-------
 1 file changed, 1 insertion(+), 7 deletions(-)

diff --git a/vendor/erlware_commons/rebar.config.script b/vendor/erlware_commons/rebar.config.script
index 0f7c22b28..4905b0db7 100644
--- a/vendor/erlware_commons/rebar.config.script
+++ b/vendor/erlware_commons/rebar.config.script
@@ -1,10 +1,4 @@
-IsRebar3 = case application:get_key(rebar, vsn) of
-               {ok, Vsn} ->
-                   [MajorVersion|_] = string:tokens(Vsn, "."),
-                   (list_to_integer(MajorVersion) >= 3);
-               undefined ->
-                   false
-           end,
+IsRebar3 = true,
 
 Rebar2Deps = [
               {cf, ".*", {git, "https://github.com/project-fifo/cf", {tag, "0.2.2"}}}