File 2204-runtime_tools-Add-scheduler-module.patch of Package erlang

From 0359cdc8552ad056e976a8c097624b4305ef6755 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Thu, 11 Jan 2018 20:52:27 +0100
Subject: [PATCH] runtime_tools: Add scheduler module

---
 lib/runtime_tools/doc/src/Makefile          |   8 +-
 lib/runtime_tools/doc/src/ref_man.xml       |   1 +
 lib/runtime_tools/doc/src/scheduler.xml     | 135 ++++++++++++++++++++++++
 lib/runtime_tools/doc/src/specs.xml         |   1 +
 lib/runtime_tools/src/Makefile              |   1 +
 lib/runtime_tools/src/runtime_tools.app.src |   1 +
 lib/runtime_tools/src/scheduler.erl         | 152 ++++++++++++++++++++++++++++
 lib/runtime_tools/test/Makefile             |   1 +
 lib/runtime_tools/test/scheduler_SUITE.erl  | 104 +++++++++++++++++++
 9 files changed, 403 insertions(+), 1 deletion(-)
 create mode 100644 lib/runtime_tools/doc/src/scheduler.xml
 create mode 100644 lib/runtime_tools/src/scheduler.erl
 create mode 100644 lib/runtime_tools/test/scheduler_SUITE.erl

diff --git a/lib/runtime_tools/doc/src/Makefile b/lib/runtime_tools/doc/src/Makefile
index 5ce40bb995..83375d4525 100644
--- a/lib/runtime_tools/doc/src/Makefile
+++ b/lib/runtime_tools/doc/src/Makefile
@@ -41,7 +41,13 @@ RELSYSDIR = $(RELEASE_PATH)/lib/$(APPLICATION)-$(VSN)
 # Target Specs
 # ----------------------------------------------------
 XML_APPLICATION_FILES = ref_man.xml
-XML_REF3_FILES = dbg.xml dyntrace.xml erts_alloc_config.xml system_information.xml msacc.xml
+XML_REF3_FILES = \
+	dbg.xml \
+	dyntrace.xml \
+	erts_alloc_config.xml \
+	system_information.xml \
+	msacc.xml \
+	scheduler.xml
 XML_REF6_FILES = runtime_tools_app.xml
 
 XML_PART_FILES = part_notes.xml part_notes_history.xml part.xml
diff --git a/lib/runtime_tools/doc/src/ref_man.xml b/lib/runtime_tools/doc/src/ref_man.xml
index d2fb7a29af..eb3a6f0f5c 100644
--- a/lib/runtime_tools/doc/src/ref_man.xml
+++ b/lib/runtime_tools/doc/src/ref_man.xml
@@ -37,6 +37,7 @@
   <xi:include href="dyntrace.xml"/>
   <xi:include href="erts_alloc_config.xml"/>
   <xi:include href="msacc.xml"/>
+  <xi:include href="scheduler.xml"/>
   <xi:include href="system_information.xml"/>
 </application>
 
diff --git a/lib/runtime_tools/doc/src/scheduler.xml b/lib/runtime_tools/doc/src/scheduler.xml
new file mode 100644
index 0000000000..dd8bf73bae
--- /dev/null
+++ b/lib/runtime_tools/doc/src/scheduler.xml
@@ -0,0 +1,135 @@
+<?xml version="1.0" encoding="utf-8" ?>
+<!DOCTYPE erlref SYSTEM "erlref.dtd">
+
+<erlref>
+  <header>
+    <copyright>
+      <year>2018</year>
+      <holder>Ericsson AB. All Rights Reserved.</holder>
+    </copyright>
+    <legalnotice>
+      Licensed under the Apache License, Version 2.0 (the "License");
+      you may not use this file except in compliance with the License.
+      You may obtain a copy of the License at
+
+          http://www.apache.org/licenses/LICENSE-2.0
+
+      Unless required by applicable law or agreed to in writing, software
+      distributed under the License is distributed on an "AS IS" BASIS,
+      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+      See the License for the specific language governing permissions and
+      limitations under the License.
+
+    </legalnotice>
+
+    <title></title>
+    <prepared></prepared>
+    <responsible></responsible>
+    <docno>1</docno>
+    <approved></approved>
+    <checked></checked>
+    <date></date>
+    <rev></rev>
+    <file>scheduler.xml</file>
+  </header>
+  <module>scheduler</module>
+  <modulesummary>Measure scheduler utilization</modulesummary>
+  <description>
+    <p>This module contains utility functions for easier measurement and
+    calculation of scheduler utilization, otherwise obtained from calling the
+    more primitive <seealso marker="erts:erlang#statistics_scheduler_wall_time">
+    <c>statistics(scheduler_wall_time)</c></seealso>.</p>
+    <p>The simplest usage is to call <seealso marker="#utilization-1">
+    <c>scheduler:utilization(Seconds)</c></seealso>.</p>
+  </description>
+
+  <datatypes>
+    <datatype>
+      <name name="sched_sample"/>
+    </datatype>
+    <datatype>
+      <name name="sched_type"/>
+    </datatype>
+    <datatype>
+      <name name="sched_id"/>
+    </datatype>
+    <datatype>
+      <name name="sched_util_result"/>
+      <desc>
+	<p>A list of tuples containing results for individual schedulers
+	as well as aggregated averages. <c>Util</c> is the scheduler utilization
+	as a floating point value between 0.0 and 1.0. <c>Percent</c> is the
+	same utilization as a more human readable string expressed in percent.</p>
+	<taglist>
+	  <tag><c>{normal, SchedulerId, Util, Percent}</c></tag>
+	  <item>Scheduler utilization of a normal scheduler with number
+	    <c>SchedulerId</c>.</item>
+	  <tag><c>{cpu, SchedulerId, Util, Percent}</c></tag>
+	  <item>Scheduler utilization of a dirty-cpu scheduler with number
+	    <c>SchedulerId</c>.</item>
+	  <tag><c>{io, SchedulerId, Util, Percent}</c></tag>
+	  <item>Scheduler utilization of a dirty-io scheduler with number
+	    <c>SchedulerId</c>. This tuple will only exist if both samples were
+	    taken with <seealso marker="#sample_all-0"><c>sample_all/0</c></seealso>.</item>
+	  <tag><c>{total, Util, Percent}</c></tag>
+	  <item>Total utilization of all normal and dirty-cpu schedulers.</item>
+	  <tag><c>{weighted, Util, Percent}</c></tag>
+	  <item>Total utilization of all normal and dirty-cpu schedulers,
+	  weighted against maximum amount of available CPU time.</item>
+	</taglist>
+      </desc>
+    </datatype>
+  </datatypes>
+
+  <funcs>
+
+    <func>
+      <name name="sample" arity="0"/>
+      <fsummary>Get scheduler utilization sample.</fsummary>
+      <desc>
+        <p>Return a scheduler utilization sample for normal and dirty-cpu
+	schedulers.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="sample_all" arity="0"/>
+      <fsummary>Get scheduler utilization sample.</fsummary>
+      <desc>
+        <p>Return a scheduler utilization sample for all schedulers,
+	including dirty-io schedulers.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="utilization" arity="1" clause_i="1"/>
+      <fsummary>Measure scheduler utilizations during a period of time.</fsummary>
+      <desc>
+        <p>Measure utilization for normal and dirty-cpu schedulers during
+	<c><anno>Seconds</anno></c> seconds, and then return the result.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="utilization" arity="1" clause_i="2"/>
+      <fsummary>Measure scheduler utilizations since sample.</fsummary>
+      <desc>
+        <p>Calculate scheduler utilizations for the time interval from when
+	<c><anno>Sample</anno></c> was taken and "now". The same as calling
+	<c>scheduler:utilization(Sample, scheduler:sample_all())</c>.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="utilization" arity="2"/>
+      <fsummary>Measure scheduler utilizations between two samples.</fsummary>
+      <desc>
+	<p>Calculates scheduler utilizations for the time interval between
+	the two samples obtained from calling
+	<seealso marker="#sample-0"><c>sample/0</c></seealso> or
+	<seealso marker="#sample_all-0"><c>sample_all/0</c></seealso>.</p>
+      </desc>
+    </func>
+
+  </funcs>
+ </erlref>
diff --git a/lib/runtime_tools/doc/src/specs.xml b/lib/runtime_tools/doc/src/specs.xml
index 978bd39e55..33fe7fa370 100644
--- a/lib/runtime_tools/doc/src/specs.xml
+++ b/lib/runtime_tools/doc/src/specs.xml
@@ -2,4 +2,5 @@
 <specs xmlns:xi="http://www.w3.org/2001/XInclude">
   <xi:include href="../specs/specs_system_information.xml"/>
   <xi:include href="../specs/specs_msacc.xml"/>
+  <xi:include href="../specs/specs_scheduler.xml"/>
 </specs>
diff --git a/lib/runtime_tools/src/Makefile b/lib/runtime_tools/src/Makefile
index 5a99c6e240..6faa9c2e35 100644
--- a/lib/runtime_tools/src/Makefile
+++ b/lib/runtime_tools/src/Makefile
@@ -46,6 +46,7 @@ MODULES= \
 	system_information \
 	observer_backend \
 	ttb_autostart\
+	scheduler\
 	msacc
 
 HRL_FILES= ../include/observer_backend.hrl
