Skip to content

Commit

Permalink
require the app name as the last part of git_subdir path
Browse files Browse the repository at this point in the history
  • Loading branch information
tsloughter committed Sep 3, 2020
1 parent 7224180 commit b14fa55
Show file tree
Hide file tree
Showing 4 changed files with 48 additions and 16 deletions.
25 changes: 19 additions & 6 deletions src/rebar_app_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -252,7 +252,7 @@ parse_dep(_, Dep, _, _, _) ->
IsLock :: boolean(),
State :: rebar_state:t().
dep_to_app(Parent, DepsDir, Name, Vsn, Source0, IsLock, State) ->
SubDir = subdir(Source0),
{SubDir, Source1} = subdir(Name, Source0),
FetchDir = rebar_utils:to_list(filename:join([DepsDir, Name])),
CheckoutsDir = rebar_utils:to_list(rebar_dir:checkouts_dir(State, Name)),
AppInfo = case rebar_app_info:discover(CheckoutsDir) of
Expand All @@ -272,7 +272,7 @@ dep_to_app(Parent, DepsDir, Name, Vsn, Source0, IsLock, State) ->
not_found ->
rebar_app_info:new(Parent, Name, Vsn, Dir, [])
end,
rebar_app_info:source(AppInfo0, Source0)
rebar_app_info:source(AppInfo0, Source1)
end,
Overrides = rebar_app_info:get(AppInfo, overrides, []) ++ rebar_state:get(State, overrides, []),
AppInfo2 = rebar_app_info:set(AppInfo, overrides, Overrides),
Expand All @@ -286,10 +286,23 @@ dep_to_app(Parent, DepsDir, Name, Vsn, Source0, IsLock, State) ->
%% and optionally get the version. Because of this we must keep the clone as a
%% usable git repo clone and using a subdir can not be copied out of it but must
%% have the app info set its directory to be a sub directory of the repo.
subdir({git_subdir, _Repo, _Ref, Dir}) ->
Dir;
subdir(_) ->
"".
subdir(Name, {git_subdir, _Repo, _Ref, Dir}=Source) ->
NameList = rebar_utils:to_list(Name),

%% To work with Erlang's `code' server the directory the application is in
%% must be the same name as the application.
%% Here we append the name of the application if it isn't already the last
%% part of the path.
Base = filename:basename(Dir),
case NameList =:= Base of
true ->
{Dir, Source};
false ->
NewDir = filename:join(Dir, NameList),
{NewDir, {git_subdir, _Repo, _Ref, NewDir}}
end;
subdir(_, Source) ->
{"", Source}.

%% @doc Takes a given application app_info record along with the project.
%% If the app is a package, resolve and expand the package definition.
Expand Down
3 changes: 3 additions & 0 deletions src/rebar_fetch.erl
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,9 @@ download_source(AppInfo, State) ->
{error, Reason} ->
throw(?PRV_ERROR(Reason))
catch
%% if already a PRV_ERROR format just re-raise it
?WITH_STACKTRACE(error, {error, {Module, Reason}}, S)
erlang:raise(error, {error, {Module, Reason}}, S);
throw:{no_resource, Type, Location} ->
throw(?PRV_ERROR({no_resource, Location, Type}));
?WITH_STACKTRACE(C,T,S)
Expand Down
30 changes: 23 additions & 7 deletions src/rebar_git_subdir_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,11 @@
lock/2,
download/4,
needs_update/2,
make_vsn/2]).
make_vsn/2,
format_error/1]).

-include("rebar.hrl").
-include_lib("providers/include/providers.hrl").

%% Regex used for parsing scp style remote url
-define(SCP_PATTERN, "\\A(?<username>[^@]+)@(?<host>[^:]+):(?<path>.+)\\z").
Expand All @@ -27,12 +29,13 @@ lock(AppInfo, _) ->
{git_subdir, Url1, {ref, Ref}, Dir}.

download(TmpDir, AppInfo, State, _) ->
Name = rebar_app_info:name(AppInfo),
{git_subdir, Url, Checkout, SparseDir} = rebar_app_info:source(AppInfo),
case rebar_git_resource:download_(TmpDir, {git, Url, Checkout}, State) of
ok ->
sparse_checkout(rebar_git_resource:git_vsn(), TmpDir, to_ref(Checkout), SparseDir);
sparse_checkout(Name, rebar_git_resource:git_vsn(), TmpDir, to_ref(Checkout), SparseDir);
{ok, _} ->
sparse_checkout(rebar_git_resource:git_vsn(), TmpDir, to_ref(Checkout), SparseDir);
sparse_checkout(Name, rebar_git_resource:git_vsn(), TmpDir, to_ref(Checkout), SparseDir);
{error, Reason} ->
{error, Reason};
Error ->
Expand Down Expand Up @@ -60,18 +63,31 @@ to_ref({ref, Ref}) ->
to_ref(Rev) ->
Rev.

