Skip to content

Commit

Permalink
Update hex_core and add mirror_of repo config
Browse files Browse the repository at this point in the history
  • Loading branch information
ericmj committed Dec 30, 2018
1 parent 968458b commit 6a5ad07
Show file tree
Hide file tree
Showing 7 changed files with 72 additions and 39 deletions.
20 changes: 15 additions & 5 deletions bootstrap
Expand Up @@ -135,13 +135,23 @@ compile(App, FirstFiles) ->
filelib:ensure_dir(filename:join([Dir, "ebin", "dummy.beam"])),
code:add_path(filename:join(Dir, "ebin")),
FirstFilesPaths = [filename:join([Dir, "src", Module]) || Module <- FirstFiles],
LeexFiles = filelib:wildcard(filename:join([Dir, "src", "*.xrl"])),
[compile_xrl_file(X) || X <- LeexFiles],
YeccFiles = filelib:wildcard(filename:join([Dir, "src", "*.yrl"])),
[compile_yrl_file(X) || X <- YeccFiles],
Sources = FirstFilesPaths ++ filelib:wildcard(filename:join([Dir, "src", "*.erl"])),
[compile_file(X, [{i, filename:join(Dir, "include")}
[compile_erl_file(X, [{i, filename:join(Dir, "include")}
,debug_info
,{outdir, filename:join(Dir, "ebin")}
,return | additional_defines()]) || X <- Sources].

compile_file(File, Opts) ->
compile_xrl_file(File) ->
{ok, _} = leex:file(File).

compile_yrl_file(File) ->
{ok, _} = yecc:file(File).

compile_erl_file(File, Opts) ->
case compile:file(File, Opts) of
{ok, _Mod} ->
ok;
Expand All @@ -162,7 +172,7 @@ bootstrap_rebar3() ->
filename:absname("_build/default/lib/rebar/src")),
true = Res == ok orelse Res == exists,
Sources = ["src/rebar_resource_v2.erl", "src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
[compile_file(X, [{outdir, "_build/default/lib/rebar/ebin/"}
[compile_erl_file(X, [{outdir, "_build/default/lib/rebar/ebin/"}
,return | additional_defines()]) || X <- Sources],
code:add_patha(filename:absname("_build/default/lib/rebar/ebin")).

Expand Down Expand Up @@ -471,7 +481,7 @@ make_normalized_path(Path) ->
AbsPath = make_absolute_path(Path),
Components = filename:split(AbsPath),
make_normalized_path(Components, []).

make_absolute_path(Path) ->
case filename:pathtype(Path) of
absolute ->
Expand Down Expand Up @@ -636,7 +646,7 @@ join([], Sep) when is_list(Sep) ->
join([H|T], Sep) ->
H ++ lists:append([Sep ++ X || X <- T]).

%% Same for chr; no non-deprecated equivalent in OTP20+
%% Same for chr; no non-deprecated equivalent in OTP20+
chr(S, C) when is_integer(C) -> chr(S, C, 1).
chr([C|_Cs], C, I) -> I;
chr([_|Cs], C, I) -> chr(Cs, C, I+1);
Expand Down
2 changes: 1 addition & 1 deletion rebar.config
Expand Up @@ -11,7 +11,7 @@
{relx, "3.27.0"},
{cf, "0.2.2"},
{cth_readable, "1.4.2"},
{hex_core, "0.2.0"},
{hex_core, "0.4.0"},
{eunit_formatters, "0.5.0"}]}.

{post_hooks, [{"(linux|darwin|solaris|freebsd|netbsd|openbsd)",
Expand Down
4 changes: 2 additions & 2 deletions rebar.lock
Expand Up @@ -6,7 +6,7 @@
{<<"erlware_commons">>,{pkg,<<"erlware_commons">>,<<"1.3.1">>},0},
{<<"eunit_formatters">>,{pkg,<<"eunit_formatters">>,<<"0.5.0">>},0},
{<<"getopt">>,{pkg,<<"getopt">>,<<"1.0.1">>},0},
{<<"hex_core">>,{pkg,<<"hex_core">>,<<"0.2.0">>},0},
{<<"hex_core">>,{pkg,<<"hex_core">>,<<"0.4.0">>},0},
{<<"parse_trans">>,{pkg,<<"parse_trans">>,<<"3.3.0">>},0},
{<<"providers">>,{pkg,<<"providers">>,<<"1.7.0">>},0},
{<<"relx">>,{pkg,<<"relx">>,<<"3.27.0">>},0},
Expand All @@ -20,7 +20,7 @@
{<<"erlware_commons">>, <<"0CE192AD69BC6FD0880246D852D0ECE17631E234878011D1586E053641ED4C04">>},
{<<"eunit_formatters">>, <<"6A9133943D36A465D804C1C5B6E6839030434B8879C5600D7DDB5B3BAD4CCB59">>},
{<<"getopt">>, <<"C73A9FA687B217F2FF79F68A3B637711BB1936E712B521D8CE466B29CBF7808A">>},
{<<"hex_core">>, <<"3A7EACCFB8ADD3FF05D950C10ED5BDB5D0C48C988EBBC5D7AE2A55498F0EFF1B">>},
{<<"hex_core">>, <<"6A0E0B1B519850344292298DA1BFA685E71534FDF4C69434993039F81078C7FA">>},
{<<"parse_trans">>, <<"09765507A3C7590A784615CFD421D101AEC25098D50B89D7AA1D66646BC571C1">>},
{<<"providers">>, <<"BBF730563914328EC2511D205E6477A94831DB7297DE313B3872A2B26C562EAB">>},
{<<"relx">>, <<"96CC7663EDCC02A8117AB0C64FE6D15BE79760C08726ABEAD1DAACE11BFBF75D">>},
Expand Down
11 changes: 9 additions & 2 deletions src/rebar_hex_repos.erl
Expand Up @@ -21,7 +21,8 @@
api_key => binary(),
repo_url => binary(),
repo_public_key => binary(),
repo_verify => binary()}.
repo_verify => binary(),
repo_verify_origin => binary()}.

from_state(BaseConfig, State) ->
HexConfig = rebar_state:get(State, hex, []),
Expand Down Expand Up @@ -104,7 +105,13 @@ update_repo_list(R, []) ->

default_repo() ->
HexDefaultConfig = hex_core:default_config(),
HexDefaultConfig#{name => ?PUBLIC_HEX_REPO}.
HexDefaultConfig#{name => ?PUBLIC_HEX_REPO, repo_verify_origin => repo_verify_origin()}.

repo_verify_origin() ->
case os:getenv("REBAR_NO_VERIFY_REPO_ORIGIN") of
"1" -> false;
_ -> true
end.

repo_list([]) ->
[];
Expand Down
38 changes: 27 additions & 11 deletions src/rebar_packages.erl
Expand Up @@ -49,10 +49,10 @@ get(Config, Name) ->


-spec get_all_names(rebar_state:t()) -> [binary()].
get_all_names(State) ->
get_all_names(State) ->
verify_table(State),
lists:usort(ets:select(?PACKAGE_TABLE, [{#package{key={'$1', '_', '_'},
_='_'},
_='_'},
[], ['$1']}])).

-spec get_package_versions(unicode:unicode_binary(), ec_semver:semver(),
Expand Down Expand Up @@ -101,14 +101,14 @@ load_and_verify_version(State) ->
?DEBUG("Package index version mismatch. Current version ~p, this rebar3 expecting ~p",
[V, ?PACKAGE_INDEX_VERSION]),
(catch ets:delete(?PACKAGE_TABLE)),
new_package_table()
new_package_table()
end;
_ ->
_ ->
new_package_table()
end.

handle_missing_package(PkgKey, Repo, State, Fun) ->
Name =
Name =
case PkgKey of
{N, Vsn, _Repo} ->
?DEBUG("Package ~ts-~ts not found. Fetching registry updates for "
Expand All @@ -121,8 +121,8 @@ handle_missing_package(PkgKey, Repo, State, Fun) ->
end,

update_package(Name, Repo, State),
try
Fun(State)
try
Fun(State)
catch
_:_ ->
%% Even after an update the package is still missing, time to error out
Expand Down Expand Up @@ -220,7 +220,7 @@ verify_table(State) ->
ets:info(?PACKAGE_TABLE, named_table) =:= true orelse load_and_verify_version(State).

parse_deps(Deps) ->
[{maps:get(app, D, Name), {pkg, Name, Constraint, undefined}}
[{maps:get(app, D, Name), {pkg, Name, Constraint, undefined}}
|| D=#{package := Name,
requirement := Constraint} <- Deps].

Expand All @@ -233,16 +233,19 @@ parse_checksum(Checksum) ->

update_package(Name, RepoConfig=#{name := Repo}, State) ->
?MODULE:verify_table(State),
try hex_repo:get_package(RepoConfig#{repo_key => maps:get(read_key, RepoConfig, <<>>)}, Name) of
{ok, {200, _Headers, #{releases := Releases}}} ->
try hex_repo:get_package(get_package_repo_config(RepoConfig), Name) of
{ok, {200, _Headers, Releases}} ->
_ = insert_releases(Name, Releases, Repo, ?PACKAGE_TABLE),
{ok, RegistryDir} = rebar_packages:registry_dir(State),
PackageIndex = filename:join(RegistryDir, ?INDEX_FILE),
ok = ets:tab2file(?PACKAGE_TABLE, PackageIndex);
{ok, {403, _Headers, <<>>}} ->
{ok, {403, _Headers, _}} ->
not_found;
{ok, {404, _Headers, _}} ->
not_found;
{error, unverified} ->
?WARN(unverified_repo_message(), [Repo]),
fail;
Error ->
?DEBUG("Hex get_package request failed: ~p", [Error]),
%% TODO: add better log message. hex_core should export a format_error
Expand All @@ -254,6 +257,19 @@ update_package(Name, RepoConfig=#{name := Repo}, State) ->
fail
end.

get_package_repo_config(RepoConfig=#{mirror_of := Repo}) ->
get_package_repo_config(maps:remove(mirror_of, RepoConfig#{name => Repo}));
get_package_repo_config(RepoConfig=#{read_key := Key}) ->
get_package_repo_config(maps:remove(read_key, RepoConfig#{repo_key => Key}));
get_package_repo_config(RepoConfig) ->
RepoConfig.

unverified_repo_message() ->
"Fetched deprecatated registry record version from repo ~ts, for security " ++
"reasons this registry version is no longer supported. The repository " ++
"you are using should update to fix the security reason. Set " ++
"REBAR_NO_VERIFY_REPO_ORIGIN=1 to disable this check.".

insert_releases(Name, Releases, Repo, Table) ->
[true = ets:insert(Table,
#package{key={Name, ec_semver:parse(Version), Repo},
Expand Down
22 changes: 11 additions & 11 deletions test/rebar_pkg_SUITE.erl
Expand Up @@ -99,7 +99,7 @@ init_per_testcase(bad_disconnect=Name, Config0) ->
Config = mock_config(Name, Config1),
meck:expect(hex_repo, get_tarball, fun(_, _, _) ->
{error, econnrefused}
end),
end),
Config;
init_per_testcase(Name, Config0) ->
Config = [{good_cache, false},
Expand Down Expand Up @@ -252,7 +252,7 @@ mock_config(Name, Config) ->
CacheRoot = filename:join([Priv, "cache", atom_to_list(Name)]),
TmpDir = filename:join([Priv, "tmp", atom_to_list(Name)]),
Tid = ets:new(registry_table, [public]),
AllDeps = [
AllDeps = [
{{<<"badindexchk">>,<<"1.0.0">>}, [[], ?bad_checksum, [<<"rebar3">>]]},
{{<<"goodpkg">>,<<"1.0.0">>}, [[], ?good_checksum, [<<"rebar3">>]]},
{{<<"goodpkg">>,<<"1.0.1">>}, [[], ?good_checksum, [<<"rebar3">>]]},
Expand All @@ -267,7 +267,7 @@ mock_config(Name, Config) ->
ok = ets:tab2file(Tid, filename:join([CacheDir, "registry"])),

catch ets:delete(?PACKAGE_TABLE),
rebar_packages:new_package_table(),
rebar_packages:new_package_table(),
lists:foreach(fun({{N, Vsn}, [Deps, Checksum, _]}) ->
case ets:member(?PACKAGE_TABLE, {ec_cnv:to_binary(N), Vsn, <<"hexpm">>}) of
false ->
Expand All @@ -279,18 +279,18 @@ mock_config(Name, Config) ->
ok
end
end, AllDeps),


meck:new(hex_repo, [passthrough]),
meck:expect(hex_repo, get_package,
meck:expect(hex_repo, get_package,
fun(_Config, PkgName) ->
Matches = ets:match_object(Tid, {{PkgName,'_'}, '_'}),
Releases =
Releases =
[#{checksum => Checksum,
version => Vsn,
dependencies => Deps} ||
dependencies => Deps} ||
{{_, Vsn}, [Deps, Checksum, _]} <- Matches],
{ok, {200, #{}, #{releases => Releases}}}
{ok, {200, #{}, Releases}}
end),

%% The state returns us a fake registry
Expand Down Expand Up @@ -321,16 +321,16 @@ mock_config(Name, Config) ->
%% Cache fetches are mocked -- we assume the server and clients are
%% correctly used.
GoodCache = ?config(good_cache, Config),
{Pkg,Vsn} = ?config(pkg, Config),
{Pkg,Vsn} = ?config(pkg, Config),
PkgFile = <<Pkg/binary, "-", Vsn/binary, ".tar">>,
{ok, PkgContents} = file:read_file(filename:join(?config(data_dir, Config), PkgFile)),

meck:expect(hex_repo, get_tarball, fun(_, _, _) when GoodCache ->
{ok, {304, #{<<"etag">> => ?good_etag}, <<>>}};
(_, _, _) ->
{ok, {200, #{<<"etag">> => ?good_etag}, PkgContents}}
end),
end),

[{cache_root, CacheRoot},
{cache_dir, CacheDir},
{tmp_dir, TmpDir},
Expand Down
14 changes: 7 additions & 7 deletions test/rebar_pkg_alias_SUITE.erl
Expand Up @@ -224,7 +224,7 @@ mock_config(Name, Config) ->
meck:expect(rebar_prv_update, do, fun(State) -> {ok, State} end),

catch ets:delete(?PACKAGE_TABLE),
rebar_packages:new_package_table(),
rebar_packages:new_package_table(),

lists:foreach(fun({{N, Vsn}, [Deps, Checksum, _]}) ->
case ets:member(?PACKAGE_TABLE, {ec_cnv:to_binary(N), Vsn, <<"hexpm">>}) of
Expand All @@ -238,11 +238,11 @@ mock_config(Name, Config) ->
end;
({_N, _Vsns}) ->
ok
end, AllDeps),

end, AllDeps),

meck:new(hex_repo, [passthrough]),
meck:expect(hex_repo, get_package,
meck:expect(hex_repo, get_package,
fun(_Config, PkgName) ->
Matches = ets:match_object(Tid, {{PkgName,'_'}, '_'}),
Releases =
Expand All @@ -251,13 +251,13 @@ mock_config(Name, Config) ->
dependencies => [{DAppName, {pkg, DN, DV, undefined}} ||
{DN, DV, _, DAppName} <- Deps]} ||
{{_, Vsn}, [Deps, Checksum, _]} <- Matches],
{ok, {200, #{}, #{releases => Releases}}}
{ok, {200, #{}, Releases}}
end),

meck:expect(hex_repo, get_tarball, fun(_, _, _) ->
{ok, {304, #{<<"etag">> => EtagGood}, <<>>}}
end),
end),

%% Move all packages to cache
NewConf = [{cache_root, CacheRoot},
{cache_dir, CacheDir},
Expand Down

0 comments on commit 6a5ad07

Please sign in to comment.