diff --git a/lib/runtime_tools/src/runtime_tools.app.src b/lib/runtime_tools/src/runtime_tools.app.src
index 449532e5c4..09a9b447c2 100644
--- a/lib/runtime_tools/src/runtime_tools.app.src
+++ b/lib/runtime_tools/src/runtime_tools.app.src
@@ -23,6 +23,7 @@
     {modules,      [appmon_info, dbg,observer_backend,percept_profile,
 		    runtime_tools,runtime_tools_sup,erts_alloc_config,
 		    ttb_autostart,dyntrace,system_information,
+                    scheduler,
                     msacc]},
     {registered,   [runtime_tools_sup]},
     {applications, [kernel, stdlib]},
diff --git a/lib/runtime_tools/src/scheduler.erl b/lib/runtime_tools/src/scheduler.erl
new file mode 100644
index 0000000000..c896b671ac
--- /dev/null
+++ b/lib/runtime_tools/src/scheduler.erl
@@ -0,0 +1,152 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2018. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%% @doc Utility functions for easier measurement of scheduler utilization
+%%      using erlang:statistics(scheduler_wall_time).
+
+-module(scheduler).
+
+-export([sample/0,
+         sample_all/0,
+         utilization/1,
+         utilization/2]).
+
+-export_type([sched_sample/0]).
+
+
+-opaque sched_sample() ::
+          {scheduler_wall_time | scheduler_wall_time_all,
+           [{sched_type(), sched_id(), ActiveTime::integer(), TotalTime::integer()}]}.
+
+-type sched_type() :: normal | cpu | io.
+
+-type sched_id() :: integer().
+
+-spec sample() -> sched_sample().
+sample() ->
+    sample(scheduler_wall_time).
+
+-spec sample_all() -> sched_sample().
+sample_all() ->
+    sample(scheduler_wall_time_all).
+
+sample(Stats) ->
+    case erlang:statistics(Stats) of
+        undefined ->
+            erlang:system_flag(scheduler_wall_time, true),
+            sample(Stats);
+        
+        List ->
+            Sorted = lists:sort(List),
+            Tagged = lists:map(fun({I, A, T}) -> {sched_tag(I), I, A, T} end,
+                               Sorted),
+            {Stats, Tagged}
+    end.
+
+-type sched_util_result() ::
+        [{sched_type(), sched_id(), float(), string()} |
+         {total, float(), string()} |
+         {weighted, float(), string()}].
+
+-spec utilization(Seconds) -> sched_util_result() when
+      Seconds :: pos_integer();
+                 (Sample) -> sched_util_result() when
+      Sample :: sched_sample().
+utilization(Seconds) when is_integer(Seconds), Seconds > 0 ->
+    OldFlag = erlang:system_flag(scheduler_wall_time, true),
+    T0 = sample(),
+    receive after Seconds*1000 -> ok end,
+    T1 = sample(),
+    case OldFlag of
+        false ->
+            erlang:system_flag(scheduler_wall_time, OldFlag);
+        true ->
+            ok
+    end,
+    utilization(T0,T1);
+
+utilization({Stats, _}=T0) when Stats =:= scheduler_wall_time;
+                                Stats =:= scheduler_wall_time_all ->
+    utilization(T0, sample(Stats)).
+
+-spec utilization(Sample1, Sample2) -> sched_util_result() when
+      Sample1 :: sched_sample(),
+      Sample2 :: sched_sample().
+utilization({Stats, Ts0}, {Stats, Ts1}) ->
+    Diffs = lists:map(fun({{Tag, I, A0, T0}, {Tag, I, A1, T1}}) ->
+                              {Tag, I, (A1 - A0), (T1 - T0)}
+                      end,
+                      lists:zip(Ts0,Ts1)),
+
+    {Lst0, {A, T, N}} = lists:foldl(fun({Tag, I, Adiff, Tdiff}, {Lst, Acc}) ->
+                                            R = safe_div(Adiff, Tdiff),
+                                            {[{Tag, I, R, percent(R)} | Lst],
+                                             acc(Tag, Adiff, Tdiff, Acc)}
+                                    end,
+                                    {[], {0, 0, 0}},
+                               Diffs),
+
+    Total = safe_div(A, T),
+    Lst1 = lists:reverse(Lst0),
+    Lst2 = case erlang:system_info(logical_processors_available) of
+               unknown -> Lst1;
+               LPA ->
+                   Weighted = Total * (N / LPA),
+                   [{weighted, Weighted, percent(Weighted)} | Lst1]
+           end,
+    [{total, Total, percent(Total)} | Lst2];
+
+utilization({scheduler_wall_time, _}=T0,
+            {scheduler_wall_time_all, Ts1}) ->
+    utilization(T0, {scheduler_wall_time, remove_io(Ts1)});
+
+utilization({scheduler_wall_time_all, Ts0},
+            {scheduler_wall_time, _}=T1) ->
+    utilization({scheduler_wall_time, remove_io(Ts0)}, T1).
+
+%% Do not include dirty-io in totals
+acc(io, _, _, Acc) ->
+    Acc;
+acc(Tag, Adiff, Tdiff, {Asum, Tsum, N}) when Tag =:= normal; Tag =:= cpu ->
+    {Adiff+Asum, Tdiff+Tsum, N+1}.
+
+
+remove_io(Ts) ->
+    lists:filter(fun({io,_,_,_}) -> false;
+                    (_) -> true end,
+                 Ts).
+
+safe_div(A, B) ->
+    if B == 0.0 -> 0.0;
+       true -> A / B
+    end.            
+
+sched_tag(Nr) ->
+    Normal = erlang:system_info(schedulers),
+    Cpu = Normal + erlang:system_info(dirty_cpu_schedulers),
+    case Nr of
+        _ when Nr =< Normal -> normal;
+        _ when Nr =< Cpu -> cpu;
+        _ -> io
+    end.
+
+
+percent(F) ->
+    float_to_list(F*100, [{decimals,1}]) ++ [$%].
diff --git a/lib/runtime_tools/test/Makefile b/lib/runtime_tools/test/Makefile
index 61377ea09e..de37b2570d 100644
--- a/lib/runtime_tools/test/Makefile
+++ b/lib/runtime_tools/test/Makefile
@@ -9,6 +9,7 @@ MODULES =  \
 	system_information_SUITE \
 	dbg_SUITE \
 	erts_alloc_config_SUITE \
+	scheduler_SUITE \
 	msacc_SUITE
 
 ERL_FILES= $(MODULES:%=%.erl)
diff --git a/lib/runtime_tools/test/scheduler_SUITE.erl b/lib/runtime_tools/test/scheduler_SUITE.erl
new file mode 100644
index 0000000000..1c80253371
--- /dev/null
+++ b/lib/runtime_tools/test/scheduler_SUITE.erl
@@ -0,0 +1,104 @@
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2018. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+%%
+
+-module(scheduler_SUITE).
+
+-export([suite/0, all/0]).
+
+%% Test cases
+-export([basic/1]).
+
+all() -> [basic].
+
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+
+basic(_Config) ->
+    S1 = scheduler:sample(),
+    S2 = scheduler:sample_all(),
+
+    check(scheduler:utilization(1)),
+
+    check(scheduler:utilization(S1)),
+    check(scheduler:utilization(S2)),
+    check(scheduler:utilization(S1, scheduler:sample())),
+    check(scheduler:utilization(S2, scheduler:sample())),
+
+    S3 = scheduler:sample_all(),
+    U13 = scheduler:utilization(S1, S3),
+    U13 = scheduler:utilization(S1, remove_io(S3)),
+    check(U13),
+
+    U23all = scheduler:utilization(S2, S3),
+    check(U23all),
+    U23 = scheduler:utilization(S2, remove_io(S3)),
+    U23 = scheduler:utilization(remove_io(S2), S3),
+    U23 = remove_io(U23all),
+    check(U23),
+
+    ok.
+
+
+check([{total, Tf, Ts} | List]=U) ->
+    io:format("\nU = ~p\n", [U]),
+    check_values(Tf, Ts, true),
+
+    SchdList = case hd(List) of
+                   {weighted, Wf, Ws} ->
+                       check_values(Wf, Ws, false),
+                       tl(List);
+                   _ ->
+                       unknown = erlang:system_info(logical_processors_available),
+                       List
+               end,
+
+    lists:foreach(fun({Type, Id, F, S}) when ((Type =:= normal) or (Type =:= cpu) or (Type =:= io)),
+                                             is_integer(Id) ->
+                          check_values(F, S, true)
+                  end,
+                  SchdList),
+    ok.
+
+check_values(F, S, Max100) ->
+    true = is_float(F),
+    true = F >= 0.0,
+
+    $% = lists:last(S),
+    Sf = list_to_float(lists:droplast(S)),
+    true = Sf >= 0.0,
+    true = case Max100 of
+               true ->
+                   true = F =< 1.0,
+                   true = Sf =< 100.0;
+               false ->
+                   true
+           end,
+    MaxDiff = 0.055555555555555555,  %% change to 0.05 when float_to_list/2 is fixed
+    true = abs(F*100 - Sf) =< MaxDiff,
+    ok.
+
+
+remove_io({scheduler_wall_time_all,Lst}) ->
+    {scheduler_wall_time, remove_io(Lst)};
+remove_io(Lst) ->
+    lists:filter(fun({io,_,_,_}) -> false;
+                    (_) -> true end,
+                 Lst).
-- 
2.16.0

openSUSE Build Service is sponsored by