View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2015-2020, VU University Amsterdam
    7			      CWI, Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(swish_debug,
   37	  [ pengine_stale_module/1,	% -Module
   38	    pengine_stale_module/2,	% -Module, -State
   39	    stale_pengine/1,		% -Pengine
   40	    swish_statistics/1,		% -Statistics
   41	    start_swish_stat_collector/0,
   42	    swish_stats/2,		% ?Period, ?Dicts
   43	    swish_save_stats/1,		% ?File
   44	    swish_died_thread/2		% ?Thread, ?State
   45	  ]).   46:- use_module(library(pengines)).   47:- use_module(library(broadcast)).   48:- use_module(library(lists)).   49:- use_module(library(apply)).   50:- use_module(library(debug)).   51:- use_module(library(aggregate)).   52:- use_module(library(settings)).   53:- use_module(procps).   54:- use_module(highlight).   55:- if(exists_source(library(mallocinfo))).   56:- use_module(library(mallocinfo)).   57:- export(malloc_info/1).   58:- endif.   59
   60:- setting(stats_file, callable, data('stats.db'),
   61	   "Save statistics to achieve a long term view").   62:- setting(stats_interval, integer, 300,	% 5 minutes
   63	   "Save stats every N seconds").
 stale_pengine(-Pengine) is nondet
True if Pengine is a Pengine who's thread died.
   69stale_pengine(Pengine) :-
   70	pengine_property(Pengine, thread(Thread)),
   71	\+ catch(thread_property(Thread, status(running)), _, fail).
 pengine_stale_module(-M) is nondet
 pengine_stale_module(-M, -State) is nondet
True if M seems to be a pengine module with no associated pengine. State is a dict that describes what we know about the module.
   81pengine_stale_module(M) :-
   82	current_module(M),
   83	is_uuid(M),
   84	\+ live_module(M),
   85	\+ current_highlight_state(M, _).
   86
   87pengine_stale_module(M, State) :-
   88	pengine_stale_module(M),
   89	stale_module_state(M, State).
   90
   91live_module(M) :-
   92	pengine_property(Pengine, module(M)),
   93	pengine_property(Pengine, thread(Thread)),
   94	catch(thread_property(Thread, status(running)), _, fail).
   95
   96stale_module_state(M, State) :-
   97	findall(N-V, stale_module_property(M, N, V), Properties),
   98	dict_create(State, stale, Properties).
   99
  100stale_module_property(M, pengine, Pengine) :-
  101	pengine_property(Pengine, module(M)).
  102stale_module_property(M, pengine_queue, Queue) :-
  103	pengine_property(Pengine, module(M)),
  104	member(G, [pengines:pengine_queue(Pengine, Queue, _TimeOut, _Time)]),
  105	call(G).		% fool ClioPatria cpack xref
  106stale_module_property(M, pengine_pending_queue, Queue) :-
  107	pengine_property(Pengine, module(M)),
  108	member(G, [pengines:output_queue(Pengine, Queue, _Time)]),
  109	call(G).		% fool ClioPatria cpack xref
  110stale_module_property(M, thread, Thread) :-
  111	pengine_property(Pengine, module(M)),
  112	member(G, [pengines:pengine_property(Pengine, thread(Thread))]),
  113	call(G).		% fool ClioPatria cpack xref
  114stale_module_property(M, thread_status, Status) :-
  115	pengine_property(Pengine, module(M)),
  116	pengine_property(Pengine, thread(Thread)),
  117	catch(thread_property(Thread, status(Status)), _, fail).
  118stale_module_property(M, module_class, Class) :-
  119	module_property(M, class(Class)).
  120stale_module_property(M, program_space, Space) :-
  121	module_property(M, program_space(Space)).
  122stale_module_property(M, program_size, Size) :-
  123	module_property(M, program_size(Size)).
  124stale_module_property(M, predicates, List) :-
  125	current_module(M),
  126	findall(PI, pi_in_module(M, PI), List).
  127stale_module_property(UUID, highlight_state, State) :-
  128	current_highlight_state(UUID, State).
  129
  130pi_in_module(M, Name/Arity) :-
  131	'$c_current_predicate'(_, M:Head),
  132	functor(Head, Name, Arity).
 swish_statistics(?State)
