File 2335-Add-shell-shortcut-for-recompiling-existing-modules.patch of Package erlang

From 0eb45e21d406539caaad98bfc1740f9a11e32565 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <richardc@klarna.com>
Date: Tue, 6 Dec 2016 12:14:18 +0100
Subject: [PATCH 5/8] Add shell shortcut for recompiling existing modules

This extends the shell function c/1 and c/2 so that if the argument is a
module name instead of a file name, it automatically locates the .beam file
and the corresponding source file, and then recompiles the module using the
same compiler options (plus any options passed to c/2). If compilation
fails, the old beam file is preserved. Also adds c(Mod, Opts, Filter),
where the Filter argument allows you to remove old compiler options before
the new options are added.
---
 lib/stdlib/doc/src/c.xml         |  26 +++-
 lib/stdlib/doc/src/shell.xml     |  10 +-
 lib/stdlib/src/c.erl             | 254 ++++++++++++++++++++++++++++++++++-----
 lib/stdlib/src/shell_default.erl |   3 +-
 lib/stdlib/test/shell_SUITE.erl  |   2 +-
 5 files changed, 252 insertions(+), 43 deletions(-)

diff --git a/lib/stdlib/doc/src/c.xml b/lib/stdlib/doc/src/c.xml
index 55a77d1bc..766669918 100644
--- a/lib/stdlib/doc/src/c.xml
+++ b/lib/stdlib/doc/src/c.xml
@@ -52,13 +52,27 @@
     <func>
       <name name="c" arity="1"/>
       <name name="c" arity="2"/>
-      <fsummary>Compile and load code in a file.</fsummary>
+      <name name="c" arity="3"/>
+      <fsummary>Compile and load a file or module.</fsummary>
       <desc>
-        <p>Compiles and then purges and loads the code for a file.
-          <c><anno>Options</anno></c> defaults to <c>[]</c>. Compilation is
-          equivalent to:</p>
-        <code type="none">
-compile:file(<anno>File</anno>, <anno>Options</anno> ++ [report_errors, report_warnings])</code>
+        <p>Compiles and then purges and loads the code for a module.
+          <c><anno>Module</anno></c> can be either a module name or a source
+          file path, with or without <c>.erl</c> extension.
+          <c><anno>Options</anno></c> defaults to <c>[]</c>.</p>
+        <p>If <c><anno>Module</anno></c> is an atom and is not the path of a
+          source file, then the code path is searched to locate the object
+          file for the module and extract its original compiler options and
+          source path. If the source file is not found in the original
+          location, <seealso
+          marker="filelib#find_source/1"><c>filelib:find_source/1</c></seealso>
+          is used to search for it relative to the directory of the object
+          file.</p>
+        <p>The source file is compiled with the the original
+          options appended to the given <c><anno>Options</anno></c>, the
+          output replacing the old object file if and only if compilation
+          succeeds. A function <c><anno>Filter</anno></c> can be specified
+          for removing elements from from the original compiler options
+          before the new options are added.</p>
         <p>Notice that purging the code means that any processes
           lingering in old code for the module are killed without
           warning. For more information, see <c>code/3</c>.</p>
diff --git a/lib/stdlib/doc/src/shell.xml b/lib/stdlib/doc/src/shell.xml
index d6e8036d4..f52bc39de 100644
--- a/lib/stdlib/doc/src/shell.xml
+++ b/lib/stdlib/doc/src/shell.xml
@@ -165,12 +165,12 @@
       <item>
         <p>Evaluates <c>shell_default:help()</c>.</p>
       </item>
-      <tag><c>c(File)</c></tag>
+      <tag><c>c(Mod)</c></tag>
       <item>
-        <p>Evaluates <c>shell_default:c(File)</c>. This compiles
-          and loads code in <c>File</c> and purges old versions of
-          code, if necessary. Assumes that the file and module names
-          are the same.</p>
+        <p>Evaluates <c>shell_default:c(Mod)</c>. This compiles and
+          loads the module <c>Mod</c> and purges old versions of the
+          code, if necessary. <c>Mod</c> can be either a module name or a
+          a source file path, with or without <c>.erl</c> extension.</p>
       </item>
       <tag><c>catch_exception(Bool)</c></tag>
       <item>
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index d36630214..d3f9a9c7a 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -23,7 +23,7 @@
 
 %% Avoid warning for local function error/2 clashing with autoimported BIF.
 -compile({no_auto_import,[error/2]}).