sparse_checkout(GitVsn, Dir, Ref, SparseDir) when GitVsn >= {1,7,4};
GitVsn =:= undefined ->
sparse_checkout(Name, GitVsn, Dir, Ref, SparseDir) when GitVsn >= {1,7,4};
GitVsn =:= undefined ->
?DEBUG("doing sparse checkout in ~s of dir ~s", [Dir, SparseDir]),

check_directory(Name, Dir, SparseDir),
rebar_utils:sh(?FMT("git --git-dir=.git config core.sparsecheckout true", []),
[{cd, Dir}]),
filelib:ensure_dir(filename:join(Dir, ".git/info/sparse-checkout")),
file:write_file(filename:join(Dir, ".git/info/sparse-checkout"), SparseDir),
rebar_utils:sh(?FMT("git checkout -q ~ts", [rebar_utils:escape_chars(Ref)]), [{cd, Dir}]),
ok;
sparse_checkout(_, _, _, _) ->
sparse_checkout(Name, _, Dir, _, SparseDir) ->
%% sparse checkout not supported but we can still use the subdirectory
%% so no need to fail, just don't do the sparse checkout
?DEBUG("too old a git version to do a sparse checkout for a subdir dep", []),
check_directory(Name, Dir, SparseDir),
ok.

%% verify that subdirectory exists
check_directory(Name, Dir, SparseDir) ->
case filelib:is_dir(filename:join(Dir, SparseDir)) of
true ->
ok;
false ->
erlang:error(?PRV_ERROR({bad_subdir, Name, SparseDir}))
end.

format_error({bad_subdir, Name, SubDir}) ->
io_lib:format("Failed to fetch git_subdir dependency ~ts: directory ~ts does not exist.", [Name, SubDir]).
6 changes: 3 additions & 3 deletions test/rebar_test_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -184,10 +184,10 @@ random_seed() ->

expand_deps(_, []) -> [];
expand_deps(git_subdir, [{Name, Deps} | Rest]) ->
Dep = {Name, {git_subdir, "https://example.org/user/"++Name++".git", {branch, "master"}, "appsubdir"}},
Dep = {Name, {git_subdir, "https://example.org/user/"++Name++".git", {branch, "master"}, filename:join("appsubdir", Name)}},
[{Dep, expand_deps(git_subdir, Deps)} | expand_deps(git_subdir, Rest)];
expand_deps(git_subdir, [{Name, Vsn, Deps} | Rest]) ->
Dep = {Name, Vsn, {git_subdir, "https://example.org/user/"++Name++".git", {tag, Vsn}, "appsubdir"}},
Dep = {Name, Vsn, {git_subdir, "https://example.org/user/"++Name++".git", {tag, Vsn}, filename:join("appsubdir", Name)}},
[{Dep, expand_deps(git_subdir, Deps)} | expand_deps(git_subdir, Rest)];
expand_deps(git, [{Name, Deps} | Rest]) ->
Dep = {Name, ".*", {git, "https://example.org/user/"++Name++".git", "master"}},
Expand Down Expand Up @@ -260,7 +260,7 @@ top_level_deps([{{Name, Vsn, Ref}, _} | Deps]) ->
%%%%%%%%%%%%%%%
check_results(AppDir, Expected, ProfileRun) ->
BuildDirs = filelib:wildcard(filename:join([AppDir, "_build", ProfileRun, "lib", "*"])),
BuildSubDirs = [D || D <- filelib:wildcard(filename:join([AppDir, "_build", ProfileRun, "lib", "*", "*"])),
BuildSubDirs = [D || D <- filelib:wildcard(filename:join([AppDir, "_build", ProfileRun, "lib", "*", "*", "*"])),
filelib:is_dir(D)],
PluginDirs = filelib:wildcard(filename:join([AppDir, "_build", ProfileRun, "plugins", "*"])),
GlobalPluginDirs = filelib:wildcard(filename:join([AppDir, "global", "plugins", "*"])),
Expand Down

0 comments on commit b14fa55

Please sign in to comment.