Skip to content

Commit

Permalink
Merge pull request #1660 from ferd/otp-21-preparedness
Browse files Browse the repository at this point in the history
OTP-21 readiness, Full Unicode support
  • Loading branch information
ferd authored Nov 17, 2017
2 parents 9d050dd + 2d5cd9c commit 94976d5
Show file tree
Hide file tree
Showing 29 changed files with 143 additions and 86 deletions.
24 changes: 18 additions & 6 deletions bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ fetch({pkg, Name, Vsn}, App) ->
false ->
CDN = "https://repo.hex.pm/tarballs",
Package = binary_to_list(<<Name/binary, "-", Vsn/binary, ".tar">>),
Url = string:join([CDN, Package], "/"),
Url = join([CDN, Package], "/"),
case request(Url) of
{ok, Binary} ->
{ok, Contents} = extract(Binary),
Expand Down Expand Up @@ -210,7 +210,7 @@ cp_r(Sources, Dest) ->
case os:type() of
{unix, _} ->
EscSources = [escape_path(Src) || Src <- Sources],
SourceStr = string:join(EscSources, " "),
SourceStr = join(EscSources, " "),
os:cmd(?FMT("cp -R ~s \"~s\"", [SourceStr, Dest])),
ok;
{win32, _} ->
Expand Down Expand Up @@ -336,7 +336,11 @@ format_error(AbsSource, Extra, {Mod, Desc}) ->
io_lib:format("~s: ~s~s~n", [AbsSource, Extra, ErrorDesc]).

additional_defines() ->
[{d, D} || {Re, D} <- [{"^[0-9]+", namespaced_types}, {"^R1[4|5]", deprecated_crypto}, {"^((1[8|9])|2)", rand_module}], is_otp_release(Re)].
[{d, D} || {Re, D} <- [{"^[0-9]+", namespaced_types},
{"^R1[4|5]", deprecated_crypto},
{"^2", unicode_str},
{"^((1[8|9])|2)", rand_module}],
is_otp_release(Re)].

is_otp_release(ArchRegex) ->
case re:run(otp_release(), ArchRegex, [{capture, none}]) of
Expand Down Expand Up @@ -388,9 +392,8 @@ otp_release1(Rel) ->
set_proxy_auth([]) ->
ok;
set_proxy_auth(UserInfo) ->
Idx = string:chr(UserInfo, $:),
Username = string:sub_string(UserInfo, 1, Idx-1),
Password = string:sub_string(UserInfo, Idx+1),
[Username, Password] = re:split(UserInfo, ":",
[{return, list}, {parts,2}, unicode]),
%% password may contain url encoded characters, need to decode them first
put(proxy_auth, [{proxy_auth, {Username, http_uri:decode(Password)}}]).

Expand All @@ -400,3 +403,12 @@ get_proxy_auth() ->
ProxyAuth -> ProxyAuth
end.

%% string:join/2 copy; string:join/2 is getting obsoleted
%% and replaced by lists:join/2, but lists:join/2 is too new
%% for version support (only appeared in 19.0) so it cannot be
%% used. Instead we just adopt join/2 locally and hope it works
%% for most unicode use cases anyway.
join([], Sep) when is_list(Sep) ->
[];
join([H|T], Sep) ->
H ++ lists:append([Sep ++ X || X <- T]).
16 changes: 9 additions & 7 deletions rebar.config
Original file line number Diff line number Diff line change
@@ -1,16 +1,16 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 ft=erlang et

{deps, [{erlware_commons, "1.0.0"},
{ssl_verify_fun, "1.1.2"},
{deps, [{erlware_commons, "1.0.3"},
{ssl_verify_fun, "1.1.3"},
{certifi, "2.0.0"},
{providers, "1.6.0"},
{getopt, "0.8.2"},
{providers, "1.7.0"},
{getopt, "1.0.1"},
{bbmustache, "1.3.0"},
{relx, "3.23.1"},
{relx, "3.24.1"},
{cf, "0.2.2"},
{cth_readable, "1.3.0"},
{eunit_formatters, "0.4.0"}]}.
{cth_readable, "1.3.1"},
{eunit_formatters, "0.5.0"}]}.

{post_hooks, [{"(linux|darwin|solaris|freebsd|netbsd|openbsd)",
escriptize,
Expand All @@ -30,6 +30,7 @@

{erl_opts, [{platform_define, "^[0-9]+", namespaced_types},
{platform_define, "^(19|2)", rand_only},
{platform_define, "^2", unicode_str},
no_debug_info,
warnings_as_errors]}.

Expand Down Expand Up @@ -62,6 +63,7 @@
{overrides, [{override, erlware_commons, [{erl_opts, [{platform_define, "^[0-9]+", namespaced_types},
{platform_define, "^R1[4|5]", deprecated_crypto},
{platform_define, "^((1[8|9])|2)", rand_module},
{platform_define, "^2", unicode_str},
no_debug_info,
warnings_as_errors]},
{deps, []}, {plugins, []}]},
Expand Down
28 changes: 14 additions & 14 deletions rebar.lock
Original file line number Diff line number Diff line change
Expand Up @@ -2,23 +2,23 @@
[{<<"bbmustache">>,{pkg,<<"bbmustache">>,<<"1.3.0">>},0},
{<<"certifi">>,{pkg,<<"certifi">>,<<"2.0.0">>},0},
{<<"cf">>,{pkg,<<"cf">>,<<"0.2.2">>},0},
{<<"cth_readable">>,{pkg,<<"cth_readable">>,<<"1.3.0">>},0},
{<<"erlware_commons">>,{pkg,<<"erlware_commons">>,<<"1.0.0">>},0},
{<<"eunit_formatters">>,{pkg,<<"eunit_formatters">>,<<"0.4.0">>},0},
{<<"getopt">>,{pkg,<<"getopt">>,<<"0.8.2">>},0},
{<<"providers">>,{pkg,<<"providers">>,<<"1.6.0">>},0},
{<<"relx">>,{pkg,<<"relx">>,<<"3.23.1">>},0},
{<<"ssl_verify_fun">>,{pkg,<<"ssl_verify_fun">>,<<"1.1.2">>},0}]}.
{<<"cth_readable">>,{pkg,<<"cth_readable">>,<<"1.3.1">>},0},
{<<"erlware_commons">>,{pkg,<<"erlware_commons">>,<<"1.0.3">>},0},
{<<"eunit_formatters">>,{pkg,<<"eunit_formatters">>,<<"0.5.0">>},0},
{<<"getopt">>,{pkg,<<"getopt">>,<<"1.0.1">>},0},
{<<"providers">>,{pkg,<<"providers">>,<<"1.7.0">>},0},
{<<"relx">>,{pkg,<<"relx">>,<<"3.24.1">>},0},
{<<"ssl_verify_fun">>,{pkg,<<"ssl_verify_fun">>,<<"1.1.3">>},0}]}.
[
{pkg_hash,[
{<<"bbmustache">>, <<"2010ADAE78830992A4C69680115ECD7D475DD03A72C076BBADDCCBF2D4B32035">>},
{<<"certifi">>, <<"A0C0E475107135F76B8C1D5BC7EFB33CD3815CB3CF3DEA7AEFDD174DABEAD064">>},
{<<"cf">>, <<"7F2913FFF90ABCABD0F489896CFEB0B0674F6C8DF6C10B17A83175448029896C">>},
{<<"cth_readable">>, <<"3F3B4C9CA1C96D5986557A033647A0D7072E25C241AE5EACD894D490EB656706">>},
{<<"erlware_commons">>, <<"087467DE5833C0BB5B3CCDD387F9E9C1FB816A75B7A709629BF24B5ED3246C51">>},
{<<"eunit_formatters">>, <<"49B78A45BC06893140DB9FC928307044E0A93794ED90FA181A6F70F2190C1330">>},
{<<"getopt">>, <<"B17556DB683000BA50370B16C0619DF1337E7AF7ECBF7D64FBF8D1D6BCE3109B">>},
{<<"providers">>, <<"DB0E2F9043AE60C0155205FCD238D68516331D0E5146155E33D1E79DC452964A">>},
{<<"relx">>, <<"8AF4433934D9BB664E8282D2E45AC5DEAFF44859DDAABBE50CD7D885581CD24D">>},
{<<"ssl_verify_fun">>, <<"01289CAD67B280B7F8F7E87117966995FAD19236367386BE2A9D7716E92CE7FF">>}]}
{<<"cth_readable">>, <<"53B2C20F823D827A30ABF4F79C93A58DB46934AA038C41792C518BA5FDE9D65B">>},
{<<"erlware_commons">>, <<"ABD000FE5893342A405B5F4A2900FF560875B3234E8FE915FDEF172D98EAF250">>},
{<<"eunit_formatters">>, <<"6A9133943D36A465D804C1C5B6E6839030434B8879C5600D7DDB5B3BAD4CCB59">>},
{<<"getopt">>, <<"C73A9FA687B217F2FF79F68A3B637711BB1936E712B521D8CE466B29CBF7808A">>},
{<<"providers">>, <<"BBF730563914328EC2511D205E6477A94831DB7297DE313B3872A2B26C562EAB">>},
{<<"relx">>, <<"8211A2C55EA67621C64FDF6A40877D95DA790478B78E3B18496E1C5916046032">>},
{<<"ssl_verify_fun">>, <<"6C49665D4326E26CD4A5B7BD54AA442B33DADFB7C5D59A0D0CD0BF5534BBFBD7">>}]}
].
2 changes: 1 addition & 1 deletion src/rebar_dialyzer_format.erl
Original file line number Diff line number Diff line change
Expand Up @@ -427,4 +427,4 @@ separate_args(D, [C | R], Arg, Args) ->
separate_args(D, R, [C | Arg], Args).

join_args(Args) ->
[$(, string:join(Args, ", "), $)].
[$(, rebar_string:join(Args, ", "), $)].
2 changes: 1 addition & 1 deletion src/rebar_dir.erl
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ profile_dir(Opts, Profiles) ->
%% of profiles to match order passed to `as`
["default"|Rest] -> {rebar_opts:get(Opts, base_dir, ?DEFAULT_BASE_DIR), Rest}
end,
ProfilesDir = string:join(ProfilesStrings, "+"),
ProfilesDir = rebar_string:join(ProfilesStrings, "+"),
filename:join(BaseDir, ProfilesDir).

%% @doc returns the directory where dependencies should be placed
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_file_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -190,7 +190,7 @@ cp_r(Sources, Dest) ->
case os:type() of
{unix, _} ->
EscSources = [rebar_utils:escape_chars(Src) || Src <- Sources],
SourceStr = string:join(EscSources, " "),
SourceStr = rebar_string:join(EscSources, " "),
{ok, []} = rebar_utils:sh(?FMT("cp -Rp ~ts \"~ts\"",
[SourceStr, rebar_utils:escape_double_quotes(Dest)]),
[{use_stdout, false}, abort_on_error]),
Expand Down
19 changes: 10 additions & 9 deletions src/rebar_git_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -28,16 +28,16 @@ lock(AppDir, {git, Url}) ->
rebar_utils:sh("git --git-dir=\"" ++ Dir ++ "/.git\" rev-parse --verify HEAD",
[{use_stdout, false}, {debug_abort_on_error, AbortMsg}])
end,
Ref = string:strip(VsnString, both, $\n),
Ref = rebar_string:trim(VsnString, both, "\n"),
{git, Url, {ref, Ref}}.

%% Return true if either the git url or tag/branch/ref is not the same as the currently
%% checked out git repo for the dep
needs_update(Dir, {git, Url, {tag, Tag}}) ->
{ok, Current} = rebar_utils:sh(?FMT("git describe --tags --exact-match", []),
[{cd, Dir}]),
Current1 = string:strip(string:strip(Current, both, $\n), both, $\r),

Current1 = rebar_string:trim(rebar_string:trim(Current, both, "\n"),
both, "\r"),
?DEBUG("Comparing git tag ~ts with ~ts", [Tag, Current1]),
not ((Current1 =:= Tag) andalso compare_url(Dir, Url));
needs_update(Dir, {git, Url, {branch, Branch}}) ->
Expand All @@ -55,8 +55,8 @@ needs_update(Dir, {git, Url, "master"}) ->
needs_update(Dir, {git, _, Ref}) ->
{ok, Current} = rebar_utils:sh(?FMT("git rev-parse --short=7 -q HEAD", []),
[{cd, Dir}]),
Current1 = string:strip(string:strip(Current, both, $\n), both, $\r),

