Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
2031-kernel-Remove-support-for-distributed-disk...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2031-kernel-Remove-support-for-distributed-disk-logs.patch of Package erlang
From 0e71844663a10d6b237cc96804cd000f12d22709 Mon Sep 17 00:00:00 2001 From: Hans Bolinder <hasse@erlang.org> Date: Fri, 21 Aug 2020 09:38:25 +0200 Subject: [PATCH 1/5] kernel: Remove support for distributed disk logs disk_log:all/0 is a new function, which is to be used instead of disk_log:accessible_logs/0. disk_log:accessible_logs/0 and disk_log:lclose/1,2 are deprecated. --- lib/kernel/doc/src/disk_log.xml | 147 ++---- lib/kernel/src/disk_log.erl | 124 ++--- lib/kernel/src/disk_log.hrl | 6 +- lib/kernel/src/disk_log_server.erl | 203 ++------ lib/kernel/test/disk_log_SUITE.erl | 730 +-------------------------- lib/stdlib/src/otp_internal.erl | 6 + system/doc/general_info/DEPRECATIONS | 3 + 7 files changed, 112 insertions(+), 1107 deletions(-) diff --git a/lib/kernel/doc/src/disk_log.xml b/lib/kernel/doc/src/disk_log.xml index 5a33796005..d49ab07267 100644 --- a/lib/kernel/doc/src/disk_log.xml +++ b/lib/kernel/doc/src/disk_log.xml @@ -127,52 +127,10 @@ functions fail. The corresponding terms (not the binaries) are returned when <c>chunk/2,3</c> is called. </p> - <note><p> - The distributed disk log feature has been deprecated. This - feature has also been scheduled for removal in OTP 24. - </p></note> - <p>A collection of open disk logs with the same name running on - different nodes is said to be a <em>distributed disk log</em> - if requests made to any of the logs are automatically made to - the other logs as well. The members of such a collection are - called individual distributed disk logs, or just distributed - disk logs if there is no risk of confusion. There is no order - between the members of such a collection. For example, logged - terms are not necessarily written to the node where the - request was made before written to the other nodes. However, - a few functions do not make requests to all - members of distributed disk logs, namely - <seemfa marker="#info/1"><c>info/1</c></seemfa>, - <seemfa marker="#chunk/2"><c>chunk/2,3</c></seemfa>, - <seemfa marker="#bchunk/2"><c>bchunk/2,3</c></seemfa>, - <seemfa marker="#chunk_step/3"><c>chunk_step/3</c></seemfa>, and - <seemfa marker="#lclose/1"><c>lclose/1,2</c></seemfa>.</p> - <p>An open disk log that is not a distributed disk - log is said to be a <em>local disk log</em>. A local disk log is - only accessible from the node where the disk log process runs, - whereas a distributed disk log is accessible from all nodes in - the Erlang system, except for those nodes where a local - disk log with the same name as the distributed disk log exists. - All processes on nodes that have access to a local or - distributed disk log can log items or otherwise change, inspect, - or close the log. + <p>An open disk log is only accessible from the node where the disk + log process runs. All processes on the node where the disk log process + runs can log items or otherwise change, inspect, or close the log. </p> - <p>It is not guaranteed that all log files of a distributed disk log - contain the same log items. No attempt is made to synchronize - the contents of the files. However, as long as at least one of - the involved nodes is alive at each time, all items are logged. - When logging items to a distributed log, or otherwise trying to - change the log, the replies from individual logs are - ignored. If all nodes are down, the disk log functions - reply with a <c>nonode</c> error. - </p> - <note> - <p>In some applications, it can be unacceptable that - replies from individual logs are ignored. An alternative in such - situations is to use many local disk logs instead of one - distributed disk log, and implement the distribution without use - of the <c>disk_log</c> module.</p> - </note> <p>Errors are reported differently for asynchronous log attempts and other uses of the <c>disk_log</c> module. When used synchronously, this module replies with an error message, but when called @@ -242,15 +200,27 @@ </datatypes> <funcs> <func> - <name name="accessible_logs" arity="0" since=""/> + <name name="all" arity="0" since="OTP 24.0"/> <fsummary>Return the accessible disk logs on the current node.</fsummary> <desc> <p>Returns the names of the disk logs accessible on the current node. - The first list contains local disk logs and the - second list contains distributed disk logs. </p> </desc> </func> + <func> + <name name="accessible_logs" arity="0" since=""/> + <fsummary>Return the accessible disk logs on the current node.</fsummary> + <desc> + <p>Returns the names of the disk logs accessible on the current node. + The first list contains the logs. The second list is always empty + (before Erlang/OTP 24.0 it used to contain so called distributed + disk logs). + </p> + <note><p>This function is deprecated. + Use <seemfa marker="#all/0"><c>all/0</c></seemfa> instead. + </p></note> + </desc> + </func> <func> <name name="alog" arity="2" since=""/> <name name="balog" arity="2" since=""/> @@ -409,10 +379,7 @@ </p> <p>The first time <c>chunk()</c> (or <c>bchunk()</c>) is called, an initial continuation, the atom <c>start</c>, must be - provided. If a disk log process is running on the - current node, terms are read from that log. Otherwise, an - individual distributed log on some other node is chosen, if - such a log exists. + provided. </p> <p>When <c>chunk/3</c> is called, <c><anno>N</anno></c> controls the maximum number of terms that are read from the log in each @@ -472,10 +439,8 @@ continuation returned, points to the first log item in the new current file. </p> - <p>If atom <c>start</c> is specified as continuation, a disk log - to read terms from is chosen. A local or distributed disk log - on the current node is preferred to an - individual distributed log on some other node. + <p>If atom <c>start</c> is specified as continuation, the first + file of the wrap log is chosen as the new current file. </p> <p>If the wrap log is not full because all files are not yet used, <c>{error, end_of_log}</c> is returned if trying to @@ -489,7 +454,7 @@ <type name="close_error_rsn"/> <desc> <p><marker id="close_1"></marker>Closes a - local or distributed disk log properly. An internally + disk log properly. An internally formatted log must be closed before the Erlang system is stopped. Otherwise, the log is regarded as unclosed and the automatic repair procedure is activated next time the @@ -542,10 +507,8 @@ <fsummary>Return information about a disk log.</fsummary> <type name="dlog_info"/> <desc> - <p>Returns a list of <c>{Tag, Value}</c> pairs describing the log. - If a disk log process is running on the current node, - that log is used as source of information, otherwise an individual - distributed log on some other node is chosen, if such a log exists. + <p>Returns a list of <c>{Tag, Value}</c> pairs describing a log + running on the node. </p> <p>The following pairs are returned for all logs: </p> @@ -607,17 +570,6 @@ current invocation of function <c>info/1</c> is gathered from the disk log process running on <c><anno>Node</anno></c>.</p> </item> - <tag><c>{distributed, <anno>Dist</anno>}</c></tag> - <item> - <p>If the log is local on - the current node, <c><anno>Dist</anno></c> has the value <c>local</c>, - otherwise all nodes where the log is distributed - are returned as a list.</p> - <warning><p> - The distributed disk log feature has been deprecated. This - feature has also been scheduled for removal in OTP 24. - </p></warning> - </item> </taglist> <p>The following pairs are returned for all logs opened in <c>read_write</c> mode: @@ -698,17 +650,19 @@ <fsummary>Close a disk log on one node.</fsummary> <type name="lclose_error_rsn"/> <desc> - <p><c>lclose/1</c> closes a local log or an individual distributed - log on the current node.</p> - <p><c>lclose/2</c> closes an individual distributed log on the - specified node if the node is not the current one.</p> + <p><c>lclose/1</c> closes a disk log on the current node.</p> + <p><c>lclose/2</c> closes a disk log on the + current node if <anno>Node</anno> is the current node.</p> <p><c>lclose(<anno>Log</anno>)</c> is equivalent to <c>lclose(<anno>Log</anno>, node())</c>. See also <seeerl marker="#close_1"><c>close/1</c></seeerl>. </p> - <p>If no log with the specified name exist on the specified node, + <p>If no log with the specified name exist on the current node, <c>no_such_log</c> is returned. </p> + <note><p>These functions are deprecated. Use + <seemfa marker="#close/1"><c>close/1</c></seemfa> + instead.</p></note> </desc> </func> <func> @@ -723,8 +677,7 @@ <p>Synchronously appends a term to a disk log. Returns <c>ok</c> or <c>{error, <anno>Reason</anno>}</c> when the term is written to - disk. If the log is distributed, <c>ok</c> is returned, - unless all nodes are down. Terms are written by + disk. Terms are written by the ordinary <c>write()</c> function of the operating system. Hence, it is not guaranteed that the term is written to disk, it can linger in @@ -781,9 +734,6 @@ <type name="dlog_options"/> <type name="dlog_option"/> <type name="open_ret"/> - <type name="ret"/> - <type name="dist_open_ret"/> - <type name="dist_error_rsn"/> <type name="open_error_rsn"/> <type name="dlog_optattr"/> <type name="dlog_size"/> @@ -873,18 +823,6 @@ the tuple <c>{error, {size_mismatch, <anno>CurrentSize</anno>, <anno>NewSize</anno>}}</c> is returned.</p> </item> - <tag><c>{distributed, <anno>Nodes</anno>}</c></tag> - <item> - <p>This option can be used for - adding members to a distributed disk log. - Defaults to <c>[]</c>, which means that - the log is local on the current node. - </p> - <warning><p> - The distributed disk log feature has been deprecated. This - feature has also been scheduled for removal in OTP 24. - </p></warning> - </item> <tag><c>{notify, boolean()}</c><marker id="notify"></marker></tag> <item> <p>If <c>true</c>, the log owners @@ -994,10 +932,7 @@ is returned, where <c><anno>Rec</anno></c> is the number of whole Erlang terms found in the file and <c><anno>Bad</anno></c> is the number of bytes in the file that - are non-Erlang terms. If the parameter <c>distributed</c> - is specified, <c>open/1</c> returns a list of - successful replies and a list of erroneous replies. Each - reply is tagged with the node name. + are non-Erlang terms. </p> <p>When a disk log is opened in read-write mode, any existing log file is checked for. If there is none, a new empty @@ -1024,23 +959,9 @@ as owner once again, it is acknowledged with the return value <c>{ok, <anno>Log</anno>}</c>, but the state of the disk log is not affected.</p></note> - <p>If a log with a specified name is local on some node, - and one tries to open the log distributed on the same node, - the tuple <c>{error, {node_already_open, <anno>Log</anno>}}</c> is - returned. The same tuple is returned if the log is distributed on - some node, and one tries to open the log locally on the same node. - Opening individual distributed disk logs for the first time - adds those logs to a (possibly empty) distributed disk log. - The supplied option values are used - on all nodes mentioned by option <c>distributed</c>. - Individual distributed logs know nothing - about each other's option values, so each node can be - given unique option values by creating a distributed - log with many calls to <c>open/1</c>. - </p> <p>A log file can be opened more than once by giving different values to option <c>name</c> or by using the - same file when distributing a log on different nodes. + same file when opening a log on different nodes. It is up to the user of module <c>disk_log</c> to ensure that not more than one disk log process has write access to any file, otherwise the file can be corrupted. diff --git a/lib/kernel/src/disk_log.erl b/lib/kernel/src/disk_log.erl index 6b3eb35f92..89a9bd2f51 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]). + accessible_logs/0, all/0]). %% Internal exports -export([init/2, internal_open/2, @@ -47,6 +47,10 @@ -export_type([continuation/0]). +-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"}]). + -type dlog_state_error() :: 'ok' | {'error', term()}. -record(state, {queue = [], @@ -102,16 +106,13 @@ | {'invalid_header', invalid_header()} | {'file_error', file:filename(), file_error()} | {'node_already_open', Log :: log()}. --type dist_error_rsn() :: 'nodedown' | open_error_rsn(). --type ret() :: {'ok', Log :: log()} +-type open_ret() :: {'ok', Log :: log()} | {'repaired', Log :: log(), {'recovered', Rec :: non_neg_integer()}, - {'badbytes', Bad :: non_neg_integer()}}. --type open_ret() :: ret() | {'error', open_error_rsn()}. --type dist_open_ret() :: {[{node(), ret()}], - [{node(), {'error', dist_error_rsn()}}]}. + {'badbytes', Bad :: non_neg_integer()}} + | {'error', open_error_rsn()}. --spec open(ArgL) -> open_ret() | dist_open_ret() when +-spec open(ArgL) -> open_ret() when ArgL :: dlog_options(). open(A) -> disk_log_server:open(check_arg(A, #arg{options = A})). @@ -195,8 +196,10 @@ lclose(Log) -> -spec lclose(Log, Node) -> 'ok' | {'error', lclose_error_rsn()} when Log :: log(), Node :: node(). -lclose(Log, Node) -> - lreq(Log, close, Node). +lclose(Log, Node) when node() =:= Node -> + req(Log, close); +lclose(_Log, _Node) -> + {error, no_such_log}. -type trunc_error_rsn() :: 'no_such_log' | 'nonode' | {'read_only_mode', log()} @@ -337,7 +340,6 @@ format_error(Error) -> | {status, Status :: ok | {blocked, QueueLogRecords :: boolean()}} | {node, Node :: node()} - | {distributed, Dist :: local | [node()]} | {head, Head :: none | {head, binary()} | (MFA :: {atom(), atom(), list()})} @@ -353,7 +355,7 @@ format_error(Error) -> Log :: log(), InfoList :: [dlog_info()]. info(Log) -> - sreq(Log, info). + req(Log, info). -spec pid2name(Pid) -> {'ok', Log} | 'undefined' when Pid :: pid(), @@ -401,7 +403,7 @@ chunk(Log, Cont, N) when is_integer(N), N > 0 -> ichunk(Log, Cont, N). ichunk(Log, start, N) -> - R = sreq(Log, {chunk, 0, [], N}), + R = req(Log, {chunk, 0, [], N}), ichunk_end(R, Log); ichunk(Log, More, N) when is_record(More, continuation) -> R = req2(More#continuation.pid, @@ -484,7 +486,7 @@ bchunk(Log, Cont, N) when is_integer(N), N > 0 -> bichunk(Log, Cont, N). bichunk(Log, start, N) -> - R = sreq(Log, {chunk, 0, [], N}), + R = req(Log, {chunk, 0, [], N}), bichunk_end(R); bichunk(_Log, #continuation{pid = Pid, pos = Pos, b = B}, N) -> R = req2(Pid, {chunk, Pos, B, N}), @@ -511,7 +513,7 @@ chunk_step(Log, Cont, N) when is_integer(N) -> ichunk_step(Log, Cont, N). ichunk_step(Log, start, N) -> - sreq(Log, {chunk_step, 0, N}); + req(Log, {chunk_step, 0, N}); ichunk_step(_Log, More, N) when is_record(More, continuation) -> req2(More#continuation.pid, {chunk_step, More#continuation.pos, N}); ichunk_step(_Log, _, _) -> @@ -526,11 +528,15 @@ chunk_info(More = #continuation{}) -> chunk_info(BadCont) -> {error, {no_continuation, BadCont}}. --spec accessible_logs() -> {[LocalLog], [DistributedLog]} when - LocalLog :: log(), - DistributedLog :: log(). +-spec accessible_logs() -> {[Log], []} when + Log :: log(). accessible_logs() -> - disk_log_server:accessible_logs(). + {disk_log_server:all(), []}. + +-spec all() -> [Log] when + Log :: log(). +all() -> + disk_log_server:all(). istart_link(Server) -> {ok, proc_lib:spawn_link(disk_log, init, [self(), Server])}. @@ -622,10 +628,6 @@ check_arg([{format, internal}|Tail], Res) -> check_arg(Tail, Res#arg{format = internal}); check_arg([{format, external}|Tail], Res) -> check_arg(Tail, Res#arg{format = external}); -check_arg([{distributed, []}|Tail], Res) -> - check_arg(Tail, Res#arg{distributed = false}); -check_arg([{distributed, Nodes}|Tail], Res) when is_list(Nodes) -> - check_arg(Tail, Res#arg{distributed = {true, Nodes}}); check_arg([{notify, true}|Tail], Res) -> check_arg(Tail, Res#arg{notify = true}); check_arg([{notify, false}|Tail], Res) -> @@ -1519,9 +1521,6 @@ do_format_error({arg_mismatch, Option, FirstValue, ArgValue}) -> "the current value ~tp~n", [ArgValue, Option, FirstValue]); do_format_error({name_already_open, Log}) -> io_lib:format("The disk log ~tp has already opened another file~n", [Log]); -do_format_error({node_already_open, Log}) -> - io_lib:format("The distribution option of the disk log ~tp does not match " - "already open log~n", [Log]); do_format_error({open_read_write, Log}) -> io_lib:format("The disk log ~tp has already been opened read-write~n", [Log]); @@ -1573,15 +1572,6 @@ do_info(L, Cnt) -> halt -> Extra#halt.size end, - Distribution = - case disk_log_server:get_log_pids(Name) of - {local, _Pid} -> - local; - {distributed, Pids} -> - [node(P) || P <- Pids]; - undefined -> % "cannot happen" - [] - end, RW = case Type of wrap when Mode =:= read_write -> #handle{curB = CurB, curF = CurF, @@ -1629,8 +1619,7 @@ do_info(L, Cnt) -> HeadL ++ [{mode, Mode}, {status, Status}, - {node, node()}, - {distributed, Distribution} + {node, node()} ], Common ++ RW. @@ -1861,65 +1850,13 @@ reply(To, Reply, S) -> loop(S). req(Log, R) -> - case disk_log_server:get_log_pids(Log) of - {local, Pid} -> - monitor_request(Pid, R); - undefined -> - {error, no_such_log}; - {distributed, Pids} -> - multi_req({self(), R}, Pids) - end. - -multi_req(Msg, Pids) -> - Refs = - lists:map(fun(Pid) -> - Ref = erlang:monitor(process, Pid), - Pid ! Msg, - {Pid, Ref} - end, Pids), - lists:foldl(fun({Pid, Ref}, Reply) -> - receive - {'DOWN', Ref, process, Pid, _Info} -> - Reply; - {disk_log, Pid, _Reply} -> - erlang:demonitor(Ref, [flush]), - ok - end - end, {error, nonode}, Refs). - -sreq(Log, R) -> - case nearby_pid(Log, node()) of + case disk_log_server:get_log_pid(Log) of undefined -> {error, no_such_log}; Pid -> monitor_request(Pid, R) end. -%% Local req - always talk to log on Node -lreq(Log, R, Node) -> - case nearby_pid(Log, Node) of - Pid when is_pid(Pid), node(Pid) =:= Node -> - monitor_request(Pid, R); - _Else -> - {error, no_such_log} - end. - -nearby_pid(Log, Node) -> - case disk_log_server:get_log_pids(Log) of - undefined -> - undefined; - {local, Pid} -> - Pid; - {distributed, Pids} -> - get_near_pid(Pids, Node) - end. - --spec get_near_pid([pid(),...], node()) -> pid(). - -get_near_pid([Pid | _], Node) when node(Pid) =:= Node -> Pid; -get_near_pid([Pid], _ ) -> Pid; -get_near_pid([_ | T], Node) -> get_near_pid(T, Node). - monitor_request(Pid, Req) -> Ref = erlang:monitor(process, Pid), Pid ! {self(), Req}, @@ -1964,14 +1901,11 @@ add_ext(File, Ext) -> lists:concat([File, ".", Ext]). notify(Log, R) -> - case disk_log_server:get_log_pids(Log) of + case disk_log_server:get_log_pid(Log) of undefined -> {error, no_such_log}; - {local, Pid} -> + Pid -> Pid ! R, - ok; - {distributed, Pids} -> - lists:foreach(fun(Pid) -> Pid ! R end, Pids), ok end. diff --git a/lib/kernel/src/disk_log.hrl b/lib/kernel/src/disk_log.hrl index a362881f40..3cd124b8a7 100644 --- a/lib/kernel/src/disk_log.hrl +++ b/lib/kernel/src/disk_log.hrl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2017. All Rights Reserved. +%% Copyright Ericsson AB 1997-2020. 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. @@ -63,7 +63,7 @@ -type dlog_mode() :: 'read_only' | 'read_write'. -type dlog_name() :: atom() | string(). -type dlog_optattr() :: 'name' | 'file' | 'linkto' | 'repair' | 'type' - | 'format' | 'size' | 'distributed' | 'notify' + | 'format' | 'size' | 'notify' | 'head' | 'head_func' | 'mode'. -type dlog_option() :: {name, Log :: log()} | {file, FileName :: file:filename()} @@ -72,7 +72,6 @@ | {type, Type :: dlog_type()} | {format, Format :: dlog_format()} | {size, Size :: dlog_size()} - | {distributed, Nodes :: [node()]} | {notify, boolean()} | {head, Head :: dlog_head_opt()} | {head_func, MFA :: {atom(), atom(), list()}} @@ -97,7 +96,6 @@ repair = true :: dlog_repair(), size = infinity :: dlog_size(), type = halt :: dlog_type(), - distributed = false :: 'false' | {'true', [node()]}, format = internal :: dlog_format(), linkto = self() :: 'none' | pid(), head = none, diff --git a/lib/kernel/src/disk_log_server.erl b/lib/kernel/src/disk_log_server.erl index 2e22f28b14..ea8cbc808e 100644 --- a/lib/kernel/src/disk_log_server.erl +++ b/lib/kernel/src/disk_log_server.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2016. All Rights Reserved. +%% Copyright Ericsson AB 1997-2020. 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. @@ -21,10 +21,7 @@ -behaviour(gen_server). -export([start_link/0, start/0, open/1, close/1, - get_log_pids/1, accessible_logs/0]). - -%% Local export. --export([dist_open/1, get_local_pid/1]). + get_log_pid/1, all/0]). %% gen_server callbacks -export([init/1, handle_call/3, handle_info/2, terminate/2]). @@ -32,22 +29,15 @@ -include("disk_log.hrl"). --compile({inline,[{do_get_log_pids,1}]}). +-compile({inline,[{do_get_log_pid,1}]}). -record(pending, {log, pid, req, from, attach, clients}). % [{Request,From}] -record(state, {pending = [] :: [#pending{}]}). --compile({nowarn_deprecated_function, [{pg2, create, 1}]}). --compile({nowarn_deprecated_function, [{pg2, join, 2}]}). --compile({nowarn_deprecated_function, [{pg2, leave, 2}]}). --compile({nowarn_deprecated_function, [{pg2, which_groups, 0}]}). --compile({nowarn_deprecated_function, [{pg2, get_members, 1}]}). - %%%----------------------------------------------------------------- %%% This module implements the disk_log server. Its primary purpose -%%% is to keep the ets table 'disk_log_names' updated and to handle -%%% distribution data (pids) using the module pg2. +%%% is to keep the ets table 'disk_log_names' updated. %%%----------------------------------------------------------------- %%%---------------------------------------------------------------------- %%% API @@ -60,42 +50,32 @@ start() -> open({ok, A}) -> ensure_started(), - gen_server:call(disk_log_server, {open, local, A}, infinity); + gen_server:call(disk_log_server, {open, A}, infinity); open(Other) -> Other. -%% To be used from this module only. -dist_open(A) -> - ensure_started(), - gen_server:call(disk_log_server, {open, distr, A}, infinity). - close(Pid) -> gen_server:call(disk_log_server, {close, Pid}, infinity). -get_log_pids(LogName) -> - do_get_log_pids(LogName). +get_log_pid(LogName) -> + do_get_log_pid(LogName). -accessible_logs() -> +all() -> ensure_started(), - do_accessible_logs(). + do_all(). %%%---------------------------------------------------------------------- %%% Callback functions from gen_server %%%---------------------------------------------------------------------- -%% It would have been really nice to have a tag for disk log groups, -%% like {distributed_disk_log, Log}, but backward compatibility makes -%% it hard to introduce. --define(group(Log), Log). - init([]) -> process_flag(trap_exit, true), _ = ets:new(?DISK_LOG_NAME_TABLE, [named_table, set]), _= ets:new(?DISK_LOG_PID_TABLE, [named_table, set]), {ok, #state{}}. -handle_call({open, W, A}, From, State) -> - open([{{open, W, A}, From}], State); +handle_call({open, A}, From, State) -> + open([{{open, A}, From}], State); handle_call({close, Pid}, _From, State) -> Reply = do_close(Pid), {reply, Reply, State}. @@ -120,17 +100,10 @@ handle_info({pending_reply, Pid, Result0}, State) -> _ -> put(Pid, Name), link(Pid), - {_, Locality, _} = Request, ets:insert(?DISK_LOG_PID_TABLE, {Pid, Name}), - ets:insert(?DISK_LOG_NAME_TABLE, {Name, Pid, Locality}), - if - Locality =:= distr -> - ok = pg2:join(?group(Name), Pid); - true -> - ok - end + ets:insert(?DISK_LOG_NAME_TABLE, {Name, Pid}) end, - gen_server:reply(From, result(Request, Result0)), + gen_server:reply(From, Result0), open(Clients, State1) end; handle_info({'EXIT', Pid, _Reason}, State) -> @@ -199,89 +172,29 @@ open([], State) -> %% -> {OpenRet, NewState} | {{node(),OpenRet}, NewState} | %% {pending, NewState} -do_open({open, W, #arg{name = Name}=A}=Req, From, State) -> +do_open({open, #arg{name = Name}}=Req, From, State) -> case check_pending(Name, From, State, Req) of {pending, NewState} -> {pending, NewState}; - false when W =:= local -> - case A#arg.distributed of - {true, Nodes} -> - Fun = open_distr_rpc_fun(Nodes, A, From), - _Pid = spawn(Fun), - %% No pending reply is expected, but don't reply yet. - {pending, State}; - false -> - case get_local_pid(Name) of - {local, Pid} -> - do_internal_open(Name, Pid, From, Req, true,State); - {distributed, _Pid} -> - {{error, {node_already_open, Name}}, State}; - undefined -> - start_log(Name, Req, From, State) - end - end; - false when W =:= distr -> - ok = pg2:create(?group(Name)), - case get_local_pid(Name) of + false -> + case do_get_log_pid(Name) of undefined -> start_log(Name, Req, From, State); - {local, _Pid} -> - {{node(),{error, {node_already_open, Name}}}, State}; - {distributed, Pid} -> - do_internal_open(Name, Pid, From, Req, true, State) + Pid -> + do_internal_open(Name, Pid, From, Req, true,State) end end. --spec open_distr_rpc_fun([node()], _, _) -> % XXX: underspecified - fun(() -> no_return()). - -open_distr_rpc_fun(Nodes, A, From) -> - fun() -> open_distr_rpc(Nodes, A, From) end. - -%% Spawning a process is a means to avoid deadlock when -%% disk_log_servers mutually open disk_logs. - -open_distr_rpc(Nodes, A, From) -> - {AllReplies, BadNodes} = rpc:multicall(Nodes, ?MODULE, dist_open, [A]), - {Ok, Bad} = cr(AllReplies, [], []), - Old = find_old_nodes(Nodes, AllReplies, BadNodes), - NotOk = [{BadNode, {error, nodedown}} || BadNode <- BadNodes ++ Old], - Reply = {Ok, Bad ++ NotOk}, - %% Send the reply to the waiting client: - gen_server:reply(From, Reply), - exit(normal). - -cr([{badrpc, {'EXIT', _}} | T], Nodes, Bad) -> - %% This clause can be removed in next release. - cr(T, Nodes, Bad); -cr([R={_Node, {error, _}} | T], Nodes, Bad) -> - cr(T, Nodes, [R | Bad]); -cr([Reply | T], Nodes, Bad) -> - cr(T, [Reply | Nodes], Bad); -cr([], Nodes, Bad) -> - {Nodes, Bad}. - -%% If a "new" node (one that calls dist_open/1) tries to open a log -%% on an old node (one that does not have dist_open/1), then the old -%% node is considered 'down'. In next release, this test will not be -%% needed since all nodes can be assumed to be "new" by then. -%% One more thing: if an old node tries to open a log on a new node, -%% the new node is also considered 'down'. -find_old_nodes(Nodes, Replies, BadNodes) -> - R = [X || {X, _} <- Replies], - ordsets:to_list(ordsets:subtract(ordsets:from_list(Nodes), - ordsets:from_list(R ++ BadNodes))). - start_log(Name, Req, From, State) -> Server = self(), case supervisor:start_child(disk_log_sup, [Server]) of {ok, Pid} -> do_internal_open(Name, Pid, From, Req, false, State); Error -> - {result(Req, Error), State} + {Error, State} end. -do_internal_open(Name, Pid, From, {open, _W, A}=Req, Attach, State) -> +do_internal_open(Name, Pid, From, {open, A}=Req, Attach, State) -> Server = self(), F = fun() -> Res = disk_log:internal_open(Pid, A), @@ -303,11 +216,6 @@ check_pending(Name, From, State, Req) -> false end. -result({_, distr, _}, R) -> - {node(), R}; -result({_, local, _}, R) -> - R. - do_close(Pid) -> case get(Pid) of undefined -> @@ -319,71 +227,28 @@ do_close(Pid) -> end. erase_log(Name, Pid) -> - case get_local_pid(Name) of + case do_get_log_pid(Name) of undefined -> ok; - {local, Pid} -> + Pid -> true = ets:delete(?DISK_LOG_NAME_TABLE, Name), - true = ets:delete(?DISK_LOG_PID_TABLE, Pid); - {distributed, Pid} -> - true = ets:delete(?DISK_LOG_NAME_TABLE, Name), - true = ets:delete(?DISK_LOG_PID_TABLE, Pid), - ok = pg2:leave(?group(Name), Pid) + true = ets:delete(?DISK_LOG_PID_TABLE, Pid) end, erase(Pid). -do_accessible_logs() -> +do_all() -> LocalSpec = {'$1','_',local}, Local0 = [hd(L) || L <- ets:match(?DISK_LOG_NAME_TABLE, LocalSpec)], - Local = lists:sort(Local0), - Groups0 = ordsets:from_list(pg2:which_groups()), - Groups = ordsets:to_list(ordsets:subtract(Groups0, Local)), - Dist = [L || L <- Groups, dist_pids(L) =/= []], - {Local, Dist}. - -get_local_pid(LogName) -> - case ets:lookup(?DISK_LOG_NAME_TABLE, LogName) of - [{LogName, Pid, local}] -> - {local, Pid}; - [{LogName, Pid, distr}] -> - {distributed, Pid}; - [] -> - undefined - end. + lists:sort(Local0). %% Inlined. -do_get_log_pids(LogName) -> - case catch ets:lookup(?DISK_LOG_NAME_TABLE, LogName) of - [{LogName, Pid, local}] -> - {local, Pid}; - [{LogName, _Pid, distr}] -> - case pg2:get_members(?group(LogName)) of - [] -> % The disk_log process has died recently - undefined; - Members -> - {distributed, Members} - end; - _EmptyOrError -> - case dist_pids(LogName) of - [] -> undefined; - Pids -> {distributed, Pids} - end - end. - -dist_pids(LogName) -> - %% Would be much simpler if disk log group names were tagged. - GroupName = ?group(LogName), - case catch pg2:get_members(GroupName) of - [Pid | _] = Pids -> - case rpc:call(node(Pid), ?MODULE, get_local_pid, [LogName]) of - undefined -> % does not seem to be a disk_log group - case catch lists:member(Pid,pg2:get_members(GroupName)) of - true -> []; - _ -> dist_pids(LogName) - end; - _ -> % badrpc if get_local_pid is not exported - Pids - end; - _ -> - [] +do_get_log_pid(LogName) -> + try ets:lookup(?DISK_LOG_NAME_TABLE, LogName) of + [{LogName, Pid}] -> + Pid; + [] -> + undefined + catch + _:_ -> + undefined end. diff --git a/lib/kernel/test/disk_log_SUITE.erl b/lib/kernel/test/disk_log_SUITE.erl index 724bec17ed..96a5bfbbdf 100644 --- a/lib/kernel/test/disk_log_SUITE.erl +++ b/lib/kernel/test/disk_log_SUITE.erl @@ -85,14 +85,10 @@ change_attribute/1, - dist_open/1, dist_error_open/1, dist_notify/1, - dist_terminate/1, dist_accessible/1, dist_deadlock/1, - dist_open2/1, other_groups/1, - otp_6278/1, otp_10131/1, otp_16768/1, otp_16809/1]). -export([head_fun/1, hf/0, lserv/1, - measure/0, init_m/1, xx/0, head_exit/0, slow_header/1]). + measure/0, init_m/1, xx/0]). -export([init_per_testcase/2, end_per_testcase/2]). @@ -121,12 +117,9 @@ [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, otp_6278, otp_10131, otp_16768, + change_attribute, otp_6278, otp_10131, otp_16768, otp_16809]). -%% These test cases should be skipped if the VxWorks card is -%% configured without NFS cache. --define(SKIP_NO_CACHE,[distribution]). %% These tests should be skipped if the VxWorks card is configured *with* %% nfs cache. -define(SKIP_LARGE_CACHE,[inc_wrap_file, halt_ext, wrap_ext, read_mode, @@ -148,7 +141,7 @@ all() -> {group, open}, {group, close}, {group, error}, chunk, truncate, many_users, {group, info}, {group, change_size}, change_attribute, - {group, distribution}, otp_6278, otp_10131, otp_16768, otp_16809]. + otp_6278, otp_10131, otp_16768, otp_16809]. groups() -> [{halt_int, [], [halt_int_inf, {group, halt_int_sz}]}, @@ -173,11 +166,7 @@ groups() -> {change_size, [], [change_size_before, change_size_during, change_size_after, default_size, change_size2, - change_size_truncate]}, - {distribution, [], - [dist_open, dist_error_open, dist_notify, - dist_terminate, dist_accessible, dist_deadlock, - dist_open2, other_groups]}]. + change_size_truncate]}]. init_per_suite(Config) -> Config. @@ -2338,18 +2327,6 @@ close_deadlock(Conf) when is_list(Conf) -> receive {P2, done} -> ok end, del(F1, No), file:del_dir(LDir), - - %% To the same thing, this time using distributed logs. - %% (Does not seem to work very well, unfortunately.) - FunD = fun() -> open_close_dist(Self, Name, F1) end, - PD = spawn(FunD), - receive {PD, Name} -> ok end, - {[_], []} = disk_log:open([{name,Name},{file,F1}, - {distributed,[node()]}]), - ok = disk_log:close(L), - receive {PD, done} -> ok end, - file:delete(F1), - ok. open_close(Pid, Name, File) -> @@ -2366,13 +2343,6 @@ open_truncate(Pid, Name, File, No) -> %% The file has been closed, the disklog process has terminated. Pid ! {self(), done}. -open_close_dist(Pid, Name, File) -> - {[{_,{ok,L}}], []} = disk_log:open([{name,Name},{file,File}, - {distributed,[node()]}]), - Pid ! {self(), Name}, - ok = disk_log:close(L), - Pid ! {self(), done}. - async_do(Pid, Req) -> Pid ! {self(), Req}, %% make sure the request is queued @@ -2408,13 +2378,6 @@ lserv(Log) -> {From, {int_open, File, Size}} -> From ! disk_log:open([{name, Log}, {file, File}, {type, wrap}, {size, Size}]); - {From, {dist_open, File, Node}} -> - From ! disk_log:open([{name, Log}, {file, File}, {type, wrap}, - {size, {100,1}}, {distributed, [Node]}]); - {From, {dist_open, File, LinkTo, Node}} -> - From ! disk_log:open([{name, Log}, {file, File}, {type, wrap}, - {linkto, LinkTo}, {size, {100,1}}, - {distributed, [Node]}]); {From, block} -> From ! disk_log:block(Log); {From, {block, Bool}} -> @@ -4036,646 +3999,6 @@ change_attribute(Conf) when is_list(Conf) -> del(File, No). -%% Open a distributed log. -dist_open(Conf) when is_list(Conf) -> - PrivDir = ?privdir(Conf), - true = is_alive(), - - Q = qlen(), - File = filename:join(PrivDir, "n.LOG"), - File1 = filename:join(PrivDir, "n1.LOG"), - No = 3, - file:delete(File), - del(File, No), % cleanup - del(File1, No), % cleanup - B = mk_bytes(60), - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node} = start_node(disk_log, "-pa " ++ PA), - wait_for_ready_net(), - - %% open non-distributed on this node: - {ok,n} = disk_log:open([{name, n}, {file, File}, {type, halt}, - {distributed, []}]), - - Error1 = {error, {halt_log, n}} = disk_log:inc_wrap_file(n), - "The halt log" ++ _ = format_error(Error1), - ok = disk_log:lclose(n), - file:delete(File), - - %% open distributed on this node: - {[_],[]} = disk_log:open([{name, n}, {file, File}, {type, halt}, - {distributed, [node()]}]), - %% the error message is ignored: - ok = disk_log:inc_wrap_file(n), - ok = disk_log:close(n), - file:delete(File), - - %% open a wrap log on this node, write something on this node - {[_],[]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}]), - ok = disk_log:log(n, B), - ok = disk_log:close(n), - - %% open a wrap log on this node and aother node, write something - {[_],[]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}]), - {[_],[]} = disk_log:open([{name, n}, {file, File1}, - {type, wrap}, {size, {50, No}}, - {distributed, [Node]}]), - ok = disk_log:log(n, B), - ok = rpc:call(Node, disk_log, log, [n, B]), - ok = disk_log:close(n), - del(File, No), - del(File1, No), - file:delete(File), - - %% open a wrap log on this node and another node, use lclose - {[_],[]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}]), - {[_],[]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}, - {linkto,none}]), - {[_],[]} = disk_log:open([{name, n}, {file, File1}, - {type, wrap}, {size, {50, No}}, - {distributed, [Node]}]), - [_, _] = distributed(n), - ok = disk_log:lclose(n, Node), - [_] = distributed(n), - ok = disk_log:lclose(n), - ok = disk_log:lclose(n), - {error, no_such_log} = disk_log:info(n), - del(File, No), - del(File1, No), - file:delete(File), - - %% open an invalid log file, and see how error are handled - First = "n.LOG.1", - make_file(PrivDir, First, 8), - - {[], [_,_]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [Node,node()]}]), - del(File, No), - file:delete(File), - - %% open a wrap on one other node (not on this node) - {[_],[]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [Node]}]), - ok = rpc:call(Node, disk_log, log, [n, B]), - {error, no_such_log} = disk_log:lclose(n), - ok = disk_log:close(n), - - Q = qlen(), - - {error, no_such_log} = disk_log:info(n), - del(File, No), - file:delete(File), - stop_node(Node), - ok. - -%% Open a log distributed and not distributed. -dist_error_open(Conf) when is_list(Conf) -> - PrivDir = ?privdir(Conf), - true = is_alive(), - - Q = qlen(), - File = filename:join(PrivDir, "bert.LOG"), - File1 = filename:join(PrivDir, "bert1.LOG"), - No = 3, - file:delete(File), - del(File, No), % cleanup - del(File1, No), % cleanup - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node} = start_node(disk_log, "-pa " ++ PA), - wait_for_ready_net(), - - %% open non-distributed on this node: - {ok,n} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}]), - - %% trying to open distributed on this node (error): - {[],[Error1={ENode,{error,{node_already_open,n}}}]} = - disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}]), - true = - lists:prefix(lists:flatten(io_lib:format("~p: The distribution", - [ENode])), - format_error(Error1)), - ok = disk_log:lclose(n), - - %% open distributed on this node: - {[_],[]} = disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}]), - - %% trying to open non-distributed on this node (error): - {_,{node_already_open,n}} = - disk_log:open([{name, n}, {file, File}, - {type, wrap}, {size, {50, No}}]), - - ok = disk_log:close(n), - Q = qlen(), - - del(File, No), - del(File1, No), - file:delete(File), - stop_node(Node), - ok. - -%% Notification from other node. -dist_notify(Conf) when is_list(Conf) -> - PrivDir = ?privdir(Conf), - true = is_alive(), - - File = filename:join(PrivDir, "bert.LOG"), - File1 = filename:join(PrivDir, "bert1.LOG"), - No = 3, - B = mk_bytes(60), - file:delete(File), - file:delete(File1), - del(File, No), % cleanup - del(File1, No), - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node} = start_node(disk_log, "-pa " ++ PA), - wait_for_ready_net(), - - %% opening distributed on this node: - {[_],[]} = disk_log:open([{name, n}, {file, File}, {notify, false}, - {type, wrap}, {size, {50, No}}, - {distributed, [node()]}]), - - %% opening distributed on other node: - {[_],[]} = disk_log:open([{name, n}, {file, File1}, - {notify, true}, {linkto, self()}, - {type, wrap}, {size, {50, No}}, - {distributed, [Node]}]), - disk_log:alog(n, B), - disk_log:alog(n, B), - ok = disk_log:sync(n), - rec(1, {disk_log, Node, n, {wrap, 0}}), - ok = disk_log:close(n), - - del(File, No), - del(File1, No), - file:delete(File), - stop_node(Node), - ok. - -%% Terminating nodes with distributed logs. -dist_terminate(Conf) when is_list(Conf) -> - Dir = ?privdir(Conf), - true = is_alive(), - - File = filename:join(Dir, "n.LOG"), - File1 = filename:join(Dir, "n1.LOG"), - No = 1, - del(File, No), % cleanup - del(File1, No), % cleanup - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node} = start_node(disk_log, "-pa " ++ PA), - wait_for_ready_net(), - - %% Distributed versions of two of the situations in close_block(/1. - - %% One of two owners terminates. - Pid1 = spawn_link(?MODULE, lserv, [n]), - Pid2 = spawn_link(?MODULE, lserv, [n]), - {[{_, {ok, n}}], []} = sync_do(Pid1, {dist_open, File, node()}), - {[{_, {ok, n}}], []} = sync_do(Pid2, {dist_open, File1, Node}), - [_] = sync_do(Pid1, owners), - [_] = sync_do(Pid2, owners), - 0 = sync_do(Pid1, users), - 0 = sync_do(Pid2, users), - sync_do(Pid1, terminate), - [_] = sync_do(Pid2, owners), - 0 = sync_do(Pid2, users), - sync_do(Pid2, terminate), - {error, no_such_log} = disk_log:info(n), - - %% Users terminate (no link...). - Pid3 = spawn_link(?MODULE, lserv, [n]), - Pid4 = spawn_link(?MODULE, lserv, [n]), - {[{_, {ok, n}}], []} = - sync_do(Pid3, {dist_open, File, none, node()}), - {[{_, {ok, n}}], []} = - sync_do(Pid4, {dist_open, File1, none, Node}), - [] = sync_do(Pid3, owners), - [] = sync_do(Pid4, owners), - 1 = sync_do(Pid3, users), - 1 = sync_do(Pid4, users), - sync_do(Pid3, terminate), - [] = sync_do(Pid4, owners), - 1 = sync_do(Pid4, users), - sync_do(Pid4, terminate), - ok = disk_log:close(n), % closing all nodes - {error, no_such_log} = disk_log:info(n), - - del(File, No), - del(File1, No), - stop_node(Node), - ok. - -%% Accessible logs on nodes. -dist_accessible(Conf) when is_list(Conf) -> - PrivDir = ?privdir(Conf), - - true = is_alive(), - - F1 = filename:join(PrivDir, "a.LOG"), - file:delete(F1), - F2 = filename:join(PrivDir, "b.LOG"), - file:delete(F2), - F3 = filename:join(PrivDir, "c.LOG"), - file:delete(F3), - F4 = filename:join(PrivDir, "d.LOG"), - file:delete(F1), - F5 = filename:join(PrivDir, "e.LOG"), - file:delete(F2), - F6 = filename:join(PrivDir, "f.LOG"), - file:delete(F3), - - {[],[]} = disk_log:accessible_logs(), - {ok, a} = disk_log:open([{name, a}, {type, halt}, {file, F1}]), - {[a],[]} = disk_log:accessible_logs(), - {ok, b} = disk_log:open([{name, b}, {type, halt}, {file, F2}]), - {[a,b],[]} = disk_log:accessible_logs(), - {ok, c} = disk_log:open([{name, c}, {type, halt}, {file, F3}]), - {[a,b,c],[]} = disk_log:accessible_logs(), - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node} = start_node(disk_log, "-pa " ++ PA), - wait_for_ready_net(), - - {[_],[]} = disk_log:open([{name, a}, {file, F4}, {type, halt}, - {distributed, [Node]}]), - {[a,b,c],[]} = disk_log:accessible_logs(), - {[],[a]} = rpc:call(Node, disk_log, accessible_logs, []), - {[_],[]} = disk_log:open([{name, b}, {file, F5}, {type, halt}, - {distributed, [Node]}]), - {[],[a,b]} = rpc:call(Node, disk_log, accessible_logs, []), - {[_],[]} = disk_log:open([{name, c}, {file, F6}, {type, halt}, - {distributed, [Node]}]), - {[],[a,b,c]} = rpc:call(Node, disk_log, accessible_logs, []), - {[a,b,c],[]} = disk_log:accessible_logs(), - ok = disk_log:close(a), - {[b,c],[a]} = disk_log:accessible_logs(), - ok = disk_log:close(b), - {[c],[a,b]} = disk_log:accessible_logs(), - ok = disk_log:close(b), - {[c],[a]} = disk_log:accessible_logs(), - {[],[a,c]} = rpc:call(Node, disk_log, accessible_logs, []), - ok = disk_log:close(c), - {[],[a,c]} = disk_log:accessible_logs(), - ok = disk_log:close(c), - {[],[a]} = disk_log:accessible_logs(), - {[],[a]} = rpc:call(Node, disk_log, accessible_logs, []), - ok = disk_log:close(a), - {[],[]} = disk_log:accessible_logs(), - {[],[]} = rpc:call(Node, disk_log, accessible_logs, []), - - file:delete(F1), - file:delete(F2), - file:delete(F3), - file:delete(F4), - file:delete(F5), - file:delete(F6), - - stop_node(Node), - ok. - -%% OTP-4405. Deadlock between two nodes could happen. -dist_deadlock(Conf) when is_list(Conf) -> - PrivDir = ?privdir(Conf), - - true = is_alive(), - - F1 = filename:join(PrivDir, "a.LOG"), - file:delete(F1), - F2 = filename:join(PrivDir, "b.LOG"), - file:delete(F2), - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node1} = start_node(disk_log_node1, "-pa " ++ PA), - {ok, Node2} = start_node(disk_log_node2, "-pa " ++ PA), - wait_for_ready_net(), - - Self = self(), - Fun1 = fun() -> dist_dl(Node2, a, F1, Self) end, - Fun2 = fun() -> dist_dl(Node1, b, F2, Self) end, - P1 = spawn(Node1, Fun1), - P2 = spawn(Node2, Fun2), - receive {P1, a} -> ok end, - receive {P2, b} -> ok end, - - stop_node(Node1), - stop_node(Node2), - - file:delete(F1), - file:delete(F2), - ok. - -dist_dl(Node, Name, File, Pid) -> - {[{Node,{ok,Log}}], []} = - disk_log:open([{name,Name},{file,File},{distributed,[Node]}]), - timer:sleep(50), % give the nodes chance to exchange pg2 information - ok = disk_log:close(Log), - Pid ! {self(), Name}, - ok. - -%% OTP-4480. Opening several logs simultaneously. -dist_open2(Conf) when is_list(Conf) -> - true = is_alive(), - {ok, _Pg2} = pg2:start(), - - dist_open2_1(Conf, 0), - dist_open2_1(Conf, 100), - - dist_open2_2(Conf, 0), - dist_open2_2(Conf, 100), - - PrivDir = ?privdir(Conf), - Log = n, - - %% Open a log three times (very fast). Two of the opening - %% processes will be put on hold (pending). The first one failes - %% to open the log. The second one succeeds, and the third one is - %% attached. - P0 = pps(), - File0 = "n.LOG", - File = filename:join(PrivDir, File0), - make_file(PrivDir, File0, 8), - - Parent = self(), - F1 = fun() -> R = disk_log:open([{name, Log}, {file, File}, - {type, halt}, {format,internal}, - {distributed, [node()]}]), - Parent ! {self(), R} - end, - F2 = fun() -> R = disk_log:open([{name, Log}, {file, File}, - {type, halt}, {format,external}, - {distributed, [node()]}]), - Parent ! {self(), R}, - timer:sleep(300) - end, - Pid1 = spawn(F1), - timer:sleep(10), - Pid2 = spawn(F2), - Pid3 = spawn(F2), - - receive {Pid1,R1} -> {[],[_]} = R1 end, - receive {Pid2,R2} -> {[_],[]} = R2 end, - receive {Pid3,R3} -> {[_],[]} = R3 end, - - timer:sleep(500), - file:delete(File), - check_pps(P0), - - %% This time the first process has a naughty head_func. This test - %% does not add very much. Perhaps it should be removed. However, - %% a head_func like this is why it's necessary to have an separate - %% process calling disk_log:internal_open: the server cannot wait - %% for the reply, but the call must be monitored, and this is what - %% is accomplished by having a proxy process. - F3 = fun() -> - R = disk_log:open([{name,Log},{file,File}, - {format,internal}, - {head_func,{?MODULE,head_exit,[]}}, - {type,halt}, {linkto,none}]), - Parent ! {self(), R} - end, - F4 = fun() -> - R = disk_log:open([{name,Log},{file,File}, - {format,internal}, - {type,halt}]), - Parent ! {self(), R} - end, - Pid4 = spawn(F3), - timer:sleep(10), - Pid5 = spawn(F4), - Pid6 = spawn(F4), - %% The timing is crucial here. - R = case receive {Pid4,R4} -> R4 end of - {error, no_such_log} -> - R5 = receive {Pid5, R5a} -> R5a end, - R6 = receive {Pid6, R6a} -> R6a end, - case {R5, R6} of - {{repaired, _, _, _}, {ok, Log}} -> ok; - {{ok, Log}, {repaired, _, _, _}} -> ok; - _ -> test_server_fail({bad_replies, R5, R6}) - end, - ok; - {ok, Log} -> % uninteresting case - receive {Pid5,_R5} -> ok end, - receive {Pid6,_R6} -> ok end, - {comment, - "Timing dependent test did not check anything."} - end, - - timer:sleep(100), - {error, no_such_log} = disk_log:close(Log), - file:delete(File), - check_pps(P0), - - No = 2, - Log2 = n2, - File2 = filename:join(PrivDir, "b.LOG"), - file:delete(File2), - del(File, No), - - %% If a client takes a long time when writing the header, other - %% processes should be able to attach to other log without having to - %% wait. - - {ok,Log} = - disk_log:open([{name,Log},{file,File},{type,wrap},{size,{100,No}}]), - Pid = spawn(fun() -> - receive {HeadPid, start} -> ok end, - {ok,Log2} = disk_log:open([{name,Log2},{file,File2}, - {type,halt}]), - HeadPid ! {self(), done} - end), - HeadFunc = {?MODULE, slow_header, [Pid]}, - ok = disk_log:change_header(Log, {head_func, HeadFunc}), - ok = disk_log:inc_wrap_file(Log), % header is written - - timer:sleep(100), - ok = disk_log:close(Log), - - file:delete(File2), - del(File, No), - check_pps(P0), - - R. - -dist_open2_1(Conf, Delay) -> - Dir = ?privdir(Conf), - File = filename:join(Dir, "n.LOG"), - Log = n, - - A0 = [{name,Log},{file,File},{type,halt}], - create_opened_log(File, A0), - P0 = pps(), - - Log2 = log2, - File2 = "log2.LOG", - file:delete(File2), - {ok,Log2} = disk_log:open([{name,Log2},{file,File2},{type,halt}]), - - Parent = self(), - F = fun() -> - R = disk_log:open(A0), - timer:sleep(Delay), - Parent ! {self(), R} - end, - Pid1 = spawn(F), - timer:sleep(10), - Pid2 = spawn(F), - Pid3 = spawn(F), - {error, no_such_log} = disk_log:log(Log, term), % is repairing now - 0 = qlen(), - - %% The file is already open, so this will not take long. - {ok,Log2} = disk_log:open([{name,Log2},{file,File2},{type,halt}]), - 0 = qlen(), % still repairing - ok = disk_log:close(Log2), - {error, no_such_log} = disk_log:close(Log2), - file:delete(File2), - - receive {Pid1,R1} -> {repaired,_,_,_} = R1 end, - receive {Pid2,R2} -> {ok,_} = R2 end, - receive {Pid3,R3} -> {ok,_} = R3 end, - timer:sleep(500), - {error, no_such_log} = disk_log:info(Log), - - file:delete(File), - check_pps(P0), - - ok. - -dist_open2_2(Conf, Delay) -> - Dir = ?privdir(Conf), - File = filename:join(Dir, "n.LOG"), - Log = n, - - PA = filename:dirname(code:which(?MODULE)), - {ok, Node1} = start_node(disk_log_node2, "-pa " ++ PA), - wait_for_ready_net(), - P0 = pps(), - - A0 = [{name,Log},{file,File},{type,halt}], - create_opened_log(File, A0), - - Log2 = log2, - File2 = "log2.LOG", - file:delete(File2), - {[{Node1,{ok,Log2}}],[]} = - disk_log:open([{name,Log2},{file,File2},{type,halt}, - {distributed,[Node1]}]), - - Parent = self(), - F = fun() -> - %% It would be nice to slow down the repair. head_func - %% cannot be used since it is not called when repairing. - R = disk_log:open([{distributed,[Node1]} | A0]), - timer:sleep(Delay), - Parent ! {self(), R} - end, - %% And {priority, ...} probably has no effect either. - Pid1 = spawn_opt(F, [{priority, low}]), - %% timer:sleep(1), % no guarantee that Pid1 will return {repaired, ...} - Pid2 = spawn_opt(F, [{priority, low}]), - {error, no_such_log} = - disk_log:log(Log, term), % maybe repairing now - 0 = qlen(), - - %% The file is already open, so this will not take long. - {[{Node1,{ok,Log2}}],[]} = - disk_log:open([{name,Log2},{file,File2},{type,halt}, - {distributed,[Node1]}]), - 0 = qlen(), % probably still repairing - ok = disk_log:close(Log2), - file:delete(File2), - - receive {Pid1,R1} -> R1 end, - receive {Pid2,R2} -> R2 end, - case {R1, R2} of - {{[{Node1,{repaired,_,_,_}}],[]}, - {[{Node1,{ok,Log}}],[]}} -> ok; - {{[{Node1,{ok,Log}}],[]}, - {[{Node1,{repaired,_,_,_}}],[]}} -> ok - end, - - check_pps(P0), - stop_node(Node1), - file:delete(File), - ok. - -head_exit() -> - process_flag(trap_exit, false), % Don't do like this! - spawn_link(fun() -> exit(helfel) end), - {ok,"123"}. - -slow_header(Pid) -> - Pid ! {self(), start}, - receive {Pid, done} -> ok end, - {ok, <<>>}. - -create_opened_log(File, Args) -> - Log = n, - file:delete(File), - {ok, Log} = disk_log:open(Args), - log_terms(Log, 400000), - ok = disk_log:close(Log), - mark(File, ?OPENED), - ok. - -log_terms(_Log, 0) -> - ok; -log_terms(Log, N) when N > 100 -> - Terms = [{term,I} || I <- lists:seq(N-99, N)], - ok = disk_log:log_terms(Log, Terms), - log_terms(Log, N-100); -log_terms(Log, N) -> - ok = disk_log:log(Log, {term, N}), - log_terms(Log, N-1). - -%% OTP-5810. Cope with pg2 groups that are not disk logs. -other_groups(Conf) when is_list(Conf) -> - true = is_alive(), - PrivDir = ?privdir(Conf), - - File = filename:join(PrivDir, "n.LOG"), - file:delete(File), - - {[],[]} = disk_log:accessible_logs(), - {[_],[]} = disk_log:open([{name, n}, {file, File}, {type, halt}, - {distributed, [node()]}]), - {[],[n]} = disk_log:accessible_logs(), - Group = grupp, - pg2:create(Group), - ok = pg2:join(Group, self()), - {[],[n]} = disk_log:accessible_logs(), - [_] = - lists:filter(fun(P) -> disk_log:pid2name(P) =/= undefined end, - erlang:processes()), - pg2:delete(Group), - {[],[n]} = disk_log:accessible_logs(), - ok = disk_log:close(n), - {[],[]} = disk_log:accessible_logs(), - file:delete(File), - - ok. - %% OTP-6278. open/1 creates no status or crash report. otp_6278(Conf) when is_list(Conf) -> Dir = ?privdir(Conf), @@ -4925,9 +4248,6 @@ users(Log) -> status(Log) -> %% io:format("status ~p~n", [info(Log, status, -1)]), info(Log, status, -1). -distributed(Log) -> -%% io:format("distributed ~p~n", [info(Log, distributed, -1)]), - info(Log, distributed, -1). no_items(Log) -> %% io:format("no_items ~p~n", [info(Log, no_items, -1)]), info(Log, no_items, -1). @@ -4966,48 +4286,6 @@ rec(N, Msg) -> test_server_fail({no_msg, N, Msg}) end. -%% Copied from global_SUITE.erl. --define(UNTIL(Seq), loop_until_true(fun() -> Seq end)). - -loop_until_true(Fun) -> - case Fun() of - true -> - ok; - _ -> - timer:sleep(1000), - loop_until_true(Fun) - end. - -wait_for_ready_net() -> - Nodes = lists:sort([node() | nodes()]), - ?UNTIL(begin - lists:all(fun(N) -> Nodes =:= get_known(N) end, Nodes) and - lists:all(fun(N) -> - LNs = rpc:call(N, erlang, nodes, []), - Nodes =:= lists:sort([N | LNs]) - end, Nodes) - end). - -get_known(Node) -> - case catch gen_server:call({global_name_server,Node}, get_known) of - {'EXIT', _} -> - [list, without, nodenames]; - Known -> - lists:sort([Node | Known]) - end. - -%% Copied from erl_distribution_SUITE.erl: -start_node(Name, Param) -> - test_server:start_node(Name, slave, [{args, Param}]). - -stop_node(Node) -> - test_server:stop_node(Node). - -%% from(H, [H | T]) -> T; -%% from(H, [_ | T]) -> from(H, T); -%% from(_H, []) -> []. - - %%----------------------------------------------------------------- %% The error_logger handler used. %% (Copied from stdlib/test/proc_lib_SUITE.erl.) diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 49f7788495..de65eb2a0a 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -29,6 +29,12 @@ obsolete(auth, cookie, 1) -> {deprecated, "use erlang:set_cookie/2 instead"}; obsolete(auth, is_auth, 1) -> {deprecated, "use net_adm:ping/1 instead"}; +obsolete(disk_log, accessible_logs, 0) -> + {deprecated, "use disk_log:all/0 instead"}; +obsolete(disk_log, lclose, 1) -> + {deprecated, "use disk_log:close/1 instead"}; +obsolete(disk_log, lclose, 2) -> + {deprecated, "use disk_log:close/1 instead"}; obsolete(calendar, local_time_to_universal_time, 1) -> {deprecated, "use calendar:local_time_to_universal_time_dst/1 instead"}; obsolete(code, rehash, 0) -> diff --git a/system/doc/general_info/DEPRECATIONS b/system/doc/general_info/DEPRECATIONS index 6846f9fbc2..9df565e797 100644 --- a/system/doc/general_info/DEPRECATIONS +++ b/system/doc/general_info/DEPRECATIONS @@ -17,6 +17,9 @@ httpd_util:hexlist_to_integer/1 since=24 remove=26 # is scheduled to be removed in OTP 25. # +disk_log:accessible_logs/0 since=24 remove=26 +disk_log:lclose/1 since=24 remove=26 +disk_log:lclose/2 since=24 remove=26 erlang:phash/2 since=24 # -- 2.26.2
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor