gen_event.erl 21 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659
  1. %% ``The contents of this file are subject to the Erlang Public License,
  2. %% Version 1.1, (the "License"); you may not use this file except in
  3. %% compliance with the License. You should have received a copy of the
  4. %% Erlang Public License along with this software. If not, it can be
  5. %% retrieved via the world wide web at http://www.erlang.org/.
  6. %%
  7. %% Software distributed under the License is distributed on an "AS IS"
  8. %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
  9. %% the License for the specific language governing rights and limitations
  10. %% under the License.
  11. %%
  12. %% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
  13. %% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
  14. %% AB. All Rights Reserved.''
  15. %%
  16. %% $Id$
  17. %%
  18. -module(gen_event).
  19. %%%
  20. %%% A general event handler.
  21. %%% Several handlers (functions) can be added.
  22. %%% Each handler holds a state and will be called
  23. %%% for every event received of the handler.
  24. %%%
  25. %%% Modified by Magnus.
  26. %%% Take care of fault situations and made notify asynchronous.
  27. %%% Re-written by Joe with new functional interface !
  28. %%% Modified by Martin - uses proc_lib, sys and gen!
  29. -export([start/0, start/1, start_link/0, start_link/1, stop/1, notify/2,
  30. sync_notify/2,
  31. add_handler/3, add_sup_handler/3, delete_handler/3, swap_handler/3,
  32. swap_sup_handler/3, which_handlers/1, call/3, call/4]).
  33. -export([behaviour_info/1]).
  34. -export([init_it/6,
  35. system_continue/3,
  36. system_terminate/4,
  37. system_code_change/4,
  38. print_event/3,
  39. format_status/2]).
  40. -import(error_logger, [error_msg/2]).
  41. -define(reply(X), From ! {element(2,Tag), X}).
  42. -record(handler, {module,
  43. id = false,
  44. state,
  45. supervised = false}).
  46. behaviour_info(callbacks) ->
  47. [{init,1},{handle_event,2},{handle_call,2},{handle_info,2},
  48. {terminate,2},{code_change,3}];
  49. behaviour_info(_Other) ->
  50. undefined.
  51. %% gen_event:start(Handler) -> ok | {error, What}
  52. %% gen_event:add_handler(Handler, Mod, Args) -> ok | Other
  53. %% gen_event:notify(Handler, Event) -> ok
  54. %% gen_event:call(Handler, Mod, Query) -> {ok, Val} | {error, Why}
  55. %% gen_event:call(Handler, Mod, Query, Timeout) -> {ok, Val} | {error, Why}
  56. %% gen_event:delete_handler(Handler, Mod, Args) -> Val
  57. %% gen_event:swap_handler(Handler, {OldMod, Args1}, {NewMod, Args2}) -> ok
  58. %% gen_event:which_handler(Handler) -> [Mod]
  59. %% gen_event:stop(Handler) -> ok
  60. %% handlers must export
  61. %% Mod:init(Args) -> {ok, State} | Other
  62. %% Mod:handle_event(Event, State) ->
  63. %% {ok, State'} | remove_handler | {swap_handler,Args1,State1,Mod2,Args2}
  64. %% Mod:handle_info(Info, State) ->
  65. %% {ok, State'} | remove_handler | {swap_handler,Args1,State1,Mod2,Args2}
  66. %% Mod:handle_call(Query, State) ->
  67. %% {ok, Reply, State'} | {remove_handler, Reply} |
  68. %% {swap_handler, Reply, Args1,State1,Mod2,Args2}
  69. %% Mod:terminate(Args, State) -> Val
  70. %% add_handler(H, Mod, Args) -> ok | Other
  71. %% Mod:init(Args) -> {ok, State} | Other
  72. %% delete_handler(H, Mod, Args) -> Val
  73. %% Mod:terminate(Args, State) -> Val
  74. %% notify(H, Event)
  75. %% Mod:handle_event(Event, State) ->
  76. %% {ok, State1}
  77. %% remove_handler
  78. %% Mod:terminate(remove_handler, State) is called
  79. %% the return value is ignored
  80. %% {swap_handler, Args1, State1, Mod2, Args2}
  81. %% State2 = Mod:terminate(Args1, State1) is called
  82. %% the return value is chained into the new module and
  83. %% Mod2:init({Args2, State2}) is called
  84. %% Other
  85. %% Mod:terminate({error, Other}, State) is called
  86. %% The return value is ignored
  87. %% call(H, Mod, Query) -> Val
  88. %% call(H, Mod, Query, Timeout) -> Val
  89. %% Mod:handle_call(Query, State) -> as above
  90. start() ->
  91. gen:start(gen_event, nolink, [], [], []).
  92. start(Name) ->
  93. gen:start(gen_event, nolink, Name, [], [], []).
  94. start_link() ->
  95. gen:start(gen_event, link, [], [], []).
  96. start_link(Name) ->
  97. gen:start(gen_event, link, Name, [], [], []).
  98. init_it(Starter, self, Name, Mod, Args, Options) ->
  99. init_it(Starter, self(), Name, Mod, Args, Options);
  100. init_it(Starter, Parent, Name, _, _, Options) ->
  101. process_flag(trap_exit, true),
  102. gen:reg_behaviour(?MODULE),
  103. Debug = gen:debug_options(Options),
  104. proc_lib:init_ack(Starter, {ok, self()}),
  105. loop(Parent, Name, [], Debug).
  106. add_handler(M, Handler, Args) -> rpc (M, {add_handler, Handler, Args}).
  107. add_sup_handler(M, Handler, Args) ->
  108. rpc (M, {add_sup_handler, Handler, Args, self()}).
  109. notify(M, Event) -> send(M, {notify, Event}).
  110. sync_notify(M, Event) -> rpc (M, {sync_notify, Event}).
  111. call(M, Handler, Query) -> call1(M, Handler, Query).
  112. call(M, Handler, Query, Timeout) -> call1(M, Handler, Query, Timeout).
  113. delete_handler(M, Handler, Args) -> rpc (M, {delete_handler, Handler, Args}).
  114. swap_handler(M, {H1, A1},{H2, A2}) -> rpc (M, {swap_handler, H1, A1, H2, A2}).
  115. swap_sup_handler(M, {H1, A1},{H2, A2}) ->
  116. rpc (M, {swap_sup_handler, H1, A1, H2, A2, self()}).
  117. which_handlers(M) -> rpc (M, which_handlers).
  118. stop(M) -> rpc (M, stop).
  119. rpc(M, Cmd) ->
  120. {ok,Reply} = gen:call(M, self(), Cmd, infinity),
  121. Reply.
  122. call1(M, Handler, Query) ->
  123. Cmd = {call, Handler, Query},
  124. case catch gen:call(M, self(), Cmd) of
  125. {ok,Res} ->
  126. Res;
  127. {'EXIT', Reason} ->
  128. exit({Reason, {gen_event, call, [M, Handler, Query]}})
  129. end.
  130. call1(M, Handler, Query, Timeout) ->
  131. Cmd = {call, Handler, Query},
  132. case catch gen:call(M, self(), Cmd, Timeout) of
  133. {ok,Res} ->
  134. Res;
  135. {'EXIT', Reason} ->
  136. exit({Reason, {gen_event, call, [M, Handler, Query, Timeout]}})
  137. end.
  138. send({global, Name}, Cmd) ->
  139. catch global:send(Name, Cmd),
  140. ok;
  141. send(M, Cmd) ->
  142. M ! Cmd,
  143. ok.
  144. loop(Parent, ServerName, MSL, Debug) ->
  145. receive
  146. {system, From, Req} ->
  147. sys:handle_system_msg(Req, From, Parent, gen_event, Debug,
  148. [ServerName, MSL]);
  149. {'EXIT', Parent, Reason} ->
  150. terminate_server(Reason, Parent, MSL, ServerName);
  151. Msg when Debug =:= [] ->
  152. handle_msg(Msg, Parent, ServerName, MSL, []);
  153. Msg ->
  154. Debug1 = sys:handle_debug(Debug, {gen_event, print_event},
  155. ServerName, {in, Msg}),
  156. handle_msg(Msg, Parent, ServerName, MSL, Debug1)
  157. end.
  158. handle_msg(Msg, Parent, ServerName, MSL, Debug) ->
  159. case Msg of
  160. {notify, Event} ->
  161. MSL1 = server_notify(Event, handle_event, MSL, ServerName),
  162. loop(Parent, ServerName, MSL1, Debug);
  163. {From, Tag, {sync_notify, Event}} ->
  164. MSL1 = server_notify(Event, handle_event, MSL, ServerName),
  165. ?reply(ok),
  166. loop(Parent, ServerName, MSL1, Debug);
  167. {'EXIT', From, Reason} ->
  168. MSL1 = handle_exit(From, Reason, MSL, ServerName),
  169. loop(Parent, ServerName, MSL1, Debug);
  170. {From, Tag, {call, Handler, Query}} ->
  171. {Reply, MSL1} = server_call(Handler, Query, MSL, ServerName),
  172. ?reply(Reply),
  173. loop(Parent, ServerName, MSL1, Debug);
  174. {From, Tag, {add_handler, Handler, Args}} ->
  175. {Reply, MSL1} = server_add_handler(Handler, Args, MSL),
  176. ?reply(Reply),
  177. loop(Parent, ServerName, MSL1, Debug);
  178. {From, Tag, {add_sup_handler, Handler, Args, SupP}} ->
  179. {Reply, MSL1} = server_add_sup_handler(Handler, Args, MSL, SupP),
  180. ?reply(Reply),
  181. loop(Parent, ServerName, MSL1, Debug);
  182. {From, Tag, {delete_handler, Handler, Args}} ->
  183. {Reply, MSL1} = server_delete_handler(Handler, Args, MSL,
  184. ServerName),
  185. ?reply(Reply),
  186. loop(Parent, ServerName, MSL1, Debug);
  187. {From, Tag, {swap_handler, Handler1, Args1, Handler2, Args2}} ->
  188. {Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2,
  189. Args2, MSL, ServerName),
  190. ?reply(Reply),
  191. loop(Parent, ServerName, MSL1, Debug);
  192. {From, Tag, {swap_sup_handler, Handler1, Args1, Handler2, Args2,
  193. Sup}} ->
  194. {Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2,
  195. Args2, MSL, Sup, ServerName),
  196. ?reply(Reply),
  197. loop(Parent, ServerName, MSL1, Debug);
  198. {From, Tag, stop} ->
  199. catch terminate_server(normal, Parent, MSL, ServerName),
  200. ?reply(ok);
  201. {From, Tag, which_handlers} ->
  202. ?reply(the_handlers(MSL)),
  203. loop(Parent, ServerName, MSL, Debug);
  204. {From, Tag, get_modules} ->
  205. ?reply(get_modules(MSL)),
  206. loop(Parent, ServerName, MSL, Debug);
  207. Other ->
  208. MSL1 = server_notify(Other, handle_info, MSL, ServerName),
  209. loop(Parent, ServerName, MSL1, Debug)
  210. end.
  211. terminate_server(Reason, Parent, MSL, ServerName) ->
  212. stop_handlers(MSL, ServerName),
  213. do_unlink(Parent, MSL),
  214. exit(Reason).
  215. %% unlink the supervisor process of all supervised handlers.
  216. %% We do not want a handler supervisor to EXIT due to the
  217. %% termination of the event manager (server).
  218. %% Do not unlink Parent !
  219. do_unlink(Parent, MSL) ->
  220. lists:foreach(fun(Handler) when Handler#handler.supervised =:= Parent ->
  221. true;
  222. (Handler) when is_pid(Handler#handler.supervised) ->
  223. unlink(Handler#handler.supervised),
  224. true;
  225. (_) ->
  226. true
  227. end,
  228. MSL).
  229. %% First terminate the supervised (if exists) handlers and
  230. %% then inform other handlers.
  231. %% We do not know if any handler really is interested but it
  232. %% may be so !
  233. handle_exit(From, Reason, MSL, SName) ->
  234. MSL1 = terminate_supervised(From, Reason, MSL, SName),
  235. server_notify({'EXIT', From, Reason}, handle_info, MSL1, SName).
  236. terminate_supervised(Pid, Reason, MSL, SName) ->
  237. F = fun(Ha) when Ha#handler.supervised =:= Pid ->
  238. do_terminate(Ha#handler.module,
  239. Ha,
  240. {stop,Reason},
  241. Ha#handler.state,
  242. {parent_terminated, {Pid,Reason}},
  243. SName,
  244. shutdown),
  245. false;
  246. (_) ->
  247. true
  248. end,
  249. lists:filter(F, MSL).
  250. %%-----------------------------------------------------------------
  251. %% Callback functions for system messages handling.
  252. %%-----------------------------------------------------------------
  253. system_continue(Parent, Debug, [ServerName, MSL]) ->
  254. loop(Parent, ServerName, MSL, Debug).
  255. system_terminate(Reason, Parent, _Debug, [ServerName, MSL]) ->
  256. terminate_server(Reason, Parent, MSL, ServerName).
  257. %%-----------------------------------------------------------------
  258. %% Module here is sent in the system msg change_code. It specifies
  259. %% which module should be changed.
  260. %%-----------------------------------------------------------------
  261. system_code_change([ServerName, MSL], Module, OldVsn, Extra) ->
  262. MSL1 = lists:zf(fun(H) when H#handler.module =:= Module ->
  263. {ok, NewState} =
  264. Module:code_change(OldVsn,
  265. H#handler.state, Extra),
  266. {true, H#handler{state = NewState}};
  267. (_) -> true
  268. end,
  269. MSL),
  270. {ok, [ServerName, MSL1]}.
  271. %%-----------------------------------------------------------------
  272. %% Format debug messages. Print them as the call-back module sees
  273. %% them, not as the real erlang messages. Use trace for that.
  274. %%-----------------------------------------------------------------
  275. print_event(Dev, {in, Msg}, Name) ->
  276. case Msg of
  277. {notify, Event} ->
  278. io:format(Dev, "*DBG* ~p got event ~p~n", [Name, Event]);
  279. {_,_,{call, Handler, Query}} ->
  280. io:format(Dev, "*DBG* ~p(~p) got call ~p~n",
  281. [Name, Handler, Query]);
  282. _ ->
  283. io:format(Dev, "*DBG* ~p got ~p~n", [Name, Msg])
  284. end;
  285. print_event(Dev, Dbg, Name) ->
  286. io:format(Dev, "*DBG* ~p : ~p~n", [Name, Dbg]).
  287. %% server_add_handler(Handler, Args, MSL) -> {Ret, MSL'}.
  288. %% where MSL = [#handler]
  289. %% Ret goes to the top level MSL' is the new internal state of the
  290. %% event handler
  291. server_add_handler({Mod,Id}, Args, MSL) ->
  292. Handler = #handler{module = Mod,
  293. id = Id},
  294. server_add_handler(Mod, Handler, Args, MSL);
  295. server_add_handler(Mod, Args, MSL) ->
  296. Handler = #handler{module = Mod},
  297. server_add_handler(Mod, Handler, Args, MSL).
  298. server_add_handler(Mod, Handler, Args, MSL) ->
  299. case catch Mod:init(Args) of
  300. {ok, State} ->
  301. {ok, [Handler#handler{state = State}|MSL]};
  302. Other ->
  303. {Other, MSL}
  304. end.
  305. %% Set up a link to the supervising process.
  306. %% (Ought to be unidirected links here, Erl5.0 !!)
  307. %% NOTE: This link will not be removed then the
  308. %% handler is removed in case another handler has
  309. %% own link to this process.
  310. server_add_sup_handler({Mod,Id}, Args, MSL, Parent) ->
  311. link(Parent),
  312. Handler = #handler{module = Mod,
  313. id = Id,
  314. supervised = Parent},
  315. server_add_handler(Mod, Handler, Args, MSL);
  316. server_add_sup_handler(Mod, Args, MSL, Parent) ->
  317. link(Parent),
  318. Handler = #handler{module = Mod,
  319. supervised = Parent},
  320. server_add_handler(Mod, Handler, Args, MSL).
  321. %% server_delete_handler(HandlerId, Args, MSL) -> {Ret, MSL'}
  322. server_delete_handler(HandlerId, Args, MSL, SName) ->
  323. case split(HandlerId, MSL) of
  324. {Mod, Handler, MSL1} ->
  325. {do_terminate(Mod, Handler, Args,
  326. Handler#handler.state, delete, SName, normal),
  327. MSL1};
  328. error ->
  329. {{error, module_not_found}, MSL}
  330. end.
  331. %% server_swap_handler(Handler1, Args1, Handler2, Args2, MSL, SN)= -> MSL'
  332. %% server_swap_handler(Handler1, Args1, Handler2, Args2, MSL, Sup, SN)= -> MSL'
  333. server_swap_handler(Handler1, Args1, Handler2, Args2, MSL, SName) ->
  334. {State2, Sup, MSL1} = split_and_terminate(Handler1, Args1, MSL,
  335. SName, Handler2, false),
  336. case s_s_h(Sup, Handler2, {Args2, State2}, MSL1) of
  337. {ok, MSL2} ->
  338. {ok, MSL2};
  339. {What, MSL2} ->
  340. {{error, What}, MSL2}
  341. end.
  342. server_swap_handler(Handler1, Args1, Handler2, Args2, MSL, Sup, SName) ->
  343. {State2, _, MSL1} = split_and_terminate(Handler1, Args1, MSL,
  344. SName, Handler2, Sup),
  345. case s_s_h(Sup, Handler2, {Args2, State2}, MSL1) of
  346. {ok, MSL2} ->
  347. {ok, MSL2};
  348. {What, MSL2} ->
  349. {{error, What}, MSL2}
  350. end.
  351. s_s_h(false, Handler, Args, MSL) ->
  352. server_add_handler(Handler, Args, MSL);
  353. s_s_h(Pid, Handler, Args, MSL) ->
  354. server_add_sup_handler(Handler, Args, MSL, Pid).
  355. split_and_terminate(HandlerId, Args, MSL, SName, Handler2, Sup) ->
  356. case split(HandlerId, MSL) of
  357. {Mod, Handler, MSL1} ->
  358. OldSup = Handler#handler.supervised,
  359. NewSup = if
  360. not Sup -> OldSup;
  361. true -> Sup
  362. end,
  363. {do_terminate(Mod, Handler, Args,
  364. Handler#handler.state, swapped, SName,
  365. {swapped, Handler2, NewSup}),
  366. OldSup,
  367. MSL1};
  368. error ->
  369. {error, false, MSL}
  370. end.
  371. %% server_notify(Event, Func, MSL, SName) -> MSL'
  372. server_notify(Event, Func, [Handler|T], SName) ->
  373. case server_update(Handler, Func, Event, SName) of
  374. {ok, Handler1} ->
  375. [Handler1|server_notify(Event, Func, T, SName)];
  376. no ->
  377. server_notify(Event, Func, T, SName)
  378. end;
  379. server_notify(_, _, [], _) ->
  380. [].
  381. %% server_update(Handler, Func, Event, ServerName) -> Handler1 | no
  382. server_update(Handler1, Func, Event, SName) ->
  383. Mod1 = Handler1#handler.module,
  384. State = Handler1#handler.state,
  385. case catch Mod1:Func(Event, State) of
  386. {ok, State1} ->
  387. {ok, Handler1#handler{state = State1}};
  388. {swap_handler, Args1, State1, Handler2, Args2} ->
  389. do_swap(Mod1,Handler1,Args1,State1,Handler2,Args2,SName);
  390. remove_handler ->
  391. do_terminate(Mod1, Handler1, remove_handler, State,
  392. remove, SName, normal),
  393. no;
  394. Other ->
  395. do_terminate(Mod1, Handler1, {error, Other}, State,
  396. Event, SName, crash),
  397. no
  398. end.
  399. do_swap(Mod1,Handler1,Args1,State1,Handler2,Args2,SName) ->
  400. %% finalise the existing handler
  401. State2 = do_terminate(Mod1, Handler1, Args1, State1,
  402. swapped, SName,
  403. {swapped, Handler2, Handler1#handler.supervised}),
  404. {Mod2,Handler} = new_handler(Handler2, Handler1),
  405. case catch Mod2:init({Args2, State2}) of
  406. {ok, State2a} ->
  407. {ok, Handler#handler{state = State2a}};
  408. Other ->
  409. report_terminate(Handler2, crash, {error, Other}, SName, false),
  410. no
  411. end.
  412. new_handler({Mod,Id}, Handler1) ->
  413. {Mod,#handler{module = Mod,
  414. id = Id,
  415. supervised = Handler1#handler.supervised}};
  416. new_handler(Mod, Handler1) ->
  417. {Mod,#handler{module = Mod,
  418. supervised = Handler1#handler.supervised}}.
  419. %% split(Handler, [#handler]) ->
  420. %% {Mod, #handler, [#handler]} | error
  421. split(Ha, MSL) -> split(Ha, MSL, []).
  422. split({Mod,Id}, [Ha|T], L) when Ha#handler.module =:= Mod,
  423. Ha#handler.id =:= Id ->
  424. {Mod, Ha, lists:reverse(L, T)};
  425. split(Mod, [Ha|T], L) when Ha#handler.module =:= Mod,
  426. not Ha#handler.id ->
  427. {Mod, Ha, lists:reverse(L, T)};
  428. split(Ha, [H|T], L) ->
  429. split(Ha, T, [H|L]);
  430. split(_, [], _) ->
  431. error.
  432. %% server_call(Handler, Query, MSL, ServerName) ->
  433. %% {Reply, MSL1}
  434. server_call(Handler, Query, MSL, SName) ->
  435. case search(Handler, MSL) of
  436. {ok, Ha} ->
  437. case server_call_update(Ha, Query, SName) of
  438. {no, Reply} ->
  439. {Reply, delete(Handler, MSL)};
  440. {{ok, Ha1}, Reply} ->
  441. {Reply, replace(Handler, MSL, Ha1)}
  442. end;
  443. false ->
  444. {{error, bad_module}, MSL}
  445. end.
  446. search({Mod, Id}, [Ha|_MSL]) when Ha#handler.module =:= Mod,
  447. Ha#handler.id =:= Id ->
  448. {ok, Ha};
  449. search(Mod, [Ha|_MSL]) when Ha#handler.module =:= Mod,
  450. not Ha#handler.id ->
  451. {ok, Ha};
  452. search(Handler, [_|MSL]) ->
  453. search(Handler, MSL);
  454. search(_, []) ->
  455. false.
  456. delete({Mod, Id}, [Ha|MSL]) when Ha#handler.module =:= Mod,
  457. Ha#handler.id =:= Id ->
  458. MSL;
  459. delete(Mod, [Ha|MSL]) when Ha#handler.module =:= Mod,
  460. not Ha#handler.id ->
  461. MSL;
  462. delete(Handler, [Ha|MSL]) ->
  463. [Ha|delete(Handler, MSL)];
  464. delete(_, []) ->
  465. [].
  466. replace({Mod, Id}, [Ha|MSL], NewHa) when Ha#handler.module =:= Mod,
  467. Ha#handler.id =:= Id ->
  468. [NewHa|MSL];
  469. replace(Mod, [Ha|MSL], NewHa) when Ha#handler.module =:= Mod,
  470. not Ha#handler.id ->
  471. [NewHa|MSL];
  472. replace(Handler, [Ha|MSL], NewHa) ->
  473. [Ha|replace(Handler, MSL, NewHa)];
  474. replace(_, [], NewHa) ->
  475. [NewHa].
  476. %% server_call_update(Handler, Query, ServerName) ->
  477. %% {{Handler1, State1} | no, Reply}
  478. server_call_update(Handler1, Query, SName) ->
  479. Mod1 = Handler1#handler.module,
  480. State = Handler1#handler.state,
  481. case catch Mod1:handle_call(Query, State) of
  482. {ok, Reply, State1} ->
  483. {{ok, Handler1#handler{state = State1}}, Reply};
  484. {swap_handler, Reply, Args1, State1, Handler2, Args2} ->
  485. {do_swap(Mod1,Handler1,Args1,State1,Handler2,Args2,SName), Reply};
  486. {remove_handler, Reply} ->
  487. do_terminate(Mod1, Handler1, remove_handler, State,
  488. remove, SName, normal),
  489. {no, Reply};
  490. Other ->
  491. do_terminate(Mod1, Handler1, {error, Other}, State,
  492. Query, SName, crash),
  493. {no, {error, Other}}
  494. end.
  495. do_terminate(Mod, Handler, Args, State, LastIn, SName, Reason) ->
  496. Res = (catch Mod:terminate(Args, State)),
  497. report_terminate(Handler, Reason, Args, State, LastIn, SName, Res),
  498. Res.
  499. report_terminate(Handler, crash, {error, Why}, State, LastIn, SName, _) ->
  500. report_terminate(Handler, Why, State, LastIn, SName);
  501. report_terminate(Handler, How, _, State, LastIn, SName, _) ->
  502. %% How == normal | shutdown | {swapped, NewHandler, NewSupervisor}
  503. report_terminate(Handler, How, State, LastIn, SName).
  504. report_terminate(Handler, Reason, State, LastIn, SName) ->
  505. report_error(Handler, Reason, State, LastIn, SName),
  506. case Handler#handler.supervised of
  507. false ->
  508. ok;
  509. Pid ->
  510. Pid ! {gen_event_EXIT,handler(Handler),Reason},
  511. ok
  512. end.
  513. report_error(_Handler, normal, _, _, _) -> ok;
  514. report_error(_Handler, shutdown, _, _, _) -> ok;
  515. report_error(_Handler, {swapped,_,_}, _, _, _) -> ok;
  516. report_error(Handler, Reason, State, LastIn, SName) ->
  517. Reason1 =
  518. case Reason of
  519. {'EXIT',{undef,[{M,F,A}|MFAs]}} ->
  520. case code:is_loaded(M) of
  521. false ->
  522. {'module could not be loaded',[{M,F,A}|MFAs]};
  523. _ ->
  524. case erlang:function_exported(M, F, length(A)) of
  525. true ->
  526. {undef,[{M,F,A}|MFAs]};
  527. false ->
  528. {'function not exported',[{M,F,A}|MFAs]}
  529. end
  530. end;
  531. {'EXIT',Why} ->
  532. Why;
  533. _ ->
  534. Reason
  535. end,
  536. error_msg("** gen_event handler ~p crashed.~n"
  537. "** Was installed in ~p~n"
  538. "** Last event was: ~p~n"
  539. "** When handler state == ~p~n"
  540. "** Reason == ~p~n",
  541. [handler(Handler),SName,LastIn,State,Reason1]).
  542. handler(Handler) when not Handler#handler.id ->
  543. Handler#handler.module;
  544. handler(Handler) ->
  545. {Handler#handler.module, Handler#handler.id}.
  546. %% stop_handlers(MSL, ServerName) -> []
  547. stop_handlers([Handler|T], SName) ->
  548. Mod = Handler#handler.module,
  549. do_terminate(Mod, Handler, stop, Handler#handler.state,
  550. stop, SName, shutdown),
  551. stop_handlers(T, SName);
  552. stop_handlers([], _) ->
  553. [].
  554. the_handlers(MSL) ->
  555. lists:map(fun(Handler) when not Handler#handler.id ->
  556. Handler#handler.module;
  557. (Handler) ->
  558. {Handler#handler.module, Handler#handler.id}
  559. end,
  560. MSL).
  561. %% Message from the release_handler.
  562. %% The list of modules got to be a set !
  563. get_modules(MSL) ->
  564. Mods = lists:map(fun(Handler) -> Handler#handler.module end,
  565. MSL),
  566. ordsets:to_list(ordsets:from_list(Mods)).
  567. %%-----------------------------------------------------------------
  568. %% Status information
  569. %%-----------------------------------------------------------------
  570. format_status(_Opt, StatusData) ->
  571. [_PDict, SysState, Parent, _Debug, [ServerName, MSL]] = StatusData,
  572. Header = lists:concat(["Status for event handler ", ServerName]),
  573. [{header, Header},
  574. {data, [{"Status", SysState},
  575. {"Parent", Parent}]},
  576. {items, {"Installed handlers", MSL}}].