Current1 = rebar_string:trim(rebar_string:trim(Current, both, "\n"),
both, "\r"),
Ref2 = case Ref of
{ref, Ref1} ->
Length = length(Current1),
Expand All @@ -74,7 +74,8 @@ needs_update(Dir, {git, _, Ref}) ->
compare_url(Dir, Url) ->
{ok, CurrentUrl} = rebar_utils:sh(?FMT("git config --get remote.origin.url", []),
[{cd, Dir}]),
CurrentUrl1 = string:strip(string:strip(CurrentUrl, both, $\n), both, $\r),
CurrentUrl1 = rebar_string:trim(rebar_string:trim(CurrentUrl, both, "\n"),
both, "\r"),
{ok, ParsedUrl} = parse_git_url(Url),
{ok, ParsedCurrentUrl} = parse_git_url(CurrentUrl1),
?DEBUG("Comparing git url ~p with ~p", [ParsedUrl, ParsedCurrentUrl]),
Expand Down Expand Up @@ -215,7 +216,7 @@ collect_default_refcount(Dir) ->
?WARN("Getting log of git dependency failed in ~ts. Falling back to version 0.0.0", [rebar_dir:get_cwd()]),
{plain, "0.0.0"};
{ok, String} ->
RawRef = string:strip(String, both, $\n),
RawRef = rebar_string:trim(String, both, "\n"),

{Tag, TagVsn} = parse_tags(Dir),
{ok, RawCount} =
Expand Down Expand Up @@ -275,9 +276,9 @@ parse_tags(Dir) ->
{undefined, "0.0.0"};
%% strip the v prefix if it exists like is done in the above match
{ok, [$v | LatestVsn]} ->
{undefined, string:strip(LatestVsn, both, $\n)};
{undefined, rebar_string:trim(LatestVsn, both, "\n")};
{ok, LatestVsn} ->
{undefined, string:strip(LatestVsn, both, $\n)}
{undefined, rebar_string:trim(LatestVsn,both, "\n")}
end
end
end.
20 changes: 10 additions & 10 deletions src/rebar_hg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ make_vsn(Dir) ->
{ok, VsnString} =
rebar_utils:sh(Cmd,
[{use_stdout, false}, {debug_abort_on_error, AbortMsg}]),
RawVsn = string:strip(VsnString, both, $\n),
RawVsn = rebar_string:trim(VsnString, both, "\n"),

Vsn = case RawVsn of
"null+" ++ Rest -> "0.0.0+" ++ Rest;
Expand All @@ -107,16 +107,16 @@ make_vsn(Dir) ->
%%% Internal functions

compare_url(Dir, Url) ->
CurrentUrl = string:strip(os:cmd("hg -R \"" ++ rebar_utils:escape_double_quotes(Dir) ++"\" paths default"), both, $\n),
CurrentUrl1 = string:strip(CurrentUrl, both, $\r),
CurrentUrl = rebar_string:trim(os:cmd("hg -R \"" ++ rebar_utils:escape_double_quotes(Dir) ++"\" paths default"), both, "\n"),
CurrentUrl1 = rebar_string:trim(CurrentUrl, both, "\r"),
parse_hg_url(CurrentUrl1) =:= parse_hg_url(Url).

get_ref(Dir) ->
AbortMsg = io_lib:format("Get ref of hg dependency failed in ~ts", [Dir]),
{ok, RefString} =
rebar_utils:sh("hg -R \"" ++ rebar_utils:escape_double_quotes(Dir) ++ "\" --debug id -i",
[{use_stdout, false}, {debug_abort_on_error, AbortMsg}]),
string:strip(RefString, both, $\n).
rebar_string:trim(RefString, both, "\n").

get_tag_distance(Dir, Ref) ->
AbortMsg = io_lib:format("Get tag distance of hg dependency failed in ~ts", [Dir]),
Expand All @@ -125,8 +125,8 @@ get_tag_distance(Dir, Ref) ->
"log --template \"{latesttag}-{latesttagdistance}\n\" "
"--rev " ++ rebar_utils:escape_chars(Ref),
[{use_stdout, false}, {debug_abort_on_error, AbortMsg}]),
Log = string:strip(LogString,
both, $\n),
Log = rebar_string:trim(LogString,
both, "\n"),
[Tag, Distance] = re:split(Log, "-([0-9]+)$",
[{parts,0}, {return,list}, unicode]),
{Tag, Distance}.
Expand All @@ -137,7 +137,7 @@ get_branch_ref(Dir, Branch) ->
rebar_utils:sh("hg -R \"" ++ rebar_utils:escape_double_quotes(Dir) ++
"\" log --template \"{node}\n\" --rev " ++ rebar_utils:escape_chars(Branch),
[{use_stdout, false}, {debug_abort_on_error, AbortMsg}]),
string:strip(BranchRefString, both, $\n).
rebar_string:strip(BranchRefString, both, "\n").


maybe_warn_local_url(Url) ->
Expand All @@ -150,11 +150,11 @@ maybe_warn_local_url(Url) ->
end.

parse_hg_url("ssh://" ++ HostPath) ->
[Host | Path] = string:tokens(HostPath, "/"),
[Host | Path] = rebar_string:lexemes(HostPath, "/"),
{Host, filename:rootname(filename:join(Path), ".hg")};
parse_hg_url("http://" ++ HostPath) ->
[Host | Path] = string:tokens(HostPath, "/"),
[Host | Path] = rebar_string:lexemes(HostPath, "/"),
{Host, filename:rootname(filename:join(Path), ".hg")};
parse_hg_url("https://" ++ HostPath) ->
[Host | Path] = string:tokens(HostPath, "/"),
[Host | Path] = rebar_string:lexemes(HostPath, "/"),
{Host, filename:rootname(filename:join(Path), ".hg")}.
2 changes: 1 addition & 1 deletion src/rebar_hooks.erl
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ create_env(State, Opts) ->
].

join_dirs(BaseDir, Dirs) ->
string:join([ filename:join(BaseDir, Dir) || Dir <- Dirs ], ":").
rebar_string:join([filename:join(BaseDir, Dir) || Dir <- Dirs], ":").

