File 0322-Fix-bug-in-hybrid-boot-file-used-for-restart_new_emu.patch of Package erlang

From 74afc0655a455913caf1cebdadcf869653e7947f Mon Sep 17 00:00:00 2001
From: Siri Hansen <siri@erlang.org>
Date: Fri, 13 Apr 2018 17:33:08 +0200
Subject: [PATCH] Fix bug in hybrid boot file used for restart_new_emulator

The old hybrid did not update preloaded and mandatory module lists and
kernel processes.
---
 lib/sasl/src/release_handler.erl |  14 +--
 lib/sasl/src/systools_make.erl   | 193 +++++++++++++++++++++++++--------------
 lib/sasl/test/systools_SUITE.erl |  30 +++---
 3 files changed, 146 insertions(+), 91 deletions(-)

diff --git a/lib/sasl/src/release_handler.erl b/lib/sasl/src/release_handler.erl
index d0a7c7332d..49756f5799 100644
--- a/lib/sasl/src/release_handler.erl
+++ b/lib/sasl/src/release_handler.erl
@@ -1052,8 +1052,8 @@ new_emulator_make_tmp_release(CurrentRelease,ToRelease,RelDir,Opts,Masters) ->
     ToVsn = ToRelease#release.vsn,
     TmpVsn = ?tmp_vsn(CurrentVsn),
     case get_base_libs(ToRelease#release.libs) of
-	{ok,{Kernel,Stdlib,Sasl}=BaseLibs,_} ->
-	    case get_base_libs(ToRelease#release.libs) of
+	{ok,{Kernel,Stdlib,Sasl},_} ->
+	    case get_base_libs(CurrentRelease#release.libs) of
 		{ok,_,RestLibs} ->
 		    TmpErtsVsn = ToRelease#release.erts_vsn,
 		    TmpLibs = [Kernel,Stdlib,Sasl|RestLibs],
@@ -1062,7 +1062,7 @@ new_emulator_make_tmp_release(CurrentRelease,ToRelease,RelDir,Opts,Masters) ->
 							libs = TmpLibs,
 							status = unpacked},
 		    new_emulator_make_hybrid_boot(CurrentVsn,ToVsn,TmpVsn,
-						  BaseLibs,RelDir,Opts,Masters),
+						  RelDir,Opts,Masters),
 		    new_emulator_make_hybrid_config(CurrentVsn,ToVsn,TmpVsn,
 						    RelDir,Masters),
 		    {TmpVsn,TmpRelease};
@@ -1095,7 +1095,7 @@ get_base_libs([],_Kernel,_Stdlib,undefined,_Rest) ->
 get_base_libs([],Kernel,Stdlib,Sasl,Rest) ->
     {ok,{Kernel,Stdlib,Sasl},lists:reverse(Rest)}.
 
-new_emulator_make_hybrid_boot(CurrentVsn,ToVsn,TmpVsn,BaseLibs,RelDir,Opts,Masters) ->
+new_emulator_make_hybrid_boot(CurrentVsn,ToVsn,TmpVsn,RelDir,Opts,Masters) ->
     FromBootFile = filename:join([RelDir,CurrentVsn,"start.boot"]),
     ToBootFile = filename:join([RelDir,ToVsn,"start.boot"]),
     TmpBootFile = filename:join([RelDir,TmpVsn,"start.boot"]),
@@ -1103,11 +1103,7 @@ new_emulator_make_hybrid_boot(CurrentVsn,ToVsn,TmpVsn,BaseLibs,RelDir,Opts,Maste
     Args = [ToVsn,Opts],
     {ok,FromBoot} = read_file(FromBootFile,Masters),
     {ok,ToBoot} = read_file(ToBootFile,Masters),
-    {{_,_,KernelPath},{_,_,StdlibPath},{_,_,SaslPath}} = BaseLibs,
-    Paths = {filename:join(KernelPath,"ebin"),
-	     filename:join(StdlibPath,"ebin"),
-	     filename:join(SaslPath,"ebin")},
-    case systools_make:make_hybrid_boot(TmpVsn,FromBoot,ToBoot,Paths,Args) of
+    case systools_make:make_hybrid_boot(TmpVsn,FromBoot,ToBoot,Args) of
 	{ok,TmpBoot} ->
 	    write_file(TmpBootFile,TmpBoot,Masters);
 	{error,Reason} ->
diff --git a/lib/sasl/src/systools_make.erl b/lib/sasl/src/systools_make.erl
index 391b1fb5cc..ffd5ecdf6d 100644
--- a/lib/sasl/src/systools_make.erl
+++ b/lib/sasl/src/systools_make.erl
@@ -32,7 +32,7 @@
 
 -export([read_application/4]).
 
--export([make_hybrid_boot/5]).
+-export([make_hybrid_boot/4]).
 
 -import(lists, [filter/2, keysort/2, keysearch/3, map/2, reverse/1,
 		append/1, foldl/3,  member/2, foreach/2]).
@@ -178,94 +178,153 @@ return({error,Mod,Error},_,Flags) ->
 %% and sasl.
 %%
 %% TmpVsn = string(),
-%% Paths = {KernelPath,StdlibPath,SaslPath}
 %% Returns {ok,Boot} | {error,Reason}
 %% Boot1 = Boot2 = Boot = binary()
 %% Reason = {app_not_found,App} | {app_not_replaced,App}
-%% App = kernel | stdlib | sasl
-make_hybrid_boot(TmpVsn, Boot1, Boot2, Paths, Args) ->
-    catch do_make_hybrid_boot(TmpVsn, Boot1, Boot2, Paths, Args).
-do_make_hybrid_boot(TmpVsn, Boot1, Boot2, Paths, Args) ->
-    {script,{_RelName1,_RelVsn1},Script1} = binary_to_term(Boot1),
-    {script,{RelName2,_RelVsn2},Script2} = binary_to_term(Boot2),
-    MatchPaths = get_regexp_path(Paths),
-    NewScript1 = replace_paths(Script1,MatchPaths),
-    {Kernel,Stdlib,Sasl} = get_apps(Script2,undefined,undefined,undefined),
-    NewScript2 = replace_apps(NewScript1,Kernel,Stdlib,Sasl),
-    NewScript3 = add_apply_upgrade(NewScript2,Args),
-    Boot = term_to_binary({script,{RelName2,TmpVsn},NewScript3}),
+%% App = stdlib | sasl
+make_hybrid_boot(TmpVsn, Boot1, Boot2, Args) ->
+    catch do_make_hybrid_boot(TmpVsn, Boot1, Boot2, Args).
+do_make_hybrid_boot(TmpVsn, OldBoot, NewBoot, Args) ->
+    {script,{_RelName1,_RelVsn1},OldScript} = binary_to_term(OldBoot),
+    {script,{NewRelName,_RelVsn2},NewScript} = binary_to_term(NewBoot),
+
+    %% Everyting upto kernel_load_completed must come from the new script
+    Fun1 = fun({progress,kernel_load_completed}) -> false;
+              (_) -> true
+           end,
+    {_OldKernelLoad,OldRest1} = lists:splitwith(Fun1,OldScript),
+    {NewKernelLoad,NewRest1} = lists:splitwith(Fun1,NewScript),
+
+    Fun2 = fun({progress,modules_loaded}) -> false;
+              (_) -> true
+           end,
+    {OldModLoad,OldRest2} = lists:splitwith(Fun2,OldRest1),
+    {NewModLoad,NewRest2} = lists:splitwith(Fun2,NewRest1),
+
+    Fun3 = fun({kernelProcess,_,_}) -> false;
+              (_) -> true
+           end,
+    {OldPaths,OldRest3} = lists:splitwith(Fun3,OldRest2),
+    {NewPaths,NewRest3} = lists:splitwith(Fun3,NewRest2),
+
+    Fun4 = fun({progress,init_kernel_started}) -> false;
+              (_) -> true
+           end,
+    {_OldKernelProcs,OldApps} = lists:splitwith(Fun4,OldRest3),
+    {NewKernelProcs,NewApps} = lists:splitwith(Fun4,NewRest3),
+
+    %% Then comes all module load, which for each app consist of:
+    %% {path,[AppPath]},
+    %% {primLoad,ModuleList}
+    %% Replace kernel, stdlib and sasl here
+    MatchPaths = get_regexp_path(),
+    ModLoad = replace_module_load(OldModLoad,NewModLoad,MatchPaths),
+    Paths = replace_paths(OldPaths,NewPaths,MatchPaths),
+
+    {Stdlib,Sasl} = get_apps(NewApps,undefined,undefined),
+    Apps0 = replace_apps(OldApps,Stdlib,Sasl),
+    Apps = add_apply_upgrade(Apps0,Args),
+
+    Script = NewKernelLoad++ModLoad++Paths++NewKernelProcs++Apps,
+    Boot = term_to_binary({script,{NewRelName,TmpVsn},Script}),
     {ok,Boot}.
 
 %% For each app, compile a regexp that can be used for finding its path
-get_regexp_path({KernelPath,StdlibPath,SaslPath}) ->
+get_regexp_path() ->
     {ok,KernelMP} = re:compile("kernel-[0-9\.]+",[unicode]),
     {ok,StdlibMP} = re:compile("stdlib-[0-9\.]+",[unicode]),
     {ok,SaslMP} = re:compile("sasl-[0-9\.]+",[unicode]),
-    [{KernelMP,KernelPath},{StdlibMP,StdlibPath},{SaslMP,SaslPath}].
-
-%% For each path in the script, check if it matches any of the MPs
-%% found above, and if so replace it with the correct new path.
-replace_paths([{path,Path}|Script],MatchPaths) ->
-    [{path,replace_path(Path,MatchPaths)}|replace_paths(Script,MatchPaths)];
-replace_paths([Stuff|Script],MatchPaths) ->
-    [Stuff|replace_paths(Script,MatchPaths)];
-replace_paths([],_) ->
+    [KernelMP,StdlibMP,SaslMP].
+
+replace_module_load(Old,New,[MP|MatchPaths]) ->
+    replace_module_load(do_replace_module_load(Old,New,MP),New,MatchPaths);
+replace_module_load(Script,_,[]) ->
+    Script.
+
+do_replace_module_load([{path,[OldAppPath]},{primLoad,OldMods}|OldRest],New,MP) ->
+    case re:run(OldAppPath,MP,[{capture,none}]) of
+        nomatch ->
+            [{path,[OldAppPath]},{primLoad,OldMods}|
+             do_replace_module_load(OldRest,New,MP)];
+        match ->
+            get_module_load(New,MP) ++ OldRest
+    end;
+do_replace_module_load([Other|Rest],New,MP) ->
+    [Other|do_replace_module_load(Rest,New,MP)];
+do_replace_module_load([],_,_) ->
+    [].
+
+get_module_load([{path,[AppPath]},{primLoad,Mods}|Rest],MP) ->
+    case re:run(AppPath,MP,[{capture,none}]) of
+        nomatch ->
+            get_module_load(Rest,MP);
+        match ->
+            [{path,[AppPath]},{primLoad,Mods}]
+    end;
+get_module_load([_|Rest],MP) ->
+    get_module_load(Rest,MP);
+get_module_load([],_) ->
     [].
 
-replace_path([Path|Paths],MatchPaths) ->
-    [do_replace_path(Path,MatchPaths)|replace_path(Paths,MatchPaths)];
-replace_path([],_) ->
+replace_paths([{path,OldPaths}|Old],New,MatchPaths) ->
+    {path,NewPath} = lists:keyfind(path,1,New),
+    [{path,do_replace_paths(OldPaths,NewPath,MatchPaths)}|Old];
+replace_paths([Other|Old],New,MatchPaths) ->
+    [Other|replace_paths(Old,New,MatchPaths)].
+
+do_replace_paths(Old,New,[MP|MatchPaths]) ->
+    do_replace_paths(do_replace_paths1(Old,New,MP),New,MatchPaths);
+do_replace_paths(Paths,_,[]) ->
+    Paths.
+
+do_replace_paths1([P|Ps],New,MP) ->
+    case re:run(P,MP,[{capture,none}]) of
+        nomatch ->
+            [P|do_replace_paths1(Ps,New,MP)];
+        match ->
+            get_path(New,MP) ++ Ps
+    end;
+do_replace_paths1([],_,_) ->
     [].
 
-do_replace_path(Path,[{MP,ReplacePath}|MatchPaths]) ->
-    case re:run(Path,MP,[{capture,none}]) of
-	nomatch -> do_replace_path(Path,MatchPaths);
-	match -> ReplacePath
+get_path([P|Ps],MP) ->
+    case re:run(P,MP,[{capture,none}]) of
+        nomatch ->
+            get_path(Ps,MP);
+        match ->
+            [P]
     end;
-do_replace_path(Path,[]) ->
-    Path.
-
-%% Return the entries for loading the three base applications
-get_apps([{kernelProcess,application_controller,
-	   {application_controller,start,[{application,kernel,_}]}}=Kernel|
-	  Script],_,Stdlib,Sasl) ->
-    get_apps(Script,Kernel,Stdlib,Sasl);
+get_path([],_) ->
+    [].
+
+
+%% Return the entries for loading stdlib and sasl
 get_apps([{apply,{application,load,[{application,stdlib,_}]}}=Stdlib|Script],
-	 Kernel,_,Sasl) ->
-    get_apps(Script,Kernel,Stdlib,Sasl);
+	 _,Sasl) ->
+    get_apps(Script,Stdlib,Sasl);
 get_apps([{apply,{application,load,[{application,sasl,_}]}}=Sasl|_Script],
-	 Kernel,Stdlib,_) ->
-    {Kernel,Stdlib,Sasl};
-get_apps([_|Script],Kernel,Stdlib,Sasl) ->
-    get_apps(Script,Kernel,Stdlib,Sasl);
-get_apps([],undefined,_,_) ->
-    throw({error,{app_not_found,kernel}});
-get_apps([],_,undefined,_) ->
+	 Stdlib,_) ->
+    {Stdlib,Sasl};
+get_apps([_|Script],Stdlib,Sasl) ->
+    get_apps(Script,Stdlib,Sasl);
+get_apps([],undefined,_) ->
     throw({error,{app_not_found,stdlib}});
-get_apps([],_,_,undefined) ->
+get_apps([],_,undefined) ->
     throw({error,{app_not_found,sasl}}).
 
-
-%% Replace the entries for loading the base applications
-replace_apps([{kernelProcess,application_controller,
-	       {application_controller,start,[{application,kernel,_}]}}|
-	      Script],Kernel,Stdlib,Sasl) ->
-    [Kernel|replace_apps(Script,undefined,Stdlib,Sasl)];
+%% Replace the entries for loading the stdlib and sasl
 replace_apps([{apply,{application,load,[{application,stdlib,_}]}}|Script],
-	     Kernel,Stdlib,Sasl) ->
-    [Stdlib|replace_apps(Script,Kernel,undefined,Sasl)];
+	     Stdlib,Sasl) ->
+    [Stdlib|replace_apps(Script,undefined,Sasl)];
 replace_apps([{apply,{application,load,[{application,sasl,_}]}}|Script],
-	     _Kernel,_Stdlib,Sasl) ->
+	     _Stdlib,Sasl) ->
     [Sasl|Script];
-replace_apps([Stuff|Script],Kernel,Stdlib,Sasl) ->
-    [Stuff|replace_apps(Script,Kernel,Stdlib,Sasl)];
-replace_apps([],undefined,undefined,_) ->
+replace_apps([Stuff|Script],Stdlib,Sasl) ->
+    [Stuff|replace_apps(Script,Stdlib,Sasl)];
+replace_apps([],undefined,_) ->
     throw({error,{app_not_replaced,sasl}});
