Skip to content

Commit f24df6a

Browse files
committed
Vendor all dependencies, make bootstrap use them
And fix Dialyzer oddities
1 parent 7a97040 commit f24df6a

File tree

142 files changed

+25953
-115
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

142 files changed

+25953
-115
lines changed

apps/rebar/src/rebar_prv_dialyzer.erl

+2
Original file line numberDiff line numberDiff line change
@@ -246,6 +246,8 @@ get_files(State, Apps, SkipApps, Mods, SkipMods, ExtraDirs) ->
246246
Files1 = extras_files(BaseDir, ExtraDirs, Files0),
247247
ExcludeMods = get_config(State, exclude_mods, []),
248248
Files2 = mods_files(Mods, ExcludeMods ++ SkipMods, Files1),
249+
?DEBUG("{dialyzer, [{exclude_apps, ~p}, {exclude_mods, ~p}]}.",
250+
[ExcludeApps, ExcludeMods]),
249251
dict:fold(fun(_, File, Acc) -> [File | Acc] end, [], Files2).
250252

251253
apps_files([], _, _ExtraDirs, Files) ->

apps/rebar/src/rebar_prv_vendor.erl

+10-6
Original file line numberDiff line numberDiff line change
@@ -137,9 +137,13 @@ check_project_layout(State) ->
137137

138138
vendor_plugins(State, PluginVDir) ->
139139
PluginDir = rebar_dir:plugins_dir(State),
140-
{ok, Files} = file:list_dir_all(PluginDir),
141-
[rebar_file_utils:mv(Path, filename:join(PluginVDir, PathPart))
142-
|| PathPart <- Files,
143-
Path <- [filename:join(PluginDir, PathPart)],
144-
filelib:is_dir(Path)],
145-
ok.
140+
case file:list_dir_all(PluginDir) of
141+
{ok, Files} ->
142+
[rebar_file_utils:mv(Path, filename:join(PluginVDir, PathPart))
143+
|| PathPart <- Files,
144+
Path <- [filename:join(PluginDir, PathPart)],
145+
filelib:is_dir(Path)],
146+
ok;
147+
{error, enoent} ->
148+
ok
149+
end.

bootstrap

+13-69
Original file line numberDiff line numberDiff line change
@@ -89,12 +89,12 @@ ensure_app(App) ->
8989
end.
9090

9191
fetch_and_compile({Name, ErlFirstFiles}, Deps) ->
92-
case lists:keyfind(Name, 1, Deps) of
93-
{Name, Vsn} ->
94-
ok = fetch({pkg, atom_to_binary(Name, utf8), list_to_binary(Vsn)}, Name);
95-
{Name, _, Source} ->
96-
ok = fetch(Source, Name)
97-
end,
92+
%% Use vendored dependencies, don't hit the network; to update
93+
%% dependencies first bootstrap, then use the escript to do
94+
%% fancier dep management.
95+
filelib:ensure_dir("_build/default/lib/.touch"),
96+
[cp_r([DepDir], "_build/default/lib/")
97+
|| {Dep, DepDir} <- Deps, atom_to_list(Name) =:= Dep],
9898

9999
%% Hack: erlware_commons depends on a .script file to check if it is being built with
100100
%% rebar2 or rebar3. But since rebar3 isn't built yet it can't get the vsn with get_key.
@@ -103,51 +103,6 @@ fetch_and_compile({Name, ErlFirstFiles}, Deps) ->
103103

104104
compile(Name, ErlFirstFiles).
105105

106-
fetch({pkg, Name, Vsn}, App) ->
107-
Dir = filename:join([filename:absname("_build/default/lib/"), App]),
108-
case filelib:is_dir(Dir) of
109-
false ->
110-
CDN = "https://repo.hex.pm/tarballs",
111-
Package = binary_to_list(<<Name/binary, "-", Vsn/binary, ".tar">>),
112-
Url = join([CDN, Package], "/"),
113-
case request(Url) of
114-
{ok, Binary} ->
115-
{ok, Contents} = extract(Binary),
116-
ok = erl_tar:extract({binary, Contents}, [{cwd, Dir}, compressed]);
117-
{error, {Reason, _}} ->
118-
ReasonText = re:replace(atom_to_list(Reason), "_", " ", [global,{return,list}]),
119-
io:format("Error: Unable to fetch package ~s ~s: ~s~n", [Name, Vsn, ReasonText])
120-
end;
121-
true ->
122-
io:format("Dependency ~s already exists~n", [Name])
123-
end.
124-
125-
extract(Binary) ->
126-
{ok, Files} = erl_tar:extract({binary, Binary}, [memory]),
127-
{"contents.tar.gz", Contents} = lists:keyfind("contents.tar.gz", 1, Files),
128-
{ok, Contents}.
129-
130-
request(Url) ->
131-
case os:getenv("REBAR_OFFLINE") of
132-
"1" ->
133-
{error, {offline, Url}};
134-
_ ->
135-
request_online(Url)
136-
end.
137-
138-
request_online(Url) ->
139-
HttpOptions = [{relaxed, true} | get_proxy_auth()],
140-
141-
case httpc:request(get, {Url, []},
142-
HttpOptions,
143-
[{body_format, binary}],
144-
rebar) of
145-
{ok, {{_Version, 200, _Reason}, _Headers, Body}} ->
146-
{ok, Body};
147-
Error ->
148-
Error
149-
end.
150-
151106
get_rebar_config() ->
152107
{ok, [[Home]]} = init:get_argument(home),
153108
ConfDir = filename:join(Home, ".config/rebar3"),
@@ -637,19 +592,8 @@ reset_env() ->
637592
application:load(rebar).
638593

639594
get_deps() ->
640-
case file:consult("rebar.lock") of
641-
{ok, [[]]} ->
642-
%% Something went wrong in a previous build, lock file shouldn't be empty
643-
io:format("Empty list in lock file, deleting rebar.lock~n"),
644-
ok = file:delete("rebar.lock"),
645-
{ok, Config} = file:consult("apps/rebar/rebar.config"),
646-
proplists:get_value(deps, Config);
647-
{ok, [Deps]} ->
648-
[{binary_to_atom(Name, utf8), "", Source} || {Name, Source, _Level} <- Deps];
649-
_ ->
650-
{ok, Config} = file:consult("apps/rebar/rebar.config"),
651-
proplists:get_value(deps, Config)
652-
end.
595+
{ok, Deps} = file:list_dir("vendor"),
596+
[{Dep, filename:join("vendor", Dep)} || Dep <- Deps].
653597

654598
format_errors(Source, Errors) ->
655599
format_errors(Source, "", Errors).
@@ -741,11 +685,11 @@ set_proxy_auth(UserInfo) ->
741685
%% password may contain url encoded characters, need to decode them first
742686
put(proxy_auth, [{proxy_auth, {Username, rebar_uri_percent_decode(Password)}}]).
743687

744-
get_proxy_auth() ->
745-
case get(proxy_auth) of
746-
undefined -> [];
747-
ProxyAuth -> ProxyAuth
748-
end.
688+
%get_proxy_auth() ->
689+
% case get(proxy_auth) of
690+
% undefined -> [];
691+
% ProxyAuth -> ProxyAuth
692+
% end.
749693

750694

751695
%% string:join/2 copy; string:join/2 is getting obsoleted

rebar.config

+53-5
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,13 @@
11
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
22
%% ex: ts=4 sw=4 ft=erlang et
33

4-
%% The rest of the config is in apps/rebar/
4+
%% Vendoring deps
5+
{project_app_dirs, ["apps/*","lib/*",".","vendor/*"]}.
6+
{project_plugin_dirs, ["plugins/*","vendor_plugins/*"]}.
7+
8+
%% Duplicated from apps/rebar3:
9+
%% - we want people who rely on rebar3 as a dependency to still be able
10+
%% to fetch it with git_subdir and have it work
511
{escript_main_app, rebar}.
612
{escript_name, rebar3}.
713
{escript_wrappers_windows, ["cmd", "powershell"]}.
@@ -12,8 +18,50 @@
1218
{escript_incl_priv, [{relx, "templates/*"},
1319
{rebar, "templates/*"}]}.
1420