re_version(Path) ->
case re:run(Path, "^.*-(?<VER>[^/-]*)$", [{capture,[1],list}, unicode]) of
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,7 @@ registry_dir(State) ->
case rebar_utils:url_append_path(CDN, ?REMOTE_PACKAGE_DIR) of
{ok, Parsed} ->
{ok, {_, _, Host, _, Path, _}} = http_uri:parse(Parsed),
CDNHostPath = lists:reverse(string:tokens(Host, ".")),
CDNHostPath = lists:reverse(rebar_string:lexemes(Host, ".")),
CDNPath = tl(filename:split(Path)),
RegistryDir = filename:join([CacheDir, "hex"] ++ CDNHostPath ++ CDNPath),
ok = filelib:ensure_dir(filename:join(RegistryDir, "placeholder")),
Expand Down
8 changes: 4 additions & 4 deletions src/rebar_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ extract(TmpDir, CachePath) ->
checksums(Pkg={pkg, _Name, _Vsn, Hash}, Files, Contents, Version, Meta, State) ->
Blob = <<Version/binary, Meta/binary, Contents/binary>>,
<<X:256/big-unsigned>> = crypto:hash(sha256, Blob),
BinChecksum = list_to_binary(string:to_upper(lists:flatten(io_lib:format("~64.16.0b", [X])))),
BinChecksum = list_to_binary(rebar_string:uppercase(lists:flatten(io_lib:format("~64.16.0b", [X])))),
RegistryChecksum = rebar_packages:registry_checksum(Pkg, State),
{"CHECKSUM", TarChecksum} = lists:keyfind("CHECKSUM", 1, Files),
{Hash, BinChecksum, RegistryChecksum, TarChecksum}.
Expand All @@ -116,7 +116,7 @@ request(Url, ETag) ->
{ok, {{_Version, 200, _Reason}, Headers, Body}} ->
?DEBUG("Successfully downloaded ~ts", [Url]),
{"etag", ETag1} = lists:keyfind("etag", 1, Headers),
{ok, Body, string:strip(ETag1, both, $")};
{ok, Body, rebar_string:trim(ETag1, both, [$"])};
{ok, {{_Version, 304, _Reason}, _Headers, _Body}} ->
?DEBUG("Cached copy of ~ts still valid", [Url]),
{ok, cached};
Expand All @@ -132,7 +132,7 @@ etag(Path) ->
case file:read_file(Path) of
{ok, Binary} ->
<<X:128/big-unsigned-integer>> = crypto:hash(md5, Binary),
string:to_lower(lists:flatten(io_lib:format("~32.16.0b", [X])));
rebar_string:lowercase(lists:flatten(io_lib:format("~32.16.0b", [X])));
{error, _} ->
false
end.
Expand Down Expand Up @@ -205,7 +205,7 @@ get_ssl_config() ->
end.

parse_vsn(Vsn) ->
version_pad(string:tokens(Vsn, ".-")).
version_pad(rebar_string:lexemes(Vsn, ".-")).

version_pad([Major]) ->
{list_to_integer(Major), 0, 0};
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_app_discovery.erl
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ do(State) ->

-spec format_error(any()) -> iolist().
format_error({multiple_app_files, Files}) ->
io_lib:format("Multiple app files found in one app dir: ~ts", [string:join(Files, " and ")]);
io_lib:format("Multiple app files found in one app dir: ~ts", [rebar_string:join(Files, " and ")]);
format_error({invalid_app_file, File, Reason}) ->
case Reason of
{Line, erl_parse, Description} ->
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_bare_compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ do(State) ->
Paths = proplists:get_value(paths, RawOpts),
Sep = proplists:get_value(separator, RawOpts, " "),
[ code:add_pathsa(filelib:wildcard(PathWildcard))
|| PathWildcard <- string:tokens(Paths, Sep) ],
|| PathWildcard <- rebar_string:lexemes(Paths, Sep) ],

[AppInfo] = rebar_state:project_apps(State),
AppInfo1 = rebar_app_info:out_dir(AppInfo, rebar_dir:get_cwd()),
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_common_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,7 @@ transform_opts([Opt|Rest], Acc) ->
transform_opts(Rest, [Opt|Acc]).

split_string(String) ->
string:tokens(String, [$,]).
rebar_string:lexemes(String, [$,]).

cfgopts(State) ->
case rebar_state:get(State, ct_opts, []) of
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_dialyzer.erl
Original file line number Diff line number Diff line change
Expand Up @@ -565,7 +565,7 @@ collect_nested_dependent_apps(App, Seen) ->
dialyzer_version() ->
_ = application:load(dialyzer),
{ok, Vsn} = application:get_key(dialyzer, vsn),
case string:tokens(Vsn, ".") of
case rebar_string:lexemes(Vsn, ".") of
[Major, Minor] ->
version_tuple(Major, Minor, "0");
[Major, Minor, Patch | _] ->
Expand Down
3 changes: 2 additions & 1 deletion src/rebar_prv_eunit.erl
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,8 @@ resolve(Flag, RawOpts) -> resolve(Flag, Flag, RawOpts).
resolve(Flag, EUnitKey, RawOpts) ->
case proplists:get_value(Flag, RawOpts) of
undefined -> [];
Args -> lists:map(fun(Arg) -> normalize(EUnitKey, Arg) end, string:tokens(Args, [$,]))
Args -> lists:map(fun(Arg) -> normalize(EUnitKey, Arg) end,
rebar_string:lexemes(Args, [$,]))
end.

normalize(Key, Value) when Key == dir; Key == file -> {Key, Value};
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_local_upgrade.erl
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ get_md5(Rebar3Path) ->
{ok, Rebar3File} = file:read_file(Rebar3Path),
Digest = crypto:hash(md5, Rebar3File),
DigestHex = lists:flatten([io_lib:format("~2.16.0B", [X]) || X <- binary_to_list(Digest)]),
string:to_lower(DigestHex).
rebar_string:lowercase(DigestHex).

maybe_fetch_rebar3(Rebar3Md5) ->
TmpDir = ec_file:insecure_mkdtemp(),
Expand Down
Loading

0 comments on commit 94976d5

Please sign in to comment.