-
Notifications
You must be signed in to change notification settings - Fork 519
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge pull request #2241 from ferd/otp-23-compat
OTP-23 compatibility and warning removal
- Loading branch information
1 parent
5f3aec7
commit 6a56a62
Showing
6 changed files
with
196 additions
and
32 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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. |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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")). |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters