summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rwxr-xr-xbootstrap105
-rw-r--r--rebar.config6
-rw-r--r--rebar.lock4
-rw-r--r--src/rebar_app_discover.erl13
-rw-r--r--src/rebar_git_resource.erl30
-rw-r--r--src/rebar_mustache.erl296
-rw-r--r--src/rebar_prv_app_discovery.erl8
-rw-r--r--src/rebar_prv_shell.erl62
-rw-r--r--src/rebar_templater.erl2
-rw-r--r--src/rebar_utils.erl8
10 files changed, 215 insertions, 319 deletions
diff --git a/bootstrap b/bootstrap
index a96483b..d8c97a7 100755
--- a/bootstrap
+++ b/bootstrap
@@ -2,6 +2,7 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ft=erlang ts=4 sw=4 et
+
main(_Args) ->
%% Fetch and build deps required to build rebar3
BaseDeps = [{providers, []}
@@ -105,12 +106,114 @@ compile_file(File, Opts) ->
bootstrap_rebar3() ->
filelib:ensure_dir("_build/default/lib/rebar/ebin/dummy.beam"),
code:add_path("_build/default/lib/rebar/ebin/"),
- file:make_symlink(filename:absname("src"), filename:absname("_build/default/lib/rebar/src")),
+ ok = symlink_or_copy(filename:absname("src"),
+ filename:absname("_build/default/lib/rebar/src")),
Sources = ["src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
[compile_file(X, [{outdir, "_build/default/lib/rebar/ebin/"}
,return | additional_defines()]) || X <- Sources],
code:add_patha(filename:absname("_build/default/lib/rebar/ebin")).
+%%rebar.hrl
+-define(FMT(Str, Args), lists:flatten(io_lib:format(Str, Args))).
+%%/rebar.hrl
+%%rebar_file_utils
+symlink_or_copy(Source, Target) ->
+ Link = case os:type() of
+ {win32, _} ->
+ Source;
+ _ ->
+ make_relative_path(Source, Target)
+ end,
+ case file:make_symlink(Link, Target) of
+ ok ->
+ ok;
+ {error, eexist} ->
+ ok;
+ {error, _} ->
+ cp_r([Source], Target)
+ end.
+
+make_relative_path(Source, Target) ->
+ do_make_relative_path(filename:split(Source), filename:split(Target)).
+
+do_make_relative_path([H|T1], [H|T2]) ->
+ do_make_relative_path(T1, T2);
+do_make_relative_path(Source, Target) ->
+ Base = lists:duplicate(max(length(Target) - 1, 0), ".."),
+ filename:join(Base ++ Source).
+
+cp_r([], _Dest) ->
+ ok;
+cp_r(Sources, Dest) ->
+ case os:type() of
+ {unix, _} ->
+ EscSources = [escape_path(Src) || Src <- Sources],
+ SourceStr = string:join(EscSources, " "),
+ os:cmd(?FMT("cp -R ~s \"~s\"", [SourceStr, Dest])),
+ ok;
+ {win32, _} ->
+ lists:foreach(fun(Src) -> ok = cp_r_win32(Src,Dest) end, Sources),
+ ok
+ end.
+
+xcopy_win32(Source,Dest)->
+ R = os:cmd(?FMT("xcopy \"~s\" \"~s\" /q /y /e 2> nul",
+ [filename:nativename(Source), filename:nativename(Dest)])),
+ case length(R) > 0 of
+ %% when xcopy fails, stdout is empty and and error message is printed
+ %% to stderr (which is redirected to nul)
+ true -> ok;
+ false ->
+ {error, lists:flatten(
+ io_lib:format("Failed to xcopy from ~s to ~s~n",
+ [Source, Dest]))}
+ end.
+
+cp_r_win32({true, SourceDir}, {true, DestDir}) ->
+ %% from directory to directory
+ SourceBase = filename:basename(SourceDir),
+ ok = case file:make_dir(filename:join(DestDir, SourceBase)) of
+ {error, eexist} -> ok;
+ Other -> Other
+ end,
+ ok = xcopy_win32(SourceDir, filename:join(DestDir, SourceBase));
+cp_r_win32({false, Source} = S,{true, DestDir}) ->
+ %% from file to directory
+ cp_r_win32(S, {false, filename:join(DestDir, filename:basename(Source))});
+cp_r_win32({false, Source},{false, Dest}) ->
+ %% from file to file
+ {ok,_} = file:copy(Source, Dest),
+ ok;
+cp_r_win32({true, SourceDir}, {false, DestDir}) ->
+ case filelib:is_regular(DestDir) of
+ true ->
+ %% From directory to file? This shouldn't happen
+ {error, lists:flatten(
+ io_lib:format("Cannot copy dir (~p) to file (~p)\n",
+ [SourceDir, DestDir]))};
+ false ->
+ %% Specifying a target directory that doesn't currently exist.
+ %% So let's attempt to create this directory
+ case filelib:ensure_dir(filename:join(DestDir, "dummy")) of
+ ok ->
+ ok = xcopy_win32(SourceDir, DestDir);
+ {error, Reason} ->
+ {error, lists:flatten(
+ io_lib:format("Unable to create dir ~p: ~p\n",
+ [DestDir, Reason]))}
+ end
+ end;
+cp_r_win32(Source,Dest) ->
+ Dst = {filelib:is_dir(Dest), Dest},
+ lists:foreach(fun(Src) ->
+ ok = cp_r_win32({filelib:is_dir(Src), Src}, Dst)
+ end, filelib:wildcard(Source)),
+ ok.
+
+escape_path(Str) ->
+ re:replace(Str, "([ ()?])", "\\\\&", [global, {return, list}]).
+%%/rebar_file_utils
+
setup_env() ->
%% We don't need or want relx providers loaded yet
application:load(rebar),
diff --git a/rebar.config b/rebar.config
index e58ae0e..876f725 100644
--- a/rebar.config
+++ b/rebar.config
@@ -11,6 +11,9 @@
{relx, "",
{git, "https://github.com/tsloughter/relx.git",
{branch, "mustache"}}},
+ {mustache, ".*",
+ {git, "https://github.com/soranoba/mustache.git",
+ {branch, "master"}}},
{getopt, "",
{git, "https://github.com/jcomellas/getopt.git",
{branch, "master"}}}]}.
@@ -48,4 +51,5 @@
]}.
%% Overrides
-{overrides, [{override, erlware_commons, [{deps, []}, {plugins, []}]}]}.
+{overrides, [{override, erlware_commons, [{deps, []}, {plugins, []}]},
+ {override, mustache, [{deps, []}, {plugins, []}]}]}.
diff --git a/rebar.lock b/rebar.lock
index f4afed9..39b3b48 100644
--- a/rebar.lock
+++ b/rebar.lock
@@ -2,6 +2,10 @@
{git,"https://github.com/tsloughter/providers.git",
{ref,"7563ba7e916d5a35972b25b3aa1945ffe0a8e7a5"}},
0},
+ {<<"mustache">>,
+ {git,"https://github.com/tsloughter/mustache.git",
+ {ref,"fe99ec4fcc4cf3f169d4851b4d1b7b5780b8d464"}},
+ 0},
{<<"getopt">>,
{git,"https://github.com/jcomellas/getopt.git",
{ref,"626698975e63866156159661d100785d65eab6f9"}},
diff --git a/src/rebar_app_discover.erl b/src/rebar_app_discover.erl
index 41f41f5..73401bc 100644
--- a/src/rebar_app_discover.erl
+++ b/src/rebar_app_discover.erl
@@ -159,7 +159,12 @@ find_app(AppDir, Validate) ->
case Validate of
V when V =:= invalid ; V =:= all ->
AppInfo = create_app_info(AppDir, File),
- {true, rebar_app_info:app_file_src(AppInfo, File)};
+ case AppInfo of
+ {error, Reason} ->
+ throw({error, {invalid_app_file, File, Reason}});
+ _ ->
+ {true, rebar_app_info:app_file_src(AppInfo, File)}
+ end;
valid ->
false
end;
@@ -175,7 +180,7 @@ find_app(AppDir, Validate) ->
app_dir(AppFile) ->
filename:join(rebar_utils:droplast(filename:split(filename:dirname(AppFile)))).
--spec create_app_info(file:name(), file:name()) -> rebar_app_info:t() | error.
+-spec create_app_info(file:name(), file:name()) -> rebar_app_info:t() | {error, term()}.
create_app_info(AppDir, AppFile) ->
case file:consult(AppFile) of
{ok, [{application, AppName, AppDetails}]} ->
@@ -193,8 +198,8 @@ create_app_info(AppDir, AppFile) ->
false
end,
rebar_app_info:dir(rebar_app_info:valid(AppInfo1, Valid), AppDir);
- _ ->
- error
+ {error, Reason} ->
+ {error, Reason}
end.
dedup([]) -> [];
diff --git a/src/rebar_git_resource.erl b/src/rebar_git_resource.erl
index 07c9b4d..2d83579 100644
--- a/src/rebar_git_resource.erl
+++ b/src/rebar_git_resource.erl
@@ -16,7 +16,7 @@ lock(AppDir, {git, Url, _}) ->
lock(AppDir, {git, Url}) ->
AbortMsg = io_lib:format("Locking of git dependency failed in ~s", [AppDir]),
{ok, VsnString} =
- rebar_utils:sh("git --git-dir='" ++ AppDir ++ "/.git' rev-parse --verify HEAD",
+ rebar_utils:sh("git --git-dir=\"" ++ AppDir ++ "/.git\" rev-parse --verify HEAD",
[{use_stdout, false}, {debug_abort_on_error, AbortMsg}]),
Ref = string:strip(VsnString, both, $\n),
{git, Url, {ref, Ref}}.
@@ -125,7 +125,7 @@ collect_default_refcount() ->
%% timestamp is really important from an ordering perspective.
AbortMsg1 = "Getting log of git dependency failed in " ++ rebar_dir:get_cwd(),
{ok, String} =
- rebar_utils:sh("git log -n 1 --pretty=format:'%h\n' ",
+ rebar_utils:sh("git log -n 1 --pretty=format:\"%h\n\" ",
[{use_stdout, false},
{debug_abort_on_error, AbortMsg1}]),
RawRef = string:strip(String, both, $\n),
@@ -135,41 +135,43 @@ collect_default_refcount() ->
case Tag of
undefined ->
AbortMsg2 = "Getting rev-list of git depedency failed in " ++ rebar_dir:get_cwd(),
- rebar_utils:sh("git rev-list HEAD | wc -l",
- [{use_stdout, false},
- {debug_abort_on_error, AbortMsg2}]);
+ {ok, PatchLines} = rebar_utils:sh("git rev-list HEAD",
+ [{use_stdout, false},
+ {debug_abort_on_error, AbortMsg2}]),
+ rebar_utils:line_count(PatchLines);
_ ->
get_patch_count(Tag)
end,
{TagVsn, RawRef, RawCount}.
-build_vsn_string(Vsn, RawRef, RawCount) ->
+build_vsn_string(Vsn, RawRef, Count) ->
%% Cleanup the tag and the Ref information. Basically leading 'v's and
%% whitespace needs to go away.
RefTag = [".ref", re:replace(RawRef, "\\s", "", [global])],
- Count = erlang:iolist_to_binary(re:replace(RawCount, "\\s", "", [global])),
%% Create the valid [semver](http://semver.org) version from the tag
case Count of
- <<"0">> ->
+ 0 ->
erlang:binary_to_list(erlang:iolist_to_binary(Vsn));
_ ->
erlang:binary_to_list(erlang:iolist_to_binary([Vsn, "+build.",
- Count, RefTag]))
+ integer_to_list(Count), RefTag]))
end.
get_patch_count(RawRef) ->
AbortMsg = "Getting rev-list of git dep failed in " ++ rebar_dir:get_cwd(),
Ref = re:replace(RawRef, "\\s", "", [global]),
- Cmd = io_lib:format("git rev-list ~s..HEAD | wc -l",
+ Cmd = io_lib:format("git rev-list ~s..HEAD",
[Ref]),
- rebar_utils:sh(Cmd,
- [{use_stdout, false},
- {debug_abort_on_error, AbortMsg}]).
+ {ok, PatchLines} = rebar_utils:sh(Cmd,
+ [{use_stdout, false},
+ {debug_abort_on_error, AbortMsg}]),
+ rebar_utils:line_count(PatchLines).
+
parse_tags() ->
%% Don't abort on error, we want the bad return to be turned into 0.0.0
- case rebar_utils:sh("git log --oneline --decorate | fgrep \"tag: \" -1000",
+ case rebar_utils:sh("git log --oneline --no-walk --tags --decorate",
[{use_stdout, false}, return_on_error]) of
{error, _} ->
{undefined, "0.0.0"};
diff --git a/src/rebar_mustache.erl b/src/rebar_mustache.erl
deleted file mode 100644
index af8a342..0000000
--- a/src/rebar_mustache.erl
+++ /dev/null
@@ -1,296 +0,0 @@
-%% The MIT License (MIT)
-%%
-%% Copyright (c) 2015 Hinagiku Soranoba
-%%
-%% Permission is hereby granted, free of charge, to any person obtaining a copy
-%% of this software and associated documentation files (the "Software"), to deal
-%% in the Software without restriction, including without limitation the rights
-%% to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
-%% copies of the Software, and to permit persons to whom the Software is
-%% furnished to do so, subject to the following conditions:
-%%
-%% The above copyright notice and this permission notice shall be included in all
-%% copies or substantial portions of the Software.
-%%
-%% @doc Mustache template engine for Erlang/OTP.
--module(rebar_mustache).
-
-%%----------------------------------------------------------------------------------------------------------------------
-%% Exported API
-%%----------------------------------------------------------------------------------------------------------------------
--export([
- render/2,
- parse_binary/1,
- parse_file/1,
- compile/2
- ]).
-
--export_type([
- template/0,
- data/0
- ]).
-
-%%----------------------------------------------------------------------------------------------------------------------
-%% Defines & Records & Types
-%%----------------------------------------------------------------------------------------------------------------------
-
--define(PARSE_ERROR, incorrect_format).
--define(FILE_ERROR, file_not_found).
--define(COND(Cond, TValue, FValue),
- case Cond of true -> TValue; false -> FValue end).
-
--type key() :: binary().
--type tag() :: {n, key()} |
- {'&', key()} |
- {'#', key(), [tag()], Source :: binary()} |
- {'^', key(), [tag()]} |
- binary().
-
--record(state,
- {
- dirname = <<>> :: file:filename_all(),
- start = <<"{{">> :: binary(),
- stop = <<"}}">> :: binary()
- }).
--type state() :: #state{}.
-
--record(?MODULE,
- {
- data :: [tag()]
- }).
-
--opaque template() :: #?MODULE{}.
-%% @see parse_binary/1
-%% @see parse_file/1
--ifdef(namespaced_types).
--type data() :: #{string() => data() | iodata() | fun((data(), function()) -> iodata())}.
--else.
--type data() :: dict().
--endif.
-%% @see render/2
-%% @see compile/2
--type partial() :: {partial, {state(), EndTag :: binary(), LastTagSize :: non_neg_integer(), Rest :: binary(), [tag()]}}.
-
-%%----------------------------------------------------------------------------------------------------------------------
-%% Exported Functions
-%%----------------------------------------------------------------------------------------------------------------------
-
-%% @equiv compile(parse_binary(Bin), Map)
--spec render(binary(), data()) -> binary().
-render(Bin, Map) ->
- compile(parse_binary(Bin), Map).
-
-%% @doc Create a {@link template/0} from a binary.
--spec parse_binary(binary()) -> template().
-parse_binary(Bin) when is_binary(Bin) ->
- parse_binary_impl(#state{}, Bin).
-
-%% @doc Create a {@link template/0} from a file.
--spec parse_file(file:filename()) -> template().
-parse_file(Filename) ->
- case file:read_file(Filename) of
- {ok, Bin} -> parse_binary_impl(#state{dirname = filename:dirname(Filename)}, Bin);
- _ -> error(?FILE_ERROR, [Filename])
- end.
-
-%% @doc Embed the data in the template.
--spec compile(template(), data()) -> binary().
-compile(#?MODULE{data = Tags}, Map) ->
- ec_cnv:to_binary(lists:reverse(compile_impl(Tags, Map, []))).
-
-%%----------------------------------------------------------------------------------------------------------------------
-%% Internal Function
-%%----------------------------------------------------------------------------------------------------------------------
-
-%% @doc {@link compile/2}
-%%
-%% ATTENTION: The result is a list that is inverted.
--spec compile_impl(Template :: [tag()], data(), Result :: iodata()) -> iodata().
-compile_impl([], _, Result) ->
- Result;
-compile_impl([{n, Key} | T], Map, Result) ->
- compile_impl(T, Map, [escape(to_binary(dict_get(binary_to_list(Key), Map, <<>>))) | Result]);
-compile_impl([{'&', Key} | T], Map, Result) ->
- compile_impl(T, Map, [to_binary(dict_get(binary_to_list(Key), Map, <<>>)) | Result]);
-compile_impl([{'#', Key, Tags, Source} | T], Map, Result) ->
- Value = dict_get(binary_to_list(Key), Map, undefined),
- if
- is_list(Value) -> compile_impl(T, Map, lists:foldl(fun(X, Acc) -> compile_impl(Tags, X, Acc) end,
- Result, Value));
- Value =:= false; Value =:= undefined -> compile_impl(T, Map, Result);
- is_function(Value, 2) -> compile_impl(T, Map, [Value(Source, fun(Text) -> render(Text, Map) end) | Result]);
- %is_dict(Value) -> compile_impl(T, Map, compile_impl(Tags, Value, Result));
- true -> compile_impl(T, Map, compile_impl(Tags, Map, Result))
- end;
-compile_impl([{'^', Key, Tags} | T], Map, Result) ->
- Value = dict_get(binary_to_list(Key), Map, undefined),
- case Value =:= undefined orelse Value =:= [] orelse Value =:= false of
- true -> compile_impl(T, Map, compile_impl(Tags, Map, Result));
- false -> compile_impl(T, Map, Result)
- end;
-compile_impl([Bin | T], Map, Result) ->
- compile_impl(T, Map, [Bin | Result]).
-
-%% @see parse_binary/1
--spec parse_binary_impl(state(), Input :: binary()) -> template().
-parse_binary_impl(State, Input) ->
- #?MODULE{data = parse(State, Input)}.
-
-%% @doc Analyze the syntax of the mustache.
--spec parse(state(), binary()) -> [tag()].
-parse(State, Bin) ->
- case parse1(State, Bin, []) of
- {partial, _} -> error(?PARSE_ERROR);
- {_, Tags} -> lists:reverse(Tags)
- end.
-
-%% @doc Part of the `parse/1'
-%%
-%% ATTENTION: The result is a list that is inverted.
--spec parse1(state(), Input :: binary(), Result :: [tag()]) -> {state(), [tag()]} | partial().
-parse1(#state{start = Start, stop = Stop} = State, Bin, Result) ->
- case binary:split(Bin, Start) of
- [] -> {State, Result};
- [B1] -> {State, [B1 | Result]};
- [B1, <<"{", B2/binary>>] -> parse2(State, binary:split(B2, <<"}", Stop/binary>>), [B1 | Result]);
- [B1, B2] -> parse3(State, binary:split(B2, Stop), [B1 | Result])
- end.
-
-%% @doc Part of the `parse/1'
-%%
-%% ATTENTION: The result is a list that is inverted.
-parse2(State, [B1, B2], Result) ->
- parse1(State, B2, [{'&', remove_space_from_edge(B1)} | Result]);
-parse2(_, _, _) ->
- error(?PARSE_ERROR).
-
-%% @doc Part of the `parse/1'
-%%
-%% ATTENTION: The result is a list that is inverted.
-parse3(State, [B1, B2], Result) ->
- case remove_space_from_head(B1) of
- <<"&", Tag/binary>> ->
- parse1(State, B2, [{'&', remove_space_from_edge(Tag)} | Result]);
- <<T, Tag/binary>> when T =:= $#; T =:= $^ ->
- parse_loop(State, ?COND(T =:= $#, '#', '^'), remove_space_from_edge(Tag), B2, Result);
- <<"=", Tag0/binary>> ->
- Tag1 = remove_space_from_tail(Tag0),
- Size = byte_size(Tag1) - 1,
- case Size >= 0 andalso Tag1 of
- <<Tag2:Size/binary, "=">> -> parse_delimiter(State, Tag2, B2, Result);
- _ -> error(?PARSE_ERROR)
- end;
- <<"!", _/binary>> ->
- parse1(State, B2, Result);
- <<"/", Tag/binary>> ->
- {partial, {State, remove_space_from_edge(Tag), byte_size(B1) + 4, B2, Result}};
- <<">", Tag/binary>> ->
- parse_jump(State, remove_space_from_edge(Tag), B2, Result);
- Tag ->
- parse1(State, B2, [{n, remove_space_from_tail(Tag)} | Result])
- end;
-parse3(_, _, _) ->
- error(?PARSE_ERROR).
-
-%% @doc Loop processing part of the `parse/1'
-%%
-%% `{{# Tag}}' or `{{^ Tag}}' corresponds to this.
--spec parse_loop(state(), '#' | '^', Tag :: binary(), Input :: binary(), Result :: [tag()]) -> [tag()] | partial().
-parse_loop(State0, Mark, Tag, Input, Result0) ->
- case parse1(State0, Input, []) of
- {partial, {State, Tag, LastTagSize, Rest, Result1}} when is_list(Result1) ->
- case Mark of
- '#' -> Source = binary:part(Input, 0, byte_size(Input) - byte_size(Rest) - LastTagSize),
- parse1(State, Rest, [{'#', Tag, lists:reverse(Result1), Source} | Result0]);
- '^' -> parse1(State, Rest, [{'^', Tag, lists:reverse(Result1)} | Result0])
- end;
- _ ->
- error(?PARSE_ERROR)
- end.
-
-%% @doc Partial part of the `parse/1'
--spec parse_jump(state(), Tag :: binary(), NextBin :: binary(), Result :: [tag()]) -> [tag()] | partial().
-parse_jump(#state{dirname = Dirname} = State0, Tag, NextBin, Result0) ->
- Filename0 = <<Tag/binary, ".mustache">>,
- Filename = filename:join(?COND(Dirname =:= <<>>, [Filename0], [Dirname, Filename0])),
- case file:read_file(Filename) of
- {ok, Bin} ->
- case parse1(State0, Bin, Result0) of
- {partial, _} -> error(?PARSE_ERROR);
- {State, Result} -> parse1(State, NextBin, Result)
- end;
- _ ->
- error(?FILE_ERROR, [Filename])
- end.
-
-%% @doc Update delimiter part of the `parse/1'
-%%
-%% Parse_BinaryDelimiterBin :: e.g. `{{=%% %%=}}' -> `%% %%'
--spec parse_delimiter(state(), Parse_BinaryDelimiterBin :: binary(), NextBin :: binary(), Result :: [tag()]) -> [tag()] | partial().
-parse_delimiter(State0, Parse_BinaryDelimiterBin, NextBin, Result) ->
- case binary:match(Parse_BinaryDelimiterBin, <<"=">>) of
- nomatch ->
- case [X || X <- binary:split(Parse_BinaryDelimiterBin, <<" ">>, [global]), X =/= <<>>] of
- [Start, Stop] -> parse1(State0#state{start = Start, stop = Stop}, NextBin, Result);
- _ -> error(?PARSE_ERROR)
- end;
- _ ->
- error(?PARSE_ERROR)
- end.
-
-%% @doc Remove the space from the edge.
--spec remove_space_from_edge(binary()) -> binary().
-remove_space_from_edge(Bin) ->
- remove_space_from_tail(remove_space_from_head(Bin)).
-
-%% @doc Remove the space from the head.
--spec remove_space_from_head(binary()) -> binary().
-remove_space_from_head(<<" ", Rest/binary>>) -> remove_space_from_head(Rest);
-remove_space_from_head(Bin) -> Bin.
-
-%% @doc Remove the space from the tail.
--spec remove_space_from_tail(binary()) -> binary().
-remove_space_from_tail(<<>>) -> <<>>;
-remove_space_from_tail(Bin) ->
- PosList = binary:matches(Bin, <<" ">>),
- LastPos = remove_space_from_tail_impl(lists:reverse(PosList), byte_size(Bin)),
- binary:part(Bin, 0, LastPos).
-
-%% @see remove_space_from_tail/1
--spec remove_space_from_tail_impl([{non_neg_integer(), pos_integer()}], non_neg_integer()) -> non_neg_integer().
-remove_space_from_tail_impl([{X, Y} | T], Size) when Size =:= X + Y ->
- remove_space_from_tail_impl(T, X);
-remove_space_from_tail_impl(_, Size) ->
- Size.
-
-%% @doc Number to binary
--spec to_binary(number() | binary() | string()) -> binary() | string().
-to_binary(Integer) when is_integer(Integer) ->
- ec_cnv:to_binary(Integer);
-to_binary(Float) when is_float(Float) ->
- io_lib:format("~p", [Float]);
-to_binary(X) ->
- X.
-
-%% @doc HTML Escape
--spec escape(iodata()) -> binary().
-escape(IoData) ->
- Bin = ec_cnv:to_binary(IoData),
- << <<(escape_char(X))/binary>> || <<X:8>> <= Bin >>.
-
-%% @see escape/1
--spec escape_char(0..16#FFFF) -> binary().
-escape_char($<) -> <<"&lt;">>;
-escape_char($>) -> <<"&gt;">>;
-escape_char($&) -> <<"&amp;">>;
-escape_char($") -> <<"&quot;">>;
-escape_char($') -> <<"&apos;">>;
-escape_char(C) -> <<C:8>>.
-
-dict_get(Key, Dict, Default) ->
- case dict:find(ec_cnv:to_atom(Key), Dict) of
- {ok, Value} ->
- Value;
- error ->
- Default
- end.
diff --git a/src/rebar_prv_app_discovery.erl b/src/rebar_prv_app_discovery.erl
index 31c0f59..97862c1 100644
--- a/src/rebar_prv_app_discovery.erl
+++ b/src/rebar_prv_app_discovery.erl
@@ -45,5 +45,13 @@ do(State) ->
-spec format_error(any()) -> iolist().
format_error({multiple_app_files, Files}) ->
io_lib:format("Multiple app files found in one app dir: ~s", [string:join(Files, " and ")]);
+format_error({invalid_app_file, File, Reason}) ->
+ case Reason of
+ {Line, erl_parse, Description} ->
+ io_lib:format("Invalid app file ~s at line ~b: ~p",
+ [File, Line, lists:flatten(Description)]);
+ _ ->
+ io_lib:format("Invalid app file ~s: ~p", [File, Reason])
+ end;
format_error(Reason) ->
io_lib:format("~p", [Reason]).
diff --git a/src/rebar_prv_shell.erl b/src/rebar_prv_shell.erl
index 6153952..ec2f692 100644
--- a/src/rebar_prv_shell.erl
+++ b/src/rebar_prv_shell.erl
@@ -52,7 +52,7 @@ init(State) ->
{example, "rebar3 shell"},
{short_desc, "Run shell with project apps and deps in path."},
{desc, info()},
- {opts, []}])),
+ {opts, [{config, undefined, "config", string, "Path to the config file to use. Defaults to the sys_config defined for relx, if present."}]}])),
{ok, State1}.
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
@@ -96,6 +96,8 @@ shell(State) ->
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
%% add project app test paths
ok = add_test_paths(State),
+ %% try to read in sys.config file
+ ok = reread_config(State),
%% this call never returns (until user quits shell)
timer:sleep(infinity).
@@ -129,3 +131,61 @@ add_test_paths(State) ->
end, rebar_state:project_apps(State)),
_ = code:add_path(filename:join([rebar_dir:base_dir(State), "test"])),
ok.
+
+reread_config(State) ->
+ case find_config(State) of
+ no_config ->
+ ok;
+ {ok, ConfigList} ->
+ lists:foreach(fun ({Application, Items}) ->
+ lists:foreach(fun ({Key, Val}) ->
+ application:set_env(Application, Key, Val)
+ end,
+ Items)
+ end,
+ ConfigList);
+ {error, Error} ->
+ ?ABORT("Error while attempting to read configuration file: ~p", [Error])
+ end.
+
+% First try the --config flag, then try the relx sys_config
+-spec find_config(rebar_state:t()) -> {ok, [tuple()]}|no_config|{error, tuple()}.
+find_config(State) ->
+ case find_config_option(State) of
+ no_config ->
+ find_config_relx(State);
+ Result ->
+ Result
+ end.
+
+-spec find_config_option(rebar_state:t()) -> {ok, [tuple()]}|no_config|{error, tuple()}.
+find_config_option(State) ->
+ {Opts, _} = rebar_state:command_parsed_args(State),
+ case proplists:get_value(config, Opts) of
+ undefined ->
+ no_config;
+ Filename ->
+ consult_config(State, Filename)
+ end.
+
+-spec find_config_relx(rebar_state:t()) -> {ok, [tuple()]}|no_config|{error, tuple()}.
+find_config_relx(State) ->
+ case proplists:get_value(sys_config, rebar_state:get(State, relx, [])) of
+ undefined ->
+ no_config;
+ Filename ->
+ consult_config(State, Filename)
+ end.
+
+-spec consult_config(rebar_state:t(), string()) -> {ok, [tuple()]}|{error, tuple()}.
+consult_config(State, Filename) ->
+ Fullpath = filename:join(rebar_dir:root_dir(State), Filename),
+ ?DEBUG("Loading configuration from ~p", [Fullpath]),
+ case file:consult(Fullpath) of
+ {ok, [Config]} ->
+ {ok, Config};
+ {ok, []} ->
+ {ok, []};
+ {error, Error} ->
+ {error, {Error, Fullpath}}
+ end.
diff --git a/src/rebar_templater.erl b/src/rebar_templater.erl
index 1bd4e09..c5cec9f 100644
--- a/src/rebar_templater.erl
+++ b/src/rebar_templater.erl
@@ -380,4 +380,4 @@ write_file(Output, Data, Force) ->
%% Render a binary to a string, using mustache and the specified context
%%
render(Bin, Context) ->
- rebar_mustache:render(ec_cnv:to_binary(Bin), dict:from_list(Context)).
+ mustache:render(ec_cnv:to_binary(Bin), Context).
diff --git a/src/rebar_utils.erl b/src/rebar_utils.erl
index b7a9583..4f0bc80 100644
--- a/src/rebar_utils.erl
+++ b/src/rebar_utils.erl
@@ -53,7 +53,8 @@
get_arch/0,
wordsize/0,
tup_umerge/2,
- tup_sort/1]).
+ tup_sort/1,
+ line_count/1]).
%% for internal use only
-export([otp_release/0]).
@@ -281,6 +282,11 @@ umerge([], Olds, Merged, CmpMerged, Cmp) when CmpMerged == Cmp ->
umerge([], Olds, Merged, _CmpMerged, Cmp) ->
lists:reverse(Olds, [Cmp | Merged]).
+%% Implements wc -l functionality used to determine patchcount from git output
+line_count(PatchLines) ->
+ Tokenized = string:tokens(PatchLines, "\n"),
+ {ok, length(Tokenized)}.
+
%% ====================================================================
%% Internal functions
%% ====================================================================