True if State is a statistics about SWISH
  138swish_statistics(highlight_states(Count)) :-
  139	aggregate_all(count, current_highlight_state(_,_), Count).
  140swish_statistics(pengines(Count)) :-
  141	aggregate_all(count, pengine_property(_,thread(_)), Count).
  142swish_statistics(remote_pengines(Count)) :-
  143	aggregate_all(count, pengine_property(_,remote(_)), Count).
  144swish_statistics(pengines_created(Count)) :-
  145	(   flag(pengines_created, Old, Old)
  146	->  Count = Old
  147	;   Count = 0
  148	).
  149
  150:- listen(pengine(Action), swish_update_stats(Action)).  151
  152swish_update_stats(create(_Pengine, _Application, _Options0)) :-
  153	flag(pengines_created, Old, Old+1).
  154swish_update_stats(send(_Pengine, _Event)).
 is_uuid(@UUID)
True if UUID looks like a UUID
  161is_uuid(M) :-
  162	atom(M),
  163	atom_length(M, 36),
  164	forall(sub_atom(M, S, 1, _, C),
  165	       uuid_code(S, C)).
  166
  167uuid_sep(8).
  168uuid_sep(13).
  169uuid_sep(18).
  170uuid_sep(23).
  171
  172uuid_code(S, -) :- !, uuid_sep(S).
  173uuid_code(_, X) :- char_type(X, xdigit(_)).
  174
  175		 /*******************************
  176		 *	     STATISTICS		*
  177		 *******************************/
  178
  179:- if(current_predicate(http_unix_daemon:http_daemon/0)).  180:- use_module(library(broadcast)).  181:- listen(http(post_server_start), start_swish_stat_collector).  182:- else.  183:- initialization
  184	start_swish_stat_collector.  185:- endif.
 start_swish_stat_collector
Start collecting statistical performance information for the running SWISH server.
  192start_swish_stat_collector :-
  193	thread_property(_, alias(swish_stats)), !.
  194start_swish_stat_collector :-
  195	persistent_stats(Persists),
  196	swish_stat_collector(
  197	    swish_stats,
  198			% Time collected |  Ticks  | Push
  199	    [ 60,	%	1 min	 |  1 sec  |  1 min
  200	      60/10,	%       1 hr     |  1 min  | 10 min
  201	      24*6/6,	%       1 day    | 10 min  |  1 hr
  202	      7*24/24,	%       1 week   |  1 hr   |  1 day
  203	      52	%       1 yr     |  1 day
  204	    ],
  205	    1,
  206	    Persists),
  207	at_halt(swish_save_stats(_)).
  208
  209swish_stat_collector(Name, Dims, Interval, Persists) :-
  210	atom(Name), !,
  211	thread_create(stat_collect(Dims, Interval, Persists), _, [alias(Name)]).
  212swish_stat_collector(Thread, Dims, Interval, Persists) :-
  213	thread_create(stat_collect(Dims, Interval, Persists), Thread, []).
  214
  215persistent_stats(save(Path, Interval)) :-
  216	setting(stats_interval, Interval),
  217	Interval > 0,
  218	setting(stats_file, File),
  219	(   absolute_file_name(File, Path,
  220			       [ access(write),
  221				 file_errors(fail)
  222			       ])
  223	->  true
  224	;   File =.. [Alias,_],
  225	    DirSpec =.. [Alias, '.'],
  226	    absolute_file_name(DirSpec, Dir,
  227			   [ solutions(all)
  228			   ]),
  229	    \+ exists_directory(Dir),
  230	    catch(make_directory(Dir),
  231		  error(permission_error(create, directory, Dir), _),
  232		  fail),
  233	    absolute_file_name(File, Path,
  234			       [ access(write),
  235				 file_errors(fail)
  236			       ])
  237	), !.
  238persistent_stats(save(-, 0)).
 swish_stats(?Period, ?Stats:list(dict)) is nondet
