Skip to content

Commit 2235876

Browse files
authored
Merge pull request #2948 from richcarl/shell-env-subst-defaults
Support env variable substitution with defaults in rebar shell
2 parents f7f9f33 + d1606ef commit 2235876

File tree

3 files changed

+76
-67
lines changed

3 files changed

+76
-67
lines changed

apps/rebar/src/rebar_file_utils.erl

Lines changed: 74 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,8 @@
2828

2929
-export([try_consult/1,
3030
consult_config/2,
31+
consult_env_config/2,
32+
consult_any_config/2,
3133
consult_config_terms/2,
3234
format_error/1,
3335
symlink_or_copy/2,
@@ -83,6 +85,37 @@ consult_config(State, Filename) ->
8385
end,
8486
consult_config_terms(State, Config).
8587

88+
%% @doc Reads a config file via consult_env_config/2 if the file name has
89+
%% the suffix `.src`, and with consult_config/2 otherwise
90+
-spec consult_any_config(rebar_state:t(), file:filename()) -> [[tuple()]].
91+
consult_any_config(State, Filename) ->
92+
case is_src_config(Filename) of
93+
false ->
94+
consult_config(State, Filename);
95+
true ->
96+
consult_env_config(State, Filename)
97+
end.
98+
99+
-spec is_src_config(file:filename()) -> boolean().
100+
is_src_config(Filename) ->
101+
filename:extension(Filename) =:= ".src".
102+
103+
%% @doc Like consult_config/2 but expanding environment variables
104+
%% as for a sys.config.src file
105+
-spec consult_env_config(rebar_state:t(), file:filename()) -> [[tuple()]].
106+
consult_env_config(State, Filename) ->
107+
RawString = case file:read_file(Filename) of
108+
{error, _} -> "[].";
109+
{ok, Bin} -> unicode:characters_to_list(Bin)
110+
end,
111+
ReplacedStr = replace_env_vars(RawString),
112+
case rebar_string:consult(unicode:characters_to_list(ReplacedStr)) of
113+
{error, Reason} ->
114+
throw(?PRV_ERROR({bad_term_file, Filename, Reason}));
115+
[Terms] ->
116+
consult_config_terms(State, Terms)
117+
end.
118+
86119
%% @doc From a parsed sys.config file, expand all the terms to include
87120
%% its potential nested configs. It is also possible that no sub-terms
88121
%% (i.e. the config file does not refer to "some/other/file.config")
@@ -108,6 +141,41 @@ consult_config_terms(State, Config) ->
108141
format_error({bad_term_file, AppFile, Reason}) ->
109142
io_lib:format("Error reading file ~ts: ~ts", [AppFile, file:format_error(Reason)]).
110143

144+
%% @doc quick and simple variable substitution writeup.
145+
%% Supports `${varname}' but not `$varname' nor nested
146+
%% values such as `${my_${varname}}'.
147+
%% The variable are also defined as only supporting
148+
%% the form `[a-zA-Z_]+[a-zA-Z0-9_]*' as per the POSIX
149+
%% standard.
150+
-spec replace_env_vars(string()) -> unicode:charlist().
151+
replace_env_vars("") -> "";
152+
replace_env_vars("${" ++ Str) ->
153+
case until_var_end(Str) of
154+
{ok, VarName, Default, Rest} ->
155+
replace_varname(VarName, Default) ++ replace_env_vars(Rest);
156+
error ->
157+
"${" ++ replace_env_vars(Str)
158+
end;
159+
replace_env_vars([Char|Str]) ->
160+
[Char | replace_env_vars(Str)].
161+
162+
until_var_end(Str) ->
163+
case re:run(Str, "^([a-zA-Z_]+[a-zA-Z0-9_]*)(:-([^}]*))?}", [{capture, [1,3], list}]) of
164+
nomatch ->
165+
error;
166+
{match, [Name,Default]} ->
167+
%% the Default part will be "" if not present
168+
Rest = lists:nthtail(length(Name) + length(Default) + 1, Str),
169+
{ok, Name, Default, Rest}
170+
end.
171+
172+
replace_varname(Var, Default) ->
173+
%% os:getenv(Var, "") is only available in OTP-18.0
174+
case os:getenv(Var) of
175+
false -> Default;
176+
Val -> Val
177+
end.
178+
111179
symlink_or_copy(Source, Target) ->
112180
Link = case os:type() of
113181
{win32, _} ->
@@ -551,17 +619,17 @@ delete_each_dir_win32([Dir | Rest]) ->
551619
xcopy_win32(Source,Dest, Options)->
552620
%% "xcopy \"~ts\" \"~ts\" /q /y /e 2> nul", Changed to robocopy to
553621
%% handle long names. May have issues with older windows.
554-
622+
555623
CopySubdirectories = "/e",
556624
DontFollow = "/sl",
557-
625+
558626
Opt = [CopySubdirectories],
559627
% By default Windows follows symbolic links except if the "/sl" options is given.
560628
% Add "/sl" for default so it doesn't follow symbolic links and behaves more like unix
561629
OptStr = case proplists:get_value(dereference, Options, false) of
562-
true ->
630+
true ->
563631
string:join(Opt, " ");
564-
false ->
632+
false ->
565633
% Default option
566634
string:join([DontFollow|Opt], " ")
567635
end,
@@ -612,10 +680,10 @@ cp_r_win32({false, Source},{false, Dest}, Options) ->
612680
true ->
613681
{ok, _} = file:copy(Source, Dest),
614682
ok;
615-
false ->
683+
false ->
616684
file:make_symlink(OriginalFile, Dest)
617685
end;
618-
_ ->
686+
_ ->
619687
{ok, _} = file:copy(Source, Dest),
620688
ok
621689
end,

apps/rebar/src/rebar_prv_common_test.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -311,7 +311,7 @@ select_tests(State, ProjectApps, CmdOpts, CfgOpts) ->
311311
%% set application env if sys_config argument is provided
312312
SysConfigs = sys_config_list(CmdOpts, CfgOpts),
313313
Configs = lists:flatmap(fun(Filename) ->
314-
rebar_file_utils:consult_config(State, Filename)
314+
rebar_file_utils:consult_any_config(State, Filename)
315315
end, SysConfigs),
316316
%% NB: load the applications (from user directories too) to support OTP < 17
317317
%% to our best ability.

apps/rebar/src/rebar_prv_shell.erl

Lines changed: 1 addition & 60 deletions
Original file line numberDiff line numberDiff line change
@@ -580,12 +580,7 @@ find_config(State) ->
580580
no_value ->
581581
no_config;
582582
Filename when is_list(Filename) ->
583-
case is_src_config(Filename) of
584-
false ->
585-
rebar_file_utils:consult_config(State, Filename);
586-
true ->
587-
consult_env_config(State, Filename)
588-
end
583+
rebar_file_utils:consult_any_config(State, Filename)
589584
end.
590585

591586
-spec first_value([Fun], State) -> no_value | Value when
@@ -643,24 +638,6 @@ find_config_relx(State) ->
643638
Src
644639
end.
645640

646-
-spec is_src_config(file:filename()) -> boolean().
647-
is_src_config(Filename) ->
648-
filename:extension(Filename) =:= ".src".
649-
650-
-spec consult_env_config(rebar_state:t(), file:filename()) -> [[tuple()]].
651-
consult_env_config(State, Filename) ->
652-
RawString = case file:read_file(Filename) of
653-
{error, _} -> "[].";
654-
{ok, Bin} -> unicode:characters_to_list(Bin)
655-
end,
656-
ReplacedStr = replace_env_vars(RawString),
657-
case rebar_string:consult(unicode:characters_to_list(ReplacedStr)) of
658-
{error, Reason} ->
659-
throw(?PRV_ERROR({bad_term_file, Filename, Reason}));
660-
[Terms] ->
661-
rebar_file_utils:consult_config_terms(State, Terms)
662-
end.
663-
664641
maybe_set_env_vars(State) ->
665642
EnvFile =debug_get_value(env_file, rebar_state:get(State, shell, []), undefined,
666643
"Found env_file from config."),
@@ -699,39 +676,3 @@ maybe_read_file(undefined) ->
699676
ignore;
700677
maybe_read_file(EnvFile) ->
701678
file:read_file(EnvFile).
702-
703-
%% @doc quick and simple variable substitution writeup.
704-
%% Supports `${varname}' but not `$varname' nor nested
705-
%% values such as `${my_${varname}}'.
706-
%% The variable are also defined as only supporting
707-
%% the form `[a-zA-Z_]+[a-zA-Z0-9_]*' as per the POSIX
708-
%% standard.
709-
-spec replace_env_vars(string()) -> unicode:charlist().
710-
replace_env_vars("") -> "";
711-
replace_env_vars("${" ++ Str) ->
712-
case until_var_end(Str) of
713-
{ok, VarName, Rest} ->
714-
replace_varname(VarName) ++ replace_env_vars(Rest);
715-
error ->
716-
"${" ++ replace_env_vars(Str)
717-
end;
718-
replace_env_vars([Char|Str]) ->
719-
[Char | replace_env_vars(Str)].
720-
721-
until_var_end(Str) ->
722-
case re:run(Str, "([a-zA-Z_]+[a-zA-Z0-9_]*)}", [{capture, [1], list}]) of
723-
nomatch ->
724-
error;
725-
{match, [Name]} ->
726-
{ok, Name, drop_varname(Name, Str)}
727-
end.
728-
729-
replace_varname(Var) ->
730-
%% os:getenv(Var, "") is only available in OTP-18.0
731-
case os:getenv(Var) of
732-
false -> "";
733-
Val -> Val
734-
end.
735-
736-
drop_varname("", "}" ++ Str) -> Str;
737-
drop_varname([_|Var], [_|Str]) -> drop_varname(Var, Str).

0 commit comments

Comments
 (0)