Skip to content

Commit

Permalink
Merge pull request #2241 from ferd/otp-23-compat
Browse files Browse the repository at this point in the history
OTP-23 compatibility and warning removal
  • Loading branch information
tsloughter committed Feb 28, 2020
1 parent 5f3aec7 commit 6a56a62
Show file tree
Hide file tree
Showing 6 changed files with 196 additions and 32 deletions.
13 changes: 3 additions & 10 deletions src/rebar_git_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -100,13 +100,6 @@ compare_url(Dir, Url) ->
?DEBUG("Comparing git url ~p with ~p", [ParsedUrl, ParsedCurrentUrl]),
ParsedCurrentUrl =:= ParsedUrl.

-ifdef (OTP_RELEASE).
-if(?OTP_RELEASE >= 23).
-compile({nowarn_deprecated_function, [{http_uri, parse, 2},
{http_uri, scheme_defaults, 0}]}).
-endif.
-endif.

parse_git_url(Url) ->
%% Checks for standard scp style git remote
case re:run(Url, ?SCP_PATTERN, [{capture, [host, path], list}, unicode]) of
Expand All @@ -116,9 +109,9 @@ parse_git_url(Url) ->
parse_git_url(not_scp, Url)
end.
parse_git_url(not_scp, Url) ->
UriOpts = [{scheme_defaults, [{git, 9418} | http_uri:scheme_defaults()]}],
case http_uri:parse(Url, UriOpts) of
{ok, {_Scheme, _User, Host, _Port, Path, _Query}} ->
UriOpts = [{scheme_defaults, [{git, 9418} | rebar_uri:scheme_defaults()]}],
case rebar_uri:parse(Url, UriOpts) of
#{path := Path, host := Host} ->
{ok, {Host, filename:rootname(Path, ".git")}};
{error, Reason} ->
{error, Reason}
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_hex_repos.erl
Original file line number Diff line number Diff line change
Expand Up @@ -96,8 +96,8 @@ update_organizations(Repos) ->
{ok, Parent} = get_repo_config(ParentName, Repos),
ParentRepoUrl = rebar_utils:to_list(maps:get(repo_url, Parent)),
{ok, _RepoUrl} =
rebar_utils:url_append_path(ParentRepoUrl,
filename:join("repos", rebar_utils:to_list(RepoName))),
rebar_uri:append_path(ParentRepoUrl,
filename:join("repos", rebar_utils:to_list(RepoName))),
%% still let the organization config override this constructed repo url
maps:merge(Parent#{repo_url => rebar_utils:to_binary(ParentRepoUrl)}, Repo);
(Repo) ->
Expand Down
130 changes: 130 additions & 0 deletions src/rebar_uri.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,130 @@
%%% @doc multi-OTP version compatibility shim for working with URIs
-module(rebar_uri).

-export([
parse/1, parse/2, scheme_defaults/0,
append_path/2
]).

-ifdef(OTP_RELEASE).
-spec parse(URIString) -> URIMap when
URIString :: uri_string:uri_string(),
URIMap :: uri_string:uri_map() | uri_string:error().

parse(URIString) ->
parse(URIString, []).

parse(URIString, URIOpts) ->
case uri_string:parse(URIString) of
#{path := ""} = Map -> apply_opts(Map#{path => "/"}, URIOpts);
Map -> apply_opts(Map, URIOpts)
end.
-else.
-spec parse(URIString) -> URIMap when
URIString :: iodata(),
URIMap :: map() | {error, atom(), term()}.

parse(URIString) ->
parse(URIString, []).

parse(URIString, URIOpts) ->
case http_uri:parse(URIString, URIOpts) of
{error, Reason} ->
%% no additional parser/term info available to us,
%% e.g. see what uri_string returns in
%% uri_string:parse(<<"h$ttp:::://////lolz">>).
{error, Reason, ""};
{ok, {Scheme, UserInfo, Host, Port, Path, Query}} ->
#{
scheme => rebar_utils:to_list(Scheme),
host => Host,
port => Port,
path => Path,
%% http_uri:parse/1 includes the leading question mark
%% in query string but uri_string:parse/1 leaves it out.
%% string:slice/2 isn't available in OTP <= 19.
query => case Query of
[] -> "";
_ -> string:substr(Query, 2)
end,
userinfo => UserInfo
}
end.
-endif.

