File 1072-kernel-Correct-disk_log-s-calculation-of-no_items.patch of Package erlang

From 2b40082715f419988537bf430ad0045ba8a71839 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Wed, 19 Aug 2020 08:15:01 +0200
Subject: [PATCH] kernel: Correct disk_log's calculation of no_items

disk_log:truncate/1 did not take the header into account when
calculating number of items.

The docs are updated to state that disk_log:truncate/1 can be used for
logs on the external format.
---
 lib/kernel/doc/src/disk_log.xml    |  9 ++++---
 lib/kernel/src/disk_log.erl        |  2 +-
 lib/kernel/test/disk_log_SUITE.erl | 41 +++++++++++++++++++++++++++---
 3 files changed, 45 insertions(+), 7 deletions(-)

diff --git a/lib/kernel/doc/src/disk_log.xml b/lib/kernel/doc/src/disk_log.xml
index e033a3baad..5a33796005 100644
--- a/lib/kernel/doc/src/disk_log.xml
+++ b/lib/kernel/doc/src/disk_log.xml
@@ -958,7 +958,7 @@
               written first on the log file. If the log is a wrap
               log, the item <c><anno>Head</anno></c> is written first in each new file.
               <c><anno>Head</anno></c> is to be a term if the format is
-              <c>internal</c>, otherwise a sequence of bytes.
+              <c>internal</c>, otherwise an <c>iodata()</c>.
               Defaults to <c>none</c>, which means that
               no header is written first on the file.
               </p>
@@ -970,7 +970,7 @@
               The call <c>M:F(A)</c> is assumed to return <c>{ok, Head}</c>.
               The item <c>Head</c> is written first in each file.
               <c>Head</c> is to be a term if the format is
-              <c>internal</c>, otherwise a sequence of bytes.
+              <c>internal</c>, otherwise an <c>iodata()</c>.
               </p>
           </item>
 	  <tag><c>{mode, <anno>Mode</anno>}</c></tag>
@@ -1125,7 +1125,10 @@
           The header argument is used only once. Next time a wrap log file
           is opened, the header given to <c>open/1</c> is used.
           </p>
-        <p><c>truncate/1,2</c> are used for internally
+        <p><c>truncate/1</c> is used for both internally and externally
+          formatted logs.
+          </p>
+        <p><c>truncate/2</c> is used for internally
           formatted logs, and <c>btruncate/2</c> for externally formatted
           logs.
           </p>
diff --git a/lib/kernel/src/disk_log.erl b/lib/kernel/src/disk_log.erl
index 05ea6a648f..3e1d0a2224 100644
--- a/lib/kernel/src/disk_log.erl
+++ b/lib/kernel/src/disk_log.erl
@@ -763,7 +763,7 @@ handle({From, {truncate, Head, F, A}}=Message, S) ->
 		ok ->
 		    erase(is_full),
 		    notify_owners({truncated, S#state.cnt}),
-		    N = if Head =:= none -> 0; true -> 1 end,
+		    N = if H =:= none -> 0; true -> 1 end,
 		    reply(From, ok, (state_ok(S))#state{cnt = N});
 		Error ->
 		    do_exit(S, From, Error, ?failure(Error, F, A))
diff --git a/lib/kernel/test/disk_log_SUITE.erl b/lib/kernel/test/disk_log_SUITE.erl
index dc72c304cc..99711bcf75 100644
--- a/lib/kernel/test/disk_log_SUITE.erl
+++ b/lib/kernel/test/disk_log_SUITE.erl
@@ -91,7 +91,7 @@
 
          evil/1,
 
-         otp_6278/1, otp_10131/1]).
+         otp_6278/1, otp_10131/1, otp_16768/1]).
 
 -export([head_fun/1, hf/0, lserv/1, 
 	 measure/0, init_m/1, xx/0, head_exit/0, slow_header/1]).
@@ -123,7 +123,7 @@
 	[halt_int, wrap_int, halt_ext, wrap_ext, read_mode, head,
 	 notif, new_idx_vsn, reopen, block, unblock, open, close,
 	 error, chunk, truncate, many_users, info, change_size,
-	 change_attribute, distribution, evil, otp_6278, otp_10131]).
+	 change_attribute, distribution, evil, otp_6278, otp_10131, otp_16768]).
 
 %% These test cases should be skipped if the VxWorks card is 
 %% configured without NFS cache.
@@ -149,7 +149,7 @@ all() ->
      {group, open}, {group, close}, {group, error}, chunk,
      truncate, many_users, {group, info},
      {group, change_size}, change_attribute,
-     {group, distribution}, evil, otp_6278, otp_10131].
+     {group, distribution}, evil, otp_6278, otp_10131, otp_16768].
 
 groups() -> 
     [{halt_int, [], [halt_int_inf, {group, halt_int_sz}]},
@@ -4820,6 +4820,41 @@ otp_10131(Conf) when is_list(Conf) ->
     ok = disk_log:close(Log),
     ok.
 
+%% OTP-16768. Bad number of items with truncate/1. ERL-1312, ERL-1313.
+otp_16768(Conf) when is_list(Conf) ->
+    Dir = ?privdir(Conf),
+    Log = otp_16768,
+    File = filename:join(Dir, Log),
+    Header = <<"123456789\n">>,
+    head_count(Log, File, Header, external, 25),
+    head_count(Log, File, none, external, 20),
+    head_count(Log, File, Header, internal, 30),
+    head_count(Log, File, none, internal, 20),
+    ok.
+
+head_count(Log, File, Header, Format, Expected) ->
+    del(File, 10),
+    Content = <<"1234567890123456789\n">>,
+    HeaderSize = case Header of
+                     none -> 0;
+                     _ -> byte_size(Header)
+                 end,
+    %% 5 files for the external format, more for the internal format
+    MaxSizePerFile = HeaderSize + (5 * byte_size(Content)) - 1,
+    {ok, Log} = disk_log:open([{file, File},
+                               {name, Log},
+                               {format, Format},
+                               {head, Header},
+                               {size, {MaxSizePerFile, 999}},
+                               {type, wrap}
+                              ]),
+    ok = disk_log:truncate(Log),
+    lists:foreach(fun(_I) -> disk_log:blog(Log, Content) end,
+                  lists:seq(1, 20)),
+    DiskLogInfo = disk_log:info(Log),
+    Expected = proplists:get_value(no_items, DiskLogInfo),
+    ok = disk_log:close(Log).
+
 mark(FileName, What) ->
     {ok,Fd} = file:open(FileName, [raw, binary, read, write]),
     {ok,_} = file:position(Fd, 4),
-- 
2.26.2

openSUSE Build Service is sponsored by