Skip to content

Commit 6a56a62

Browse files
committed
Merge pull request #2241 from ferd/otp-23-compat
OTP-23 compatibility and warning removal
1 parent 5f3aec7 commit 6a56a62

File tree

6 files changed

+196
-32
lines changed

6 files changed

+196
-32
lines changed

src/rebar_git_resource.erl

Lines changed: 3 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -100,13 +100,6 @@ compare_url(Dir, Url) ->
100100
?DEBUG("Comparing git url ~p with ~p", [ParsedUrl, ParsedCurrentUrl]),
101101
ParsedCurrentUrl =:= ParsedUrl.
102102

103-
-ifdef (OTP_RELEASE).
104-
-if(?OTP_RELEASE >= 23).
105-
-compile({nowarn_deprecated_function, [{http_uri, parse, 2},
106-
{http_uri, scheme_defaults, 0}]}).
107-
-endif.
108-
-endif.
109-
110103
parse_git_url(Url) ->
111104
%% Checks for standard scp style git remote
112105
case re:run(Url, ?SCP_PATTERN, [{capture, [host, path], list}, unicode]) of
@@ -116,9 +109,9 @@ parse_git_url(Url) ->
116109
parse_git_url(not_scp, Url)
117110
end.
118111
parse_git_url(not_scp, Url) ->
119-
UriOpts = [{scheme_defaults, [{git, 9418} | http_uri:scheme_defaults()]}],
120-
case http_uri:parse(Url, UriOpts) of
121-
{ok, {_Scheme, _User, Host, _Port, Path, _Query}} ->
112+
UriOpts = [{scheme_defaults, [{git, 9418} | rebar_uri:scheme_defaults()]}],
113+
case rebar_uri:parse(Url, UriOpts) of
114+
#{path := Path, host := Host} ->
122115
{ok, {Host, filename:rootname(Path, ".git")}};
123116
{error, Reason} ->
124117
{error, Reason}

