File 2243-tools-Allow-Emake-options-to-be-passed-in-explicitly.patch of Package erlang

From 532a74a36a889e3d7d25004ebce70da62b013755 Mon Sep 17 00:00:00 2001
From: Anthony Jackson <anthony@betaplum.com>
Date: Fri, 3 Mar 2017 10:57:58 +0200
Subject: [PATCH] tools: Allow Emake options to be passed in explicitly

This allows build scripts to use emake without needing to generate
an Emakefile before running make:all/0,1 or make:file/1,2.
---
 lib/tools/doc/src/make.xml    | 24 ++++++++------
 lib/tools/src/make.erl        | 76 +++++++++++++++++++++++--------------------
 lib/tools/test/make_SUITE.erl | 18 ++++++++--
 3 files changed, 70 insertions(+), 48 deletions(-)

diff --git a/lib/tools/doc/src/make.xml b/lib/tools/doc/src/make.xml
index fddf5ebd7..6b878f72f 100644
--- a/lib/tools/doc/src/make.xml
+++ b/lib/tools/doc/src/make.xml
@@ -43,15 +43,15 @@
       <fsummary>Compile a set of modules.</fsummary>
       <type>
         <v>Options = [Option]</v>
-        <v>&nbsp;Option = noexec | load | netload | &lt;compiler option&gt;</v>
+	<v>&nbsp;Option = noexec | load | netload | {emake, Emake} | &lt;compiler option&gt;</v>
       </type>
       <desc>
-        <p>This function first looks in the current working directory
-          for a file named <c>Emakefile</c> (see below) specifying the
-          set of modules to compile and the compile options to use. If
-          no such file is found, the set of modules to compile
-          defaults to all modules in the current working
-          directory.</p>
+      <p>This function determines the set of modules to compile and the
+          compile options to use, by first looking for the <c>emake</c> make
+          option, if not present reads the configuration from a file named
+          <c>Emakefile</c> (see below). If no such file is found, the
+          set of modules to compile defaults to all modules in the
+          current working directory.</p>
         <p>Traversing the set of modules, it then recompiles every module for
           which at least one of the following conditions apply:</p>
         <list type="bulleted">
@@ -77,6 +77,9 @@
           <item><c>netload</c>          <br></br>
 
            Net load mode. Loads all recompiled modules on all known nodes.</item>
+          <item><c>{emake, Emake}</c>          <br></br>
+
+           Rather than reading the <c>Emakefile</c> specify configuration explicitly.</item>
         </list>
         <p>All items in <c>Options</c> that are not make options are assumed
           to be compiler options and are passed as-is to
@@ -108,9 +111,10 @@
 
   <section>
     <title>Emakefile</title>
-    <p><c>make:all/0,1</c> and <c>make:files/1,2</c> looks in the
-      current working directory for a file named <c>Emakefile</c>. If
-      it exists, <c>Emakefile</c> should contain elements like this:</p>
+    <p><c>make:all/0,1</c> and <c>make:files/1,2</c> first looks for
+      <c>{emake, Emake}</c> in options, then in the current working directory
+      for a file named <c>Emakefile</c>. If present <c>Emake</c> should
+      contain elements like this:</p>
     <code type="none">
 Modules.
 {Modules,Options}.    </code>
diff --git a/lib/tools/src/make.erl b/lib/tools/src/make.erl
index 37e67cbe3..60695febb 100644
--- a/lib/tools/src/make.erl
+++ b/lib/tools/src/make.erl
@@ -29,7 +29,7 @@
 
 -include_lib("kernel/include/file.hrl").
 
--define(MakeOpts,[noexec,load,netload,noload]).
+-define(MakeOpts,[noexec,load,netload,noload,emake]).
 
 all_or_nothing() ->
     case all() of
@@ -43,29 +43,30 @@ all() ->
     all([]).
 
 all(Options) ->
-    {MakeOpts,CompileOpts} = sort_options(Options,[],[]),
-    case read_emakefile('Emakefile',CompileOpts) of
-	Files when is_list(Files) ->
-	    do_make_files(Files,MakeOpts);
-	error ->
-	    error
-    end.
+    run_emake(undefined, Options).
 
 files(Fs) ->
     files(Fs, []).
 
 files(Fs0, Options) ->
     Fs = [filename:rootname(F,".erl") || F <- Fs0],
+    run_emake(Fs, Options).
+
+run_emake(Mods, Options) ->
     {MakeOpts,CompileOpts} = sort_options(Options,[],[]),
-    case get_opts_from_emakefile(Fs,'Emakefile',CompileOpts) of
+    Emake = get_emake(Options),
+    case normalize_emake(Emake, Mods, CompileOpts) of
 	Files when is_list(Files) ->
-	    do_make_files(Files,MakeOpts);	    
-	error -> error
+	    do_make_files(Files,MakeOpts);
+	error ->
+	    error
     end.
 
 do_make_files(Fs, Opts) ->
     process(Fs, lists:member(noexec, Opts), load_opt(Opts)).
 
+sort_options([{emake, _}=H|T],Make,Comp) ->
+  sort_options(T,[H|Make],Comp);
 
 sort_options([H|T],Make,Comp) ->
     case lists:member(H,?MakeOpts) of
@@ -89,20 +90,35 @@ sort_options([],Make,Comp) ->
 %%%
 %%% These elements are converted to [{ModList,OptList},...]
 %%% ModList is a list of modulenames (strings)
