File 2171-compiler-Refactor-implementation-of-time-option.patch of Package erlang
From da9e7bca4bef530366e4c6cde1e75d28619ab77a Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej.drejhammar@gmail.com>
Date: Tue, 24 Oct 2023 11:03:53 +0200
Subject: [PATCH 1/3] compiler: Refactor implementation of time option
The undocumented `time` option to compiler:file/2 prints out the time
spent in each pass. Apart from sub-passes it does the printout after
each pass. This patch changes the implementation to collect the timing
information for each pass and then print it out when all passes have
been run.
---
lib/compiler/src/compile.erl | 53 ++++++++++++++++++++++++------------
1 file changed, 36 insertions(+), 17 deletions(-)
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index b9247046e9..67333af6f5 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -43,6 +43,7 @@
-import(lists, [member/2,reverse/1,reverse/2,keyfind/3,last/1,
map/2,flatmap/2,flatten/1,foreach/2,foldr/3,any/2]).
+-define(PASS_TIMES, compile__pass_times).
-define(SUB_PASS_TIMES, compile__sub_pass_times).
%%----------------------------------------------------------------------
@@ -379,12 +380,26 @@ internal_comp(Passes, Code0, File, Suffix, St0) ->
St1 = St0#compile{filename=File, dir=Dir, base=Base,
ifile=erlfile(Dir, Base, Suffix),
ofile=objfile(Base, St0)},
- Run = runner(File, St1),
- case fold_comp(Passes, Run, Code0, St1) of
+ Run = runner(St1),
+ Folder = case member(time, St1#compile.options) of
+ true ->
+ fun fold_comp_times/4;
+ false ->
+ fun fold_comp/4
+ end,
+ case Folder(Passes, Run, Code0, St1) of
{ok,Code,St2} -> comp_ret_ok(Code, St2);
{error,St2} -> comp_ret_err(St2)
end.
+fold_comp_times(Passes, Run, Code, St) ->
+ put(?PASS_TIMES, []),
+ R = fold_comp(Passes, Run, Code, St),
+ Times = reverse(get(?PASS_TIMES)),
+ erase(?PASS_TIMES),
+ print_pass_times(St#compile.filename, Times),
+ R.
+
fold_comp([{delay,Ps0}|Passes], Run, Code, #compile{options=Opts}=St) ->
Ps = select_passes(Ps0, Opts) ++ Passes,
fold_comp(Ps, Run, Code, St);
@@ -420,16 +435,12 @@ run_sub_passes_1([{Name,Run}|Ps], Runner, St0)
end;
run_sub_passes_1([], _, St) -> St.
-runner(File, #compile{options=Opts}) ->
+runner(#compile{options=Opts}) ->
Run0 = fun({_Name,Fun}, Code, St) ->
Fun(Code, St)
end,
Run1 = case member(time, Opts) of
true ->
- case File of
- none -> ok;
- _ -> io:format("Compiling ~ts\n", [File])
- end,
fun run_tc/3;
false ->
Run0
@@ -448,20 +459,28 @@ run_tc({Name,Fun}, Code, St) ->
T1 = erlang:monotonic_time(),
Val = Fun(Code, St),
T2 = erlang:monotonic_time(),
- Times = get(?SUB_PASS_TIMES),
+ SubTimes = get(?SUB_PASS_TIMES),
case OldTimes of
undefined -> erase(?SUB_PASS_TIMES);
_ -> put(?SUB_PASS_TIMES, OldTimes)
end,
- Elapsed = erlang:convert_time_unit(T2 - T1, native, microsecond),
- Mem0 = erts_debug:flat_size(Val)*erlang:system_info(wordsize),
- Mem = lists:flatten(io_lib:format("~.1f kB", [Mem0/1024])),
- io:format(" ~-30s: ~10.3f s ~12s\n",
- [Name,Elapsed/1000000,Mem]),
- print_times(Times, Name),
+ Elapsed = T2 - T1,
+ Mem = erts_debug:flat_size(Val)*erlang:system_info(wordsize),
+ put(?PASS_TIMES, [{Name,Elapsed,Mem,SubTimes}|get(?PASS_TIMES)]),
Val.
-print_times(Times0, Name) ->
+print_pass_times(File, Times) ->
+ io:format("Compiling ~ts\n", [File]),
+ foreach(fun({Name,ElapsedNative,Mem0,SubTimes}) ->
+ Elapsed = erlang:convert_time_unit(ElapsedNative,
+ native, microsecond),
+ Mem = lists:flatten(io_lib:format("~.1f kB", [Mem0/1024])),
+ io:format(" ~-30s: ~10.3f s ~12s\n",
+ [Name,Elapsed/1000000,Mem]),
+ print_subpass_times(SubTimes, Name)
+ end, Times).
+
+print_subpass_times(Times0, Name) ->
Fam0 = rel2fam(Times0),
Fam1 = [{W,lists:sum(Times)} || {W,Times} <- Fam0],
Fam = reverse(lists:keysort(2, Fam1)),
@@ -1176,7 +1195,7 @@ foldl_transform([T|Ts], Code0, St) ->
Fun = fun(Code, S) ->
T:parse_transform(Code, S#compile.options)
end,
- Run = runner(none, St),
+ Run = runner(St),
StrippedCode = maybe_strip_columns(Code0, T, St),
try Run({Name, Fun}, StrippedCode, St) of
{error,Es,Ws} ->
@@ -1246,7 +1265,7 @@ core_transforms(Code, St) ->
foldl_core_transforms([T|Ts], Code0, St) ->
Name = "core transform " ++ atom_to_list(T),
Fun = fun(Code, S) -> T:core_transform(Code, S#compile.options) end,
- Run = runner(none, St),
+ Run = runner(St),
try Run({Name, Fun}, Code0, St) of
Forms ->
foldl_core_transforms(Ts, Forms, St)
--
2.35.3