Skip to content

Commit

Permalink
Merge pull request #2420 from tsloughter/make_script_tar/OTP-16561
Browse files Browse the repository at this point in the history
systools: support creating start.boot in make_script and adding files to make_tar
  • Loading branch information
garazdawi committed Mar 20, 2020
2 parents 6456dec + b88c96a commit be01e1f
Show file tree
Hide file tree
Showing 3 changed files with 152 additions and 17 deletions.
15 changes: 12 additions & 3 deletions lib/sasl/doc/src/systools.xml
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@
<v>Name = string()</v>
<v>Opt = src_tests | {path,[Dir]} | local | {variables,[Var]} | exref |
{exref,[App]}] | silent | {outdir,Dir} | no_dot_erlang | no_warn_sasl |
warnings_as_errors</v>
warnings_as_errors | {script_name, Name}</v>
<v>&nbsp;Dir = string()</v>
<v>&nbsp;Var = {VarName,Prefix}</v>
<v>&nbsp;&nbsp;VarName = Prefix = string()</v>
Expand All @@ -154,7 +154,9 @@
</type>
<desc>
<p>Generates a boot script <c>Name.script</c> and its binary
version, the boot file <c>Name.boot</c>. The boot file
version, the boot file <c>Name.boot</c>, unless the <c>{script_name, ScriptName}</c>
option is given, in which case the names are <c>ScriptName.script</c>
and <c>ScriptName.boot</c> The boot file
specifies which code to be loaded and which applications
to be started when the Erlang runtime system is started.
See <seealso marker="script"><c>script(4)</c></seealso>.</p>
Expand Down Expand Up @@ -268,7 +270,7 @@
<fsummary>Creates a release package.</fsummary>
<type>
<v>Name = string()</v>
<v>Opt = {dirs,[IncDir]} | {path,[Dir]} | {variables,[Var]} | {var_tar,VarTar} | {erts,Dir} | src_tests | exref | {exref,[App]} | silent | {outdir,Dir} | | no_warn_sasl | warnings_as_errors</v>
<v>Opt = {dirs,[IncDir]} | {path,[Dir]} | {variables,[Var]} | {var_tar,VarTar} | {erts,Dir} | src_tests | exref | {exref,[App]} | silent | {outdir,Dir} | | no_warn_sasl | warnings_as_errors | {extra_files, ExtraFiles}</v>
<v>&nbsp;Dir = string()</v>
<v>&nbsp;IncDir = src | include | atom()</v>
<v>&nbsp;Var = {VarName,PreFix}</v>
Expand All @@ -279,6 +281,8 @@
<v>Result = ok | error | {ok,Module,Warnings} | {error,Module,Error}</v>
<v>&nbsp;Module = atom()</v>
<v>&nbsp;Warning = Error = term()</v>
<v>&nbsp;ExtraFiles = [{NameInArchive, file:filename_all()}]</v>
<v>&nbsp;NameInArchive = string()</v>
</type>
<desc>
<p>Creates a release package file <c>Name.tar.gz</c>.
Expand Down Expand Up @@ -311,6 +315,11 @@
appended to the current path. Wildcard <c>*</c> is
expanded to all matching directories.
Example: <c>"lib/*/ebin"</c>.</p>
<p>If the <c>{extra_files, ExtraFiles}</c> option is given then the
<c>ExtraFiles</c> are added to the tarball after everything else to be
included has been added. The <c>ExtraFiles</c> list is a list of files
or directories in the same format as the <c>add_type()</c> tuple for
<seealso marker="stdlib:erl_tar#add-3">erl_tar:add/3,4</seealso></p>
<p>Option <c>variables</c> can be used to specify an
installation directory other than <c>lib</c> for some of
the applications. If variable <c>{VarName,Prefix}</c> is
Expand Down
48 changes: 39 additions & 9 deletions lib/sasl/src/systools_make.erl
Original file line number Diff line number Diff line change
Expand Up @@ -78,15 +78,16 @@ make_script(RelName) ->
badarg(RelName,[RelName]).

make_script(RelName, Flags) when is_list(RelName), is_list(Flags) ->
ScriptName = get_script_name(RelName, Flags),
case get_outdir(Flags) of
"" ->
make_script(RelName, RelName, Flags);
make_script(RelName, ScriptName, Flags);
OutDir ->
%% To maintain backwards compatibility for make_script/3,
%% the boot script file name is constructed here, before
%% checking the validity of OutDir
%% (is done in check_args_script/1)
Output = filename:join(OutDir, filename:basename(RelName)),
Output = filename:join(OutDir, filename:basename(ScriptName)),
make_script(RelName, Output, Flags)
end.

Expand Down Expand Up @@ -144,6 +145,12 @@ machine(Flags) ->
_ -> false
end.

get_script_name(RelName, Flags) ->
case get_flag(script_name,Flags) of
{script_name,ScriptName} when is_list(ScriptName) -> ScriptName;
_ -> RelName
end.

get_path(Flags) ->
case get_flag(path,Flags) of
{path,Path} when is_list(Path) -> Path;
Expand Down Expand Up @@ -1669,8 +1676,17 @@ mk_tar(Tar, RelName, Release, Appls, Flags, Path1) ->
add_applications(Appls, Tar, Variables, Flags, false),
add_variable_tars(Variables, Appls, Tar, Flags),
add_system_files(Tar, RelName, Release, Path1),
add_erts_bin(Tar, Release, Flags).

add_erts_bin(Tar, Release, Flags),
add_additional_files(Tar, Flags).

add_additional_files(Tar, Flags) ->
case get_flag(extra_files, Flags) of
{extra_files, ToAdd} ->
[add_to_tar(Tar, From, To) || {From, To} <- ToAdd];
_ ->
ok
end.

add_applications(Appls, Tar, Variables, Flags, Var) ->
Res = foldl(fun({{Name,Vsn},App}, Errs) ->
case catch add_appl(to_list(Name), Vsn, App,
Expand Down Expand Up @@ -1767,11 +1783,16 @@ add_system_files(Tar, RelName, Release, Path1) ->
[RelDir, "."|Path1]
end,

case lookup_file(RelName0 ++ ".boot", Path) of
false ->
throw({error, {tar_error,{add, RelName0++".boot",enoent}}});
Boot ->
add_to_tar(Tar, Boot, filename:join(RelVsnDir, "start.boot"))
case lookup_file("start.boot", Path) of
false ->
case lookup_file(RelName0 ++ ".boot", Path) of
false ->
throw({error, {tar_error, {add, boot, RelName, enoent}}});
Boot ->
add_to_tar(Tar, Boot, filename:join(RelVsnDir, "start.boot"))
end;
Boot ->
add_to_tar(Tar, Boot, filename:join(RelVsnDir, "start.boot"))
end,

case lookup_file("relup", Path) of
Expand Down Expand Up @@ -2189,6 +2210,9 @@ cas([no_module_tests | Args], X) ->
cas(Args, X);
cas([no_dot_erlang | Args], X) ->
cas(Args, X);
%% set the name of the script and boot file to create
cas([{script_name, Name} | Args], X) when is_list(Name) ->
cas(Args, X);

%%% ERROR --------------------------------------------------------------
cas([Y | Args], X) ->
Expand Down Expand Up @@ -2269,6 +2293,9 @@ cat([no_warn_sasl | Args], X) ->
%%% no_module_tests (kept for backwards compatibility, but ignored) ----
cat([no_module_tests | Args], X) ->
cat(Args, X);
cat([{extra_files, ExtraFiles} | Args], X) when is_list(ExtraFiles) ->
cat(Args, X);

%%% ERROR --------------------------------------------------------------
cat([Y | Args], X) ->
cat(Args, X++[Y]).
Expand Down Expand Up @@ -2423,6 +2450,9 @@ form_reading(W) ->
form_tar_err({open, File, Error}) ->
io_lib:format("Cannot open tar file ~ts - ~ts~n",
[File, erl_tar:format_error(Error)]);
form_tar_err({add, boot, RelName, enoent}) ->
io_lib:format("Cannot find file start.boot or ~ts to add to tar file - ~ts~n",
[RelName, erl_tar:format_error(enoent)]);
form_tar_err({add, File, Error}) ->
io_lib:format("Cannot add file ~ts to tar file - ~ts~n",
[File, erl_tar:format_error(Error)]).
Expand Down
106 changes: 101 additions & 5 deletions lib/sasl/test/systools_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ all() ->

groups() ->
[{script, [],
[script_options, normal_script, unicode_script, no_mod_vsn_script,
[script_options, normal_script, start_script, unicode_script, no_mod_vsn_script,
wildcard_script, variable_script, abnormal_script,
no_sasl_script, no_dot_erlang_script,
src_tests_script, crazy_script,
Expand All @@ -66,10 +66,10 @@ groups() ->
duplicate_modules_script,
otp_3065_circular_dependenies, included_and_used_sort_script]},
{tar, [],
[tar_options, normal_tar, no_mod_vsn_tar, system_files_tar,
[tar_options, relname_tar, normal_tar, no_mod_vsn_tar, system_files_tar,
system_src_file_tar, invalid_system_files_tar, variable_tar,
src_tests_tar, var_tar, exref_tar, link_tar, no_sasl_tar,
otp_9507_path_ebin]},
otp_9507_path_ebin, additional_files_tar]},
{relup, [],
[normal_relup, restart_relup, abnormal_relup, no_sasl_relup,
no_appup_relup, bad_appup_relup, app_start_type_relup, regexp_relup
Expand Down Expand Up @@ -235,6 +235,29 @@ normal_script(Config) when is_list(Config) ->
code:set_path(PSAVE), % Restore path
ok.

%% make_script: Check that script can be named start.script
start_script(Config) when is_list(Config) ->
{ok, OldDir} = file:get_cwd(),
PSAVE = code:get_path(), % Save path

{LatestDir, LatestName} = create_script(latest,Config),

DataDir = filename:absname(?copydir),
LibDir = fname([DataDir, d_normal, lib]),
P1 = fname([LibDir, 'db-2.1', ebin]),
P2 = fname([LibDir, 'fe-3.1', ebin]),

true = code:add_patha(P1),
true = code:add_patha(P2),

ok = file:set_cwd(LatestDir),

ok = systools:make_script(filename:basename(LatestName), [{script_name, "start"}]),
{ok, _} = read_script_file("start"), % Check readabillity

ok = file:set_cwd(OldDir),
code:set_path(PSAVE), % Restore path
ok.

%% make_script: Test make_script with unicode .app file
unicode_script(Config) when is_list(Config) ->
Expand Down Expand Up @@ -869,7 +892,7 @@ tar_options(Config) when is_list(Config) ->
ok.


%% make_tar: Check normal case
%% make_tar: Check case of start.boot
normal_tar(Config) when is_list(Config) ->
{ok, OldDir} = file:get_cwd(),

Expand All @@ -882,7 +905,29 @@ normal_tar(Config) when is_list(Config) ->

ok = file:set_cwd(LatestDir),

{ok, _, []} = systools:make_script(LatestName, [silent, {path, P}]),
{ok, _, []} = systools:make_script(LatestName, [silent, {path, P}, {script_name, "start"}]),
ok = systools:make_tar(LatestName, [{path, P}]),
ok = check_tar(fname([lib,'db-2.1',ebin,'db.app']), LatestName),
{ok, _, []} = systools:make_tar(LatestName, [{path, P}, silent]),
ok = check_tar(fname([lib,'fe-3.1',ebin,'fe.app']), LatestName),

ok = file:set_cwd(OldDir),
ok.

%% make_tar: Check case of relname.boot
relname_tar(Config) when is_list(Config) ->
{ok, OldDir} = file:get_cwd(),

{LatestDir, LatestName} = create_script(latest,Config),

DataDir = filename:absname(?copydir),
LibDir = fname([DataDir, d_normal, lib]),
P = [fname([LibDir, 'db-2.1', ebin]),
fname([LibDir, 'fe-3.1', ebin])],

ok = file:set_cwd(LatestDir),

{ok, _, []} = systools:make_script(LatestName, [silent, {path, P}, {script_name, LatestName}]),
ok = systools:make_tar(LatestName, [{path, P}]),
ok = check_tar(fname([lib,'db-2.1',ebin,'db.app']), LatestName),
{ok, _, []} = systools:make_tar(LatestName, [{path, P}, silent]),
Expand Down Expand Up @@ -945,6 +990,57 @@ system_files_tar(Config) ->

ok.

%% make_tar: Check that extra_files are included in the tarball
additional_files_tar(Config) ->
{ok, OldDir} = file:get_cwd(),

{LatestDir, LatestName} = create_script(latest,Config),

DataDir = filename:absname(?copydir),
LibDir = fname([DataDir, d_normal, lib]),
P = [fname([LibDir, 'db-2.1', ebin]),
fname([LibDir, 'fe-3.1', ebin])],

ok = file:set_cwd(LatestDir),

%% Add dummy relup and sys.config
ok = file:write_file("sys.config","[].\n"),
ok = file:write_file("relup","{\"LATEST\",[],[]}.\n"),

%% unrelated files that must be included explicitly
RandomFile = "somefile",
ok = file:write_file(RandomFile,"hello\n"),

TopLevelDir = "some_dir",
TopLevelFile = filename:join(TopLevelDir, "top_level_file"),

filelib:ensure_dir(TopLevelFile),
ok = file:write_file(TopLevelFile, "hello there\n"),

{ok, _, []} = systools:make_script(LatestName, [silent, {path, P}]),
ok = systools:make_tar(LatestName, [{path, P}]),
ok = check_tar(fname(["releases","LATEST","sys.config"]), LatestName),
ok = check_tar(fname(["releases","LATEST","relup"]), LatestName),
%% random file should not be in this tarball
{error, _} = check_tar(fname(["releases","LATEST",RandomFile]), LatestName),

RandomFilePathInTar = filename:join(["releases", "LATEST", RandomFile]),

{ok, _, []} = systools:make_tar(LatestName,
[{path, P}, silent,
{extra_files, [{RandomFile, RandomFilePathInTar},
{TopLevelDir, TopLevelDir}]}]),
ok = check_tar(fname(["releases","LATEST","sys.config"]), LatestName),
ok = check_tar(fname(["releases","LATEST","relup"]), LatestName),

%% random file and dir should be in this tarball
ok = check_tar(fname(["releases","LATEST",RandomFile]), LatestName),
ok = check_tar(fname([TopLevelFile]), LatestName),

ok = file:set_cwd(OldDir),

ok.


system_files_tar(cleanup,Config) ->
Dir = ?privdir,
Expand Down

0 comments on commit be01e1f

Please sign in to comment.