1%% 2%% %CopyrightBegin% 3%% 4%% Copyright Ericsson AB 1996-2019. All Rights Reserved. 5%% 6%% Licensed under the Apache License, Version 2.0 (the "License"); 7%% you may not use this file except in compliance with the License. 8%% You may obtain a copy of the License at 9%% 10%% http://www.apache.org/licenses/LICENSE-2.0 11%% 12%% Unless required by applicable law or agreed to in writing, software 13%% distributed under the License is distributed on an "AS IS" BASIS, 14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. 15%% See the License for the specific language governing permissions and 16%% limitations under the License. 17%% 18%% %CopyrightEnd% 19%% 20-module(proc_lib_SUITE). 21 22%% 23%% Define to run outside of test server 24%% 25%%-define(STANDALONE,1). 26 27-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 28 init_per_group/2,end_per_group/2, 29 crash/1, stacktrace/1, sync_start_nolink/1, sync_start_link/1, 30 sync_start_monitor/1, sync_start_monitor_link/1, 31 sync_start_timeout/1, sync_start_link_timeout/1, 32 sync_start_monitor_link_timeout/1, 33 spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1, sp6/1, sp7/1, 34 sp8/1, sp9/1, sp10/1, 35 '\x{447}'/0, hibernate/1, stop/1, t_format/1, t_format_arbitrary/1]). 36-export([ otp_6345/1, init_dont_hang/1]). 37 38-export([hib_loop/1, awaken/1]). 39 40-export([init/1, 41 handle_event/2, handle_call/2, handle_info/2, 42 terminate/2]). 43 44-export([otp_6345_init/1, init_dont_hang_init/1]). 45 46-export([report_cb/1, report_cb_chars_limit/1, log/2, rcb_tester/0]). 47 48-export([system_terminate/4]). 49 50-ifdef(STANDALONE). 51-define(line, noop, ). 52-else. 53-include_lib("common_test/include/ct.hrl"). 54-endif. 55 56suite() -> [{ct_hooks,[ts_install_cth]}]. 57 58all() -> 59 [crash, stacktrace, {group, sync_start}, spawn_opt, hibernate, 60 {group, tickets}, stop, t_format, t_format_arbitrary, report_cb]. 61 62groups() -> 63 [{tickets, [], [otp_6345, init_dont_hang]}, 64 {sync_start, [], [sync_start_nolink, sync_start_link, 65 sync_start_monitor, sync_start_monitor_link, 66 sync_start_timeout, sync_start_link_timeout, 67 sync_start_monitor_link_timeout]}]. 68 69init_per_suite(Config) -> 70 Config. 71 72end_per_suite(_Config) -> 73 ok. 74 75init_per_group(_GroupName, Config) -> 76 Config. 77 78end_per_group(_GroupName, Config) -> 79 Config. 80 81 82 83%%----------------------------------------------------------------- 84%% We don't have to test that spwn and spawn_link actually spawns 85%% new processes - if they don't we can't run this suite! 86%% But we want to test that start and start_link really is 87%% synchronous, and we want to test that the crash report is ok. 88%%----------------------------------------------------------------- 89crash(Config) when is_list(Config) -> 90 ok = application:unset_env(kernel, error_logger_format_depth), 91 crash_1(Config), 92 ok = application:set_env(kernel, error_logger_format_depth, 30), 93 crash_1(Config), 94 ok = application:unset_env(kernel, error_logger_format_depth), 95 ok. 96 97crash_1(_Config) -> 98 error_logger:add_report_handler(?MODULE, self()), 99 100 %% Make sure that we don't get a crash report if a process 101 %% terminates with reason 'shutdown' or reason {shutdown,Reason}. 102 process_flag(trap_exit, true), 103 Pid0 = proc_lib:spawn_link(erlang, apply, 104 [fun() -> exit(shutdown) end,[]]), 105 Pid1 = proc_lib:spawn_link(erlang, apply, 106 [fun() -> exit({shutdown,{a,b,c}}) end,[]]), 107 108 receive {'EXIT',Pid0,shutdown} -> ok end, 109 receive {'EXIT',Pid1,{shutdown,{a,b,c}}} -> ok end, 110 process_flag(trap_exit, false), 111 %% We expect any unexpected messages to be caught below, 112 %% so we don't have explicitly wait some time to be sure. 113 114 %% Spawn export function. 115 Pid2 = proc_lib:spawn(?MODULE, sp1, []), 116 Pid2 ! die, 117 Exp2 = [{initial_call,{?MODULE,sp1,[]}}, 118 {ancestors,[self()]}, 119 {error_info,{exit,die,{stacktrace}}}], 120 analyse_crash(Pid2, Exp2, []), 121 122 %% Spawn fun. 123 F = fun sp1/0, 124 Pid3 = proc_lib:spawn(node(), F), 125 Pid3 ! die, 126 {module,?MODULE} = erlang:fun_info(F, module), 127 {name,Fname} = erlang:fun_info(F, name), 128 Exp3 = [{initial_call,{?MODULE,Fname,[]}}, 129 {ancestors,[self()]}, 130 {error_info,{exit,die,{stacktrace}}}], 131 analyse_crash(Pid3, Exp3, []), 132 133 %% Spawn function with neighbour. 134 Pid4 = proc_lib:spawn(?MODULE, sp2, []), 135 ct:sleep(100), 136 {?MODULE,sp2,[]} = proc_lib:initial_call(Pid4), 137 {?MODULE,sp2,0} = proc_lib:translate_initial_call(Pid4), 138 Pid4 ! die, 139 Exp4 = [{initial_call,{?MODULE,sp2,[]}}, 140 {ancestors,[self()]}, 141 {error_info,{exit,die,{stacktrace}}}], 142 Links4 = [[{initial_call,{?MODULE,sp1,[]}}, 143 {ancestors,[Pid4,self()]}]], 144 analyse_crash(Pid4, Exp4, Links4), 145 146 %% Make sure that we still get a crash report if the 147 %% process dictionary have been tampered with. 148 149 Pid5 = proc_lib:spawn(erlang, apply, 150 [fun() -> 151 erase(), 152 exit(abnormal) 153 end,[]]), 154 Exp5 = [{initial_call,absent}, 155 {ancestors,[]}, 156 {error_info,{exit,abnormal,{stacktrace}}}], 157 analyse_crash(Pid5, Exp5, []), 158 159 %% Unicode atom 160 Pid6 = proc_lib:spawn(?MODULE, '\x{447}', []), 161 Pid6 ! die, 162 Exp6 = [{initial_call,{?MODULE,'\x{447}',[]}}, 163 {ancestors,[self()]}, 164 {error_info,{exit,die,{stacktrace}}}], 165 analyse_crash(Pid6, Exp6, []), 166 167 error_logger:delete_report_handler(?MODULE), 168 ok. 169 170analyse_crash(Pid, Expected0, ExpLinks) -> 171 Expected = [{pid,Pid}|Expected0], 172 receive 173 {crash_report, Pid, Report} -> 174 _ = proc_lib:format(Report), %Smoke test. 175 [Crash,Links] = Report, 176 analyse_crash_1(Expected, Crash), 177 analyse_links(ExpLinks, Links); 178 Unexpected -> 179 io:format("~p\n", [Unexpected]), 180 ct:fail(unexpected_message) 181 after 5000 -> 182 ct:fail(no_crash_report) 183 end. 184 185analyse_links([H|Es], [{neighbour,N}|Links]) -> 186 analyse_crash_1(H, N), 187 analyse_links(Es, Links); 188analyse_links([], []) -> 189 ok. 190 191analyse_crash_1([{Key,absent}|T], Report) -> 192 false = lists:keymember(Key, 1, Report), 193 analyse_crash_1(T, Report); 194analyse_crash_1([{Key,Pattern}|T], Report) -> 195 case lists:keyfind(Key, 1, Report) of 196 false -> 197 io:format("~p", [Report]), 198 ct:fail({missing_key,Key}); 199 {Key,Info} -> 200 try 201 match_info(Pattern, Info) 202 catch 203 no_match -> 204 io:format("key: ~p", [Key]), 205 io:format("pattern: ~p", [Pattern]), 206 io:format("actual: ~p", [Report]), 207 ct:fail(no_match) 208 end, 209 analyse_crash_1(T, Report) 210 end; 211analyse_crash_1([], _Report) -> 212 []. 213 214match_info(T, T) -> 215 ok; 216match_info({stacktrace}, Stk) when is_list(Stk) -> 217 ok; 218match_info([H1|T1], [H2|T2]) -> 219 match_info(H1, H2), 220 match_info(T1, T2); 221match_info(Tuple1, Tuple2) when tuple_size(Tuple1) =:= tuple_size(Tuple2) -> 222 match_info(tuple_to_list(Tuple1), tuple_to_list(Tuple2)); 223match_info(_, _) -> 224 throw(no_match). 225 226stacktrace(Config) when is_list(Config) -> 227 process_flag(trap_exit, true), 228 %% Errors. 229 Pid1 = proc_lib:spawn_link(fun() -> 1 = 2 end), 230 receive 231 {'EXIT',Pid1,{{badmatch,2},_Stack1}} -> ok 232 after 500 -> 233 ct:fail(error) 234 end, 235 %% Exits. 236 Pid2 = proc_lib:spawn_link(fun() -> exit(bye) end), 237 receive 238 {'EXIT',Pid2,bye} -> ok 239 after 500 -> 240 ct:fail(exit) 241 end, 242 %% Throws. 243 Pid3 = proc_lib:spawn_link(fun() -> throw(ball) end), 244 receive 245 {'EXIT',Pid3,{{nocatch,ball},_Stack3}} -> ok 246 after 500 -> 247 ct:fail(throw) 248 end, 249 ok. 250 251sync_start_nolink(Config) when is_list(Config) -> 252 _Pid = spawn_link(?MODULE, sp5, [self()]), 253 receive 254 {sync_started, F} -> 255 exit(F, kill), 256 ct:fail(async_start) 257 after 1000 -> ok 258 end, 259 receive 260 {Pid2, init} -> 261 Pid2 ! go_on 262 end, 263 receive 264 {sync_started, _} -> ok 265 after 1000 -> 266 exit(Pid2, kill), 267 ct:fail(no_sync_start) 268 end, 269 ok. 270 271sync_start_link(Config) when is_list(Config) -> 272 _Pid = spawn_link(?MODULE, sp3, [self()]), 273 receive 274 {sync_started, _} -> ct:fail(async_start) 275 after 1000 -> ok 276 end, 277 receive 278 {Pid2, init} -> 279 Pid2 ! go_on 280 end, 281 receive 282 {sync_started, _} -> ok 283 after 1000 -> ct:fail(no_sync_start) 284 end, 285 ok. 286 287sync_start_monitor(Config) when is_list(Config) -> 288 _Pid = spawn_link(?MODULE, sp6, [self()]), 289 receive 290 {sync_started, _} -> ct:fail(async_start) 291 after 1000 -> ok 292 end, 293 receive 294 {Pid2, init} -> 295 Pid2 ! go_on 296 end, 297 receive 298 {sync_started, _} -> ok 299 after 1000 -> ct:fail(no_sync_start) 300 end, 301 receive received_down -> ok 302 after 2000 -> ct:fail(no_down) 303 end, 304 ok. 305 306sync_start_monitor_link(Config) when is_list(Config) -> 307 _Pid = spawn_link(?MODULE, sp7, [self()]), 308 receive 309 {sync_started, _} -> ct:fail(async_start) 310 after 1000 -> ok 311 end, 312 receive 313 {Pid2, init} -> 314 Pid2 ! go_on 315 end, 316 receive 317 {sync_started, _} -> ok 318 after 1000 -> ct:fail(no_sync_start) 319 end, 320 receive received_down -> ok 321 after 1000 -> ct:fail(no_down) 322 end, 323 receive received_exit -> ok 324 after 1000 -> ct:fail(no_exit) 325 end, 326 ok. 327 328sync_start_timeout(Config) when is_list(Config) -> 329 _Pid = spawn_link(?MODULE, sp8, [self()]), 330 receive done -> ok end, 331 receive {received_exit, _} = M1 -> ct:fail(M1) 332 after 0 -> ok 333 end, 334 receive {received_down, _} = M2 -> ct:fail(M2) 335 after 0 -> ok 336 end, 337 ok. 338 339sync_start_link_timeout(Config) when is_list(Config) -> 340 _Pid = spawn_link(?MODULE, sp9, [self()]), 341 receive done -> ok end, 342 receive {received_exit, _} = M1 -> ct:fail(M1) 343 after 0 -> ok 344 end, 345 receive {received_down, _} = M2 -> ct:fail(M2) 346 after 0 -> ok 347 end, 348 ok. 349 350sync_start_monitor_link_timeout(Config) when is_list(Config) -> 351 _Pid = spawn_link(?MODULE, sp10, [self()]), 352 receive done -> ok end, 353 receive {received_exit, _} = M1 -> ct:fail(M1) 354 after 0 -> ok 355 end, 356 receive 357 {received_down, R} -> 358 killed = R, 359 ok 360 after 0 -> ct:fail(no_down) 361 end, 362 ok. 363 364 365spawn_opt(Config) when is_list(Config) -> 366 F = fun sp1/0, 367 {name,Fname} = erlang:fun_info(F, name), 368 FunMFArgs = {?MODULE,Fname,[]}, 369 FunMFArity = {?MODULE,Fname,0}, 370 Pid1 = proc_lib:spawn_opt(node(), F, [{priority,low}]), 371 Pid = proc_lib:spawn_opt(F, [{priority,low}]), 372 ct:sleep(100), 373 FunMFArgs = proc_lib:initial_call(Pid), 374 FunMFArity = proc_lib:translate_initial_call(Pid), 375 Pid ! die, 376 FunMFArgs = proc_lib:initial_call(Pid1), 377 FunMFArity = proc_lib:translate_initial_call(Pid1), 378 Pid1 ! die, 379 ok. 380 381 382sp1() -> 383 receive 384 die -> exit(die); 385 _ -> sp1() 386 end. 387 388sp2() -> 389 _Pid = proc_lib:spawn_link(?MODULE, sp1, []), 390 receive 391 die -> exit(die); 392 _ -> sp1() 393 end. 394 395sp3(Tester) -> 396 Pid = proc_lib:start_link(?MODULE, sp4, [self(), Tester]), 397 Tester ! {sync_started, Pid}. 398 399sp5(Tester) -> 400 Pid = proc_lib:start(?MODULE, sp4, [self(), Tester]), 401 Tester ! {sync_started, Pid}. 402 403sp6(Tester) -> 404 process_flag(trap_exit, true), 405 {Pid, Mon} = proc_lib:start_monitor(?MODULE, sp4, [self(), Tester]), 406 Tester ! {sync_started, Pid}, 407 receive 408 {'EXIT', Pid, normal} -> 409 exit(received_exit) 410 after 1000 -> 411 ok 412 end, 413 receive 414 {'DOWN', Mon, process, Pid, normal} -> 415 Tester ! received_down 416 end. 417 418sp7(Tester) -> 419 process_flag(trap_exit, true), 420 {Pid, Mon} = proc_lib:start_monitor(?MODULE, sp4, [self(), Tester], infinity, [link]), 421 Tester ! {sync_started, Pid}, 422 receive 423 {'EXIT', Pid, normal} -> 424 Tester ! received_exit 425 end, 426 receive 427 {'DOWN', Mon, process, Pid, normal} -> 428 Tester ! received_down 429 end. 430 431sp8(Tester) -> 432 process_flag(trap_exit, true), 433 {error,timeout} = proc_lib:start(?MODULE, sp4, [self(), Tester], 500, [link]), 434 receive after 500 -> ok end, 435 receive 436 {'EXIT', _Pid1, Reason1} -> 437 Tester ! {received_exit, Reason1} 438 after 0 -> 439 ok 440 end, 441 receive 442 {'DOWN', _Mon2, process, _Pid2, Reason2} -> 443 Tester ! {received_down, Reason2} 444 after 0 -> 445 ok 446 end, 447 Tester ! done. 448 449sp9(Tester) -> 450 process_flag(trap_exit, true), 451 {error,timeout} = proc_lib:start_link(?MODULE, sp4, [self(), Tester], 500), 452 receive after 500 -> ok end, 453 receive 454 {'EXIT', _Pid1, Reason1} -> 455 Tester ! {received_exit, Reason1} 456 after 0 -> 457 ok 458 end, 459 receive 460 {'DOWN', _Mon, process, _Pid2, Reason2} -> 461 Tester ! {received_down, Reason2} 462 after 0 -> 463 ok 464 end, 465 Tester ! done. 466 467 468sp10(Tester) -> 469 process_flag(trap_exit, true), 470 {{error,timeout}, Mon} = proc_lib:start_monitor(?MODULE, sp4, [self(), Tester], 500, [link]), 471 receive after 500 -> ok end, 472 receive 473 {'EXIT', _Pid1, Reason1} -> 474 Tester ! {received_exit, Reason1} 475 after 0 -> 476 ok 477 end, 478 receive 479 {'DOWN', Mon, process, _Pid2, Reason2} -> 480 Tester ! {received_down, Reason2} 481 after 0 -> 482 ok 483 end, 484 Tester ! done. 485 486sp4(Parent, Tester) -> 487 Tester ! {self(), init}, 488 receive 489 go_on -> ok 490 end, 491 proc_lib:init_ack(Parent, self()). 492 493'\x{447}'() -> 494 receive 495 die -> exit(die); 496 _ -> sp1() 497 end. 498 499hibernate(Config) when is_list(Config) -> 500 Ref = make_ref(), 501 Self = self(), 502 LoopData = {Ref,Self}, 503 Pid = proc_lib:spawn_link(?MODULE, hib_loop, [LoopData]), 504 505 %% Just check that the child process can process and answer messages. 506 Pid ! {Self,loop_data}, 507 receive 508 {loop_data,LoopData} -> ok; 509 Unexpected0 -> 510 io:format("Unexpected: ~p\n", [Unexpected0]), 511 ct:fail(failed) 512 after 1000 -> 513 io:format("Timeout"), 514 ct:fail(failed) 515 end, 516 517 %% Hibernate the process. 518 Pid ! hibernate, 519 erlang:yield(), 520 io:format("~p\n", [process_info(Pid, heap_size)]), 521 522 523 %% Send a message to the process... 524 525 Pid ! {Self,loop_data}, 526 527 %% ... expect first a wake up message from the process... 528 receive 529 {awaken,LoopData} -> ok; 530 Unexpected1 -> 531 io:format("Unexpected: ~p\n", [Unexpected1]), 532 ct:fail(failed) 533 after 1000 -> 534 io:format("Timeout"), 535 ct:fail(failed) 536 end, 537 538 %% ... followed by the answer to the actual request. 539 receive 540 {loop_data,LoopData} -> ok; 541 Unexpected2 -> 542 io:format("Unexpected: ~p\n", [Unexpected2]), 543 ct:fail(failed) 544 after 1000 -> 545 io:format("Timeout"), 546 ct:fail(failed) 547 end, 548 549 %% Test that errors are handled correctly after wake up from hibernation... 550 551 process_flag(trap_exit, true), 552 error_logger:add_report_handler(?MODULE, self()), 553 Pid ! crash, 554 555 %% We should receive two messages. Especially in the SMP emulator, 556 %% we can't be sure of the message order, so sort the messages before 557 %% matching. 558 559 Messages = lists:sort(hib_receive_messages(2)), 560 io:format("~p", [Messages]), 561 [{'EXIT',Pid,i_crashed},{crash_report,Pid,[Report,[]]}] = Messages, 562 563 %% Check that the initial_call has the expected format. 564 {value,{initial_call,{?MODULE,hib_loop,[_]}}} = 565 lists:keysearch(initial_call, 1, Report), 566 567 error_logger:delete_report_handler(?MODULE), 568 ok. 569 570hib_loop(LoopData) -> 571 receive 572 hibernate -> 573 proc_lib:hibernate(?MODULE, awaken, [LoopData]); 574 {Pid,loop_data} -> 575 Pid ! {loop_data,LoopData}; 576 crash -> 577 exit(i_crashed) 578 end, 579 hib_loop(LoopData). 580 581awaken({_,Parent}=LoopData) -> 582 Parent ! {awaken,LoopData}, 583 hib_loop(LoopData). 584 585hib_receive_messages(0) -> []; 586hib_receive_messages(N) -> 587 receive 588 Any -> [Any|hib_receive_messages(N-1)] 589 end. 590 591%% 'monitor' spawn_opt option. 592otp_6345(Config) when is_list(Config) -> 593 Opts = [link,monitor], 594 try 595 blupp = proc_lib:start(?MODULE, otp_6345_init, [self()], 596 1000, Opts) 597 catch 598 error:badarg -> ok 599 end. 600 601otp_6345_init(Parent) -> 602 proc_lib:init_ack(Parent, {ok, self()}), 603 otp_6345_loop(). 604 605otp_6345_loop() -> 606 receive 607 _Msg -> 608 otp_6345_loop() 609 end. 610 611%% OTP-9803. Check that proc_lib:start() doesn't hang if spawned process 612%% crashes before proc_lib:init_ack/2. 613init_dont_hang(Config) when is_list(Config) -> 614 %% Start should behave as start_link 615 process_flag(trap_exit, true), 616 StartLinkRes = proc_lib:start_link(?MODULE, init_dont_hang_init, [self()]), 617 try 618 StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000), 619 StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000, []), 620 ok 621 catch _:Error:Stacktrace -> 622 io:format("Error ~p /= ~p ~n",[Stacktrace, StartLinkRes]), 623 exit(Error) 624 end. 625 626init_dont_hang_init(_Parent) -> 627 error(bad_init). 628 629%% Test proc_lib:stop/1,3 630stop(_Config) -> 631 Parent = self(), 632 SysMsgProc = 633 fun() -> 634 receive 635 {system,From,Request} -> 636 sys:handle_system_msg(Request,From,Parent,?MODULE,[],[]) 637 end 638 end, 639 640 %% Normal case: 641 %% Process handles system message and terminated with given reason 642 Pid1 = proc_lib:spawn(SysMsgProc), 643 ok = proc_lib:stop(Pid1), 644 false = erlang:is_process_alive(Pid1), 645 646 %% Process does not exit 647 {'EXIT',noproc} = (catch proc_lib:stop(Pid1)), 648 649 %% Badly handled system message 650 DieProc = 651 fun() -> 652 receive 653 {system,_From,_Request} -> 654 exit(die) 655 end 656 end, 657 Pid2 = proc_lib:spawn(DieProc), 658 {'EXIT',{die,_}} = (catch proc_lib:stop(Pid2)), 659 660 %% Hanging process => timeout 661 HangProc = 662 fun() -> 663 receive 664 {system,_From,_Request} -> 665 timer:sleep(5000) 666 end 667 end, 668 Pid3 = proc_lib:spawn(HangProc), 669 {'EXIT',timeout} = (catch proc_lib:stop(Pid3,normal,1000)), 670 671 %% Success case with other reason than 'normal' 672 Pid4 = proc_lib:spawn(SysMsgProc), 673 ok = proc_lib:stop(Pid4,other_reason,infinity), 674 false = erlang:is_process_alive(Pid4), 675 676 %% System message is handled, but process dies with other reason 677 %% than the given (in system_terminate/4 below) 678 Pid5 = proc_lib:spawn(SysMsgProc), 679 {'EXIT',{{badmatch,2},_Stacktrace}} = (catch proc_lib:stop(Pid5,crash,infinity)), 680 false = erlang:is_process_alive(Pid5), 681 682 %% Local registered name 683 Pid6 = proc_lib:spawn(SysMsgProc), 684 register(to_stop,Pid6), 685 ok = proc_lib:stop(to_stop), 686 undefined = whereis(to_stop), 687 false = erlang:is_process_alive(Pid6), 688 689 %% Remote registered name 690 {ok,Node} = test_server:start_node(proc_lib_SUITE_stop,slave,[]), 691 Dir = filename:dirname(code:which(?MODULE)), 692 rpc:call(Node,code,add_path,[Dir]), 693 Pid7 = spawn(Node,SysMsgProc), 694 true = rpc:call(Node,erlang,register,[to_stop,Pid7]), 695 Pid7 = rpc:call(Node,erlang,whereis,[to_stop]), 696 ok = proc_lib:stop({to_stop,Node}), 697 undefined = rpc:call(Node,erlang,whereis,[to_stop]), 698 false = rpc:call(Node,erlang,is_process_alive,[Pid7]), 699 700 %% Local and remote registered name, but non-existing 701 {'EXIT',noproc} = (catch proc_lib:stop(to_stop)), 702 {'EXIT',noproc} = (catch proc_lib:stop({to_stop,Node})), 703 704 true = test_server:stop_node(Node), 705 706 %% Remote registered name, but non-existing node 707 {'EXIT',{{nodedown,Node},_}} = (catch proc_lib:stop({to_stop,Node})), 708 ok. 709 710system_terminate(crash,_Parent,_Deb,_State) -> 711 error({badmatch,2}); 712system_terminate(Reason,_Parent,_Deb,_State) -> 713 exit(Reason). 714 715 716t_format(_Config) -> 717 {ok,#{level:=Level}} = logger:get_handler_config(default), 718 logger:set_handler_config(default,level,none), 719 error_logger:add_report_handler(?MODULE, self()), 720 try 721 t_format() 722 after 723 error_logger:delete_report_handler(?MODULE), 724 logger:set_handler_config(default,level,Level) 725 end, 726 ok. 727 728t_format() -> 729 Pid = proc_lib:spawn(fun '\x{aaa}t_format_looper'/0), 730 HugeData = gb_sets:from_list(lists:seq(1, 100)), 731 SomeData1 = list_to_atom([246]), 732 SomeData2 = list_to_atom([1024]), 733 Pid ! {SomeData1,SomeData2}, 734 Pid ! {die,{HugeData,SomeData1,SomeData2}}, 735 Report = receive 736 {crash_report, Pid, Report0} -> Report0 737 end, 738 Usz = do_test_format(Report, latin1, unlimited), 739 Tsz = do_test_format(Report, latin1, 20), 740 741 if 742 Tsz >= Usz -> 743 ct:fail(failed); 744 true -> 745 ok 746 end, 747 748 UszU = do_test_format(Report, unicode, unlimited), 749 TszU = do_test_format(Report, unicode, 20), 750 751 if 752 TszU >= UszU -> 753 ct:fail(failed); 754 true -> 755 ok 756 end, 757 758 ok. 759 760t_format_arbitrary(_Config) -> 761 {ok,#{level:=Level}} = logger:get_handler_config(default), 762 logger:set_handler_config(default,level,none), 763 try 764 t_format_arbitrary() 765 after 766 logger:set_handler_config(default,level,Level) 767 end, 768 ok. 769 770t_format_arbitrary() -> 771 A = list_to_atom([1024]), 772 do_test_format([fake_report, A], unlimited), 773 do_test_format([fake_report, A], 20), 774 775 do_test_format([fake_report, foo], unlimited), 776 do_test_format([fake_report, foo], 20), 777 do_test_format([fake_report, []], unlimited), 778 do_test_format([fake_report, []], 20). 779 780do_test_format(Report, Depth) -> 781 do_test_format(Report, latin1, Depth), 782 do_test_format(Report, unicode, Depth). 783 784do_test_format(Report, Encoding, Depth) -> 785 io:format("*** Depth = ~p, Encoding = ~p", [Depth, Encoding]), 786 S0 = proc_lib:format(Report, Encoding, Depth), 787 S = lists:flatten(S0), 788 case Encoding of 789 latin1 -> io:format("~s\n", [S]); 790 _ -> io:format("~ts\n", [S]) 791 end, 792 length(S). 793 794'\x{aaa}t_format_looper'() -> 795 receive 796 {die,Data} -> 797 exit(Data); 798 M -> 799 put(M, M), 800 '\x{aaa}t_format_looper'() 801 end. 802 803%% Test report callback for any Logger handler 804report_cb(_Config) -> 805 ok = logger:add_handler(?MODULE,?MODULE,#{config=>self()}), 806 Pid = proc_lib:spawn(?MODULE, sp2, []), 807 ct:sleep(100), 808 {links,[NPid]} = process_info(Pid,links), 809 NPidStr = pid_to_list(NPid), 810 Pid ! die, 811 Report = 812 receive 813 {report,R} -> 814 R 815 after 5000 -> 816 ct:fail(no_report_received) 817 end, 818 819 Str1 = flatten_report_cb(Report,#{}), 820 L1 = length(Str1), 821 Expected1 = " crasher:\n initial call: proc_lib_SUITE:sp2/0\n", 822 ct:log("Str1: ~p",[Str1]), 823 ct:log("length(Str1): ~p",[L1]), 824 true = lists:prefix(Expected1,Str1), 825 826 FormatOpts1 = #{}, 827 Str1 = flatten_report_cb(Report,FormatOpts1), 828 L1 = length(Str1), 829 Expected1 = " crasher:\n initial call: proc_lib_SUITE:sp2/0\n", 830 ct:log("Str1: ~p",[Str1]), 831 ct:log("length(Str1): ~p",[L1]), 832 true = lists:prefix(Expected1,Str1), 833 834 Depth = 10, 835 FormatOpts2 = #{depth=>Depth}, 836 Str2 = flatten_report_cb(Report,FormatOpts2), 837 L2 = length(Str2), 838 Expected2 = " crasher:\n initial call: proc_lib_SUITE:sp2/0\n", 839 ct:log("Str2: ~p",[Str2]), 840 ct:log("length(Str2): ~p",[L2]), 841 true = lists:prefix(Expected2,Str2), 842 true = L2<L1, 843 844 FormatOpts3 = #{chars_limit=>500}, 845 Str3 = flatten_report_cb(Report,FormatOpts3), 846 L3 = length(Str3), 847 Expected3 = " crasher:\n initial call: proc_lib_SUITE:sp2/0\n", 848 ct:log("Str3: ~p",[Str3]), 849 ct:log("length(Str3): ~p",[L3]), 850 true = lists:prefix(Expected3,Str3), 851 true = L3<L1, 852 853 FormatOpts4 = #{single_line=>true}, 854 Str4 = flatten_report_cb(Report,FormatOpts4), 855 L4 = length(Str4), 856 Expected4 = "crasher: initial call: proc_lib_SUITE:sp2/0,", 857 ct:log("Str4: ~p",[Str4]), 858 ct:log("length(Str4): ~p",[L4]), 859 true = lists:prefix(Expected4,Str4), 860 true = L4<L1, 861 862 FormatOpts5 = #{single_line=>true, depth=>Depth}, 863 Str5 = flatten_report_cb(Report,FormatOpts5), 864 L5 = length(Str5), 865 Expected5 = "crasher: initial call: proc_lib_SUITE:sp2/0,", 866 ct:log("Str5: ~p",[Str5]), 867 ct:log("length(Str5): ~p",[L5]), 868 true = lists:prefix(Expected5,Str5), 869 true = L5<L4, 870 %% Check that neighbour information is printed 871 SplitFun = fun($;) -> false; (_) -> true end, 872 ExpectedNeighbours5 = "; neighbours: neighbour: pid: "++NPidStr++ 873 ", registered_name: []", 874 true = lists:prefix(ExpectedNeighbours5,lists:dropwhile(SplitFun, Str5)), 875 876 FormatOpts6 = #{single_line=>true, chars_limit=>500}, 877 Str6 = flatten_report_cb(Report,FormatOpts6), 878 L6 = length(Str6), 879 Expected6 = "crasher: initial call: proc_lib_SUITE:sp2/0,", 880 ct:log("Str6: ~p",[Str6]), 881 ct:log("length(Str6): ~p",[L6]), 882 true = lists:prefix(Expected6,Str6), 883 true = L6<L4, 884 %% Check that only pid is printed for neighbour, due to chars_limit 885 ExpectedNeighbours6 = "; neighbours: ["++NPidStr++"]", 886 ExpectedNeighbours6 = lists:dropwhile(SplitFun, Str6), 887 888 ok = logger:remove_handler(?MODULE), 889 ok. 890 891report_cb_chars_limit(_Config) -> 892 %% This test does not really test anything, it just formats the 893 %% crash reports with different settings and prints the result. It 894 %% could be used as an example if report_cb was to be modified 895 %% for better utilization of the available number of characters 896 %% according to the chars_limit setting. 897 %% 898 %% Currently, multi-line formatting with chars_limit=1024 gives 899 %% a final report of 1696 character. The excess is due to the fact 900 %% that io_lib_pretty counts non-white characters--the indentation 901 %% of the formatted exception is not counted. 902 %% 903 %% Single-line formatting with chars_limit=1024 gives a final 904 %% report of 1104 characters. 905 %% 906 %% Single-line formatting a fake report with chars_limit=1024 gives 907 %% a final report of 1024 characters. 908 909 ok = logger:add_handler(?MODULE,?MODULE,#{config=>self()}), 910 Pid = proc_lib:spawn(?MODULE, rcb_tester, []), 911 ct:sleep(500), 912 Pid ! die, 913 Report = 914 receive 915 {report,R} -> 916 R 917 after 5000 -> 918 ct:fail(no_report_received) 919 end, 920 921 ct:sleep(500), % To separate debug calls to erlang:display(), if any. 922 Str1 = flatten_report_cb(Report,#{}), 923 L1 = length(Str1), 924 ct:log("Multi-line, no size limit:~n~s",[Str1]), 925 ct:log("Length, multi-line, no size limit: ~p",[L1]), 926 927 ct:sleep(500), 928 FormatOpts2 = #{chars_limit=>1024}, 929 Str2 = flatten_report_cb(Report,FormatOpts2), 930 L2 = length(Str2), 931 ct:log("Multi-line, chars_limit=1024:~n~s",[Str2]), 932 ct:log("Length, multi-line, chars_limit=1024: ~p",[L2]), 933 934 ct:sleep(500), 935 FormatOpts3 = #{single_line=>true, chars_limit=>1024}, 936 Str3 = flatten_report_cb(Report,FormatOpts3), 937 L3 = length(Str3), 938 ct:log("Single-line, chars_limit=1024:~n~s",[Str3]), 939 ct:log("Length, single-line, chars_limit=1024: ~p",[L3]), 940 941 ct:sleep(500), 942 Seq = lists:seq(1, 1000), 943 FakeReport = [[{fake_tag,Seq}],Seq], 944 FReport = #{label=>{proc_lib,crash}, report=>FakeReport}, 945 Str4 = flatten_report_cb(FReport,FormatOpts3), 946 L4 = length(Str4), 947 ct:log("Fake: Single-line, chars_limit=1024:~n~s",[Str4]), 948 ct:log("Fake: Length, single-line, chars_limit=1024: ~p",[L4]), 949 950 ok = logger:remove_handler(?MODULE), 951 ok. 952 953rcb_tester() -> 954 L = lists:seq(1,255), 955 Term = [{some_data,#{pids=>processes(), 956 info=>process_info(self())}}, 957 {tabs,lists:sort(ets:all())}, 958 {bin,list_to_binary(L)}, 959 {list,L}], 960 961 %% Put something in process dictionary 962 [put(K,V) ||{K,V} <- Term], 963 964 %% Add some messages 965 [self() ! {some_message,T} || T <- Term], 966 967 %% Create some neighbours 968 [_ = proc_lib:spawn_link(?MODULE,sp1,[]) || _ <- lists:seq(1,5)], 969 970 receive 971 die -> error({badmatch,Term}) 972 end. 973 974flatten_report_cb(Report, Format) -> 975 lists:flatten(proc_lib:report_cb(Report, Format)). 976 977%%----------------------------------------------------------------- 978%% The error_logger handler used. 979%%----------------------------------------------------------------- 980init(Tester) -> 981 {ok, Tester}. 982 983handle_event({error_report, _GL, {Pid, crash_report, Report}}, Tester) -> 984 io:format("~ts\n", [proc_lib:format(Report)]), 985 Tester ! {crash_report, Pid, Report}, 986 {ok, Tester}; 987handle_event(_Event, State) -> 988 {ok, State}. 989 990handle_info(_, State) -> 991 {ok, State}. 992 993handle_call(_Query, State) -> {ok, {error, bad_query}, State}. 994 995terminate(_Reason, State) -> 996 State. 997 998%%----------------------------------------------------------------- 999%% The Logger handler used. 1000%%----------------------------------------------------------------- 1001log(#{msg:={report,Report}},#{config:=Pid}) -> 1002 Pid ! {report,Report}; 1003log(_,_) -> 1004 ok. 1005