15-
{ profiles, [{systest, [
16-
{erl_opts, [debug_info, nowarn_export_all]},
17-
{ct_opts, [{dir, "systest"}]}
18-
]}
21+
{profiles, [
22+
%% Only works at the top-level
23+
{systest, [
24+
{erl_opts, [debug_info, nowarn_export_all]},
25+
{ct_opts, [{dir, "systest"}]}
26+
]},
27+
%% Don't check these vendored deps
28+
{dialyzer, [
29+
{erl_opts, [debug_info, nowarn_export_all]},
30+
%% Ignore deps known to generate warnings
31+
{dialyzer, [{exclude_apps, [cth_readable, erlware_commons, relx]}]}
32+
]},
33+
%% Duplicated from apps/rebar3:
34+
%% - we don't want the test profile applied to our vendored deps.
35+
%% - we want people who rely on rebar3 as a dependency to still be able
36+
%% to fetch it with git_subdir and have it work
37+
{test, [
38+
{deps, [{meck, "0.8.13"}]},
39+
{erl_opts, [debug_info, nowarn_export_all]}
40+
]},
41+
{prod, [
42+
{erl_opts, [no_debug_info]},
43+
{overrides, [
44+
{override, erlware_commons, [
45+
{erl_opts, [{platform_define, "^[0-9]+", namespaced_types},
46+
{platform_define, "^R1[4|5]", deprecated_crypto},
47+
{platform_define, "^((1[8|9])|2)", rand_module},
48+
{platform_define, "^2", unicode_str},
49+
{platform_define, "^(R|1|20)", fun_stacktrace},
50+
no_debug_info,
51+
warnings_as_errors]},
52+
{deps, []}, {plugins, []}]},
53+
{add, ssl_verify_hostname, [{erl_opts, [no_debug_info]}]},
54+
{add, certifi, [{erl_opts, [no_debug_info]}]},
55+
{add, cf, [{erl_opts, [no_debug_info]}]},
56+
{add, cth_readable, [{erl_opts, [no_debug_info]}]},
57+
{add, eunit_formatters, [{erl_opts, [no_debug_info]}]},
58+
{override, bbmustache, [
59+
{erl_opts, [no_debug_info, {platform_define, "^[0-9]+", namespaced_types}]},
60+
{deps, []}, {plugins, []}]},
61+
{add, getopt, [{erl_opts, [no_debug_info]}]},
62+
{add, providers, [{erl_opts, [no_debug_info]}]},
63+
{add, relx, [{erl_opts, [no_debug_info]}]}]}
64+
]}
1965
]}.
66+
67+
%% The rest of the config is in apps/rebar/

rebar.lock

+1-35
Original file line numberDiff line numberDiff line change
@@ -1,35 +1 @@
1-
{"1.2.0",
2-
[{<<"bbmustache">>,{pkg,<<"bbmustache">>,<<"1.12.2">>},0},
3-
{<<"certifi">>,{pkg,<<"certifi">>,<<"2.9.0">>},0},
4-
{<<"cf">>,{pkg,<<"cf">>,<<"0.3.1">>},0},
5-
{<<"cth_readable">>,{pkg,<<"cth_readable">>,<<"1.5.1">>},0},
6-
{<<"erlware_commons">>,{pkg,<<"erlware_commons">>,<<"1.5.0">>},0},
7-
{<<"eunit_formatters">>,{pkg,<<"eunit_formatters">>,<<"0.5.0">>},0},
8-
{<<"getopt">>,{pkg,<<"getopt">>,<<"1.0.1">>},0},
9-
{<<"providers">>,{pkg,<<"providers">>,<<"1.9.0">>},0},
10-
{<<"relx">>,{pkg,<<"relx">>,<<"4.7.0">>},0},
11-
{<<"ssl_verify_fun">>,{pkg,<<"ssl_verify_fun">>,<<"1.1.6">>},0}]}.
12-
[
13-
{pkg_hash,[
14-
{<<"bbmustache">>, <<"0CABDCE0DB9FE6D3318131174B9F2B351328A4C0AFBEB3E6E99BB0E02E9B621D">>},
15-
{<<"certifi">>, <<"6F2A475689DD47F19FB74334859D460A2DC4E3252A3324BD2111B8F0429E7E21">>},
16-
{<<"cf">>, <<"5CB902239476E141EA70A740340233782D363A31EEA8AD37049561542E6CD641">>},
17-
{<<"cth_readable">>, <<"F511EFCFDE04A48B014A9197FFF1B4C4860E4E35CDB8E2F3AE3C4178E20299B1">>},
18-
{<<"erlware_commons">>, <<"918C56D8FB3BE52AF0DF138ED6E0755E764AD4467CD7D025761F7D0A17D3DEC1">>},
19-
{<<"eunit_formatters">>, <<"6A9133943D36A465D804C1C5B6E6839030434B8879C5600D7DDB5B3BAD4CCB59">>},
20-
{<<"getopt">>, <<"C73A9FA687B217F2FF79F68A3B637711BB1936E712B521D8CE466B29CBF7808A">>},
21-
{<<"providers">>, <<"46F6645B0C677B1029E02B013BFD69092A2232854DAF359F2378FA42AC0BEC0D">>},
22-
{<<"relx">>, <<"CF8F3ECA5FAF0D25746AFAA4042DA4B5061E2CFFC9C190632C6E4F2C20A47573">>},
23-
{<<"ssl_verify_fun">>, <<"CF344F5692C82D2CD7554F5EC8FD961548D4FD09E7D22F5B62482E5AEAEBD4B0">>}]},
24-
{pkg_hash_ext,[
25-
{<<"bbmustache">>, <<"688B33A4D5CC2D51F575ADF0B3683FC40A38314A2F150906EDCFC77F5B577B3B">>},
26-
{<<"certifi">>, <<"266DA46BDB06D6C6D35FDE799BCB28D36D985D424AD7C08B5BB48F5B5CDD4641">>},
27-
{<<"cf">>, <<"315E8D447D3A4B02BCDBFA397AD03BBB988A6E0AA6F44D3ADD0F4E3C3BF97672">>},
28-
{<<"cth_readable">>, <<"686541A22EFE6CA5A41A047B39516C2DD28FB3CADE5F24A2F19145B3967F9D80">>},
29-
{<<"erlware_commons">>, <<"3E7C6FB2BA4C29B0DD5DFE9D031B66449E2088ECEC1A81465BD9FDE05ED7D0DB">>},
30-
{<<"eunit_formatters">>, <<"D6C8BA213424944E6E05BBC097C32001CDD0ABE3925D02454F229B20D68763C9">>},
31-
{<<"getopt">>, <<"53E1AB83B9CEB65C9672D3E7A35B8092E9BDC9B3EE80721471A161C10C59959C">>},
32-
{<<"providers">>, <<"D287E874406A1505608642B0A3DB5B68D6ADA3F2AB001AEC87E7F4D7C79FC017">>},
33-
{<<"relx">>, <<"A2ABFAFA70BCE3A0B98A6E5140AC98429B9980F835FFB47357F0645422FC2FA3">>},
34-
{<<"ssl_verify_fun">>, <<"BDB0D2471F453C88FF3908E7686F86F9BE327D065CC1EC16FA4540197EA04680">>}]}
35-
].
1+
[].

vendor/bbmustache/LICENSE

+22
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
The MIT License (MIT)
2+
3+
Copyright (c) 2015 Hinagiku Soranoba
4+
5+
Permission is hereby granted, free of charge, to any person obtaining a copy
6+
of this software and associated documentation files (the "Software"), to deal
7+
in the Software without restriction, including without limitation the rights
8+
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
9+
copies of the Software, and to permit persons to whom the Software is
10+
furnished to do so, subject to the following conditions:
11+
12+
The above copyright notice and this permission notice shall be included in all
13+
copies or substantial portions of the Software.
14+
15+
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
16+
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
17+
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
18+
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
19+
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
20+
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
21+
SOFTWARE.
22+

0 commit comments

Comments
 (0)