%% OTP 21+
-ifdef(OTP_RELEASE).
append_path(Url, ExtraPath) ->
case parse(Url) of
#{path := Path} = Map ->
FullPath = join(Path, ExtraPath),
{ok, uri_string:recompose(maps:update(path, FullPath, Map))};
_ ->
error
end.
-else.
append_path(Url, ExtraPath) ->
case parse(Url) of
#{scheme := Scheme, userinfo := UserInfo, host := Host,
port := Port, path := Path, query := Query} ->
ListScheme = rebar_utils:to_list(Scheme),
PrefixedQuery = case Query of
[] -> [];
Other -> lists:append(["?", Other])
end,
NormPath = case Path of
"" -> "/";
_ -> Path
end,
{ok, maybe_port(
Url, lists:append([ListScheme, "://", UserInfo, Host]),
[$: | rebar_utils:to_list(Port)],
lists:append([join(NormPath, ExtraPath), PrefixedQuery])
)};
_ ->
error
end.
-endif.

%% OTP 21+
-ifdef(OTP_RELEASE).
scheme_defaults() ->
%% no scheme defaults here; just custom ones
[].
-else.
scheme_defaults() ->
http_uri:scheme_defaults().
-endif.

join(URI, "") -> URI;
join(URI, "/") -> URI;
join("/", [$/|_] = Path) -> Path;
join("/", Path) -> [$/ | Path];
join("", [$/|_] = Path) -> Path;
join("", Path) -> [$/ | Path];
join([H|T], Path) -> [H | join(T, Path)].