--export([help/0,lc/1,c/1,c/2,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0,
+-export([help/0,lc/1,c/1,c/2,c/3,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0,
          y/1, y/2,
 	 lc_batch/0, lc_batch/1,
 	 i/3,pid/3,m/0,m/1,mm/0,lm/0,
@@ -44,7 +44,7 @@
 
 help() ->
     io:put_chars(<<"bt(Pid)    -- stack backtrace for a process\n"
-		   "c(File)    -- compile and load code in <File>\n"
+		   "c(Mod)     -- compile and load module or file <Mod>\n"
 		   "cd(Dir)    -- change working directory\n"
 		   "flush()    -- flush any messages sent to the shell\n"
 		   "help()     -- help info\n"
@@ -72,32 +72,222 @@ help() ->
 		   "xm(M)      -- cross reference check a module\n"
 		   "y(File)    -- generate a Yecc parser\n">>).
 
-%% c(FileName)
-%%  Compile a file/module.
+%% c(Module)
+%%  Compile a module/file.
 
--spec c(File) -> {'ok', Module} | 'error' when
-      File :: file:name(),
-      Module :: module().
+-spec c(Module) -> {'ok', ModuleName} | 'error' when
+      Module :: file:name(),
+      ModuleName :: module().
 
-c(File) -> c(File, []).
+c(Module) -> c(Module, []).
 
--spec c(File, Options) -> {'ok', Module} | 'error' when
-      File :: file:name(),
+-spec c(Module, Options) -> {'ok', ModuleName} | 'error' when
+      Module :: file:name(),
       Options :: [compile:option()],
-      Module :: module().
+      ModuleName :: module().
+
+c(Module, Opts) when is_atom(Module) ->
+    %% either a module name or a source file name (possibly without
+    %% suffix); if such a source file exists, it is used to compile from
+    %% scratch with the given options, otherwise look for an object file
+    Suffix = case filename:extension(Module) of
+                 "" -> src_suffix(Opts);
+                 S -> S
+             end,
+    SrcFile = filename:rootname(Module, Suffix) ++ Suffix,
+    case filelib:is_file(SrcFile) of
+        true ->
+            compile_and_load(SrcFile, Opts);
+        false ->
+            c(Module, Opts, fun (_) -> true end)
+    end;
+c(Module, Opts) ->
+    %% we never interpret a string as a module name, only as a file
+    compile_and_load(Module, Opts).
+
+%% This tries to find an existing object file and use its compile_info and
+%% source path to recompile the module, overwriting the old object file.
+%% The Filter parameter is applied to the old compile options
+
+-spec c(Module, Options, Filter) -> {'ok', ModuleName} | 'error' when
+      Module :: atom(),
+      Options :: [compile:option()],
+      Filter :: fun ((compile:option()) -> boolean()),
+      ModuleName :: module().
+
+c(Module, Options, Filter) when is_atom(Module) ->
+    case find_beam(Module) of
+        BeamFile when is_list(BeamFile) ->
+            c(Module, Options, Filter, BeamFile);
+        Error ->
+            {error, Error}
+    end.
+
+c(Module, Options, Filter, BeamFile) ->
+    case compile_info(Module, BeamFile) of
+        Info when is_list(Info) ->
+            case find_source(BeamFile, Info) of
+                SrcFile when is_list(SrcFile) ->
+                    c(SrcFile, Options, Filter, BeamFile, Info);
+                Error ->
+                    Error
+            end;
+        Error ->
+            Error
+    end.
+
+c(SrcFile, NewOpts, Filter, BeamFile, Info) ->
+    %% Filter old options; also remove options that will be replaced.
+    %% Write new beam over old beam unless other outdir is specified.
+    F = fun (Opt) -> not is_outdir_opt(Opt) andalso Filter(Opt) end,
+    Options = (NewOpts ++ [{outdir,filename:dirname(BeamFile)}]
+               ++ lists:filter(F, old_options(Info))),
+    format("Recompiling ~s\n", [SrcFile]),
+    safe_recompile(SrcFile, Options, BeamFile).
+
+old_options(Info) ->
+    case lists:keyfind(options, 1, Info) of
+        {options, Opts} -> Opts;
+        false -> []
+    end.
+
+%% prefer the source path in the compile info if the file exists,
+%% otherwise do a standard source search relative to the beam file
+find_source(BeamFile, Info) ->
+    case lists:keyfind(source, 1, Info) of
+        {source, SrcFile} ->
+            case filelib:is_file(SrcFile) of
+                true -> SrcFile;
+                false -> find_source(BeamFile)
+            end;
+        _ ->
+            find_source(BeamFile)
+    end.
+
+find_source(BeamFile) ->
+    case filelib:find_source(BeamFile) of
+        {ok, SrcFile} -> SrcFile;
+        _ -> {error, no_source}
+    end.
 
-c(File, Opts0) when is_list(Opts0) ->
-    Opts = [report_errors,report_warnings|Opts0],
+%% find the beam file for a module, preferring the path reported by code:which()
+%% if it still exists, or otherwise by searching the code path
+find_beam(Module) when is_atom(Module) ->
+    case code:which(Module) of
+        Beam when is_list(Beam), Beam =/= "" ->
+            case erlang:module_loaded(Module) of
+                false ->
+                    Beam;  % code:which/1 found this in the path
+                true ->
+                    case filelib:is_file(Beam) of
+                        true -> Beam;
+                        false -> find_beam_1(Module)  % file moved?
+                    end
+            end;
+        Other when Other =:= ""; Other =:= cover_compiled ->
+            %% module is loaded but not compiled directly from source
+            find_beam_1(Module);
+        Error ->
+            Error
+    end.
+
+find_beam_1(Module) ->
+    File = atom_to_list(Module) ++ code:objfile_extension(),
+    case code:where_is_file(File) of
+        Beam when is_list(Beam) ->
+            Beam;
+        Error ->
+            Error
+    end.
+
+%% get the compile_info for a module
+%% -will report the info for the module in memory, if loaded
+%% -will try to find and examine the beam file if not in memory
+%% -will not cause a module to become loaded by accident
+compile_info(Module, Beam) when is_atom(Module) ->
+    case erlang:module_loaded(Module) of
+        true ->
+            %% getting the compile info for a loaded module should normally
+            %% work, but return an empty info list if it fails
+            try erlang:get_module_info(Module, compile)
+            catch _:_ -> []
+            end;
+        false ->
+            case beam_lib:chunks(Beam, [compile_info]) of
+                {ok, {_Module, [{compile_info, Info}]}} ->
+                    Info;
+                Error ->
+                    Error
+            end
+    end.
+
+%% compile module, backing up any existing target file and restoring the
+%% old version if compilation fails (this should only be used when we have
+%% an old beam file that we want to preserve)
+safe_recompile(File, Options, BeamFile) ->
+    %% Note that it's possible that because of options such as 'to_asm',
+    %% the compiler might not actually write a new beam file at all
+    Backup = BeamFile ++ ".bak",
+    case file:rename(BeamFile, Backup) of
+        Status when Status =:= ok; Status =:= {error,enoent} ->
+            case compile_and_load(File, Options) of
+                {ok, _} = Result ->
+                    _ = if Status =:= ok -> file:delete(Backup);
+                           true -> ok
+                        end,
+                    Result;
+                Error ->
+                    _ = if Status =:= ok -> file:rename(Backup, BeamFile);
+                           true -> ok
+                        end,
+                    Error
+            end;
+        Error ->
+            Error
+    end.
+
+%% Compile the file and load the resulting object code (if any).
+%% Automatically ensures that there is an outdir option, by default the
+%% directory of File, and that a 'from' option will be passed to match the
+%% actual source suffix if needed (unless already specified).
+compile_and_load(File, Opts0) when is_list(Opts0) ->
+    Opts = [report_errors, report_warnings
+            | ensure_from(filename:extension(File),
+                          ensure_outdir(filename:dirname(File), Opts0))],
     case compile:file(File, Opts) of
 	{ok,Mod} ->				%Listing file.
-	    machine_load(Mod, File, Opts);
+	    purge_and_load(Mod, File, Opts);
 	{ok,Mod,_Ws} ->				%Warnings maybe turned on.
-	    machine_load(Mod, File, Opts);
+	    purge_and_load(Mod, File, Opts);
 	Other ->				%Errors go here
 	    Other
     end;
-c(File, Opt) -> 
-    c(File, [Opt]).
+compile_and_load(File, Opt) ->
+    compile_and_load(File, [Opt]).
+
+ensure_from(Suffix, Opts0) ->
+    case lists:partition(fun is_from_opt/1, Opts0++from_opt(Suffix)) of
+        {[Opt|_], Opts} -> [Opt | Opts];
+        {[], Opts} -> Opts
+    end.
+
+ensure_outdir(Dir, Opts0) ->
+    {[Opt|_], Opts} = lists:partition(fun is_outdir_opt/1,
+                                      Opts0++[{outdir,Dir}]),
+    [Opt | Opts].
+
+is_outdir_opt({outdir, _}) -> true;
+is_outdir_opt(_) -> false.
+
+is_from_opt(from_core) -> true;
+is_from_opt(from_asm) -> true;
+is_from_opt(from_beam) -> true;
+is_from_opt(_) -> false.
+
+from_opt(".core") -> [from_core];
+from_opt(".S")    -> [from_asm];
+from_opt(".beam") -> [from_beam];
+from_opt(_)       -> [].
 
 %%% Obtain the 'outdir' option from the argument. Return "." if no
 %%% such option was given.
@@ -113,18 +303,29 @@ outdir([Opt|Rest]) ->
 	    outdir(Rest)
     end.
 
+%% mimic how suffix is selected in compile:file().
+src_suffix([from_core|_]) -> ".core";
+src_suffix([from_asm|_])  -> ".S";
+src_suffix([from_beam|_]) -> ".beam";
+src_suffix([_|Opts]) -> src_suffix(Opts);
+src_suffix([]) -> ".erl".
+
 %%% We have compiled File with options Opts. Find out where the
-%%% output file went to, and load it.
-machine_load(Mod, File, Opts) ->
+%%% output file went and load it, purging any old version.
+purge_and_load(Mod, File, Opts) ->
     Dir = outdir(Opts),
-    File2 = filename:join(Dir, filename:basename(File, ".erl")),
+    Base = filename:basename(File, src_suffix(Opts)),
+    OutFile = filename:join(Dir, Base),
     case compile:output_generated(Opts) of
 	true ->
-	    Base = atom_to_list(Mod),
-	    case filename:basename(File, ".erl") of
+	    case atom_to_list(Mod) of
 		Base ->
 		    code:purge(Mod),
-		    check_load(code:load_abs(File2,Mod), Mod);
+                    %% Note that load_abs() adds the object file suffix
+		    case code:load_abs(OutFile, Mod) of
+                        {error, _R}=Error -> Error;
+                        _ -> {ok, Mod}
+                    end;
 		_OtherMod ->
 		    format("** Module name '~p' does not match file name '~tp' **~n",
 			   [Mod,File]),
@@ -135,13 +336,6 @@ machine_load(Mod, File, Opts) ->
 	    ok
     end.
 
-%%% This function previously warned if the loaded module was
-%%% loaded from some other place than current directory.
-%%% Now, loading from other than current directory is supposed to work.
-%%% so this function does nothing special.
-check_load({error, _R} = Error, _) -> Error;
-check_load(_, Mod) -> {ok, Mod}.
-
 %% Compile a list of modules
 %% enables the nice unix shell cmd
 %% erl -s c lc f1 f2 f3 @d c1=v1 @c2 @i IDir @o ODir -s erlang halt
diff --git a/lib/stdlib/src/shell_default.erl b/lib/stdlib/src/shell_default.erl
index cd63ab28b..a0c1d9851 100644
--- a/lib/stdlib/src/shell_default.erl
+++ b/lib/stdlib/src/shell_default.erl
@@ -23,7 +23,7 @@
 
 -module(shell_default).
 
--export([help/0,lc/1,c/1,c/2,nc/1,nl/1,l/1,i/0,pid/3,i/3,m/0,m/1,lm/0,mm/0,
+-export([help/0,lc/1,c/1,c/2,c/3,nc/1,nl/1,l/1,i/0,pid/3,i/3,m/0,m/1,lm/0,mm/0,
          memory/0,memory/1,uptime/0,
 	 erlangrc/1,bi/1, regs/0, flush/0,pwd/0,ls/0,ls/1,cd/1, 
          y/1, y/2,
@@ -72,6 +72,7 @@ bi(I) 		-> c:bi(I).
 bt(Pid)		-> c:bt(Pid).
 c(File) 	-> c:c(File).
 c(File, Opt)    -> c:c(File, Opt).
+c(File, Opt, Filter) -> c:c(File, Opt, Filter).
 cd(D)           -> c:cd(D).
 erlangrc(X) 	-> c:erlangrc(X).
 flush()         -> c:flush().
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 15ccdea28..4864bc3d7 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -282,7 +282,7 @@ restricted_local(Config) when is_list(Config) ->
 	comm_err(<<"begin F=fun() -> hello end, foo(F) end.">>),
     "exception error: undefined shell command banan/1" =
 	comm_err(<<"begin F=fun() -> hello end, banan(F) end.">>),
-    "{error,"++_ = t(<<"begin F=fun() -> hello end, c(F) end.">>),
+    "Recompiling "++_ = t(<<"c(shell_SUITE).">>),
     "exception exit: restricted shell does not allow l(" ++ _ =
 	comm_err(<<"begin F=fun() -> hello end, l(F) end.">>),
     "exception error: variable 'F' is unbound" =
-- 
2.11.1

openSUSE Build Service is sponsored by