-read_emakefile(Emakefile,Opts) ->
-    case file:consult(Emakefile) of
-	{ok,Emake} ->
+
+normalize_emake(EmakeRaw, Mods, Opts) ->
+    case EmakeRaw of
+	{ok, Emake} when Mods =:= undefined ->
 	    transform(Emake,Opts,[],[]);
-	{error,enoent} ->
+	{ok, Emake} when is_list(Mods) ->
+	    ModsOpts = transform(Emake,Opts,[],[]),
+	    ModStrings = [coerce_2_list(M) || M <- Mods],
+	    get_opts_from_emakefile(ModsOpts,ModStrings,Opts,[]); 
+	{error,enoent} when Mods =:= undefined ->
 	    %% No Emakefile found - return all modules in current 
 	    %% directory and the options given at command line
-	    Mods = [filename:rootname(F) ||  F <- filelib:wildcard("*.erl")],
+	    CwdMods = [filename:rootname(F) ||  F <- filelib:wildcard("*.erl")],
+	    [{CwdMods, Opts}];
+	{error,enoent} when is_list(Mods) ->
 	    [{Mods, Opts}];
-	{error,Other} ->
-	    io:format("make: Trouble reading 'Emakefile':~n~tp~n",[Other]),
+	{error, Error} ->
+	    io:format("make: Trouble reading 'Emakefile':~n~tp~n",[Error]),
 	    error
     end.
 
+get_emake(Opts) ->
+    case proplists:get_value(emake, Opts, false) of
+	false ->
+	    file:consult('Emakefile');
+	OptsEmake ->
+	    {ok, OptsEmake}
+    end.
+
 transform([{Mod,ModOpts}|Emake],Opts,Files,Already) ->
     case expand(Mod,Already) of
 	[] -> 
@@ -143,31 +159,19 @@ expand(Mod,Already) ->
 	    end
     end.
 
-%%% Reads the given Emakefile to see if there are any specific compile 
+%%% Reads the given Emake to see if there are any specific compile 
 %%% options given for the modules.
-get_opts_from_emakefile(Mods,Emakefile,Opts) ->
-    case file:consult(Emakefile) of
-	{ok,Emake} ->
-	    Modsandopts = transform(Emake,Opts,[],[]),
-	    ModStrings = [coerce_2_list(M) || M <- Mods],
-	    get_opts_from_emakefile2(Modsandopts,ModStrings,Opts,[]); 
-	{error,enoent} ->
-	    [{Mods, Opts}];
-	{error,Other} ->
-	    io:format("make: Trouble reading 'Emakefile':~n~tp~n",[Other]),
-	    error
-    end.
 
-get_opts_from_emakefile2([{MakefileMods,O}|Rest],Mods,Opts,Result) ->
+get_opts_from_emakefile([{MakefileMods,O}|Rest],Mods,Opts,Result) ->
     case members(Mods,MakefileMods,[],Mods) of
 	{[],_} -> 
-	    get_opts_from_emakefile2(Rest,Mods,Opts,Result);
+	    get_opts_from_emakefile(Rest,Mods,Opts,Result);
 	{I,RestOfMods} ->
-	    get_opts_from_emakefile2(Rest,RestOfMods,Opts,[{I,O}|Result])
+	    get_opts_from_emakefile(Rest,RestOfMods,Opts,[{I,O}|Result])
     end;
-get_opts_from_emakefile2([],[],_Opts,Result) ->
+get_opts_from_emakefile([],[],_Opts,Result) ->
     Result;
-get_opts_from_emakefile2([],RestOfMods,Opts,Result) ->
+get_opts_from_emakefile([],RestOfMods,Opts,Result) ->
     [{RestOfMods,Opts}|Result].
     
 members([H|T],MakefileMods,I,Rest) ->
diff --git a/lib/tools/test/make_SUITE.erl b/lib/tools/test/make_SUITE.erl
index e6284db8b..2a94ead32 100644
--- a/lib/tools/test/make_SUITE.erl
+++ b/lib/tools/test/make_SUITE.erl
@@ -20,7 +20,7 @@
 -module(make_SUITE).
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
-         init_per_group/2,end_per_group/2, make_all/1, make_files/1]).
+         init_per_group/2,end_per_group/2, make_all/1, make_files/1, emake_opts/1]).
 -export([otp_6057_init/1,
          otp_6057_a/1, otp_6057_b/1, otp_6057_c/1,
          otp_6057_end/1]).
@@ -40,7 +40,7 @@
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() -> 
-    [make_all, make_files, {group, otp_6057}].
+    [make_all, make_files, emake_opts, {group, otp_6057}].
 
 groups() -> 
     [{otp_6057,[],[otp_6057_a, otp_6057_b,
@@ -86,6 +86,20 @@ make_files(Config) when is_list(Config) ->
     ensure_no_messages(),
     ok.
 
+emake_opts(Config) when is_list(Config) ->
+    Current = prepare_data_dir(Config),
+
+    %% prove that emake is used in opts instead of local Emakefile
+    Opts = [{emake, [test8, test9]}],
+    error = make:all(Opts),
+    error = make:files([test9], Opts),
+    "test8.beam" = ensure_exists([test8]),
+    "test9.beam" = ensure_exists([test9]),
+    "test5.S" = ensure_exists(["test5"],".S"),
+
+    file:set_cwd(Current),
+    ensure_no_messages(),
+    ok.
 
 %% Moves to the data directory of this suite, clean it from any object
 %% files (*.jam for a JAM emulator).  Returns the previous directory.
-- 
2.12.0

openSUSE Build Service is sponsored by