-replace_apps([],undefined,_,_) ->
-    throw({error,{app_not_replaced,stdlib}});
-replace_apps([],_,_,_) ->
-    throw({error,{app_not_replaced,kernel}}).
-
+replace_apps([],_,_) ->
+    throw({error,{app_not_replaced,stdlib}}).
 
 %% Finally add an apply of release_handler:new_emulator_upgrade - which will
 %% complete the execution of the upgrade script (relup).
@@ -275,8 +334,6 @@ add_apply_upgrade(Script,Args) ->
 		   {apply,{release_handler,new_emulator_upgrade,Args}} |
 		   RevScript]).
 
-
-
 %%-----------------------------------------------------------------
 %% Create a release package from a release file.
 %% Options is a list of {path, Path} | silent |
diff --git a/lib/sasl/test/systools_SUITE.erl b/lib/sasl/test/systools_SUITE.erl
index 07748d975f..6e83b4c2e2 100644
--- a/lib/sasl/test/systools_SUITE.erl
+++ b/lib/sasl/test/systools_SUITE.erl
@@ -1760,27 +1760,28 @@ normal_hybrid(Config) ->
 
     ok = file:set_cwd(OldDir),
 
-    BasePaths = {"testkernelpath","teststdlibpath","testsaslpath"},
     {ok,Hybrid} = systools_make:make_hybrid_boot("tmp_vsn",Boot1,Boot2,
-						 BasePaths, [dummy,args]),
+                                                 [dummy,args]),
 
     {script,{"Test release","tmp_vsn"},Script} = binary_to_term(Hybrid),
     ct:log("~p.~n",[Script]),
 
     %% Check that all paths to base apps are replaced by paths from BaseLib
     Boot1Str = io_lib:format("~p~n",[binary_to_term(Boot1)]),
