File 3512-disk_log-rotate.patch of Package erlang

From 4f46f5765898e923a1e39320abd5f92cbc187ace Mon Sep 17 00:00:00 2001
From: anupamasingh10 <anupamasingh31@gmail.com>
Date: Mon, 27 Mar 2023 19:05:28 +0200
Subject: [PATCH 2/7] disk_log rotate

---
 lib/kernel/doc/src/disk_log.xml      |  80 ++++++--
 lib/kernel/src/disk_log.erl          | 144 +++++++++++--
 lib/kernel/src/disk_log.hrl          |  23 ++-
 lib/kernel/src/disk_log_1.erl        | 297 ++++++++++++++++++++++-----
 lib/kernel/test/disk_log_SUITE.erl   | 212 ++++++++++++++++++-
 system/doc/general_info/DEPRECATIONS |   1 +
 6 files changed, 669 insertions(+), 88 deletions(-)

diff --git a/lib/kernel/doc/src/disk_log.xml b/lib/kernel/doc/src/disk_log.xml
index 46ed711906..0aa724752f 100644
--- a/lib/kernel/doc/src/disk_log.xml
+++ b/lib/kernel/doc/src/disk_log.xml
@@ -39,7 +39,7 @@
   <description>
     <p><c>disk_log</c> is a disk-based term logger that enables
       efficient logging of items on files.</p>
-    <p>Two types of logs are supported:</p>
+    <p>Three types of logs are supported:</p>
       <taglist>
 	<tag>halt logs</tag>
 	<item><p>Appends items to a single file, which size can
@@ -49,6 +49,17 @@
 	wrap log file is filled up, further items are logged on to the next
 	file in the sequence, starting all over with the first file when
 	the last file is filled up.</p></item>
+	<tag>rotate logs</tag>
+        <item><p>Uses a sequence of rotate log files of limited size. As a
+        log file is filled up, it is rotated and then compressed. There is one active
+        log file and upto the configured number of compressed log files. Only externally 
+        formatted logs are supported. It follows the same naming convention as the handler
+        logger_std_h for Logger. For more details about the naming convention check the file
+        parameter for
+        <seemfa marker="#open/1"><c>open/1</c></seemfa>.</p>
+        <p>It follows the same naming convention as that for the compressed files for Linux's
+        logrotate and BSD's newsyslog.</p>
+        </item>
       </taglist>
      <p>For efficiency reasons, items are always written to files as binaries.</p>
 
@@ -197,6 +208,9 @@
     <datatype>
       <name name="file_error"/>
     </datatype>
+    <datatype>
+      <name name="next_file_error_rsn"/>
+    </datatype>
   </datatypes>
   <funcs>
     <func>
@@ -326,10 +340,10 @@
           but it cannot be decreased to something less than
           the current file size.
           </p>
-        <p>For a wrap log, both the size and the number of files can always
-	  be increased, as long as the number of files does not
-          exceed 65000. If the maximum number of files is decreased, the
-          change is not valid until the current file is full and the
+        <p>For a wrap or rotate log, both the size and the number of files can 
+          always be increased, as long as the number of files does not
+          exceed 65000. For wrap logs, if the maximum number of files is decreased,
+          the change is not valid until the current file is full and the
           log wraps to the next file.
           The redundant files are removed the next time the log wraps around,
           that is, starts to log to file number 1.
@@ -346,13 +360,16 @@
           file (that is, files 7 and 8) are removed the next time file 6
           is full.
           </p>
+        <p>For rotate logs, if the maximum number of files is decreased,
+          the redundant files are deleted instantly.
+          </p>
         <p>If the size of the files is decreased, the change immediately
           affects the current log. It does not change the
           size of log files already full until the next time they are used.
           </p>
         <p>If the log size is decreased, for example, to save space,
           function
-	  <seemfa marker="#inc_wrap_file/1"><c>inc_wrap_file/1</c></seemfa>
+	  <seemfa marker="#next_file/1"><c>next_file/1</c></seemfa>,
 	  can be used to force the log to wrap.
           </p>
       </desc>
@@ -728,6 +745,26 @@
           </p>
       </desc>
     </func>
+    <func>
+      <name name="next_file" arity="1" since=""/>
+      <fsummary>Change to the next log file of a disk log.</fsummary>
+      <type name="next_file_error_rsn"/>
+      <type name="invalid_header"/>
+      <desc>
+        <p>For wrap logs, it forces the disk log to start logging to the
+          next log file. It can be used, for example, with
+          <c>change_size/2</c> to reduce the amount of disk space allocated
+          by the disk log.
+          </p>
+        <p>Owners subscribing to notifications normally receive a
+          <c>wrap</c> message, but if an error occurs with a reason tag
+          of <c>invalid_header</c> or <c>file_error</c>, an <c>error_status</c>
+          message is sent.</p>
+        <p>For rotate logs, it forces rotation of the currently active log
+           file, compresses it and opens a new active file for logging. 
+          </p>
+      </desc>
+    </func>
     <func>
       <name name="open" arity="1" since=""/>
       <fsummary>Open a disk log file.</fsummary>
@@ -757,9 +794,16 @@
               the filename defaults to <c>lists:concat([<anno>Log</anno>, ".LOG"])</c>
 	      for halt logs.</p>
 	    <p>For wrap logs, this is the base name of the files. Each file in
-	      a wrap log is called <c><![CDATA[<base_name>.N]]></c>, where <c>N</c>
+	      a wrap log is called <c><![CDATA[<FileName>.N]]></c>, where <c>N</c>
 	      is an integer. Each wrap log also has two files called
-              <c><![CDATA[<base_name>.idx]]></c> and <c><![CDATA[<base_name>.siz]]></c>.
+              <c><![CDATA[<FileName>.idx]]></c> and <c><![CDATA[<FileName>.siz]]></c>.
+              </p>
+	    <p>For rotate logs, this is the name of the active log file. The compressed
+               files are named as <c><![CDATA[<FileName>.N.gz]]></c>, where <c>N</c> is
+               an integer and <c><![CDATA[<FileName>.0.gz]]></c> is the latest compressed
+               log file. All the compressed files are renamed at each rotation so that the
+               latest files have the smallest index. The maximum value for N is the value of
+               <c><![CDATA[MaxNoFiles]]></c> minus 1.
               </p>
           </item>
 	  <tag><c>{linkto, <anno>LinkTo</anno>}</c><marker id="linkto"></marker></tag>
@@ -803,10 +847,10 @@
               log more items are rejected. Defaults to
               <c>infinity</c>, which for halt implies that there is no
               maximum size.</p>
-	    <p>For wrap logs, parameter <c><anno>Size</anno></c>
+	    <p>For wrap and rotate logs, parameter <c><anno>Size</anno></c>
               can be a pair
-              <c>{<anno>MaxNoBytes</anno>, <anno>MaxNoFiles</anno>}</c> or
-	      <c>infinity</c>.
+              <c>{<anno>MaxNoBytes</anno>, <anno>MaxNoFiles</anno>}</c>. For wrap logs
+	      it can also be <c>infinity</c>.
 	      In the latter case, if the files of an existing wrap log
               with the same name can be found, the size is read
               from the existing wrap log, otherwise an error is returned.</p>
@@ -837,6 +881,12 @@
                 opening an existing wrap log for the first time, that
                 is, when creating the disk log process.</p>
             </note>
+            <p>Rotate logs write at most <c><anno>MaxNoBytes</anno></c>
+              bytes on the active log file and keep the latest <c><anno>MaxNoFiles</anno></c>
+              compressed files. Regardless of <c><anno>MaxNoBytes</anno></c>,
+              at least the header (if there is one) and one
+              item are written on each rotate log file before rotation.
+              </p>
 	    <p>When opening an already open halt log, option <c>size</c>
 	      is ignored.</p>
           </item>
@@ -910,7 +960,7 @@
 	  <tag><c>{head, <anno>Head</anno>}</c></tag>
           <item>
             <p>Specifies a header to be
-              written first on the log file. If the log is a wrap
+              written first on the log file. If the log is a wrap or rotate
               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 an <c>iodata()</c>.
@@ -1015,12 +1065,12 @@
       <desc>
         <p>Renames the log file
           to <c><anno>File</anno></c> and then recreates a new log file.
-          If a wrap log exists, <c><anno>File</anno></c> is used as the base name
+          If a wrap/rotate log exists, <c><anno>File</anno></c> is used as the base name
           of the renamed files.
           By default the header given to <c>open/1</c> is written first in
           the newly opened log file, but if argument <c><anno>Head</anno></c> or
           <c><anno>BHead</anno></c> is specified, this item is used instead.
-          The header argument is used only once. Next time a wrap log file
+          The header argument is used only once. Next time a wrap/rotate log file
           is opened, the header given to <c>open/1</c> is used.
           </p>
         <p><c>reopen/2,3</c> are used for internally formatted
@@ -1060,7 +1110,7 @@
           If argument <c><anno>Head</anno></c> or <c><anno>BHead</anno></c> is
           specified, this item is written first in the newly truncated
           log, otherwise the header given to <c>open/1</c> is used.
-          The header argument is used only once. Next time a wrap log file
+          The header argument is used only once. Next time a wrap/rotate log file
           is opened, the header given to <c>open/1</c> is used.
           </p>
         <p><c>truncate/1</c> is used for both internally and externally
diff --git a/lib/kernel/src/disk_log.erl b/lib/kernel/src/disk_log.erl
index 19225c9be5..0ecaf523ea 100644
--- a/lib/kernel/src/disk_log.erl
+++ b/lib/kernel/src/disk_log.erl
@@ -30,7 +30,7 @@
 	 change_notify/3, change_header/2, 
 	 chunk/2, chunk/3, bchunk/2, bchunk/3, chunk_step/3, chunk_info/1,
 	 block/1, block/2, unblock/1, info/1, format_error/1,
-	 accessible_logs/0, all/0]).
+	 accessible_logs/0, all/0, next_file/1]).
 
 %% Internal exports
 -export([init/2, internal_open/2,
@@ -49,7 +49,8 @@
 
 -deprecated([{accessible_logs, 0, "use disk_log:all/0 instead"},
              {lclose, 1, "use disk_log:close/1 instead"},
-             {lclose, 2, "use disk_log:close/1 instead"}]).
+             {lclose, 2, "use disk_log:close/1 instead"},
+             {inc_wrap_file, 1, "use disk_log:next_file/1 instead"}]).
 
 -type dlog_state_error() :: 'ok' | {'error', term()}.
 
@@ -253,12 +254,20 @@ reopen(Log, NewFile, NewHead) ->
 breopen(Log, NewFile, NewHead) ->
     req(Log, {reopen, NewFile, {ok, ensure_binary(NewHead)}, breopen, 3}).
 
--type inc_wrap_error_rsn() :: 'no_such_log' | 'nonode'
+-type next_file_error_rsn() :: 'no_such_log' | 'nonode'
                             | {'read_only_mode', log()}
                             | {'blocked_log', log()} | {'halt_log', log()}
+                            | {'rotate_log', log()}
                             | {'invalid_header', invalid_header()}
                             | {'file_error', file:filename(), file_error()}.
 
+-spec next_file(Log) -> 'ok' | {'error', next_file_error_rsn()} when
+      Log :: log().
+next_file(Log) -> 
+    req(Log, next_file).
+
+-type inc_wrap_error_rsn() :: next_file_error_rsn().
+
 -spec inc_wrap_file(Log) -> 'ok' | {'error', inc_wrap_error_rsn()} when
       Log :: log().
 inc_wrap_file(Log) -> 
