1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2002-2023, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 SWI-Prolog Solutions b.v. 10 All rights reserved. 11 12 Redistribution and use in source and binary forms, with or without 13 modification, are permitted provided that the following conditions 14 are met: 15 16 1. Redistributions of source code must retain the above copyright 17 notice, this list of conditions and the following disclaimer. 18 19 2. Redistributions in binary form must reproduce the above copyright 20 notice, this list of conditions and the following disclaimer in 21 the documentation and/or other materials provided with the 22 distribution. 23 24 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 25 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 26 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 27 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 28 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 29 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 30 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 31 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 32 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 33 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 34 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 35 POSSIBILITY OF SUCH DAMAGE. 36*/ 37 38:- module(prolog_debug, 39 [ debug/3, % +Topic, +Format, :Args 40 debug/1, % +Topic 41 nodebug/1, % +Topic 42 debugging/1, % ?Topic 43 debugging/2, % ?Topic, ?Bool 44 list_debug_topics/0, 45 list_debug_topics/1, % +Options 46 debug_message_context/1, % (+|-)What 47 48 assertion/1 % :Goal 49 ]). 50:- autoload(library(lists),[append/3,delete/3,selectchk/3,member/2]). 51:- autoload(library(prolog_stack),[backtrace/1]). 52:- autoload(library(option), [option/3, option/2]). 53 54:- set_prolog_flag(generate_debug_info, false). 55 56:- meta_predicate 57 assertion( ), 58 debug( , , ). 59 60:- multifile prolog:assertion_failed/2. 61:- dynamic prolog:assertion_failed/2. 62 63/*:- use_module(library(prolog_stack)).*/ % We use the autoloader if needed 64 65%:- set_prolog_flag(generate_debug_info, false). 66 67:- dynamic 68 debugging/3. % Topic, Enabled, To 69 70/** <module> Print debug messages and test assertions 71 72This library is a replacement for format/3 for printing debug messages. 73Messages are assigned a _topic_. By dynamically enabling or disabling 74topics the user can select desired messages. Calls to debug/3 and 75assertion/1 are removed when the code is compiled for optimization 76unless the Prolog flag `optimise_debug` is set to `true`. 77 78Using the predicate assertion/1 you can make assumptions about your 79program explicit, trapping the debugger if the condition does not hold. 80 81Output and actions by these predicates can be configured using _hooks_ 82to fit your environment. With XPCE, you can use the call below to start 83a graphical monitoring tool. 84 85 ?- prolog_ide(debug_monitor). 86*/ 87 88%! debugging(+Topic) is semidet. 89%! debugging(-Topic) is nondet. 90%! debugging(?Topic, ?Bool) is nondet. 91% 92% Examine debug topics. The form debugging(+Topic) may be used to 93% perform more complex debugging tasks. A typical usage skeleton 94% is: 95% 96% ``` 97% ( debugging(mytopic) 98% -> <perform debugging actions> 99% ; true 100% ), 101% ... 102% ``` 103% 104% The other two calls are intended to examine existing and enabled 105% debugging tokens and are typically not used in user programs. 106 107debugging(Topic) :- 108 debugging(Topic, true, _To). 109 110debugging(Topic, Bool) :- 111 debugging(Topic, Bool, _To). 112 113%! debug(+Topic) is det. 114%! nodebug(+Topic) is det. 115% 116% Add/remove a topic from being printed. nodebug(_) removes all 117% topics. Gives a warning if the topic is not defined unless it is 118% used from a directive. The latter allows placing debug topics at the 119% start of a (load-)file without warnings. 120% 121% For debug/1, Topic can be a term `Topic > Out`, where `Out` is 122% either a stream or stream-alias or a filename (an atom). This 123% redirects debug information on this topic to the given output. On 124% Linux systems redirection can be used to make the message appear, 125% even if the `user_error` stream is redefined using 126% 127% ?- debug(Topic > '/proc/self/fd/2'). 128% 129% A platform independent way to get debug messages in the current 130% console (for example, a `swipl-win` window, or login using `ssh` to 131% Prolog running an SSH server from the `libssh` pack) is to use: 132% 133% ?- stream_property(S, alias(user_error)), 134% debug(Topic > S). 135% 136% Do not forget to disable the debugging using nodebug/1 before 137% quitting the console if Prolog must remain running. 138 139debug(Topic) :- 140 with_mutex(prolog_debug, debug(Topic, true)). 141nodebug(Topic) :- 142 with_mutex(prolog_debug, debug(Topic, false)). 143 144debug(Spec, Val) :- 145 debug_target(Spec, Topic, Out), 146 ( ( retract(debugging(Topic, Enabled0, To0)) 147 *-> update_debug(Enabled0, To0, Val, Out, Enabled, To), 148 assert(debugging(Topic, Enabled, To)), 149 fail 150 ; ( prolog_load_context(file, _) 151 -> true 152 ; print_message(warning, debug_no_topic(Topic)) 153 ), 154 update_debug(false, [], Val, Out, Enabled, To), 155 assert(debugging(Topic, Enabled, To)) 156 ) 157 -> true 158 ; true 159 ). 160 161debug_target(Spec, Topic, To) :- 162 nonvar(Spec), 163 Spec = (Topic > To), 164 !. 165debug_target(Topic, Topic, -). 166 167update_debug(_, To0, true, -, true, To) :- 168 !, 169 ensure_output(To0, To). 170update_debug(true, To0, true, Out, true, Output) :- 171 !, 172 ( memberchk(Out, To0) 173 -> Output = To0 174 ; append(To0, [Out], Output) 175 ). 176update_debug(false, _, true, Out, true, [Out]) :- !. 177update_debug(_, _, false, -, false, []) :- !. 178update_debug(true, [Out], false, Out, false, []) :- !. 179update_debug(true, To0, false, Out, true, Output) :- 180 !, 181 delete(To0, Out, Output). 182 183ensure_output([], [user_error]) :- !. 184ensure_output(List, List). 185 186%! debug_topic(+Topic) is det. 187% 188% Declare a topic for debugging. This can be used to find all 189% topics available for debugging. 190 191debug_topic(Topic) :- 192 ( debugging(Registered, _, _), 193 Registered =@= Topic 194 -> true 195 ; assert(debugging(Topic, false, [])) 196 ). 197 198%! list_debug_topics is det. 199%! list_debug_topics(+Options) is det. 200% 201% List currently known topics for debug/3 and their setting. Options 202% is either an atom or string, which is a shorthand for 203% `[search(String)]` or a normal option list. Defined options are: 204% 205% - search(String) 206% Only show topics that match String. Match is case insensitive 207% on the printed representation of the term. 208% - active(+Boolean) 209% Only print topics that are active (`true`) or inactive 210% (`false`). 211% - output(+To) 212% Only print topics whose target location matches To. This option 213% implicitly restricts the output to active topics. 214 215list_debug_topics :- 216 list_debug_topics([]). 217 218list_debug_topics(Options) :- 219 ( atom(Options) 220 ; string(Options) 221 ), 222 !, 223 list_debug_topics([search(Options)]). 224list_debug_topics(Options) :- 225 print_message(information, debug_topics(header)), 226 option(active(Value), Options, _), 227 ( debugging(Topic, Value, To), 228 ( option(output(Stream), Options) 229 -> memberchk(Stream, To) 230 ; true 231 ), 232 numbervars(Topic, 0, _, [singletons(true)]), 233 term_string(Topic, String, [quoted(true), numbervars(true)]), 234 ( option(search(Search), Options) 235 -> sub_atom_icasechk(String, _, Search) 236 ; true 237 ), 238 print_message(information, debug_topic(Topic, String, Value, To)), 239 fail 240 ; true 241 ). 242 243:- multifile 244 prolog_debug_tools:debugging_hook/0. 245 246prolog_debug_toolsdebugging_hook :- 247 ( debugging(_, true) 248 -> list_debug_topics([active(true)]) 249 ). 250 251 252%! debug_message_context(+What) is det. 253% 254% Specify additional context for debug messages. 255% 256% @deprecated New code should use the Prolog flag `message_context`. 257% This predicates adds or deletes topics from this list. 258 259debug_message_context(+Topic) :- 260 current_prolog_flag(message_context, List), 261 ( memberchk(Topic, List) 262 -> true 263 ; append(List, [Topic], List2), 264 set_prolog_flag(message_context, List2) 265 ). 266debug_message_context(-Topic) :- 267 current_prolog_flag(message_context, List), 268 ( selectchk(Topic, List, Rest) 269 -> set_prolog_flag(message_context, Rest) 270 ; true 271 ). 272 273%! debug(+Topic, +Format, :Args) is det. 274% 275% Format a message if debug topic is enabled. Similar to format/3 276% to =user_error=, but only prints if Topic is activated through 277% debug/1. Args is a meta-argument to deal with goal for the 278% @-command. Output is first handed to the hook 279% prolog:debug_print_hook/3. If this fails, Format+Args is 280% translated to text using the message-translation (see 281% print_message/2) for the term debug(Format, Args) and then 282% printed to every matching destination (controlled by debug/1) 283% using print_message_lines/3. 284% 285% The message is preceded by '% ' and terminated with a newline. 286% 287% @see format/3. 288 289debug(Topic, Format, Args) :- 290 debugging(Topic, true, To), 291 !, 292 print_debug(Topic, To, Format, Args). 293debug(_, _, _). 294 295 296%! prolog:debug_print_hook(+Topic, +Format, +Args) is semidet. 297% 298% Hook called by debug/3. This hook is used by the graphical 299% frontend that can be activated using prolog_ide/1: 300% 301% == 302% ?- prolog_ide(debug_monitor). 303% == 304 305:- multifile 306 prolog:debug_print_hook/3. 307 308print_debug(_Topic, _To, _Format, _Args) :- 309 nb_current(prolog_debug_printing, true), 310 !. 311print_debug(Topic, To, Format, Args) :- 312 setup_call_cleanup( 313 nb_setval(prolog_debug_printing, true), 314 print_debug_guarded(Topic, To, Format, Args), 315 nb_delete(prolog_debug_printing)). 316 317print_debug_guarded(Topic, _To, Format, Args) :- 318 prolog:debug_print_hook(Topic, Format, Args), 319 !. 320print_debug_guarded(_, [], _, _) :- !. 321print_debug_guarded(Topic, To, Format, Args) :- 322 phrase('$messages':translate_message(debug(Format, Args)), Lines), 323 ( member(T, To), 324 debug_output(T, Stream), 325 with_output_to( 326 Stream, 327 print_message_lines(current_output, kind(debug(Topic)), Lines)), 328 fail 329 ; true 330 ). 331 332 333debug_output(user, user_error) :- !. 334debug_output(Stream, Stream) :- 335 is_stream(Stream), 336 !. 337debug_output(File, Stream) :- 338 open(File, append, Stream, 339 [ close_on_abort(false), 340 alias(File), 341 buffer(line) 342 ]). 343 344 345 /******************************* 346 * ASSERTION * 347 *******************************/ 348 349%! assertion(:Goal) is det. 350% 351% Acts similar to C assert() macro. It has no effect if Goal 352% succeeds. If Goal fails or throws an exception, the following 353% steps are taken: 354% 355% * call prolog:assertion_failed/2. If prolog:assertion_failed/2 356% fails, then: 357% 358% - If this is an interactive toplevel thread, print a 359% message, the stack-trace, and finally trap the debugger. 360% - Otherwise, throw error(assertion_error(Reason, G),_) where 361% Reason is one of =fail= or the exception raised. 362 363assertion(G) :- 364 \+ \+ catch(G, 365 Error, 366 assertion_failed(Error, G)), 367 368 !. 369assertion(G) :- 370 assertion_failed(fail, G), 371 assertion_failed. % prevent last call optimization. 372 373assertion_failed(Reason, G) :- 374 prolog:assertion_failed(Reason, G), 375 !. 376assertion_failed(Reason, _) :- 377 assertion_rethrow(Reason), 378 !, 379 throw(Reason). 380assertion_failed(Reason, G) :- 381 print_message(error, assertion_failed(Reason, G)), 382 backtrace(10), 383 ( current_prolog_flag(break_level, _) % interactive thread 384 -> trace 385 ; throw(error(assertion_error(Reason, G), _)) 386 ). 387 388assertion_failed. 389 390assertion_rethrow(time_limit_exceeded). 391assertion_rethrow('$aborted'). 392 393 394 /******************************* 395 * EXPANSION * 396 *******************************/ 397 398% The optimise_debug flag defines whether Prolog optimizes 399% away assertions and debug/3 statements. Values are =true= 400% (debug is optimized away), =false= (debug is retained) and 401% =default= (debug optimization is dependent on the optimise 402% flag). 403 404optimise_debug :- 405 ( current_prolog_flag(optimise_debug, true) 406 -> true 407 ; current_prolog_flag(optimise_debug, default), 408 current_prolog_flag(optimise, true) 409 -> true 410 ). 411 412:- multifile 413 system:goal_expansion/2. 414 415systemgoal_expansion(debug(Topic,_,_), true) :- 416 ( optimise_debug 417 -> true 418 ; debug_topic(Topic), 419 fail 420 ). 421systemgoal_expansion(debugging(Topic), fail) :- 422 ( optimise_debug 423 -> true 424 ; debug_topic(Topic), 425 fail 426 ). 427systemgoal_expansion(assertion(_), true) :- 428 optimise_debug. 429systemgoal_expansion(assume(_), true) :- 430 print_message(informational, 431 compatibility(renamed(assume/1, assertion/1))), 432 optimise_debug. 433 434 435 /******************************* 436 * MESSAGES * 437 *******************************/ 438 439:- multifile 440 prolog:message/3. 441 442prologmessage(assertion_failed(_, G)) --> 443 [ 'Assertion failed: ~q'-[G] ]. 444prologmessage(debug(Fmt, Args)) --> 445 [ Fmt-Args ]. 446prologmessage(debug_no_topic(Topic)) --> 447 [ '~q: no matching debug topic (yet)'-[Topic] ]. 448prologmessage(debug_topics(header)) --> 449 [ ansi(bold, '~w~t ~w~35| ~w~n', ['Debug Topic', 'Activated', 'To']), 450 '~`\u2015t~48|' 451 ]. 452prologmessage(debug_topic(_, TopicString, true, [user_error])) --> 453 [ ansi(bold, '~s~t \u2714~35|', [TopicString]) ]. 454prologmessage(debug_topic(_, TopicString, true, To)) --> 455 [ ansi(bold, '~s~t \u2714~35| ~q', [TopicString, To]) ]. 456prologmessage(debug_topic(_, TopicString, false, _To)) --> 457 [ '~s~t -~35|'-[TopicString] ]. 458 459 460 /******************************* 461 * HOOKS * 462 *******************************/ 463 464%! prolog:assertion_failed(+Reason, +Goal) is semidet. 465% 466% This hook is called if the Goal of assertion/1 fails. Reason is 467% unified with either =fail= if Goal simply failed or an exception 468% call otherwise. If this hook fails, the default behaviour is 469% activated. If the hooks throws an exception it will be 470% propagated into the caller of assertion/1. 471 472 473 /******************************* 474 * SANDBOX * 475 *******************************/ 476 477:- multifile sandbox:safe_meta/2. 478 479sandbox:safe_meta(prolog_debug:assertion(X), [X])