File 0844-Fix-low-priority-dirty-execution.patch of Package erlang

From 180c5e1782a94db9c6a7211bfe3a2fd159fb6111 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Mon, 3 Feb 2020 16:53:01 +0100
Subject: [PATCH] Fix low priority dirty execution

---
 erts/emulator/beam/erl_process.c       | 19 +++++++++
 erts/emulator/test/scheduler_SUITE.erl | 77 +++++++++++++++++++++++++++++++++-
 2 files changed, 94 insertions(+), 2 deletions(-)

diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 9f6adb03d0..87a86fa3c8 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -10667,6 +10667,24 @@ Process *erts_schedule(ErtsSchedulerData *esdp, Process *p, int calls)
 
 	    ASSERT(p); /* Wrong qmask in rq->flags? */
 
+#ifdef DEBUG
+            switch (((erts_aint32_t) 1) << ERTS_PSFLGS_GET_PRQ_PRIO(state)) {
+	    case MAX_BIT:
+                ASSERT(qbit == MAX_BIT);
+                break;
+            case HIGH_BIT:
+                ASSERT(qbit == HIGH_BIT);
+                break;
+            case NORMAL_BIT:
+	    case LOW_BIT:
+                ASSERT(qbit == NORMAL_BIT || qbit == LOW_BIT);
+                break;
+            default:
+                ASSERT(0);
+                break;
+            }
+#endif
+
 	    if (is_normal_sched) {
 		psflg_running = ERTS_PSFLG_RUNNING;
 		psflg_running_sys = ERTS_PSFLG_RUNNING_SYS;
@@ -10677,6 +10695,7 @@ Process *erts_schedule(ErtsSchedulerData *esdp, Process *p, int calls)
 		psflg_running = ERTS_PSFLG_DIRTY_RUNNING;
 		psflg_running_sys = ERTS_PSFLG_DIRTY_RUNNING_SYS;
 		psflg_band_mask = ~((erts_aint32_t) 0);
+                qbit = ((erts_aint32_t) 1) << ERTS_PSFLGS_GET_PRQ_PRIO(state);
 	    }
 
 	    if (!(state & ERTS_PSFLG_PROXY))
diff --git a/erts/emulator/test/scheduler_SUITE.erl b/erts/emulator/test/scheduler_SUITE.erl
index af33de237c..c378e65602 100644
--- a/erts/emulator/test/scheduler_SUITE.erl
+++ b/erts/emulator/test/scheduler_SUITE.erl
@@ -57,7 +57,8 @@
 	 scheduler_suspend_basic/1,
 	 scheduler_suspend/1,
 	 dirty_scheduler_threads/1,
-	 reader_groups/1]).
+	 reader_groups/1,
+         otp_16446/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]},
@@ -72,7 +73,8 @@ all() ->
      {group, scheduler_bind}, scheduler_threads,
      scheduler_suspend_basic, scheduler_suspend,
      dirty_scheduler_threads,
-     reader_groups].
+     reader_groups,
+     otp_16446].
 
 groups() -> 
     [{scheduler_bind, [],
@@ -1695,6 +1697,77 @@ reader_groups_map(CPUT, Groups) ->
     erlang:system_flag(cpu_topology, Old),
     lists:sort(Res).
 
+otp_16446(Config) when is_list(Config) ->
+    ct:timetrap({minutes, 1}),
+    
+    process_flag(priority, high),
+
+    DIO = erlang:system_info(dirty_io_schedulers),
+    NoPrioProcs = 10*DIO,
+    io:format("DIO = ~p~nNoPrioProcs = ~p~n", [DIO, NoPrioProcs]),
+
+    DirtyLoop = fun Loop(P, N) ->
+                        erts_debug:dirty_io(wait,1),
+                        receive {get, From} -> From ! {P, N}
+                        after 0 -> Loop(P,N+1)
+                        end
+                end,
+
+    Spawn = fun SpawnLoop(_Prio, 0, Acc) ->
+                    Acc;
+                SpawnLoop(Prio, N, Acc) ->
+                    Pid = spawn_opt(fun () -> DirtyLoop(Prio, 0) end,
+                                    [link, {priority, Prio}]),
+                    SpawnLoop(Prio, N-1, [Pid|Acc])
+            end,
+
+    Ns = Spawn(normal, NoPrioProcs, []),
+    Ls = Spawn(low, NoPrioProcs, []),
+
+    receive after 10000 -> ok end,
+    
+    RequestInfo = fun (P) -> P ! {get, self()} end,
+    lists:foreach(RequestInfo, Ns),
+    lists:foreach(RequestInfo, Ls),
+    
+    Collect = fun CollectFun(0, LLs, NLs) ->
+                      {LLs, NLs};
+                  CollectFun(N, LLs, NLs) ->
+                      receive
+                          {low, Calls} ->
+                              CollectFun(N-1, LLs+Calls, NLs);
+                          {normal, Calls} ->
+                              CollectFun(N-1, LLs, NLs+Calls)
+                      end
+              end,
+    
+    {LLs, NLs} = Collect(2*NoPrioProcs, 0, 0),
+    
+    %% expected ratio 0.125, but this is not especially exact...
+    Ratio = LLs / NLs,
+
+    io:format("LLs = ~p~nNLs = ~p~nRatio = ~p~n", [LLs, NLs, Ratio]),
+    
+    true = Ratio > 0.05,
+    true = Ratio < 0.5,
+    
+    WaitUntilDead = fun (P) ->
+                            case is_process_alive(P) of
+                                false ->
+                                    ok;
+                                true ->
+                                    unlink(P),
+                                    exit(P, kill),
+                                    false = is_process_alive(P)
+                            end
+                    end,
+
+    lists:foreach(WaitUntilDead, Ns),
+    lists:foreach(WaitUntilDead, Ls),
+    Comment = "low/normal ratio: " ++ erlang:float_to_list(Ratio,[{decimals,4}]),
+    erlang:display(Comment),
+    {comment, Comment}.
+
 %%
 %% Utils
 %%
-- 
2.16.4

openSUSE Build Service is sponsored by