-ifdef(OTP_RELEASE).
apply_opts(Map = #{port := _}, _) ->
Map;
apply_opts(Map = #{scheme := Scheme}, URIOpts) ->
SchemeDefaults = proplists:get_value(scheme_defaults, URIOpts, []),
%% Here is the funky bit: don't add the port number if it's in a default
%% to maintain proper default behaviour.
try lists:keyfind(list_to_existing_atom(Scheme), 1, SchemeDefaults) of
{_, Port} ->
Map#{port => Port};
false ->
Map
catch
error:badarg -> % not an existing atom, not in the list
Map
end.
-else.
maybe_port(Url, Host, Port, PathQ) ->
case lists:prefix(Host ++ Port, Url) of
true -> Host ++ Port ++ PathQ; % port was explicit
false -> Host ++ PathQ % port was implicit
end.
-endif.
21 changes: 9 additions & 12 deletions src/rebar_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -266,6 +266,8 @@ to_binary(A) when is_atom(A) -> atom_to_binary(A, unicode);
to_binary(Str) -> unicode:characters_to_binary(Str).

to_list(A) when is_atom(A) -> atom_to_list(A);
to_list(B) when is_binary(B) -> unicode:characters_to_list(B);
to_list(I) when is_integer(I) -> integer_to_list(I);
to_list(Str) -> unicode:characters_to_list(Str).

tup_dedup(List) ->
Expand Down Expand Up @@ -910,8 +912,7 @@ get_http_vars(Scheme) ->

-ifdef (OTP_RELEASE).
-if(?OTP_RELEASE >= 23).
-compile({nowarn_deprecated_function, [{http_uri, parse, 1},
{http_uri, decode, 1}]}).
-compile({nowarn_deprecated_function, [{http_uri, decode, 1}]}).
-endif.
-endif.

Expand All @@ -924,7 +925,10 @@ set_httpc_options(_, []) ->

set_httpc_options(Scheme, Proxy) ->
URI = normalise_proxy(Scheme, Proxy),
{ok, {_, UserInfo, Host, Port, _, _}} = http_uri:parse(URI),
Parts = rebar_uri:parse(URI),
Host = maps:get(host, Parts, []),
Port = maps:get(port, Parts, []),
UserInfo = maps:get(userinfo, Parts, []),
httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar),
set_proxy_auth(UserInfo).

Expand All @@ -936,13 +940,7 @@ normalise_proxy(Scheme, URI) ->
end.

url_append_path(Url, ExtraPath) ->
case http_uri:parse(Url) of
{ok, {Scheme, UserInfo, Host, Port, Path, Query}} ->
{ok, lists:append([atom_to_list(Scheme), "://", UserInfo, Host, ":", integer_to_list(Port),
filename:join(Path, ExtraPath), Query])};
_ ->
error
end.
rebar_uri:append_path(Url, ExtraPath).

%% escape\ as\ a\ shell\?
escape_chars(Str) when is_atom(Str) ->
Expand Down Expand Up @@ -1028,8 +1026,7 @@ ssl_opts(Url) ->
ssl_opts(ssl_verify_enabled, Url) ->
case check_ssl_version() of
true ->
{ok, {_, _, Hostname, _, _, _}} =
http_uri:parse(rebar_utils:to_list(Url)),
#{host := Hostname} = rebar_uri:parse(rebar_utils:to_list(Url)),
VerifyFun = {fun ssl_verify_hostname:verify_fun/3,
[{check_hostname, Hostname}]},
CACerts = certifi:cacerts(),
Expand Down
50 changes: 50 additions & 0 deletions test/rebar_uri_SUITE.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
-module(rebar_uri_SUITE).

-export([all/0,
parse/1,
append_path/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
-include_lib("kernel/include/file.hrl").

all() ->
[parse, append_path].

parse(_Config) ->
#{scheme := Scheme, host := Host, path := Path} = rebar_uri:parse("https://repo.hex.pm"),
?assertEqual("https", Scheme),
?assertEqual("repo.hex.pm", Host),
?assertEqual(Path, "/"), % Normalize on OTP-23 behaviour.

#{scheme := Scheme2, host := Host2, port := Port2, path := Path2, query := Query2} =
rebar_uri:parse("https://repo.hex.pm:443?foo=bar"),
?assertEqual("https", Scheme2),
?assertEqual("repo.hex.pm", Host2),
?assertEqual(443, Port2),
?assertEqual(Path2, "/"), % Normalize on old http_uri behaviour
?assertEqual("foo=bar", Query2),

#{scheme := Scheme3, host := Host3, path := Path3, query := Query3} =
rebar_uri:parse("https://repo.hex.pm/over/here?foo=bar"),
?assertEqual("https", Scheme3),
?assertEqual("repo.hex.pm", Host3),
?assertEqual("/over/here", Path3),
?assertEqual("foo=bar", Query3),

%% override default port and get it parsed as such
?assertMatch(#{port := 1337},
rebar_uri:parse("https://repo.hex.pm/",
[{scheme_defaults, [{https,1337}]}])),
ok.

append_path(_Config) ->
%% Default port for the proto is omitted if not mentioned originally
{ok, Val1} = rebar_uri:append_path("https://repo.hex.pm/", "/repos/org"),
?assertEqual("https://repo.hex.pm/repos/org", Val1),
%% QS elements come after the path
{ok, Val2} = rebar_uri:append_path("https://repo.hex.pm?foo=bar", "/repos/org"),
?assertEqual("https://repo.hex.pm/repos/org?foo=bar", Val2),
%% If the port is explicitly mentioned, keep it.
?assertEqual({ok, "https://repo.hex.pm:443/repos/org?foo=bar"},
rebar_uri:append_path("https://repo.hex.pm:443?foo=bar", "/repos/org")).
10 changes: 2 additions & 8 deletions test/rebar_utils_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,7 @@
sh_does_not_miss_messages/1,
tup_merge/1,
proxy_auth/1,
is_list_of_strings/1,
url_append_path/1]).
is_list_of_strings/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
Expand All @@ -50,7 +49,7 @@ all() ->
[{group, args_to_tasks},
sh_does_not_miss_messages,
tup_merge,
proxy_auth, is_list_of_strings, url_append_path].
proxy_auth, is_list_of_strings].

groups() ->
[{args_to_tasks, [], [empty_arglist,
Expand Down Expand Up @@ -320,8 +319,3 @@ is_list_of_strings(_Config) ->
?assert(rebar_utils:is_list_of_strings([])),
?assert(rebar_utils:is_list_of_strings("")),
?assert(rebar_utils:is_list_of_strings("foo") == false).

url_append_path(_Config) ->
?assertEqual({ok, "https://repo.hex.pm:443/repos/org"}, rebar_utils:url_append_path("https://repo.hex.pm", "/repos/org")),
?assertEqual({ok, "https://repo.hex.pm:443/repos/org?foo=bar"}, rebar_utils:url_append_path("https://repo.hex.pm",
"/repos/org?foo=bar")).

0 comments on commit 6a56a62

Please sign in to comment.