Get the collected statistics for the given Period. Period is one of minute, hour, day, week or year. Stats is a list of statistics structures, last one first. The minute period contains 60 second measurements, the hour 60 minutes, the day 24 hours, etc. Each dict constains the following keys:
cpu
Total process CPU time
d_cpu
Differential CPU (is avg CPU per second)
pengines
Number of running pengines
pengines_created
Total number of pengines created
d_pengines_created
Pengines created per second
rss
Total resident memory
stack
Memory in all Prolog stacks.
  265swish_stats(Name, Stats) :-
  266	stats_ring(Name, Ring),
  267	swish_stats(swish_stats, Ring, Stats).
  268
  269stats_ring(minute, 1).
  270stats_ring(hour,   2).
  271stats_ring(day,	   3).
  272stats_ring(week,   4).
  273stats_ring(year,   5).
  274
  275swish_stats(Name, Ring, Stats) :-
  276	thread_self(Me),
  277	catch(thread_send_message(Name, Me-get_stats(Ring)), E,
  278	      stats_died(Name, E)),
  279	thread_get_message(get_stats(Ring, Stats)).
  280
  281stats_died(Alias, E) :-
  282	print_message(error, E),
  283	thread_join(Alias, Status),
  284	print_message(error, swish_stats(died, Status)),
  285	start_swish_stat_collector,
  286	fail.
  287
  288stat_collect(Dims, Interval, Persists) :-
  289	restart_sliding_stats(Persists, Dims, SlidingStat),
  290	get_time(Now),
  291	ITime is floor(Now),
  292	stat_loop(SlidingStat, _{}, ITime, Interval, Persists, [true]).
  293
  294stat_loop(SlidingStat, Stat0, StatTime, Interval, Persists, Wrap) :-
  295	(   thread_self(Me),
  296	    thread_get_message(Me, Request,
  297			       [ deadline(StatTime)
  298			       ])
  299	->  (   reply_stats_request(Request, SlidingStat)
  300	    ->	true
  301	    ;	debug(swish_stats, 'Failed to process ~p', [Request])
  302	    ),
  303	    stat_loop(SlidingStat, Stat0, StatTime, Interval, Persists, Wrap)
  304	;   get_stats(Wrap, Stat1),
  305	    dif_stat(Stat1, Stat0, Stat),
  306	    push_sliding_stats(SlidingStat, Stat, Wrap1),
  307	    NextTime is StatTime+Interval,
  308	    save_stats(Persists, SlidingStat),
  309	    stat_loop(SlidingStat, Stat1, NextTime, Interval, Persists, Wrap1)
  310	).
  311
  312dif_stat(Stat1, Stat0, Stat) :-
  313	maplist(dif_field(Stat1, Stat0),
  314		[ cpu - d_cpu,
  315		  pengines_created - d_pengines_created
  316		],
  317		Fields), !,
  318	dict_pairs(Extra, _, Fields),
  319	put_dict(Extra, Stat1, Stat).
  320dif_stat(Stat, _, Stat).
  321
  322dif_field(Stat1, Stat0, Key-DKey, DKey-DValue) :-
  323	DValue is Stat1.get(Key) - Stat0.get(Key).
  324
  325reply_stats_request(Client-get_stats(Period), SlidingStat) :- !,
  326	arg(Period, SlidingStat, Ring),
  327	ring_values(Ring, Values),
  328	thread_send_message(Client, get_stats(Period, Values)).
  329reply_stats_request(Client-save_stats(File), SlidingStat) :- !,
  330	(   var(File)
  331	->  persistent_stats(save(File, _Interval))
  332	;   true
  333	),
  334	catch(save_stats_file(File, SlidingStat), E, true),
  335	(   var(E)
  336	->  thread_send_message(Client, save_stats(File))
  337	;   thread_send_message(Client, save_stats(error(E)))
  338	).
 get_stats(+Wrap, -Stats:dict) is det
Request elementary statistics.
  345get_stats(Wrap, Stats) :-
  346	Stats0 = stats{ cpu:CPU,
  347			rss:RSS,
  348			stack:Stack,
  349			pengines:Pengines,
  350			threads:Threads,
  351			pengines_created:PenginesCreated,
  352			time:Time
  353		      },
  354	get_time(Now),
  355	Time is floor(Now),
  356	statistics(process_cputime, PCPU),
  357	statistics(cputime, MyCPU),
  358	CPU is PCPU-MyCPU,
  359	statistics(stack, Stack),
  360	statistics(threads, Threads),
  361	catch(procps_stat(Stat), _,
  362	      Stat = stat{rss:0}),
  363	RSS = Stat.rss,
  364	swish_statistics(pengines(Pengines)),
  365	swish_statistics(pengines_created(PenginesCreated)),
  366	add_fordblks(Wrap, Stats0, Stats1),
  367	add_heap(Stats1, Stats2),
  368	add_visitors(Stats2, Stats).
  369
  370:- if(current_predicate(malloc_property/1)).  371add_heap(Stats0, Stats) :-
  372	malloc_property('generic.current_allocated_bytes'(Heap)),
  373	Stats = Stats0.put(heep, Heap).
  374:- else.  375add_heap(Stats, Stats).
  376:- endif.  377
  378:- if(current_predicate(malloc_property/1)).  379
  380add_fordblks(_, Stats0, Stats) :-
  381	malloc_property('generic.current_allocated_bytes'(Used)),
  382	malloc_property('generic.heap_size'(Heap)),
  383        !,
  384	FordBlks is Heap - Used,
  385	Stats = Stats0.put(fordblks, FordBlks).
  386
  387:- elif(current_predicate(mallinfo/1)).  388:- dynamic fordblks_wrap/1.  389fordblks_wrap(0).
  390
  391add_wrap(0) :- !.
  392add_wrap(Amount) :-
  393	retract(fordblks_wrap(Wrap0)),
  394	Wrap1 is Wrap0+Amount,
  395	asserta(fordblks_wrap(Wrap1)).
  396
  397fix_fordblks_wrap(FordBlks0, FordBlks) :-
  398	fordblks_wrap(Wrap),
  399	FordBlks1 is FordBlks0+Wrap,
  400	(   nb_current(fordblks, Prev)
  401	->  NW is FordBlks0 mod (1<<32),
  402	    PW is Prev mod (1<<32),
  403	    (   PW > (1<<32)-(1<<30),
  404		NW < (1<<30)
  405	    ->  Add is 1<<32
  406	    ;   NW > (1<<32)-(1<<30),
  407		PW < (1<<30)
  408	    ->  Add is -(1<<32)
  409	    ;   Add = 0
  410	    ),
  411	    add_wrap(Add),
  412	    FordBlks = FordBlks1+Add
  413	;   FordBlks = FordBlks1
  414	).
  415
  416add_fordblks(Wrap, Stats0, Stats) :-
  417	(   Wrap = [true|_]
  418	->  member(G, [mallinfo(MallInfo)]),
  419	    call(G),			% fool ClioPatria xref
  420	    FordBlks0 = MallInfo.get(fordblks),
  421	    fix_fordblks_wrap(FordBlks0, FordBlks),
  422	    b_setval(fordblks, FordBlks)
  423	;   nb_current(fordblks, FordBlks)
  424	), !,
  425	Stats = Stats0.put(fordblks, FordBlks).
  426:- endif.  427add_fordblks(_, Stats, Stats).
  428
  429add_visitors(Stats0, Stats) :-
  430	broadcast_request(swish(visitor_count(C))), !,
  431	Stats = Stats0.put(visitors, C).
  432add_visitors(Stats, Stats).
  433
  434
  435/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  436Maintain sliding statistics. The statistics are maintained in a ring. If
  437the ring wraps around, the average is pushed to the next ring.
  438- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  439
  440new_sliding_stats(Dims, Stats) :-
  441	maplist(new_ring, Dims, Rings),
  442	compound_name_arguments(Stats, sliding_stats, Rings).
  443
  444push_sliding_stats(Stats, Values, Wrap) :-
  445	push_sliding_stats(1, Stats, Values, Wrap).
  446
  447push_sliding_stats(I, Stats, Values, [Wrap|WrapT]) :-
  448	arg(I, Stats, Ring),
  449	push_ring(Ring, Values, Wrap),
  450	(   Wrap == true
  451	->  average_ring(Ring, Avg),
  452	    I2 is I+1,
  453	    (	push_sliding_stats(I2, Stats, Avg, WrapT)
  454	    ->	true
  455	    ;	true
  456	    )
  457	;   WrapT = []
  458	).
  459
  460new_ring(Dim0/Avg, ring(0, Avg, Ring)) :- !,
  461	Dim is Dim0,
  462	compound_name_arity(Ring, [], Dim).
  463new_ring(Dim0, ring(0, Dim, Ring)) :-
  464	Dim is Dim0,
  465	compound_name_arity(Ring, [], Dim).
  466
  467push_ring(Ring, Value, Wrap) :-
  468	Ring = ring(Here0, Avg, Data),
  469	Here is Here0+1,
  470	compound_name_arity(Data, _, Size),
  471	Arg is (Here0 mod Size)+1,
  472	(   Arg mod Avg =:= 0
  473	->  Wrap = true
  474	;   Wrap = false
  475	),
  476	nb_setarg(Arg, Data, Value),
  477	nb_setarg(1, Ring, Here).
  478
  479ring_values(Ring, Values) :-
  480	Ring = ring(Here, _, Data),
  481	compound_name_arity(Data, _, Size),
  482	Start is Here - 1,
  483	End is Start - min(Here,Size),
  484	read_ring(Start, End, Size, Data, Values).
  485
  486read_ring(End, End, _, _, []) :- !.
  487read_ring(Here0, End, Size, Data, [H|T]) :-
  488	A is (Here0 mod Size)+1,
  489	arg(A, Data, H),
  490	Here1 is Here0-1,
  491	read_ring(Here1, End, Size, Data, T).
  492
  493average_ring(ring(Here0,AvgI,Data), Avg) :-
  494	compound_name_arity(Data, _, Dim),
  495	Here is ((Here0-1) mod Dim)+1,
  496	Start0 is Here - AvgI + 1,
  497	(   Start0 < 1
  498	->  Start is Start0+Dim
  499        ;   Start is Start0
  500	),
  501	avg_window(Start, Here, Dim, Data, Dicts),
  502	average_dicts(Dicts, Avg).
  503
  504avg_window(End, End, _, Data, [Dict]) :- !,
  505	arg(End, Data, Dict).
  506avg_window(Here, End, DIM, Data, [H|T]) :-
  507	arg(Here, Data, H),
  508	Here1 is Here+1,
  509	(   Here1 > DIM
  510	->  Here2 is Here1-DIM
  511	;   Here2 is Here1
  512	),
  513	avg_window(Here2, End, DIM, Data, T).
  514
  515average_dicts(Dicts, Avg) :-
  516	dicts_to_same_keys(Dicts, dict_fill(0), Dicts1),
  517	Dicts1 = [H|_],
  518	is_dict(H, Tag),
  519	dict_keys(H, Keys),
  520	length(Dicts1, Len),
  521	maplist(avg_key(Dicts1, Len), Keys, Pairs),
  522	dict_pairs(Avg, Tag, Pairs).
  523
  524avg_key(Dicts, Len, Key, Key-Avg) :-
  525	maplist(get_dict(Key), Dicts, Values),
  526	sum_list(Values, Sum),
  527	Avg is Sum/Len.
 save_stats(+StaveSpec, +Stats) is det
Save the statistics on each interval.
  533save_stats(save(File, Interval), Stats) :-
  534	arg(1, Stats, ring(Here, _, _)),
  535	Here mod Interval =:= 0,
  536	E = error(_,_),
  537	catch(save_stats_file(File, Stats),
  538	      E, print_message(warning, E)),
  539	!.
  540save_stats(_, _).
  541
  542save_stats_file(File, Stats) :-
  543	setup_call_cleanup(
  544	    open(File, write, Out),
  545	    save_stats_stream(Stats, Out),
  546	    close(Out)).
  547
  548save_stats_stream(Stats, Out) :-
  549	get_time(Now),
  550	\+ \+ ( numbervars(Stats, 0, _, [singletons(true)]),
  551		format(Out, 'stats(~1f, ~q).~n', [Now, Stats])
  552	      ).
  553
  554restart_sliding_stats(save(File, _), Dims, Stats) :-
  555	exists_file(File),
  556	E = error(_,_),
  557	catch(setup_call_cleanup(
  558		  open(File, read, In),
  559		  read(In, stats(_Saved, Stats)),
  560		  close(In)),
  561	      E, (print_message(warning, E), fail)),
  562	new_sliding_stats(Dims, New),
  563	compatible_sliding_stats(Stats, New),
  564	!.
  565restart_sliding_stats(_, Dims, Stats) :-
  566	new_sliding_stats(Dims, Stats).
  567
  568compatible_sliding_stats(Stats1, Stats2) :-
  569	compound_name_arguments(Stats1, Name, List1),
  570	compound_name_arguments(Stats2, Name, List2),
  571	maplist(compatible_window, List1, List2).
  572
  573compatible_window(ring(_,Avg,Data1), ring(_,Avg,Data2)) :-
  574	compound_name_arity(Data1, Name, Dim),
  575	compound_name_arity(Data2, Name, Dim).
 swish_save_stats(?File)
Save statistcs to File or the default file.
  581swish_save_stats(File) :-
  582	thread_self(Me),
  583	catch(thread_send_message(swish_stats, Me-save_stats(File)), E,
  584	      stats_died(swish_stats, E)),
  585	thread_get_message(save_stats(Result)),
  586	(   Result = error(E)
  587	->  throw(E)
  588	;   File = Result
  589	).
 swish_died_thread(TID, Status) is nondet
True if Id is a thread that died with Status and has not (yet) been joined. Note that such threads may exist for a short while.
  597swish_died_thread(TID, Status) :-
  598	findall(TID-Stat, (thread_property(Thread, status(Stat)),
  599			   Stat \== running,
  600			   thread_property(Thread, id(TID))), Pairs),
  601	member(TID-Stat, Pairs),
  602	status_message(Stat, Status).
  603
  604status_message(exception(Ex), Message) :- !,
  605	message_to_string(Ex, Message0),
  606	string_concat('ERROR: ', Message0, Message).
  607status_message(Status, Status).
  608
  609
  610		 /*******************************
  611		 *	     SANDBOX		*
  612		 *******************************/
  613
  614:- multifile
  615	sandbox:safe_primitive/1.  616
  617sandbox:safe_primitive(swish_debug:pengine_stale_module(_)).
  618sandbox:safe_primitive(swish_debug:pengine_stale_module(_,_)).
  619sandbox:safe_primitive(swish_debug:stale_pengine(_)).
  620sandbox:safe_primitive(swish_debug:swish_statistics(_)).
  621sandbox:safe_primitive(swish_debug:swish_stats(_, _)).
  622sandbox:safe_primitive(swish_debug:swish_died_thread(_, _)).
  623:- if(current_predicate(malloc_info:malloc_info/1)).  624sandbox:safe_primitive(malloc_info:malloc_info(_)).
  625:- endif.