@@ -592,6 +601,8 @@ check_arg([], Res) ->
 	    {OldSize, Version} = 
 		disk_log_1:read_size_file_version(Res#arg.file),
 	    check_wrap_arg(Ret, OldSize, Version);
+        Res#arg.type =:= rotate ->
+            {ok, Res#arg{format = external}};
 	true ->
 	    Ret
     end;
@@ -620,6 +631,8 @@ check_arg([{size, {MaxB,MaxF}}|Tail], Res) when is_integer(MaxB),
 						MaxB > 0, MaxB =< ?MAX_BYTES,
 						MaxF > 0, MaxF < ?MAX_FILES ->
     check_arg(Tail, Res#arg{size = {MaxB, MaxF}});
+check_arg([{type, rotate}|Tail], Res) ->
+    check_arg(Tail, Res#arg{type = rotate});
 check_arg([{type, wrap}|Tail], Res) ->
     check_arg(Tail, Res#arg{type = wrap});
 check_arg([{type, halt}|Tail], Res) ->
@@ -879,13 +892,15 @@ handle({From, inc_wrap_file}=Message, S) ->
 	    reply(From, {error, {read_only_mode, L#log.name}}, S);
 	#log{type = halt}=L ->
 	    reply(From, {error, {halt_log, L#log.name}}, S);
+	#log{type = rotate}=L ->
+	    reply(From, {error, {rotate_log, L#log.name}}, S);
 	#log{status = ok} when S#state.cache_error =/= ok ->
 	    loop(cache_error(S, [From]));
 	#log{status = ok}=L ->
 	    case catch do_inc_wrap_file(L) of
 		{ok, L2, Lost} ->
 		    put(log, L2),
-		    notify_owners({wrap, Lost}),
+		    notify_owners({L#log.type, Lost}),
 		    reply(From, ok, S#state{cnt = S#state.cnt-Lost});
 		{error, Error, L2} ->
 		    put(log, L2),		    
@@ -898,6 +913,35 @@ handle({From, inc_wrap_file}=Message, S) ->
 	_ ->
 	    enqueue(Message, S)
     end;
+handle({From, next_file}=Message, S) ->
+    case get(log) of
+	#log{mode = read_only}=L ->
+	    reply(From, {error, {read_only_mode, L#log.name}}, S);
+	#log{type = halt}=L ->
+	    reply(From, {error, {halt_log, L#log.name}}, S);
+	#log{status = ok} when S#state.cache_error =/= ok ->
+	    loop(cache_error(S, [From]));
+	#log{status = ok, type = wrap}=L ->
+	    case catch do_inc_wrap_file(L) of
+		{ok, L2, Lost} ->
+		    put(log, L2),
+		    notify_owners({L#log.type, Lost}),
+		    reply(From, ok, S#state{cnt = S#state.cnt-Lost});
+		{error, Error, L2} ->
+		    put(log, L2),		    
+		    reply(From, Error, state_err(S, Error))
+	    end;
+        #log{status = ok, type = rotate}=L ->
+            {ok, L2} = do_inc_rotate_file(L),
+	    put(log, L2),
+	    reply(From, ok, S);
+	#log{status = {blocked, false}}=L ->
+	    reply(From, {error, {blocked_log, L#log.name}}, S);
+	#log{blocked_by = From}=L ->
+	    reply(From, {error, {blocked_log, L#log.name}}, S);
+	_ ->
+	    enqueue(Message, S)
+    end;
 handle({From, {reopen, NewFile, Head, F, A}}, S) ->
     case get(log) of
 	#log{mode = read_only}=L ->
@@ -910,7 +954,7 @@ handle({From, {reopen, NewFile, Head, F, A}}, S) ->
 	    case catch close_disk_log2(L) of
 		closed ->
 		    File = L#log.filename,
-		    case catch rename_file(File, NewFile, L#log.type) of
+		    case catch rename_file(File, NewFile, L) of
 			ok ->
 			    H = merge_head(Head, L#log.head),
 			    case do_open((S#state.args)#arg{name = L#log.name,
@@ -1233,15 +1277,20 @@ is_owner(Pid, L) ->
     end.
 
 %% ok | throw(Error)
-rename_file(File, NewFile, halt) ->
+rename_file(File, NewFile, #log{type = halt}) ->
     case file:rename(File, NewFile) of
         ok ->
             ok;
         Else ->
             file_error(NewFile, Else)
     end;
-rename_file(File, NewFile, wrap) ->
-    rename_file(wrap_file_extensions(File), File, NewFile, ok).
+rename_file(File, NewFile, #log{type = wrap}) ->
+    rename_file(wrap_file_extensions(File), File, NewFile, ok);
+rename_file(File, NewFile, #log{type = rotate, head = Head, extra = Handle}) ->
+    {_MaxB, MaxF} = disk_log_1:get_rotate_size(Handle),
+    _Handle1 = disk_log_1:rotate_file(Handle, Head),
+    _ = file:delete(File),
+    rename_file(rotate_file_extensions(File, MaxF), File, NewFile, ok).
 
 rename_file([Ext|Exts], File, NewFile0, Res) ->
     NewFile = add_ext(NewFile0, Ext),
@@ -1299,6 +1348,20 @@ compare_arg(_Attr, _Val, _A) ->
     ok.
 
 %% -> {ok, Res, log(), Cnt} | Error
+do_open(#arg{type = rotate} = A) ->
+    #arg{name = Name, size = Size, mode = Mode, head = Head0,
+         format = Format, type = Type, file = FName} = A,
+    Head = mk_head(Head0, Format),
+    case disk_log_1:open_rotate_log_file(FName, Size, Head) of
+        {ok, RotHandle} ->
+            L = #log{name = Name, type = Type, format = Format,
+                     filename = FName, size = Size, mode = Mode,
+                     extra = RotHandle, format_type = rotate_ext,
+                     head = Head},
+            {ok, {ok, Name}, L, 0};
+        Error ->
+            Error
+    end;
 do_open(A) ->
     #arg{type = Type, format = Format, name = Name, head = Head0,
          file = FName, repair = Repair, size = Size, mode = Mode,
@@ -1368,6 +1431,11 @@ do_change_size(#log{type = wrap}=L, NewSize) ->
     {ok, Handle} = disk_log_1:change_size_wrap(Extra, NewSize, Version),
     erase(is_full),
     put(log, L#log{extra = Handle}),
+    ok;
+do_change_size(#log{type =rotate, extra = Extra} = L, NewSize) ->
+    {ok, Handle} = disk_log_1:change_size_rotate(Extra, NewSize),
+    erase(is_full),
+    put(log, L#log{extra = Handle}),
     ok.
 
 %% -> {ok, Head} | Error; Head = none | {head, H} | {M,F,A}
@@ -1389,14 +1457,15 @@ check_head({head, Term}, internal) ->
 check_head(_Head, _Format) ->
     {error, {badarg, head}}.
 
-check_size(wrap, {NewMaxB,NewMaxF}) when
-  is_integer(NewMaxB), is_integer(NewMaxF),
-  NewMaxB > 0, NewMaxB =< ?MAX_BYTES, NewMaxF > 0, NewMaxF < ?MAX_FILES ->
-    ok;
 check_size(halt, NewSize) when is_integer(NewSize), NewSize > 0 ->
     ok;
 check_size(halt, infinity) ->
     ok;
+check_size(Type, {NewMaxB,NewMaxF}) when
+    (Type =:= wrap orelse Type =:= rotate) andalso
+    is_integer(NewMaxB), is_integer(NewMaxF),
+    NewMaxB > 0, NewMaxB =< ?MAX_BYTES, NewMaxF > 0, NewMaxF < ?MAX_FILES ->
+    ok;
 check_size(_, _) ->
     not_ok.
 
@@ -1423,6 +1492,13 @@ do_inc_wrap_file(L) ->
 	    end
     end.
 
+%%-----------------------------------------------------------------
+%% Force log rotation.
+%%-----------------------------------------------------------------
+%% -> {ok, log()}
+do_inc_rotate_file(#log{extra = Handle, head = Head} = L) ->
+    Handle2 = disk_log_1:rotate_file(Handle, Head),
+    {ok, L#log{extra = Handle2}}.
 
 %%-----------------------------------------------------------------
 %% Open a log file.
@@ -1495,7 +1571,9 @@ close_disk_log2(L) ->
 	#log{format_type = halt_ext, extra = Halt} ->
 	    disk_log_1:fclose(Halt#halt.fdc, L#log.filename);
 	#log{format_type = wrap_ext, mode = Mode, extra = Handle} ->
-	    disk_log_1:mf_ext_close(Handle, Mode)
+	    disk_log_1:mf_ext_close(Handle, Mode);
+        #log{type = rotate, extra = Handle} ->
+            disk_log_1:rotate_ext_close(Handle)
     end,
     closed.
 
@@ -1591,6 +1669,8 @@ do_info(L, Cnt) ->
     Size = case Type of
 	       wrap ->
 		   disk_log_1:get_wrap_size(Extra);
+               rotate ->
+                   disk_log_1:get_rotate_size(Extra);
 	       halt ->
 		   Extra#halt.size
 	   end,
@@ -1609,6 +1689,11 @@ do_info(L, Cnt) ->
 		  {current_file, CurF},
 		  {no_overflows, {NewAccFull, NoFull}}
 		 ];
+             rotate when Mode =:= read_write ->
+                 #rotate_handle{curB = CurB} = Extra,
+		 [{no_current_bytes, CurB},
+		  {no_items, Cnt}
+		 ];
 	     halt when Mode =:= read_write ->
 		 IsFull = case get(is_full) of 
 			      undefined -> false; 
@@ -1713,7 +1798,11 @@ do_log(#log{format_type = wrap_ext}=L, B, _BSz) ->
 	{error, Error, Handle, Logged, Lost} ->
 	    put(log, L#log{extra = Handle}),
 	    {error, Error, Logged - Lost}
-    end.
+    end;
+do_log(#log{type = rotate}=L, B, _BSz) ->
+    {ok, Handle, Logged} = disk_log_1:rotate_ext_log(L#log.extra, B, L#log.head), %%error case here
+    put(log, L#log{extra = Handle}),
+    Logged.
 
 logl(B, external, undefined) ->
     {B, iolist_size(B)};
@@ -1763,6 +1852,10 @@ do_write_cache(#log{filename = FName, type = halt, extra = Halt} = Log) ->
 do_write_cache(#log{type = wrap, extra = Handle} = Log) ->
     {Reply, NewHandle} = disk_log_1:mf_write_cache(Handle),
     put(log, Log#log{extra = NewHandle}),
+    Reply;
+do_write_cache(#log{type = rotate, extra = Handle} = Log) ->
+    {Reply, NewHandle} = disk_log_1:rotate_write_cache(Handle),
+    put(log, Log#log{extra = NewHandle}),
     Reply.
 
 %% -> ok | Error
@@ -1770,7 +1863,7 @@ do_sync(#log{filename = FName, type = halt, extra = Halt} = Log) ->
     {Reply, NewFdC} = disk_log_1:sync(Halt#halt.fdc, FName),
     put(log, Log#log{extra = Halt#halt{fdc = NewFdC}}),
     Reply;
-do_sync(#log{type = wrap, extra = Handle} = Log) ->
+do_sync(#log{type = Type, extra = Handle} = Log) when Type == wrap orelse Type == rotate->
     {Reply, NewHandle} = disk_log_1:mf_sync(Handle),
     put(log, Log#log{extra = NewHandle}),
     Reply.
@@ -1815,7 +1908,12 @@ do_trunc(#log{type = wrap}=L, Head) ->
     NewLog2 = trunc_wrap(NewLog),
     NewHandle = (NewLog2#log.extra)#handle{noFull = 0, accFull = 0},
     do_change_size(NewLog2#log{extra = NewHandle, head = OldHead}, 
-		   {MaxB, MaxF}).
+		   {MaxB, MaxF});
+do_trunc(#log{type = rotate, head = Head, extra = Handle}=L, none) ->
+    Handle1 = disk_log_1:rotate_file(Handle, Head),
+    disk_log_1:remove_files(rotate, Handle1#rotate_handle.file, 0, Handle1#rotate_handle.maxF),
+    put(log, L#log{extra = Handle1}),
+    ok.
 
 trunc_wrap(L) ->
     case do_inc_wrap_file(L) of
@@ -1900,7 +1998,7 @@ merge_head(Head, _) ->
     Head.
 
 %% -> List of extensions of existing files (no dot included) | throw(FileError)
-wrap_file_extensions(File) -> 
+wrap_file_extensions(File) ->
     {_CurF, _CurFSz, _TotSz, NoOfFiles} =
 	disk_log_1:read_index_file(File),
     Fs = if 
@@ -1919,6 +2017,18 @@ wrap_file_extensions(File) ->
 	  end,
     lists:filter(Fun, ["idx", "siz" | Fs]).
 
+rotate_file_extensions(File, MaxF) ->
+    rotate_file_extensions(File, MaxF, 0, []).
+
+rotate_file_extensions(_File, MaxF, MaxF, Res) ->
+    Res;
+rotate_file_extensions(File, MaxF, N, Res) ->
+    Ext = integer_to_list(N) ++ ".gz", 
+    case file:read_file_info(add_ext(File, Ext)) of
+        {ok, _} -> rotate_file_extensions(File, MaxF, N+1, [Ext|Res]);
+	_ -> rotate_file_extensions(File, MaxF, N+1, Res)
+    end.
+
 add_ext(File, Ext) ->
     lists:concat([File, ".", Ext]).
 
diff --git a/lib/kernel/src/disk_log.hrl b/lib/kernel/src/disk_log.hrl
index 6cb2c13f02..46c1d0e5b1 100644
--- a/lib/kernel/src/disk_log.hrl
+++ b/lib/kernel/src/disk_log.hrl
@@ -56,7 +56,8 @@
 %%------------------------------------------------------------------------
 
 -type dlog_format()      :: 'external' | 'internal'.
--type dlog_format_type() :: 'halt_ext' | 'halt_int' | 'wrap_ext' | 'wrap_int'.
+-type dlog_format_type() :: 'halt_ext' | 'halt_int' | 'wrap_ext' | 'wrap_int'
+                          | 'rotate_ext'.
 -type dlog_head()        :: 'none' | {'ok', binary()} | mfa().
 -type dlog_head_opt()    :: none | term() | iodata().
 -type log()              :: term().  % XXX: refine
@@ -83,7 +84,7 @@
                           | {MaxNoBytes :: pos_integer(),
                              MaxNoFiles :: pos_integer()}.
 -type dlog_status()      :: 'ok' | {'blocked', 'false' | [_]}. %QueueLogRecords
--type dlog_type()        :: 'halt' | 'wrap'.
+-type dlog_type()        :: 'halt' | 'wrap' | 'rotate'.
 
 %%------------------------------------------------------------------------
 %% Records
@@ -129,7 +130,7 @@
 				%% time the wrap log has filled the 
 				%% Dir/Name.NewMaxF file.
 	 curB     :: non_neg_integer(),	%% Number of bytes on current file.
-	 curF     :: integer(), 	%% Current file number.
+	 curF     :: integer(), 	%% Current file number
 	 cur_fdc  :: #cache{}, 	 	%% Current file descriptor.
 	 cur_name :: file:filename(),	%% Current file name for error reports.
 	 cur_cnt  :: non_neg_integer(),	%% Number of items on current file,
@@ -146,6 +147,18 @@
 					%% overflows since the log was opened.
        ).
 
+-record(rotate_handle,
+        {file :: file:filename(),
+         cur_fdc :: #cache{},
+         inode,
+         file_check,
+         maxB :: pos_integer(),
+         maxF :: pos_integer() | {pos_integer(),pos_integer()},
+	 curB = 0 :: non_neg_integer(),
+         firstPos :: non_neg_integer(),
+         compress_on_rotate = true}
+        ).
+
 -record(log,
 	{status = ok       :: dlog_status(),
 	 name              :: dlog_name(), %% the key leading to this structure
@@ -160,8 +173,8 @@
 	                      %%  called when wraplog wraps
 	 mode		   :: dlog_mode(),
 	 size,                %% value of open/1 option 'size' (never changed)
-	 extra             :: #halt{} | #handle{}, %% type of the log
-	 version           :: integer()}	   %% if wrap log file
+	 extra             :: #halt{} | #handle{} | #rotate_handle{}, %% type of the log
+	 version           :: integer() | undefined}	   %% if wrap log file, undefined for halt and rotate
 	).
 
 -record(continuation,         %% Chunk continuation.
diff --git a/lib/kernel/src/disk_log_1.erl b/lib/kernel/src/disk_log_1.erl
index a488a44dcc..c366504512 100644
--- a/lib/kernel/src/disk_log_1.erl
+++ b/lib/kernel/src/disk_log_1.erl
@@ -23,10 +23,13 @@
 
 -export([int_open/4, ext_open/4, logl/1, close/3, truncate/3, chunk/5, 
          sync/2, write_cache/2]).
--export([mf_int_open/7, mf_int_log/3, mf_int_close/2, mf_int_inc/2, 
-	 mf_ext_inc/2, mf_int_chunk/4, mf_int_chunk_step/3, 
+-export([mf_int_open/7, mf_int_log/3, mf_int_close/2, mf_int_inc/2,
+	 mf_ext_inc/2, mf_int_chunk/4, mf_int_chunk_step/3,
 	 mf_sync/1, mf_write_cache/1]).
 -export([mf_ext_open/7, mf_ext_log/3, mf_ext_close/2]).
+-export([open_rotate_log_file/3, rotate_file/2,
+         rotate_ext_log/3, rotate_write_cache/1, rotate_ext_close/1,
+         change_size_rotate/2, get_rotate_size/1]).
 
 -export([print_index_file/1]).
 -export([read_index_file/1]).
@@ -38,6 +41,7 @@
 -export([is_head/1]).
 -export([position/3, truncate_at/3, fwrite/4, fclose/2]).
 -export([set_quiet/1, is_quiet/0]).
+-export([remove_files/4]).
 
 -compile({inline,[{scan_f2,7}]}).
 
@@ -455,7 +459,7 @@ new_ext_file(FName, Head) ->
 %% -> {FdC, {NoItemsWritten, NoBytesWritten}} | throw(Error)
 ext_log_head(Fd, Head) ->
     case lh(Head, external) of
-	{ok, BinHead} -> 
+	{ok, BinHead} ->
             Size = byte_size(BinHead),
             {ok, FdC} = fwrite_header(Fd, BinHead, Size),
             {FdC, {1, Size}};
@@ -678,7 +682,7 @@ mf_int_open(FName, MaxB, MaxF, Repair, Mode, Head, Version) ->
     end.
 
 %% -> {ok, handle(), Lost} | {error, Error, handle()}
-mf_int_inc(Handle, Head) -> 
+mf_int_inc(Handle, Head) ->
     #handle{filename = FName, cur_cnt = CurCnt, acc_cnt = AccCnt, 
 	    cur_name = FileName, curF = CurF, maxF = MaxF, 
 	    cur_fdc = CurFdC, noFull = NoFull} = Handle,
@@ -732,7 +736,7 @@ mf_int_log(Handle, Bins, Head, No0, Wraps) ->
 					    noFull = NoFull + 1},
 		    case catch close(CurFdC, FileName, read_write) of
 			ok ->
-			    mf_int_log(Handle1, Bins, Head, No0 + Nh, 
+			    mf_int_log(Handle1, Bins, Head, No0 + Nh,
 				       [Lost | Wraps]);
 			Error ->
 			    Lost1 = Lost + sum(Wraps),
@@ -845,7 +849,10 @@ mf_write_cache(#handle{filename = FName, cur_fdc = FdC} = Handle) ->
 %% -> {Reply, handle()}; Reply = ok | Error
 mf_sync(#handle{filename = FName, cur_fdc = FdC} = Handle) ->
     {Reply, NewFdC} = fsync(FdC, FName),
-    {Reply, Handle#handle{cur_fdc = NewFdC}}.
+    {Reply, Handle#handle{cur_fdc = NewFdC}};
+mf_sync(#rotate_handle{file = FName, cur_fdc = FdC} = Handle) ->
+    {Reply, NewFdC} = fsync(FdC, FName),
+    {Reply, Handle#rotate_handle{cur_fdc = NewFdC}}.
 
 %% -> ok | throw(FileError)
 mf_int_close(#handle{filename = FName, curF = CurF, cur_name = FileName, 
@@ -855,7 +862,7 @@ mf_int_close(#handle{filename = FName, curF = CurF, cur_name = FileName,
     ok.
 
 %% -> {ok, handle(), Cnt} | throw(FileError)
-mf_ext_open(FName, MaxB, MaxF, Repair, Mode, Head, Version) -> 
+mf_ext_open(FName, MaxB, MaxF, Repair, Mode, Head, Version) ->
     {First, Sz, TotSz, NFiles} = read_index_file(Repair, FName, MaxF),
     write_size_file(Mode, FName, MaxB, MaxF, Version),
     NewMaxF = if 
@@ -865,37 +872,37 @@ mf_ext_open(FName, MaxB, MaxF, Repair, Mode, Head, Version) ->
 		      MaxF
 	      end,
     {ok, FdC, FileName, Lost, {NoItems, NoBytes}, CurB} = 
-	ext_file_open(FName, First, 0, 0, Head, Repair, Mode),
+        ext_file_open(FName, First, 0, 0, Head, Repair, Mode),
     CurCnt = Sz + NoItems - Lost,
     {ok, #handle{filename = FName, maxB = MaxB, cur_name = FileName, 
-		 maxF = NewMaxF, cur_cnt = CurCnt, acc_cnt = -Sz,
-		 curF = First, cur_fdc = FdC, firstPos = NoBytes,
-		 curB = CurB, noFull = 0, accFull = 0},
+        	 maxF = NewMaxF, cur_cnt = CurCnt, acc_cnt = -Sz,
+        	 curF = First, cur_fdc = FdC, firstPos = NoBytes,
+        	 curB = CurB, noFull = 0, accFull = 0},
      TotSz + CurCnt}.
 
 %% -> {ok, handle(), Lost} 
 %%   | {error, Error, handle()}
 %%   | throw(FatalError)
 %% Fatal errors should always terminate the log.
-mf_ext_inc(Handle, Head) -> 
-    #handle{filename = FName, cur_cnt = CurCnt, cur_name = FileName, 
-	    acc_cnt = AccCnt, curF = CurF, maxF = MaxF, cur_fdc = CurFdC, 
-	    noFull = NoFull} = Handle,
+mf_ext_inc(Handle, Head) ->
+    #handle{filename = FName, cur_cnt = CurCnt, cur_name = FileName,
+        acc_cnt = AccCnt, curF = CurF, maxF = MaxF, cur_fdc = CurFdC,
+        noFull = NoFull} = Handle,
     case catch wrap_ext_log(FName, CurF, MaxF, CurCnt, Head) of
-	{NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost} ->
-	    Handle1 = Handle#handle{cur_fdc = NewFdC, curF = NewF, 
-				    cur_name = NewFileName,
-				    cur_cnt = Nh, acc_cnt = AccCnt + CurCnt, 
-				    maxF = NewMaxF, firstPos = FirstPos, 
-				    curB = FirstPos, noFull = NoFull + 1},
-	    case catch fclose(CurFdC, FileName) of
-		ok ->
-		    {ok, Handle1, Lost};
-		Error -> % Error in the last file, new file opened.
-		    {error, Error, Handle1}
-	    end;
-	Error ->
-	    {error, Error, Handle}
+        {NewF, NewMaxF, NewFdC, NewFileName, Nh, FirstPos, Lost} ->
+            Handle1 = Handle#handle{cur_fdc = NewFdC, curF = NewF,
+                cur_name = NewFileName,
+                cur_cnt = Nh, acc_cnt = AccCnt + CurCnt,
+                maxF = NewMaxF, firstPos = FirstPos,
+                curB = FirstPos, noFull = NoFull + 1},
+            case catch fclose(CurFdC, FileName) of
+                ok ->
+                    {ok, Handle1, Lost};
+                Error -> % Error in the last file, new file opened.
+                    {error, Error, Handle1}
+            end;
+        Error ->
+            {error, Error, Handle}
     end.
 
 %% -> {ok, handle(), Logged, Lost, NoWraps} | {ok, handle(), Logged} 
@@ -968,18 +975,201 @@ mf_ext_close(#handle{filename = FName, curF = CurF,
     Res.
 
 %% -> {ok, handle()} | throw(FileError)
-change_size_wrap(Handle, {NewMaxB, NewMaxF}, Version) ->
-    FName = Handle#handle.filename,
+change_size_wrap(#handle{filename = FName} = Handle, {NewMaxB, NewMaxF}, Version) ->
     {_MaxB, MaxF} = get_wrap_size(Handle),
     write_size_file(read_write, FName, NewMaxB, NewMaxF, Version),
     if
-	NewMaxF > MaxF ->
-	    remove_files(FName, MaxF + 1, NewMaxF),
-	    {ok, Handle#handle{maxB = NewMaxB, maxF = NewMaxF}};
-	NewMaxF < MaxF ->
-	    {ok, Handle#handle{maxB = NewMaxB, maxF = {NewMaxF, MaxF}}};
-	true ->
-	    {ok, Handle#handle{maxB = NewMaxB, maxF = NewMaxF}}
+        NewMaxF > MaxF ->
+            remove_files(wrap, FName, MaxF + 1, NewMaxF),
+            {ok, Handle#handle{maxB = NewMaxB, maxF = NewMaxF}};
+        NewMaxF < MaxF ->
+            {ok, Handle#handle{maxB = NewMaxB, maxF = {NewMaxF, MaxF}}};
+        true ->
+            {ok, Handle#handle{maxB = NewMaxB, maxF = NewMaxF}}
+    end.
+
+change_size_rotate(#rotate_handle{maxB = MaxB, maxF = MaxF, file = FName} = Handle, {NewMaxB, NewMaxF}) ->
+    {MaxB, MaxF1} = get_size(MaxB, MaxF),
+    if
+        NewMaxF > MaxF1 ->
+            remove_files(rotate, FName, MaxF1, NewMaxF),
+            {ok, Handle#rotate_handle{maxB = NewMaxB, maxF = NewMaxF}};
+        NewMaxF < MaxF1 ->
+            remove_files(rotate, FName, NewMaxF, MaxF1),
+            {ok, Handle#rotate_handle{maxB = NewMaxB, maxF = NewMaxF}};
+        true ->
+            {ok, Handle#rotate_handle{maxB = NewMaxB, maxF = NewMaxF}}
+    end.
+
+open_rotate_log_file(FileName, Size, Head) ->
+    try
+        case filelib:ensure_dir(FileName) of
+            ok ->
+                case file:open(FileName, [raw, binary, read, append]) of
+                    {ok, Fd} ->
+                        {FdC1, _HeadSize} = ext_log_head(Fd, Head),
+                        {FdC, FileSize} = position_close(FdC1, FileName, cur),       
+                        {ok,#file_info{inode=INode}} =
+                            file:read_file_info(FileName,[raw]),
+                        {MaxB, MaxF} = Size,
+			RotHandle = #rotate_handle{file = FileName,
+						   cur_fdc = FdC,
+						   maxB = MaxB,
+						   maxF = MaxF,
+						   curB = FileSize,
+                                                   firstPos = FileSize,
+						   inode = INode},
+			update_rotation(RotHandle),
+			{ok, RotHandle};
+                    Error ->
+                        Error
+                end;
+            Error ->
+                Error
+        end
+    catch
+        _:Reason -> {error,Reason}
+    end.
+
+update_rotation(#rotate_handle{file = FName, maxF = MaxF}) ->
+    maybe_remove_archives(MaxF, FName),
+    maybe_update_compress(0, MaxF,FName).
+
+maybe_remove_archives(Count, FName) ->
+    Archive = rotate_file_name(FName, Count),
+    case file:read_file_info(Archive,[raw]) of
+        {error,enoent} ->
+            ok;
+        _ ->
+            _ = file:delete(Archive),
+            maybe_remove_archives(Count+1, FName)
+    end.
+
+maybe_update_compress(MaxF, MaxF, _FName) ->
+    ok;
+maybe_update_compress(N, MaxF, FName) ->
+    FileName = add_ext(FName, N),
+    case file:read_file_info(FileName,[raw]) of
+        {ok,_} ->
+            compress_file(FileName);
+        _ ->
+            ok
+    end,
+    maybe_update_compress(N+1, MaxF, FName).    
+
+rotate_file(#rotate_handle{file = FName, maxF = MaxF, cur_fdc = FdC} = RotHandle, Head) ->
+    #cache{fd = Fd, c = C} = FdC,
+    {_, _C1} = write_cache(Fd, FName, C),
+    _ = delayed_write_close(Fd),
+    rotate_files(FName, MaxF),
+    {ok, NewFdC, FileSize} = ensure_open(FName, Head),
+    {ok,#file_info{inode=INode}} = file:read_file_info(FName,[raw]),
+    RotHandle#rotate_handle{cur_fdc = NewFdC, inode = INode, curB = FileSize, firstPos = FileSize}.
+
+rotate_files(FileName,0) ->
+    _ = file:delete(FileName),
+    ok;
+rotate_files(FileName, 1) ->
+    FileName0 = FileName ++".0",
+    Rename = file:rename(FileName, FileName0),
+    %% Rename may fail if file has been deleted. If it has, then
+    %% we do not need to compress it...
+    if Rename =:= ok -> compress_file(FileName0);
+        true -> ok
+    end,
+    ok;
+rotate_files(FileName, Count) ->
+    _ = file:rename(rotate_file_name(FileName, Count-2), rotate_file_name(FileName, Count-1)),
+    rotate_files(FileName, Count-1).
+
+rotate_file_name(FileName, Count) ->
+    concat([FileName, ".", Count, ".gz"]).
+
+compress_file(FileName) ->
+    {ok,In} = file:open(FileName,[read,binary]),
+    {ok,Out} = file:open(FileName++".gz",[write]),
+    Z = zlib:open(),
+    zlib:deflateInit(Z, default, deflated, 31, 8, default),
+    compress_data(Z,In,Out),
+    zlib:deflateEnd(Z),
+    zlib:close(Z),
+    _ = file:close(In),
+    _ = file:close(Out),
+    _ = file:delete(FileName),
+    ok.
+
+compress_data(Z,In,Out) ->
+    case file:read(In,100000) of
+        {ok,Data} ->
+            Compressed = zlib:deflate(Z, Data),
+            _ = file:write(Out,Compressed),
+            compress_data(Z,In,Out);
+        eof ->
+            Compressed = zlib:deflate(Z, <<>>, finish),
+            _ = file:write(Out,Compressed),
+            ok
+    end.
+
+rotate_ext_log(Handle, Bin, Head) ->
+    rotate_ext_log(Handle, Bin, Head, 0).
+
+rotate_ext_log(Handle, [], _Head, N) ->
+    {ok, Handle, N};
+rotate_ext_log(Handle, Bins, Head, N0) ->
+    #rotate_handle{file = FileName, maxB = MaxB, cur_fdc = CurFdC, 
+            curB = CurB, firstPos = FirstPos} = Handle,
+    {FirstBins, LastBins, NoBytes, N} = 
+	ext_split_bins(CurB, MaxB, FirstPos, Bins),
+    case FirstBins of
+	[] ->
+            Handle1 = rotate_file(Handle, Head),
+	    rotate_ext_log(Handle1, Bins, Head, N0);
+	_ ->
+	    case fwrite(CurFdC, FileName, FirstBins, NoBytes) of
+                {ok, NewCurFdC} ->
+		    Handle1 = Handle#rotate_handle{cur_fdc = NewCurFdC, 
+                                            curB = CurB + NoBytes},
+		    rotate_ext_log(Handle1, LastBins, Head, N0 + N);
+		{Error, NewCurFdC} ->
+		    Handle1 = Handle#rotate_handle{cur_fdc = NewCurFdC},
+		    {error, Error, Handle1}
+	    end
+    end.
+
+%% -> {Reply, handle()}; Reply = ok | Error
+rotate_write_cache(#rotate_handle{file = FName, cur_fdc = FdC} = Handle) ->
+    erase(write_cache_timer_is_running),
+    #cache{fd = Fd, c = C} = FdC,
+    {Reply, NewFdC} = write_cache(Fd, FName, C),
+    {Reply, Handle#rotate_handle{cur_fdc = NewFdC}}.
+
+rotate_ext_close(#rotate_handle{file = FName, cur_fdc = CurFdC}) ->
+    (catch fclose(CurFdC, FName)).
+
+ensure_open(Filename, Head) ->
+    case filelib:ensure_dir(Filename) of
+        ok ->
+            case open_update(Filename) of
+                {ok, Fd} ->
+                    {FdC1, _HeadSize} = ext_log_head(Fd, Head),
+                    {FdC, FileSize} = position_close(FdC1, Filename, cur),
+                    {ok, FdC, FileSize};
+                Error ->
+                    exit({could_not_reopen_file,Error})
+            end;
+        Error ->
+            exit({could_not_create_dir_for_file,Error})
+    end.
+
+%% A special close that closes the FD properly when the delayed write close failed
+delayed_write_close(Fd) ->
+    case file:close(Fd) of
+        %% We got an error while closing, could be a delayed write failing
+        %% So we close again in order to make sure the file is closed.
+        {error, _} ->
+            file:close(Fd);
+        Res ->
+            Res
     end.
 
 %%-----------------------------------------------------------------
@@ -1037,7 +1227,7 @@ ext_file_open(FName, NewFile, OldFile, OldCnt, Head, Repair, Mode) ->
 -define(index_file_name(F), add_ext(F, "idx")).
 
 read_index_file(truncate, FName, MaxF) ->
-    remove_files(FName, 2, MaxF),
+    remove_files(wrap, FName, 2, MaxF),
     _ = file:delete(?index_file_name(FName)),
     {1, 0, 0, 0};
 read_index_file(_, FName, _MaxF) ->
@@ -1139,7 +1329,7 @@ write_index_file(read_write, FName, NewFile, OldFile, OldCnt) ->
 		    _ = file:close(Fd),
 		    case R of
 			{ok, <<Lost:SzSz/unit:8>>} -> Lost;
-			{ok, _} -> 
+			{ok, _} ->
                             throw({error, {invalid_index_file, FileName}});
 			eof    -> 0;
 			Error2 -> file_error(FileName, Error2)
@@ -1342,7 +1532,7 @@ inc_wrap(FName, CurF, MaxF) ->
 	    if 
 		CurF >= NewMaxF ->
 		    %% We are at or above the new number of files
-		    remove_files(FName, CurF + 1, OldMaxF),
+		    remove_files(wrap, FName, CurF + 1, OldMaxF),
 		    if 
 			CurF > NewMaxF ->
 			    %% The change was done while the current file was 
@@ -1389,24 +1579,34 @@ file_size(Fname) ->
 
 %% -> ok | throw(FileError)
 %% Tries to remove each file with name FName.I, N<=I<=Max.
-remove_files(FName, N, Max) ->
-    remove_files(FName, N, Max, ok).
+remove_files(Type, FName, N, Max) ->
+    remove_files(Type, FName, N, Max, ok).
 
-remove_files(_FName, N, Max, ok) when N > Max ->
+remove_files(_Type, _FName, N, Max, ok) when N > Max ->
     ok;
-remove_files(_FName, N, Max, {FileName, Error}) when N > Max ->
+remove_files(_Type, _FName, N, Max, {FileName, Error}) when N > Max ->
     file_error(FileName, Error);
-remove_files(FName, N, Max, Reply) ->
-    FileName = add_ext(FName, N),
+remove_files(Type, FName, N, Max, Reply) ->
+    FileName =
+        case Type of
+            wrap -> add_ext(FName, N);
+            rotate -> rotate_file_name(FName, N)
+        end,
     NewReply = case file:delete(FileName) of
 		   ok -> Reply;
 		   {error, enoent} -> Reply;
 		   Error -> {FileName, Error}
 	       end,
-    remove_files(FName, N + 1, Max, NewReply).
+    remove_files(Type, FName, N + 1, Max, NewReply).
 
 %% -> {MaxBytes, MaxFiles}
 get_wrap_size(#handle{maxB = MaxB, maxF = MaxF}) ->
+    get_size(MaxB, MaxF).
+
+get_rotate_size(#rotate_handle{maxB = MaxB, maxF = MaxF}) ->
+    get_size(MaxB, MaxF).
+
+get_size(MaxB, MaxF) ->
     case MaxF of
 	{NewMaxF,_} -> {MaxB, NewMaxF};
 	MaxF        -> {MaxB, MaxF}
@@ -1586,6 +1786,7 @@ write_cache_close(Fd, FileName, C) ->
 
 -spec file_error(file:filename(), {'error', file:posix()}) -> no_return().
 
+
 file_error(FileName, {error, Error}) ->
     throw({error, {file_error, FileName, Error}}).
 
diff --git a/lib/kernel/test/disk_log_SUITE.erl b/lib/kernel/test/disk_log_SUITE.erl
index 36b3476320..d80201679c 100644
--- a/lib/kernel/test/disk_log_SUITE.erl
+++ b/lib/kernel/test/disk_log_SUITE.erl
@@ -34,6 +34,8 @@
 -define(datadir(Conf), proplists:get_value(data_dir, Conf)).
 -endif.
 
+-compile(export_all).
+
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2, 
 
@@ -52,6 +54,9 @@
 
 	 wrap_ext_1/1, wrap_ext_2/1,
 
+	 rotate_1/1, rotate_truncate/1, rotate_reopen/1,
+         rotate_breopen/1, next_rotate_file/1,
+
 	 head_func/1, plain_head/1, one_header/1,
 
 	 wrap_notif/1, full_notif/1, trunc_notif/1, blocked_notif/1,
@@ -118,7 +123,7 @@
 	 notif, new_idx_vsn, reopen, block, unblock, open, close,
 	 error, chunk, truncate, many_users, info, change_size,
 	 open_change_size, change_attribute, otp_6278, otp_10131,
-         otp_16768, otp_16809]).
+         otp_16768, otp_16809, rotate]).
 
 
 suite() ->
@@ -127,7 +132,7 @@ suite() ->
 
 all() -> 
     [{group, halt_int}, {group, wrap_int},
-     {group, halt_ext}, {group, wrap_ext},
+     {group, halt_ext}, {group, wrap_ext}, {group, rotate},
      {group, read_mode}, {group, head}, {group, notif},
      new_idx_vsn, reopen, {group, block}, unblock,
      {group, open}, {group, close}, {group, error}, chunk,
@@ -146,6 +151,9 @@ groups() ->
      {halt_ext, [], [halt_ext_inf, {group, halt_ext_sz}]},
      {halt_ext_sz, [], [halt_ext_sz_1, halt_ext_sz_2]},
      {wrap_ext, [], [wrap_ext_1, wrap_ext_2]},
+     {rotate, [],
+      [rotate_1, rotate_truncate, rotate_reopen,
+       rotate_breopen, next_rotate_file]},
      {head, [], [head_func, plain_head, one_header]},
      {notif, [],
       [wrap_notif, full_notif, trunc_notif, blocked_notif]},
@@ -815,6 +823,166 @@ wrap_ext_2(Conf) when is_list(Conf) ->
     del(File3, 3),
     ok.
 
+%% Test rotate disk log, external, size defined.
+rotate_1(Conf) when is_list(Conf) ->
+    Dir = ?privdir(Conf),
+    File = filename:join(Dir, "a.LOG"),
+    Name = a,
+    {ok, Name} = disk_log:open([{name,Name}, {type,rotate}, {size,{8000, 3}},
+			     {format,external},
+			     {file, File}]),
+    x2simple_log(File, Name),
+    ok = disk_log:close(Name),
+    del_rot_files(File, 4),
+    {ok, Name} = disk_log:open([{name,Name}, {type,rotate}, {size,{8000, 3}},
+			     {format,external},
+			     {file, File}]),
+    {B1, _T1} = x_mk_bytes(10000), % lost due to rotation 
+    {B2, T2} = x_mk_bytes(5000),  % file a.LOG.2.gx 
+    {B3, T3} = x_mk_bytes(4000),  % file a.LOG.1.gz 
+    {B4, T4} = x_mk_bytes(2000),  % file a.LOG.1.gz
+    {B5, T5} = x_mk_bytes(5000),  % file a.LOG.0.gz 
+    {B6, T6} = x_mk_bytes(5000),  % in the active file 
+    ok = disk_log:blog(Name, B1),
+    ok = disk_log:blog(Name, B2),
+    ok = disk_log:blog(Name, B3),
+    ok = disk_log:blog_terms(a, [B4, B5, B6]),
+    case get_list(File ++ ".2.gz", Name, rotate) of
+        T2 ->
+            ok;
+        E2 ->
+            test_server_fail({bad_terms, E2, T2})
+    end,
+    T34 = T3 ++ T4,
+    case get_list(File ++ ".1.gz", Name, rotate) of
+        T34 ->
+            ok;
+        E34 ->
+            test_server_fail({bad_terms, E34, T34})
+    end,
+    case get_list(File ++ ".0.gz", Name, rotate) of
+        T5 ->
+            ok;
+        E5 ->
+            test_server_fail({bad_terms, E5, T5})
+    end,
+    case get_list(File, Name) of
+        T6 ->
+            ok;
+        E6 ->
+            test_server_fail({bad_terms, E6, T6})
+    end,
+    ok = disk_log:close(Name),
+    del_rot_files(File, 3).
+
+%% test truncate/1 for rotate logs
+rotate_truncate(Conf) when is_list(Conf) ->
+    Dir = ?privdir(Conf),
+    File = filename:join(Dir, "a.LOG"),
+    Name = a,
+    {ok, Name} = disk_log:open([{name,Name}, {type,rotate}, {size,{100, 3}},
+			     {format,external},
+			     {file, File}]),
+    B = mk_bytes(60),
+    ok = disk_log:blog_terms(Name, [B, B, B]),
+    B = get_list(File, Name),
+    B = get_list(File ++ ".0.gz", Name, rotate),
+    B = get_list(File ++ ".1.gz", Name, rotate),
+    ok = disk_log:truncate(Name),
+    [] = get_list(File, Name),
+    {error, enoent} = file:read_file_info(File ++ ".0.gz"),
+    {error, enoent} = file:read_file_info(File ++ ".1.gz"),
+    ok = disk_log:close(Name),
+    file:delete(File).
+
+%% test reopen/2 for rotate logs
+rotate_reopen(Conf) when is_list(Conf) ->
+    Dir = ?privdir(Conf),
+    File = filename:join(Dir, "a.LOG"),
+    Name = a,
+    {ok, Name} = disk_log:open([{name,Name}, {type,rotate}, {size,{100, 3}},
+			     {format,external},
+			     {file, File}]),
+    B = mk_bytes(60),
+    ok = disk_log:blog_terms(Name, [B, B, B]),
+    B = get_list(File, Name),
+    B = get_list(File ++ ".0.gz", Name, rotate),
+    B = get_list(File ++ ".1.gz", Name, rotate),
+    File1 = filename:join(Dir, "b.LOG"),
+    ok = disk_log:reopen(Name, File1),
+    [] = get_list(File, Name),
+    {error, enoent} = file:read_file_info(File ++ ".0.gz"),
+    {error, enoent} = file:read_file_info(File ++ ".1.gz"),
+    B = get_list(File1 ++ ".0.gz", Name, rotate),
+    B = get_list(File1 ++ ".1.gz", Name, rotate),
+    B = get_list(File1 ++ ".2.gz", Name, rotate),
+    ok = disk_log:close(Name),
+    file:delete(File),
+    del_rot_files(File1, 3).
+
+%% test breopen/3 for rotate logs
+rotate_breopen(Conf) when is_list(Conf) ->
+    Dir = ?privdir(Conf),
+    File1 = filename:join(Dir, "a.LOG"),
+    Name = a,
+    Head1 = "thisishead1",
+    {ok, Name} = disk_log:open([{name,Name}, {type,rotate}, {size,{100, 3}},
+			     {format,external},
+                             {head, Head1},
+			     {file, File1}]),
+    B = mk_bytes(60),
+    ok = disk_log:blog_terms(Name, [B, B, B]),
+    FileCont = Head1 ++ B,
+    FileCont = get_list(File1, Name),
+    FileCont = get_list(File1 ++ ".0.gz", Name, rotate),
+    FileCont = get_list(File1 ++ ".1.gz", Name, rotate),
+    File2 = filename:join(Dir, "b.LOG"),
+    Head2 = "thisishead2",
+    ok = disk_log:breopen(Name, File2, Head2),
+    Head2 = get_list(File1, Name),
+    {error, enoent} = file:read_file_info(File1 ++ ".0.gz"),
+    {error, enoent} = file:read_file_info(File1 ++ ".1.gz"),
+    FileCont = get_list(File2 ++ ".0.gz", Name, rotate),
+    FileCont = get_list(File2 ++ ".1.gz", Name, rotate),
+    FileCont = get_list(File2 ++ ".2.gz", Name, rotate),
+    ok = disk_log:close(Name),
+    file:delete(File1),
+    del_rot_files(File2, 3).
+
+%% Test rotate log, force a change to next file.
+next_rotate_file(Conf) when is_list(Conf) ->
+    Dir = ?privdir(Conf),
+    File1 = filename:join(Dir, "a.LOG"),
+    File2 = filename:join(Dir, "b.LOG"),
+
+    %% Test that halt and wrap logs get error messages
+    {ok, a} = disk_log:open([{name, a}, {type, halt},
+			     {format, internal},
+			     {file, File1}]),
+    ok = disk_log:log(a, "message one"),
+    {error, {halt_log, a}} = disk_log:next_file(a),
+
+    %% test a rotate log file
+    {ok, b} = disk_log:open([{name, b}, {type, rotate}, {size, {100,3}},
+			     {format,external},
+			     {file, File2}]),
+    ok = disk_log:blog(b, "message one"),
+    ok = disk_log:next_file(b),
+    ok = disk_log:blog(b, "message two"),
+    ok = disk_log:next_file(b),
+    ok = disk_log:blog(b, "message three"),
+    ok = disk_log:next_file(b),
+    ok = disk_log:blog(b, "message four"),
+    ok = disk_log:sync(b),
+    "message one" = get_list(File2 ++ ".2.gz", b, rotate),
+    "message two" = get_list(File2 ++ ".1.gz", b, rotate),
+    "message three" = get_list(File2 ++ ".0.gz", b, rotate),
+    "message four" = get_list(File2, b),
+    ok = disk_log:close(a),
+    ok = disk_log:close(b),
+    ok = file:delete(File1),
+    del_rot_files(File2, 3).
+
 simple_log(Log) ->
     T1 = "hej",
     T2 = hopp,
@@ -893,6 +1061,37 @@ get_list(File, Log) ->
     {ok, B} = file:read_file(File),
     binary_to_list(B).
 
+get_list(File, Log, rotate) ->
+    ct:pal(?HI_VERBOSITY, "File ~p~n", [File]),
+    ok = disk_log:sync(Log),
+    DFile = filename:rootname(File,".gz"),
+    decompress_file(File, DFile),
+    {ok, B} = file:read_file(DFile),
+    file:delete(DFile),
+    binary_to_list(B).
+
+decompress_file(FileName, DFileName) ->
+    {ok,In} = file:open(FileName,[read,binary]),
+    {ok,Out} = file:open(DFileName,[write]),
+    Z = zlib:open(),
+    zlib:inflateInit(Z, 31),
+    decompress_data(Z,In,Out),
+    zlib:inflateEnd(Z),
+    zlib:close(Z),
+    _ = file:close(In),
+    _ = file:close(Out),
+    ok.
+
+decompress_data(Z,In,Out) ->
+    case file:read(In,1000) of
+        {ok,Data} ->
+            Decompressed = zlib:inflate(Z, Data),
+            _ = file:write(Out,Decompressed),
+            decompress_data(Z,In,Out);
+        eof ->
+            ok
+    end.
+
 
 get_all_terms(Log, File, Type) ->
     {ok, _Log} = disk_log:open([{name,Log}, {type,Type}, {size,infinity},
@@ -969,6 +1168,13 @@ del(File, N) ->
     file:delete(File ++ "." ++ integer_to_list(N)),
     del(File, N-1).
 
+del_rot_files(File, 0) ->
+    file:delete(File ++ ".0.gz"),
+    file:delete(File);
+del_rot_files(File, N) ->
+    file:delete(File ++ "." ++ integer_to_list(N) ++ ".gz"),
+    del_rot_files(File, N-1).
+
 test_server_fail(R) ->
     exit({?MODULE, get(line), R}).
 
diff --git a/system/doc/general_info/DEPRECATIONS b/system/doc/general_info/DEPRECATIONS
index c163ecb322..4bb378c5f1 100644
--- a/system/doc/general_info/DEPRECATIONS
+++ b/system/doc/general_info/DEPRECATIONS
@@ -20,6 +20,7 @@
 #
 # Added in OTP 26.
 #
+disk_log:inc_wrap_file/1 since=26
 file:pid2name/1 since=26 remove=27
 
 #
-- 
2.35.3

openSUSE Build Service is sponsored by