+    Boot2Str = io_lib:format("~p~n",[binary_to_term(Boot2)]),
     HybridStr = io_lib:format("~p~n",[binary_to_term(Hybrid)]),
     ReOpts = [global,{capture,first,list},unicode],
     {match,OldKernelMatch} = re:run(Boot1Str,"kernel-[0-9\.]+",ReOpts),
     {match,OldStdlibMatch} = re:run(Boot1Str,"stdlib-[0-9\.]+",ReOpts),
     {match,OldSaslMatch} = re:run(Boot1Str,"sasl-[0-9\.]+",ReOpts),
 
-    nomatch = re:run(HybridStr,"kernel-[0-9\.]+",ReOpts),
-    nomatch = re:run(HybridStr,"stdlib-[0-9\.]+",ReOpts),
-    nomatch = re:run(HybridStr,"sasl-[0-9\.]+",ReOpts),
-    {match,NewKernelMatch} = re:run(HybridStr,"testkernelpath",ReOpts),
-    {match,NewStdlibMatch} = re:run(HybridStr,"teststdlibpath",ReOpts),
-    {match,NewSaslMatch} = re:run(HybridStr,"testsaslpath",ReOpts),
+    {match,NewKernelMatch} = re:run(Boot2Str,"kernel-[0-9\.]+",ReOpts),
+    {match,NewStdlibMatch} = re:run(Boot2Str,"stdlib-[0-9\.]+",ReOpts),
+    {match,NewSaslMatch} = re:run(Boot2Str,"sasl-[0-9\.]+",ReOpts),
+
+    {match,NewKernelMatch} = re:run(HybridStr,"kernel-[0-9\.]+",ReOpts),
+    {match,NewStdlibMatch} = re:run(HybridStr,"stdlib-[0-9\.]+",ReOpts),
+    {match,NewSaslMatch} = re:run(HybridStr,"sasl-[0-9\.]+",ReOpts),
 
     NewKernelN = length(NewKernelMatch),
     NewKernelN = length(OldKernelMatch),
