View source with formatted comments or as raw
    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(swish_debug,
   39          [ swish_debug/3,              % +Topic, +Format, :Args
   40            debug/1,                    % +Topic
   41            nodebug/1,                  % +Topic
   42            swish_debugging/1,          % ?Topic
   43            list_debug_topics/0,
   44            list_debug_topics/1,        % +Options
   45
   46            swish_debug_sentinel/0
   47          ]).   48:- autoload(library(option), [option/3, option/2]).   49:- autoload(library(pengines), [pengine_self/1, pengine_output/1]).   50:- autoload(library(dcg/high_order), [sequence/5]).   51:- autoload(library(pengines_io), [pengine_format/2]).   52:- autoload(library(http/html_write), [html/3, print_html/1]).   53
   54
   55:- meta_predicate
   56    debug(+,+,:).   57
   58:- thread_local
   59    debugging/2.                    % Topic, Enabled
   60:- dynamic
   61    shared_debug_topic/1.   62
   63/** <module> Print debug messages and test assertions
   64
   65This library is a SWISH  specific   replacement  for library(debug) that
   66allows for debug/3 messages in SWISH code   as  well as libraries loaded
   67into SWISH. Unlike library(debug),  this   library  maintains  the debug
   68state per thread (Pengine).
   69
   70This library allows for debug/3  calls   inside  user programs stored in
   71SWISH as well as libraries preloaded into  SWISH. Libraries that wish to
   72enable debugging by SWISH  users  must   include  this  file rather than
   73library(debug).  This  may  be  done  dynamically  using  the  following
   74snippet.
   75
   76```
   77:- if(exists_source(swish(lib/swish_debug))).
   78:- use_module(swish(lib/swish_debug)).
   79:- else.
   80:- use_module(library(debug)).
   81:- endif.
   82```
   83*/
   84
   85%!  swish_debugging(+Topic) is semidet.
   86%!  swish_debugging(-Topic) is nondet.
   87%
   88%   Examine debug topics. The form debugging(+Topic)  may be used to
   89%   perform more complex debugging tasks.   A typical usage skeleton
   90%   is:
   91%
   92%     ```
   93%           (   debugging(mytopic)
   94%           ->  <perform debugging actions>
   95%           ;   true
   96%           ),
   97%           ...
   98%     ```
   99%
  100%   The other two calls are intended to examine existing and enabled
  101%   debugging tokens and are typically not used in user programs.
  102
  103swish_debugging(Topic) :-
  104    debugging(Topic, true).
  105
  106%!  debug(+Topic) is det.
  107%!  nodebug(+Topic) is det.
  108%
  109%   Add/remove a topic  from  being   printed.  nodebug(_)  removes  all
  110%   topics. Gives a warning if the  topic   is  not defined unless it is
  111%   used from a directive. The latter allows placing debug topics at the
  112%   start of a (load-)file without warnings.
  113%
  114%   For debug/1, Topic can be  a  term   `Topic  >  Out`, where `Out` is
  115%   either a stream or  stream-alias  or   a  filename  (an  atom). This
  116%   redirects debug information on this topic   to  the given output. On
  117%   Linux systems redirection can be used   to  make the message appear,
  118%   even if the `user_error` stream is redefined using
  119%
  120%       ?- debug(Topic > '/proc/self/fd/2').
  121%
  122%   A platform independent way to  get   debug  messages  in the current
  123%   console (for example, a `swipl-win` window,  or login using `ssh` to
  124%   Prolog running an SSH server from the `libssh` pack) is to use:
  125%
  126%       ?- stream_property(S, alias(user_error)),
  127%          debug(Topic > S).
  128%
  129%   Do not forget to  disable  the   debugging  using  nodebug/1  before
  130%   quitting the console if Prolog must remain running.
  131
  132debug(Topic) :-
  133    debug(Topic, true).
  134nodebug(Topic) :-
  135    debug(Topic, false).
  136
  137debug(Topic, Enabled) :-
  138    (   retract(debugging(Topic, _))
  139    ->  true
  140    ;   shared_debug_topic(Topic)
  141    ->  true
  142    ;   print_message(warning, debug_no_topic(Topic))
  143    ),
  144    assert(debugging(Topic, Enabled)).
  145
  146%!  debug_topic(+Topic) is det.
  147%
  148%   Declare a topic for debugging.  This can be used to find all
  149%   topics available for debugging.
  150
  151debug_topic(Topic) :-
  152    pengine_self(_),
  153    !,
  154    (   debugging(Registered, _),
  155        Registered =@= Topic
  156    ->  true
  157    ;   assertz(debugging(Topic, false))
  158    ).
  159debug_topic(Topic) :-
  160    (   shared_debug_topic(Registered),
  161        Registered =@= Topic
  162    ->  true
  163    ;   assertz(shared_debug_topic(Topic))
  164    ).
  165
  166%!  list_debug_topics is det.
  167%!  list_debug_topics(+Options) is det.
  168%
  169%   List currently known topics for debug/3   and their setting. Options
  170%   is  either  an  atom  or   string,    which   is   a  shorthand  for
  171%   `[search(String)]` or a normal option list. Defined options are:
  172%
  173%     - search(String)
  174%       Only show topics that match String.  Match is case insensitive
  175%       on the printed representation of the term.
  176%     - active(+Boolean)
  177%       Only print topics that are active (`true`) or inactive
  178%       (`false`).
  179%     - output(+To)
  180%       Only print topics whose target location matches To.  This option
  181%       implicitly restricts the output to active topics.
  182
  183list_debug_topics :-
  184    list_debug_topics([]).
  185
  186list_debug_topics(Options) :-
  187    (   atom(Options)
  188    ;   string(Options)
  189    ),
  190    !,
  191    list_debug_topics([search(Options)]).
  192list_debug_topics(Options) :-
  193    option(active(Activated), Options, _),
  194    findall(debug_topic(Topic, String, Activated),
  195            matching_topic(Topic, String, Activated, Options),
  196            Triples),
  197    print_message(information, debug_topics(Triples)).
  198
  199matching_topic(Topic, String, Activated, Options) :-
  200    known_debug_topic(Topic, Activated),
  201    topic_to_string(Topic, String),
  202    (   option(search(Search), Options)
  203    ->  sub_atom_icasechk(String, _, Search)
  204    ;   true
  205    ).
  206
  207topic_to_string(Topic, String) :-
  208    numbervars(Topic, 0, _, [singletons(true)]),
  209    term_string(Topic, String, [quoted(true), numbervars(true)]).
  210
  211known_debug_topic(Topic, Value) :-
  212    debugging(Topic, Value).
  213known_debug_topic(Topic, false) :-
  214    shared_debug_topic(Topic),
  215    \+ debugging(Topic, _).
  216
  217
  218:- multifile
  219    prolog_debug_tools:debugging_hook/0.  220
  221prolog_debug_tools:debugging_hook :-
  222    (   debugging(_, true)
  223    ->  list_debug_topics([active(true)])
  224    ).
  225
  226%!  swish_debug(+Topic, +Format, :Args) is det.
  227%
  228%   Format a message if debug topic  is enabled. Similar to format/3
  229%   to =user_error=, but only prints if   Topic is activated through
  230%   debug/1. Args is a  meta-argument  to   deal  with  goal for the
  231%   @-command.   Output   is   first    handed     to    the    hook
  232%   prolog:debug_print_hook/3.  If  this  fails,    Format+Args   is
  233%   translated  to  text   using    the   message-translation   (see
  234%   print_message/2) for the  term  debug(Format,   Args)  and  then
  235%   printed to every matching destination   (controlled  by debug/1)
  236%   using print_message_lines/3.
  237%
  238%   The message is preceded by '% ' and terminated with a newline.
  239%
  240%   @see    format/3.
  241
  242swish_debug(Topic, Format, Args) :-
  243    debugging(Topic, true),
  244    !,
  245    print_debug(Topic, Format, Args).
  246swish_debug(_, _, _).
  247
  248
  249print_debug(_Topic, _Format, _Args) :-
  250    nb_current(swish_debug_printing, true),
  251    !.
  252print_debug(Topic, Format, Args) :-
  253    setup_call_cleanup(
  254        nb_setval(swish_debug_printing, true),
  255        print_debug_guarded(Topic, Format, Args),
  256        nb_delete(swish_debug_printing)).
  257
  258:- html_meta(send_html(html)).  259
  260print_debug_guarded(Topic, Format, Args) :-
  261    topic_to_string(Topic, String),
  262    format(string(Msg0), Format, Args),
  263    split_string(Msg0, "", "\n", [Msg]),
  264    send_html(\debug_msg(Msg, String)).
  265
  266send_html(HTML) :-
  267    phrase(html(HTML), Tokens),
  268    with_output_to(string(HTMlString), print_html(Tokens)),
  269    pengine_output(HTMlString).
  270
  271debug_msg(Msg, Topic) -->
  272    html(div(class('debug-msg'),
  273             [ span([class('topic'), title('Debug topic')], Topic)
  274             | pre([class('msg'), title('Debug message')], Msg)
  275             ])).
  276
  277
  278		 /*******************************
  279		 *           EXPANSION		*
  280		 *******************************/
  281
  282swish_debug_sentinel.
  283
  284imports_this_module :-
  285    prolog_load_context(module, M),
  286    predicate_property(M:swish_debug_sentinel, imported_from(swish_debug)),
  287    !.
  288
  289:- multifile
  290    user:goal_expansion/2.  291
  292user:goal_expansion(debug(Topic, Format, Args),
  293                    swish_debug(Topic, Format, Args)) :-
  294    imports_this_module,
  295    debug_topic(Topic).
  296user:goal_expansion(debugging(Topic),
  297                    swish_debugging(Topic)) :-
  298    imports_this_module,
  299    debug_topic(Topic).
  300
  301
  302                 /*******************************
  303                 *            MESSAGES          *
  304                 *******************************/
  305
  306:- multifile
  307    prolog:message/3.  308
  309prolog:message(debug_topics(List)) -->
  310    [ ansi(bold, '~w~t ~w~35|~n', ['Debug Topic', 'Activated']),
  311      '~`\u2015t~35|'-[], nl
  312    ],
  313    sequence(debug_topic, [nl], List).
  314
  315debug_topic(debug_topic(_Topic, TopicString, true)) -->
  316    [ ansi(bold, '~s~t \u2714~35|', [TopicString]) ].
  317debug_topic(debug_topic(_Topic, TopicString, false)) -->
  318    [ '~s~t -~35|'-[TopicString] ].
  319
  320:- multifile
  321    sandbox:safe_global_variable/1,
  322    sandbox:safe_meta/2.  323
  324sandbox:safe_global_variable(swish_debug_printing).
  325sandbox:safe_meta(swish_debug:print_debug(_Topic, Format, Args), Calls) :-
  326    sandbox:format_calls(Format, Args, Calls)