src/rebar_hex_repos.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -96,8 +96,8 @@ update_organizations(Repos) ->
9696
{ok, Parent} = get_repo_config(ParentName, Repos),
9797
ParentRepoUrl = rebar_utils:to_list(maps:get(repo_url, Parent)),
9898
{ok, _RepoUrl} =
99-
rebar_utils:url_append_path(ParentRepoUrl,
100-
filename:join("repos", rebar_utils:to_list(RepoName))),
99+
rebar_uri:append_path(ParentRepoUrl,
100+
filename:join("repos", rebar_utils:to_list(RepoName))),
101101
%% still let the organization config override this constructed repo url
102102
maps:merge(Parent#{repo_url => rebar_utils:to_binary(ParentRepoUrl)}, Repo);
103103
(Repo) ->

src/rebar_uri.erl

Lines changed: 130 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,130 @@
1+
%%% @doc multi-OTP version compatibility shim for working with URIs
2+
-module(rebar_uri).
3+
4+
-export([
5+
parse/1, parse/2, scheme_defaults/0,
6+
append_path/2
7+
]).
8+
9+
-ifdef(OTP_RELEASE).
10+
-spec parse(URIString) -> URIMap when
11+
URIString :: uri_string:uri_string(),
12+
URIMap :: uri_string:uri_map() | uri_string:error().
13+
14+
parse(URIString) ->
15+
parse(URIString, []).
16+
17+
parse(URIString, URIOpts) ->
18+
case uri_string:parse(URIString) of
19+
#{path := ""} = Map -> apply_opts(Map#{path => "/"}, URIOpts);
20+
Map -> apply_opts(Map, URIOpts)
21+
end.
22+
-else.
23+
-spec parse(URIString) -> URIMap when
24+
URIString :: iodata(),
25+
URIMap :: map() | {error, atom(), term()}.
26+
27+
parse(URIString) ->
28+
parse(URIString, []).
29+
30+
parse(URIString, URIOpts) ->
31+
case http_uri:parse(URIString, URIOpts) of
32+
{error, Reason} ->
33+
%% no additional parser/term info available to us,
34+
%% e.g. see what uri_string returns in
35+
%% uri_string:parse(<<"h$ttp:::://////lolz">>).
36+
{error, Reason, ""};
37+
{ok, {Scheme, UserInfo, Host, Port, Path, Query}} ->
38+
#{
39+
scheme => rebar_utils:to_list(Scheme),
40+
host => Host,
41+
port => Port,
42+
path => Path,
43+
%% http_uri:parse/1 includes the leading question mark
44+
%% in query string but uri_string:parse/1 leaves it out.
45+
%% string:slice/2 isn't available in OTP <= 19.
46+
query => case Query of
47+
[] -> "";
48+
_ -> string:substr(Query, 2)
49+
end,
50+
userinfo => UserInfo
51+
}
52+
end.
53+
-endif.
54+
55+
%% OTP 21+
56+
-ifdef(OTP_RELEASE).
57+
append_path(Url, ExtraPath) ->
58+
case parse(Url) of
59+
#{path := Path} = Map ->
60+
FullPath = join(Path, ExtraPath),
61+
{ok, uri_string:recompose(maps:update(path, FullPath, Map))};
62+
_ ->
63+
error
64+
end.
65+
-else.
66+
append_path(Url, ExtraPath) ->
67+
case parse(Url) of
68+
#{scheme := Scheme, userinfo := UserInfo, host := Host,
69+
port := Port, path := Path, query := Query} ->
70+
ListScheme = rebar_utils:to_list(Scheme),
71+
PrefixedQuery = case Query of
72+
[] -> [];
73+
Other -> lists:append(["?", Other])
74+
end,
75+
NormPath = case Path of
76+
"" -> "/";
77+
_ -> Path
78+
end,
79+
{ok, maybe_port(
80+
Url, lists:append([ListScheme, "://", UserInfo, Host]),
81+
[$: | rebar_utils:to_list(Port)],
82+
lists:append([join(NormPath, ExtraPath), PrefixedQuery])
83+
)};
84+
_ ->
85+
error
86+
end.
87+
-endif.
88+
89+
%% OTP 21+
90+
-ifdef(OTP_RELEASE).
91+
scheme_defaults() ->
92+
%% no scheme defaults here; just custom ones
93+
[].
94+
-else.
95+
scheme_defaults() ->
96+
http_uri:scheme_defaults().
97+
-endif.
98+
99+
join(URI, "") -> URI;
100+
join(URI, "/") -> URI;
101+
join("/", [$/|_] = Path) -> Path;
102+
join("/", Path) -> [$/ | Path];
103+
join("", [$/|_] = Path) -> Path;
104+
join("", Path) -> [$/ | Path];
105+
join([H|T], Path) -> [H | join(T, Path)].
106+
107+
108+
-ifdef(OTP_RELEASE).
109+
apply_opts(Map = #{port := _}, _) ->
110+
Map;
111+
apply_opts(Map = #{scheme := Scheme}, URIOpts) ->
112+
SchemeDefaults = proplists:get_value(scheme_defaults, URIOpts, []),
113+
%% Here is the funky bit: don't add the port number if it's in a default
114+
%% to maintain proper default behaviour.
115+
try lists:keyfind(list_to_existing_atom(Scheme), 1, SchemeDefaults) of
116+
{_, Port} ->
117+
Map#{port => Port};
118+
false ->
119+
Map
120+
catch
121+
error:badarg -> % not an existing atom, not in the list
122+
Map
123+
end.
124+
-else.
125+
maybe_port(Url, Host, Port, PathQ) ->
126+
case lists:prefix(Host ++ Port, Url) of
127+
true -> Host ++ Port ++ PathQ; % port was explicit
128+
false -> Host ++ PathQ % port was implicit
129+
end.
130+
-endif.

src/rebar_utils.erl

Lines changed: 9 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -266,6 +266,8 @@ to_binary(A) when is_atom(A) -> atom_to_binary(A, unicode);
266266
to_binary(Str) -> unicode:characters_to_binary(Str).
267267

268268
to_list(A) when is_atom(A) -> atom_to_list(A);
269+
to_list(B) when is_binary(B) -> unicode:characters_to_list(B);
270+
to_list(I) when is_integer(I) -> integer_to_list(I);
269271
to_list(Str) -> unicode:characters_to_list(Str).
270272

271273
tup_dedup(List) ->
@@ -910,8 +912,7 @@ get_http_vars(Scheme) ->
910912

911913
-ifdef (OTP_RELEASE).
912914
-if(?OTP_RELEASE >= 23).
913-
-compile({nowarn_deprecated_function, [{http_uri, parse, 1},
914-
{http_uri, decode, 1}]}).
915+
-compile({nowarn_deprecated_function, [{http_uri, decode, 1}]}).
915916
-endif.
916917
-endif.
917918

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

925926
set_httpc_options(Scheme, Proxy) ->
926927
URI = normalise_proxy(Scheme, Proxy),
927-
{ok, {_, UserInfo, Host, Port, _, _}} = http_uri:parse(URI),
928+
Parts = rebar_uri:parse(URI),
929+
Host = maps:get(host, Parts, []),
930+
Port = maps:get(port, Parts, []),
931+
UserInfo = maps:get(userinfo, Parts, []),
928932
httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar),
929933
set_proxy_auth(UserInfo).
930934

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

938942
url_append_path(Url, ExtraPath) ->
939-
case http_uri:parse(Url) of
940-
{ok, {Scheme, UserInfo, Host, Port, Path, Query}} ->
941-
{ok, lists:append([atom_to_list(Scheme), "://", UserInfo, Host, ":", integer_to_list(Port),
942-
filename:join(Path, ExtraPath), Query])};
943-
_ ->
944-
error
945-
end.
943+
rebar_uri:append_path(Url, ExtraPath).
946944

947945
%% escape\ as\ a\ shell\?
948946
escape_chars(Str) when is_atom(Str) ->
@@ -1028,8 +1026,7 @@ ssl_opts(Url) ->
10281026
ssl_opts(ssl_verify_enabled, Url) ->
10291027
case check_ssl_version() of
10301028
true ->
1031-
{ok, {_, _, Hostname, _, _, _}} =
1032-
http_uri:parse(rebar_utils:to_list(Url)),
1029+
#{host := Hostname} = rebar_uri:parse(rebar_utils:to_list(Url)),
10331030
VerifyFun = {fun ssl_verify_hostname:verify_fun/3,
10341031
[{check_hostname, Hostname}]},
10351032
CACerts = certifi:cacerts(),

test/rebar_uri_SUITE.erl

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
-module(rebar_uri_SUITE).
2+
3+
-export([all/0,
4+
parse/1,
5+
append_path/1]).
6+
7+
-include_lib("common_test/include/ct.hrl").
8+
-include_lib("eunit/include/eunit.hrl").
9+
-include_lib("kernel/include/file.hrl").
10+
11+
all() ->
12+
[parse, append_path].
13+
14+
parse(_Config) ->
15+
#{scheme := Scheme, host := Host, path := Path} = rebar_uri:parse("https://repo.hex.pm"),
16+
?assertEqual("https", Scheme),
17+
?assertEqual("repo.hex.pm", Host),
18+
?assertEqual(Path, "/"), % Normalize on OTP-23 behaviour.
19+
20+
#{scheme := Scheme2, host := Host2, port := Port2, path := Path2, query := Query2} =
21+
rebar_uri:parse("https://repo.hex.pm:443?foo=bar"),
22+
?assertEqual("https", Scheme2),
23+
?assertEqual("repo.hex.pm", Host2),
24+
?assertEqual(443, Port2),
25+
?assertEqual(Path2, "/"), % Normalize on old http_uri behaviour
26+
?assertEqual("foo=bar", Query2),
27+
28+
#{scheme := Scheme3, host := Host3, path := Path3, query := Query3} =
29+
rebar_uri:parse("https://repo.hex.pm/over/here?foo=bar"),
30+
?assertEqual("https", Scheme3),
31+
?assertEqual("repo.hex.pm", Host3),
32+
?assertEqual("/over/here", Path3),
33+
?assertEqual("foo=bar", Query3),
34+
35+
%% override default port and get it parsed as such
36+
?assertMatch(#{port := 1337},
37+
rebar_uri:parse("https://repo.hex.pm/",
38+
[{scheme_defaults, [{https,1337}]}])),
39+
ok.
40+
41+
append_path(_Config) ->
42+
%% Default port for the proto is omitted if not mentioned originally
43+
{ok, Val1} = rebar_uri:append_path("https://repo.hex.pm/", "/repos/org"),
44+
?assertEqual("https://repo.hex.pm/repos/org", Val1),
45+
%% QS elements come after the path
46+
{ok, Val2} = rebar_uri:append_path("https://repo.hex.pm?foo=bar", "/repos/org"),
47+
?assertEqual("https://repo.hex.pm/repos/org?foo=bar", Val2),
48+
%% If the port is explicitly mentioned, keep it.
49+
?assertEqual({ok, "https://repo.hex.pm:443/repos/org?foo=bar"},
50+
rebar_uri:append_path("https://repo.hex.pm:443?foo=bar", "/repos/org")).

test/rebar_utils_SUITE.erl

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,7 @@
3333
sh_does_not_miss_messages/1,
3434
tup_merge/1,
3535
proxy_auth/1,
36-
is_list_of_strings/1,
37-
url_append_path/1]).
36+
is_list_of_strings/1]).
3837

3938
-include_lib("common_test/include/ct.hrl").
4039
-include_lib("eunit/include/eunit.hrl").
@@ -50,7 +49,7 @@ all() ->
5049
[{group, args_to_tasks},
5150
sh_does_not_miss_messages,
5251
tup_merge,
53-
proxy_auth, is_list_of_strings, url_append_path].
52+
proxy_auth, is_list_of_strings].
5453

5554
groups() ->
5655
[{args_to_tasks, [], [empty_arglist,
@@ -320,8 +319,3 @@ is_list_of_strings(_Config) ->
320319
?assert(rebar_utils:is_list_of_strings([])),
321320
?assert(rebar_utils:is_list_of_strings("")),
322321
?assert(rebar_utils:is_list_of_strings("foo") == false).
323-
324-
url_append_path(_Config) ->
325-
?assertEqual({ok, "https://repo.hex.pm:443/repos/org"}, rebar_utils:url_append_path("https://repo.hex.pm", "/repos/org")),
326-
?assertEqual({ok, "https://repo.hex.pm:443/repos/org?foo=bar"}, rebar_utils:url_append_path("https://repo.hex.pm",
327-
"/repos/org?foo=bar")).

0 commit comments

Comments
 (0)