Skip to content

Commit

Permalink
cleanup use of rebar_resource module and unused functions
Browse files Browse the repository at this point in the history
  • Loading branch information
tsloughter committed Sep 11, 2018
1 parent 1288141 commit 57cdbe0
Show file tree
Hide file tree
Showing 21 changed files with 102 additions and 177 deletions.
6 changes: 5 additions & 1 deletion src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,10 @@
-define(HEX_AUTH_FILE, "hex.config").
-define(PUBLIC_HEX_REPO, <<"hexpm">>).

%% ignore this function in all modules
%% not every module that exports it and relies on it being called implements provider
-ignore_xref([{format_error, 1}]).

%% the package record is used in a select match spec which upsets dialyzer
%% this is the suggested workaround from Tobias
%% http://erlang.org/pipermail/erlang-questions/2009-February/041445.html
Expand All @@ -49,7 +53,7 @@
-record(resource, {type :: atom(),
module :: module(),
state :: term(),
implementation :: module()}).
implementation :: rebar_resource | rebar_resource_v2}).

-ifdef(namespaced_types).
-type rebar_dict() :: dict:dict().
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_app_info.erl
Original file line number Diff line number Diff line change
Expand Up @@ -495,12 +495,12 @@ is_checkout(AppInfo=#app_info_t{}, IsCheckout) ->
AppInfo#app_info_t{is_checkout=IsCheckout}.

%% @doc returns whether the app source exists in the deps dir
%% and profiles/overrides have been applied to the app info opts
-spec is_available(t()) -> boolean().
is_available(#app_info_t{is_available=IsAvailable}) ->
IsAvailable.

%% @doc sets whether the app is a available app or not
%% @doc sets whether the app's source is available
%% only set if the app's source is found in the expected dep directory
-spec is_available(t(), boolean()) -> t().
is_available(AppInfo=#app_info_t{}, IsAvailable) ->
AppInfo#app_info_t{is_available=IsAvailable}.
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_app_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -247,7 +247,7 @@ expand_deps_sources(Dep, State) ->
%% around version if required.
-spec update_source(rebar_app_info:t(), Source, rebar_state:t()) ->
rebar_app_info:t() when
Source :: rebar_resource:source().
Source :: rebar_resource_v2:source().
update_source(AppInfo, {pkg, PkgName, PkgVsn, Hash}, State) ->
case rebar_packages:resolve_version(PkgName, PkgVsn, Hash,
?PACKAGE_TABLE, State) of
Expand Down
10 changes: 5 additions & 5 deletions src/rebar_fetch.erl
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,13 @@
-include_lib("providers/include/providers.hrl").

-spec lock_source(rebar_app_info:t(), rebar_state:t())
-> rebar_resource:source() | {error, string()}.
lock_source(AppInfo, State) ->
-> rebar_resource_v2:source() | {error, string()}.
lock_source(AppInfo, State) ->
rebar_resource_v2:lock(AppInfo, State).

-spec download_source(rebar_app_info:t(), rebar_state:t())
-> rebar_app_info:t() | {error, any()}.
download_source(AppInfo, State) ->
download_source(AppInfo, State) ->
AppDir = rebar_app_info:dir(AppInfo),
try download_source_(AppInfo, State) of
true ->
Expand All @@ -32,7 +32,7 @@ download_source(AppInfo, State) ->
AppInfo1 = rebar_app_info:update_opts(AppInfo, rebar_app_info:opts(AppInfo), Config),
case rebar_app_discover:find_app(AppInfo1, AppDir, all) of
{true, AppInfo2} ->
AppInfo2;
rebar_app_info:is_available(AppInfo2, true);
false ->
throw(?PRV_ERROR({dep_app_not_found, AppDir, rebar_app_info:name(AppInfo1)}))
end;
Expand Down Expand Up @@ -62,7 +62,7 @@ download_source_(AppInfo, State) ->
Error
end.

-spec needs_update(file:filename_all(), rebar_state:t())
-spec needs_update(rebar_app_info:t(), rebar_state:t())
-> boolean() | {error, string()}.
needs_update(AppInfo, State) ->
try
Expand Down
2 changes: 0 additions & 2 deletions src/rebar_git_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,6 @@ lock_(AppDir, {git, Url}) ->
needs_update(AppInfo, _) ->
needs_update_(rebar_app_info:dir(AppInfo), rebar_app_info:source(AppInfo)).

needs_update_(AppInfo, Source) when is_tuple(AppInfo) ->
needs_update_(rebar_app_info:dir(AppInfo), Source);
needs_update_(Dir, {git, Url, {tag, Tag}}) ->
{ok, Current} = rebar_utils:sh(?FMT("git describe --tags --exact-match", []),
[{cd, Dir}]),
Expand Down
8 changes: 5 additions & 3 deletions src/rebar_hex_repos.erl
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@
-include("rebar.hrl").
-include_lib("providers/include/providers.hrl").

-export_type([repo/0]).

-type repo() :: #{name => unicode:unicode_binary(),
api_url => binary(),
api_key => binary(),
Expand All @@ -31,8 +33,8 @@ from_state(BaseConfig, State) ->
%% merge organizations parent repo options into each oraganization repo
update_organizations(Repos1).

-spec get_repo_config(unicode:unicode_binary(), rebar_state:t() | [hex_core:config()])
-> {ok, hex_core:config()} | error.
-spec get_repo_config(unicode:unicode_binary(), rebar_state:t() | [repo()])
-> {ok, repo()} | error.
get_repo_config(RepoName, Repos) when is_list(Repos) ->
case ec_lists:find(fun(#{name := N}) -> N =:= RepoName end, Repos) of
error ->
Expand All @@ -42,7 +44,7 @@ get_repo_config(RepoName, Repos) when is_list(Repos) ->
end;
get_repo_config(RepoName, State) ->
Resources = rebar_state:resources(State),
#{repos := Repos} = rebar_resource:find_resource_state(pkg, Resources),
#{repos := Repos} = rebar_resource_v2:find_resource_state(pkg, Resources),
get_repo_config(RepoName, Repos).

merge_with_base_and_auth(Repos, BaseConfig, Auth) ->
Expand Down
50 changes: 13 additions & 37 deletions src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2,20 +2,16 @@

-export([get/2
,get_all_names/1
,new_package_table/0
,load_and_verify_version/1
,registry_dir/1
,package_dir/2
,registry_checksum/4
,find_highest_matching/5
,find_highest_matching_/5
,verify_table/1
,format_error/1
,update_package/3
,resolve_version/5]).

-ifdef(TEST).
-export([cmp_/4, cmpl_/4, valid_vsn/1]).
-export([new_package_table/0, find_highest_matching_/5, cmp_/4, cmpl_/4, valid_vsn/1]).
-endif.

-export_type([package/0]).
Expand All @@ -33,7 +29,7 @@ format_error({missing_package, Name, Vsn}) ->
format_error({missing_package, Pkg}) ->
io_lib:format("Package not found in any repo: ~p.", [Pkg]).

-spec get(hex_core:config(), binary()) -> {ok, map()} | {error, term()}.
-spec get(rebar_hex_repos:repo(), binary()) -> {ok, map()} | {error, term()}.
get(Config, Name) ->
try hex_api_package:get(Config, Name) of
{ok, {200, _Headers, PkgInfo}} ->
Expand Down Expand Up @@ -77,7 +73,7 @@ get_package(Dep, Vsn, Hash, Repo, Table, State) ->
-> {ok, #package{}} | not_found.
get_package(Dep, Vsn, undefined, Retired, Repo, Table, State) ->
get_package(Dep, Vsn, '_', Retired, Repo, Table, State);
get_package(Dep, Vsn, Hash, Retired, Repos, Table, State) when is_list(Repos) ->
get_package(Dep, Vsn, Hash, Retired, Repos, Table, State) ->
?MODULE:verify_table(State),
case ets:select(Table, [{#package{key={Dep, Vsn, Repo},
checksum=Hash,
Expand All @@ -88,30 +84,12 @@ get_package(Dep, Vsn, Hash, Retired, Repos, Table, State) when is_list(Repos) ->
{ok, Package};
_ ->
not_found
end;
get_package(Dep, Vsn, Hash, Retired, Repo, Table, State) ->
get_package(Dep, Vsn, Hash, Retired, [Repo], Table, State).
end.

new_package_table() ->
?PACKAGE_TABLE = ets:new(?PACKAGE_TABLE, [named_table, public, ordered_set, {keypos, 2}]),
ets:insert(?PACKAGE_TABLE, {?PACKAGE_INDEX_VERSION, package_index_version}).

-spec registry_checksum(unicode:unicode_binary(), vsn(), unicode:unicode_binary(), rebar_state:t())
-> binary().
registry_checksum(Name, Vsn, Repo, State) ->
try_lookup(?PACKAGE_TABLE, {Name, Vsn, Repo}, #package.checksum, State).

try_lookup(Table, Key={_, _, Repo}, Element, State) ->
?MODULE:verify_table(State),
try
ets:lookup_element(Table, Key, Element)
catch
_:_ ->
handle_missing_package(Key, Repo, State, fun(_) ->
ets:lookup_element(Table, Key, Element)
end)
end.

load_and_verify_version(State) ->
{ok, RegistryDir} = registry_dir(State),
case ets:file2tab(filename:join(RegistryDir, ?INDEX_FILE)) of
Expand Down Expand Up @@ -164,16 +142,14 @@ registry_dir(State) ->
end,
{ok, RegistryDir}.

-spec package_dir(rebar_hex_repos:repo(), rebar_state:t()) -> {ok, filename:filename_all()}.
package_dir(Repo, State) ->
case registry_dir(State) of
{ok, RegistryDir} ->
RepoName = maps:get(name, Repo),
PackageDir = filename:join([RegistryDir, rebar_utils:to_list(RepoName), "packages"]),
ok = filelib:ensure_dir(filename:join(PackageDir, "placeholder")),
{ok, PackageDir};
Error ->
Error
end.
{ok, RegistryDir} = registry_dir(State),
RepoName = maps:get(name, Repo),
PackageDir = filename:join([RegistryDir, rebar_utils:to_list(RepoName), "packages"]),
ok = filelib:ensure_dir(filename:join(PackageDir, "placeholder")),
{ok, PackageDir}.


%% Hex supports use of ~> to specify the version required for a dependency.
%% Since rebar3 requires exact versions to choose from we find the highest
Expand Down Expand Up @@ -299,7 +275,7 @@ insert_releases(Name, Releases, Repo, Table) ->
%% if checksum is defined search for any matching repo matching pkg-vsn and checksum
resolve_version(Dep, DepVsn, Hash, HexRegistry, State) when is_binary(Hash) ->
Resources = rebar_state:resources(State),
#{repos := RepoConfigs} = rebar_resource:find_resource_state(pkg, Resources),
#{repos := RepoConfigs} = rebar_resource_v2:find_resource_state(pkg, Resources),
RepoNames = [RepoName || #{name := RepoName} <- RepoConfigs],

%% allow retired packages when we have a checksum
Expand Down Expand Up @@ -351,7 +327,7 @@ check_all_repos(Fun, RepoConfigs) ->

handle_missing_no_exception(Fun, Dep, State) ->
Resources = rebar_state:resources(State),
#{repos := RepoConfigs} = rebar_resource:find_resource_state(pkg, Resources),
#{repos := RepoConfigs} = rebar_resource_v2:find_resource_state(pkg, Resources),

%% first check all repos in order for a local match
%% if none is found then we step through checking after updating the repo registry
Expand Down
29 changes: 13 additions & 16 deletions src/rebar_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -4,19 +4,16 @@

-behaviour(rebar_resource_v2).

-export([init/2
,lock/2
,download/4
,download/5
,needs_update/2
,make_vsn/2]).

-export([request/4
,etag/1]).
-export([init/2,
lock/2,
download/4,
download/5,
needs_update/2,
make_vsn/2]).

-ifdef(TEST).
%% exported for test purposes
-export([store_etag_in_cache/2]).
-export([store_etag_in_cache/2, etag/1, request/4]).
-endif.

-include("rebar.hrl").
Expand Down Expand Up @@ -98,7 +95,7 @@ download(TmpDir, AppInfo, State, ResourceState) ->
%%------------------------------------------------------------------------------
-spec download(TmpDir, Pkg, State, ResourceState, UpdateETag) -> Res when
TmpDir :: file:name(),
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: hex_core:config()},
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: rebar_hex_repos:repo()},
State :: rebar_state:t(),
ResourceState:: rebar_resource_v2:resource_state(),
UpdateETag :: boolean(),
Expand Down Expand Up @@ -133,7 +130,7 @@ make_vsn(_, _) ->
%% {ok, Contents, NewEtag}, otherwise if some error occured return error.
%% @end
%%------------------------------------------------------------------------------
-spec request(hex_core:config(), binary(), binary(), false | binary())
-spec request(rebar_hex_repos:repo(), binary(), binary(), false | binary())
-> {ok, cached} | {ok, binary(), binary()} | error.
request(Config, Name, Version, ETag) ->
Config1 = Config#{http_etag => ETag},
Expand Down Expand Up @@ -191,7 +188,7 @@ store_etag_in_cache(Path, ETag) ->
UpdateETag) -> Res when
TmpDir :: file:name(),
CachePath :: file:name(),
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: hex_core:config()},
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: rebar_hex_repos:repo()},
ETag :: binary(),
State :: rebar_state:t(),
ETagPath :: file:name(),
Expand Down Expand Up @@ -219,7 +216,7 @@ cached_download(TmpDir, CachePath, Pkg={pkg, Name, Vsn, _Hash, RepoConfig}, ETag
-spec serve_from_cache(TmpDir, CachePath, Pkg, State) -> Res when
TmpDir :: file:name(),
CachePath :: file:name(),
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: hex_core:config()},
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: rebar_hex_repos:repo()},
State :: rebar_state:t(),
Res :: cached_result().
serve_from_cache(TmpDir, CachePath, Pkg, State) ->
Expand All @@ -244,7 +241,7 @@ serve_from_cache(TmpDir, CachePath, Pkg, State) ->
ETagPath) -> Res when
TmpDir :: file:name(),
CachePath :: file:name(),
Package :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: hex_core:config()},
Package :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: rebar_hex_repos:repo()},
ETag :: binary(),
Binary :: binary(),
State :: rebar_state:t(),
Expand Down Expand Up @@ -279,7 +276,7 @@ extract(TmpDir, CachePath) ->
{Files, Contents, Version, Meta}.

-spec checksums(Pkg, Files, Contents, Version, Meta, State) -> Res when
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: hex_core:config()},
Pkg :: {pkg, Name :: binary(), Vsn :: binary(), Hash :: binary(), RepoConfig :: rebar_hex_repos:repo()},
Files :: list({file:name(), binary()}),
Contents :: binary(),
Version :: binary(),
Expand Down
6 changes: 4 additions & 2 deletions src/rebar_prv_deps.erl
Original file line number Diff line number Diff line change
Expand Up @@ -100,15 +100,17 @@ display_dep(_State, {Name, _Vsn, Source, _Opts}) when is_tuple(Source) ->
display_dep(State, {Name, _Source={pkg, _, Vsn}, Level}) when is_integer(Level) ->
DepsDir = rebar_dir:deps_dir(State),
AppDir = filename:join([DepsDir, rebar_utils:to_binary(Name)]),
NeedsUpdate = case rebar_fetch:needs_update(AppDir, State) of
{ok, AppInfo} = rebar_app_info:discover(AppDir),
NeedsUpdate = case rebar_fetch:needs_update(AppInfo, State) of
true -> "*";
false -> ""
end,
?CONSOLE("~ts~ts (locked package ~ts)", [Name, NeedsUpdate, Vsn]);
display_dep(State, {Name, Source, Level}) when is_tuple(Source), is_integer(Level) ->
DepsDir = rebar_dir:deps_dir(State),
AppDir = filename:join([DepsDir, rebar_utils:to_binary(Name)]),
NeedsUpdate = case rebar_fetch:needs_update(AppDir, State) of
{ok, AppInfo} = rebar_app_info:discover(AppDir),
NeedsUpdate = case rebar_fetch:needs_update(AppInfo, State) of
true -> "*";
false -> ""
end,
Expand Down
6 changes: 2 additions & 4 deletions src/rebar_prv_deps_tree.erl
Original file line number Diff line number Diff line change
Expand Up @@ -39,18 +39,16 @@ format_error(Reason) ->
%% Internal functions

print_deps_tree(SrcDeps, Verbose, State) ->
Resources = rebar_state:resources(State),
D = lists:foldl(fun(App, Dict) ->
Name = rebar_app_info:name(App),
Vsn = rebar_app_info:original_vsn(App),
AppDir = rebar_app_info:dir(App),
Vsn1 = rebar_utils:vcs_vsn(App, Vsn, AppDir, Resources),
Vsn1 = rebar_utils:vcs_vsn(App, Vsn, State),
Source = rebar_app_info:source(App),
Parent = rebar_app_info:parent(App),
dict:append_list(Parent, [{Name, Vsn1, Source}], Dict)
end, dict:new(), SrcDeps),
ProjectAppNames = [{rebar_app_info:name(App)
,rebar_utils:vcs_vsn(App, rebar_app_info:original_vsn(App), rebar_app_info:dir(App), Resources)
,rebar_utils:vcs_vsn(App, rebar_app_info:original_vsn(App), State)
,project} || App <- rebar_state:project_apps(State)],
case dict:find(root, D) of
{ok, Children} ->
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_prv_install_deps.erl
Original file line number Diff line number Diff line change
Expand Up @@ -371,7 +371,7 @@ make_relative_to_root(State, Path) when is_list(Path) ->

fetch_app(AppInfo, State) ->
?INFO("Fetching ~ts (~p)", [rebar_app_info:name(AppInfo),
rebar_resource:format_source(rebar_app_info:source(AppInfo))]),
rebar_resource_v2:format_source(rebar_app_info:source(AppInfo))]),
rebar_fetch:download_source(AppInfo, State).

maybe_upgrade(AppInfo, _AppDir, Upgrade, State) ->
Expand All @@ -380,7 +380,7 @@ maybe_upgrade(AppInfo, _AppDir, Upgrade, State) ->
case rebar_fetch:needs_update(AppInfo, State) of
true ->
?INFO("Upgrading ~ts (~p)", [rebar_app_info:name(AppInfo),
rebar_resource:format_source(rebar_app_info:source(AppInfo))]),
rebar_resource_v2:format_source(rebar_app_info:source(AppInfo))]),
rebar_fetch:download_source(AppInfo, State);
false ->
case Upgrade of
Expand Down
3 changes: 2 additions & 1 deletion src/rebar_prv_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ do(State) ->
?PRV_ERROR(no_package_arg);
Name ->
Resources = rebar_state:resources(State),
#{repos := Repos} = rebar_resource:find_resource_state(pkg, Resources),
#{repos := Repos} = rebar_resource_v2:find_resource_state(pkg, Resources),
Results = get_package(rebar_utils:to_binary(Name), Repos),
case lists:all(fun({_, {error, not_found}}) -> true; (_) -> false end, Results) of
true ->
Expand All @@ -46,6 +46,7 @@ do(State) ->
end
end.

-spec get_package(binary(), [map()]) -> [{binary(), {ok, map()} | {error, term()}}].
get_package(Name, Repos) ->
lists:foldl(fun(RepoConfig, Acc) ->
[{maps:get(name, RepoConfig), rebar_packages:get(RepoConfig, Name)} | Acc]
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_repos.erl
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ init(State) ->
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
do(State) ->
Resources = rebar_state:resources(State),
#{repos := Repos} = rebar_resource:find_resource_state(pkg, Resources),
#{repos := Repos} = rebar_resource_v2:find_resource_state(pkg, Resources),

?CONSOLE("Repos:", []),
%%TODO: do some formatting
Expand Down
Loading

0 comments on commit 57cdbe0

Please sign in to comment.