@@ -1789,6 +1790,11 @@ normal_hybrid(Config) ->
     NewSaslN = length(NewSaslMatch),
     NewSaslN = length(OldSaslMatch),
 
+    %% Check that kernelProcesses are taken from new boot script
+    {script,_,Script2} = binary_to_term(Boot2),
+    NewKernelProcs = [KP || KP={kernelProcess,_,_} <- Script2],
+    NewKernelProcs = [KP || KP={kernelProcess,_,_} <- Script],
+
     %% Check that application load instruction has correct versions
     Apps = application:loaded_applications(),
     {_,_,KernelVsn} = lists:keyfind(kernel,1,Apps),
@@ -1859,10 +1865,8 @@ hybrid_no_old_sasl(Config) ->
     {ok,Boot1} = file:read_file(Name1 ++ ".boot"),
     {ok,Boot2} = file:read_file(Name2 ++ ".boot"),
 
-    BasePaths = {"testkernelpath","teststdlibpath","testsaslpath"},
     {error,{app_not_replaced,sasl}} =
-	systools_make:make_hybrid_boot("tmp_vsn",Boot1,Boot2,
-				       BasePaths,[dummy,args]),
+	systools_make:make_hybrid_boot("tmp_vsn",Boot1,Boot2,[dummy,args]),
 
     ok = file:set_cwd(OldDir),
     ok.
@@ -1892,10 +1896,8 @@ hybrid_no_new_sasl(Config) ->
     {ok,Boot1} = file:read_file(Name1 ++ ".boot"),
     {ok,Boot2} = file:read_file(Name2 ++ ".boot"),
 
-    BasePaths = {"testkernelpath","teststdlibpath","testsaslpath"},
     {error,{app_not_found,sasl}} =
-	systools_make:make_hybrid_boot("tmp_vsn",Boot1,Boot2,
-				       BasePaths,[dummy,args]),
+	systools_make:make_hybrid_boot("tmp_vsn",Boot1,Boot2,[dummy,args]),
 
     ok = file:set_cwd(OldDir),
     ok.
-- 
2.16.3

openSUSE Build Service is sponsored by