File 0264-Revert-Revert-Revert-dialyzer-Remove-native-code-com.patch of Package erlang

From ffe8727498b7f8d8f13912fedb3303c097bd5210 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Mon, 3 Feb 2020 11:23:12 +0100
Subject: [PATCH 1/2] Revert "Revert "Revert "dialyzer: Remove native code
 compilation"""

This reverts commit 646d72540b0d61ee2b010f5c510a6eeef2dd2ee8.
---
 lib/dialyzer/src/dialyzer_cl.erl | 107 +++++++++++++++++++++++++++++++++++++++
 1 file changed, 107 insertions(+)

diff --git a/lib/dialyzer/src/dialyzer_cl.erl b/lib/dialyzer/src/dialyzer_cl.erl
index 5e680062fb..f887f661bd 100644
--- a/lib/dialyzer/src/dialyzer_cl.erl
+++ b/lib/dialyzer/src/dialyzer_cl.erl
@@ -320,6 +320,12 @@ report_analysis_start(#options{analysis_type = Type,
       end
   end.
 
+report_native_comp(#options{report_mode = ReportMode}) ->
+  case ReportMode of
+    quiet -> ok;
+    _ -> io:format("  Compiling some key modules to native code...")
+  end.
+
 report_elapsed_time(T1, T2, #options{report_mode = ReportMode}) ->
   case ReportMode of
     quiet -> ok;
@@ -369,6 +375,7 @@ do_analysis(Options) ->
   
 do_analysis(Files, Options, Plt, PltInfo) ->
   assert_writable(Options#options.output_plt),
+  hipe_compile(Files, Options),
   report_analysis_start(Options),
   State0 = new_state(),
   State1 = init_output(State0, Options),
@@ -477,6 +484,106 @@ expand_dependent_modules_1([Mod|Mods], Included, ModDeps) ->
 expand_dependent_modules_1([], Included, _ModDeps) ->
   Included.
 
+-define(MIN_PARALLELISM, 7).
+-define(MIN_FILES_FOR_NATIVE_COMPILE, 20).
+
+-spec hipe_compile([file:filename()], #options{}) -> 'ok'.
+
+hipe_compile(Files, #options{erlang_mode = ErlangMode} = Options) ->
+  NoNative = (get(dialyzer_options_native) =:= false),
+  FewFiles = (length(Files) < ?MIN_FILES_FOR_NATIVE_COMPILE),
+  case NoNative orelse FewFiles orelse ErlangMode of
+    true -> ok;
+    false ->
+      case erlang:system_info(hipe_architecture) of
+	undefined -> ok;
+	_ ->
+	  Mods = [lists, dict, digraph, digraph_utils, ets,
+		  gb_sets, gb_trees, ordsets, sets, sofs,
+		  cerl, erl_types, cerl_trees, erl_bif_types,
+		  dialyzer_analysis_callgraph, dialyzer, dialyzer_behaviours,
+		  dialyzer_codeserver, dialyzer_contracts,
+		  dialyzer_coordinator, dialyzer_dataflow, dialyzer_dep,
+		  dialyzer_plt, dialyzer_succ_typings, dialyzer_typesig,
+		  dialyzer_worker],
+	  report_native_comp(Options),
+	  {T1, _} = statistics(wall_clock),
+	  Cache = (get(dialyzer_options_native_cache) =/= false),
+	  native_compile(Mods, Cache),
+	  {T2, _} = statistics(wall_clock),
+	  report_elapsed_time(T1, T2, Options)
+      end
+  end.
+
+native_compile(Mods, Cache) ->
+  case dialyzer_utils:parallelism() > ?MIN_PARALLELISM of
+    true ->
+      Parent = self(),
+      Pids = [spawn(fun () -> Parent ! {self(), hc(M, Cache)} end) || M <- Mods],
+      lists:foreach(fun (Pid) -> receive {Pid, Res} -> Res end end, Pids);
+    false ->
+      lists:foreach(fun (Mod) -> hc(Mod, Cache) end, Mods)
+  end.
+
+hc(Mod, Cache) ->
+  {module, Mod} = code:ensure_loaded(Mod),
+  case code:is_module_native(Mod) of
+    true -> ok;
+    false ->
+      %% io:format(" ~w", [Mod]),
+      case Cache of
+	false ->
+	  {ok, Mod} = hipe:c(Mod),
+	  ok;
+	true ->
+	  hc_cache(Mod)
+      end
+  end.
+
+hc_cache(Mod) ->
+  CacheBase = cache_base_dir(),
+  %% Use HiPE architecture, version and erts checksum in directory name,
+  %% to avoid clashes between incompatible binaries.
+  HipeArchVersion =
+    lists:concat(
+      [erlang:system_info(hipe_architecture), "-",
+       hipe:version(), "-",
+       hipe:erts_checksum()]),
+  CacheDir = filename:join(CacheBase, HipeArchVersion),
+  OrigBeamFile = code:which(Mod),
+  {ok, {Mod, <<Checksum:128>>}} = beam_lib:md5(OrigBeamFile),
+  CachedBeamFile = filename:join(CacheDir, lists:concat([Mod, "-", Checksum, ".beam"])),
+  ok = filelib:ensure_dir(CachedBeamFile),
+  ModBin =
+    case filelib:is_file(CachedBeamFile) of
+      true ->
+	{ok, BinFromFile} = file:read_file(CachedBeamFile),
+	BinFromFile;
+      false ->
+	{ok, Mod, CompiledBin} = compile:file(OrigBeamFile, [from_beam, native, binary]),
+	ok = file:write_file(CachedBeamFile, CompiledBin),
+	CompiledBin
+    end,
+  code:unstick_dir(filename:dirname(OrigBeamFile)),
+  {module, Mod} = code:load_binary(Mod, CachedBeamFile, ModBin),
+  true = code:is_module_native(Mod),
+  ok.
+
+cache_base_dir() ->
+  %% http://standards.freedesktop.org/basedir-spec/basedir-spec-0.7.html
+  %% If XDG_CACHE_HOME is set to an absolute path, use it as base.
+  XdgCacheHome = os:getenv("XDG_CACHE_HOME"),
+  CacheHome =
+    case is_list(XdgCacheHome) andalso filename:pathtype(XdgCacheHome) =:= absolute of
+      true ->
+	XdgCacheHome;
+      false ->
+	%% Otherwise, the default is $HOME/.cache.
+	{ok, [[Home]]} = init:get_argument(home),
+	filename:join(Home, ".cache")
+    end,
+  filename:join([CacheHome, "dialyzer_hipe_cache"]).
+
 new_state() ->
   #cl_state{}.
 
-- 
2.16.4

openSUSE Build Service is sponsored by