1:- module( debug_call, 
    2        [ 
    3            debug_call/2,
    4            debug_call/3,
    5            debug_call/4,
    6            debuc/1, debuc/2, debuc/3, debuc/4,
    7            debug_chain/2, debug_chain/3,
    8            debug_consec/3, debug_consec/4,
    9            debug_message/3,
   10            debug_on/1,
   11            debug_portray/2,
   12            debug_set/2,
   13            debugging_status/2,
   14            debug_topic/2,
   15            debug_topic/3,
   16            debug_call_version/2,
   17            debugging_topic/1
   18       ] ).   19
   20:- multifile(user:message_property/2).   21:- dynamic(debug_call_message_property/2).   22
   23user:message_property( Dbg, Property ) :-
   24    debug_call_message_property( Dbg, Property ).

Debugging with calls.

Avoids running goals to produce output that is only relevant while debugging. Includes pre-canned, often used calls that print informative messages for common debugging tasks.

See the main predicate's documenation, debug_call/4, for more details.
See file examples/exo.pl for a full pallette of examples.

Examples


?- debug(ex).
?- debug_call(ex, length, list1/[x,y,z]).
% Length for list, list1: 3

?- debug_call(ex, length, [list1,list2]/[[x,y,z],[a,b,c]], prefix('Some prefix')).
% Some prefix lengths for lists, list1: 3, list2: 3

?- debug_call(ex, dims, [m1,m2]/[[a(x),a(y),a(z)],[xy(a,b),xy(c,d),xy(e,f)]]).
%  Dimensions for matrices,  (m1) nR: 3, nC: 1. (m2) nR: 3, nC: 2.

?- debug_call(ex, enum, testo/[a,b,c]).
% Starting enumeration of list: testo
% 1.a
% 2.b
% 3.c
% Ended enumeration of list: testo
true.

?- debug_call(ex, enum, testo/[a,b,c,d,e], depth(3)).
% Starting enumeration of list: testo
% 1.a
% 2.b
% 3.c
% ... + 2 other elements
% Ended enumeration of list: testo

?- debug_call(ex, info, 'My message is ~w.'/long).
% My message is long.
true.
   % message above is printed in informational colour

?- debuc(ex, wrote, loc(file,csv)).
% Could not locate wrote on file specified by: file, and extensions: csv
?- csv_write_file('file.csv', []).

?- debuc(ex, version, debug_call).
% Using debug_call_version, at version: 2:1:1 (published on: date(2025,12,6)).

?- debuc(ex, wrote, loc(file,csv)).
% Wrote on file: 'file.csv'

?- debuc(ex, task(stop), 'write on file').
At 15:44:1 on 2nd of Jul 2024 finished task: write on file.

?- debuc(ex, task(stop), 'talking ~w', [farg(point)]).
% At 13:58:50 on 6th of Dec 2025 stop task: talking point

?- assert((simple_mess(KVs,Mess,Args):- KVs =[a=A,b=B], atom_concat(A,B,Mess), Args=[])).
?- debuc(ex, simple_mess([a=1,b=2])).
% 12
true.

Variable topics

This library avoids the messy way in which package(debug) deals with variable debug topics. That is, their term expansion and subsequent pattern matching mishandles goals of the form debugging/1 and debug/3 that have an unbound variable in the 1st argument. debug_calls uses dynamic =.. .

Pack info

author
- nicos angelopoulos
version
- 0.1 2016/3/5
- 0.2 2016/11/01
- 0.3 2017/3/9
- 1.1 2018/3/20
- 1.2 2019/4/22
- 1.3 2020/3/7
- 1.4 2020/9/18
- 1.5 2022/12/29
- 2.0 2025/10/7
- 2.1 2025/10/27
- 2.2 2025/12/8
See also
- http://stoics.org.uk/~nicos/sware/debug_call/
- debug_call/4 for information on what each version added.

*/

To be done
- options_debug( Opts, Mess, Args ) only writes if Opts contains debug(true). maybe this should be part of pack(options)
- provide a way to remove lib(debug)'s expansions
 debug_call_version(-Version, -Date)
Current version and release date for the library.
?- debug_call_version( -V, -D ).
V = 2:2:0,
D = date(2025,12,8).

*/

  130debug_call_version(2:2:0, date(2025,12,8)).
  131
  132:- use_module(library(apply)).   % maplist/4,...
  133:- use_module(library(lists)).   % member/4,...
  134:- use_module(library(debug)).   % debug/1,...
  135:- use_module(library(lib)).  136
  137:- lib(source(debug_call), [homonyms(true),index(false)]).  138:- lib(stoics_lib:locate/3 ).  139:- lib(stoics_lib:en_list/2).  140:- lib(stoics_lib:message_report/3).  141:- lib(stoics_lib:datime_readable/1).  142:- lib(end(debug_call) ).
 debuc(+Topic)
 debuc(+Topic, +Goal)
 debuc(+Topic, +Goal, +Args)
 debuc(+Topic, +Goal, +Pfx, +Args)
Shorthands for debug_call/2,3,4 and debug/1.
author
- nicos angelopoulos
version
- 0:1 2020/9/9
  154debuc( Topic ) :-
  155    debug( Topic ).
  156debuc( Topic, Goal ) :-
  157    debug_call( Topic, Goal ).
  158debuc( Topic, Goal, Arg ) :-
  159    debug_call( Topic, Goal, Arg ).
  160debuc( Topic, Goal, Arg, Opts ) :-
  161    debug_call( Topic, Goal, Arg, Opts ).
 debug_call(+Topic, +Goal)
Only call debug if we are debugging Topic.

If Goal with arity +2 is available call that instead of Goal with extra arguments Mess and Args that will be passed to debug/3. If the goal (original or +2) fail, nothing is printed by debug_call and the debug_call(T,G) itself succeeds.

 ?- goal( Goal, Mess, Args ).

Examples

 ?- debug(ex)
 ?- assert((simple_mess(KVs,Mess,Args):- KVs =[a=A,b=B], atom_concat(A,B,Mess), Args=[])).
 ?- debug_call(ex, simple_mess([a=1,b=2])).
 12
author
- nicos angelopoulos
version
- 0.2 2018/3/20
  186debug_call( Topic, Goal ) :-
  187    debugging_topic( Topic ),
  188    !,
  189    debug_call_goal( Topic, Goal ).
  190debug_call( _Topic, _Goal ).
  191
  192debug_call_goal( Topic, Moal ) :-
  193    ( Moal = Mod:Goal -> true; Goal = Moal, Mod=user ),
  194    functor( Goal, Functor, Arity ),
  195    Extra is Arity + 2,
  196    current_predicate( Mod:Functor/Extra ),
  197    !,
  198    ( call(Mod:Goal,Mess,Args) ->
  199        debug( Topic, Mess, Args )
  200        ;
  201        true
  202    ).
  203debug_call_goal( _Topic, Goal ) :-
  204    ( call(Goal) -> true; true ).
 debug_chain(+TopicCond, +TopicDep)
 debug_chain(+TopicCond, +TopicDep, -TDprior)
If already debugging TopicCond, then also start debugging TopicDep. TDprior is true if TopicDep was already debugging, else is false. Current implementation sets TDprior to true whenever Topic is not debugged, as it assumes that this value best suit independent fluctuation of TopicDep. Only in the case of debug_chain/2, TopicDep can be a list.
author
- nicos angelopoulos
version
- 0.1 2014/4/4
- 0.2 2016/11/1
See also
- debug_set/2
  220debug_chain( Topic, Then ) :-
  221    en_list( Then, Thens ),
  222    maplist( debug_chain(Topic), Thens, _Priors ).
  223
  224debug_chain( Topic, Then, Prior ) :-
  225    debugging_topic( Topic ),
  226    !,
  227    debugging_status( Then, Prior ),
  228    debug( Then ).
  229debug_chain( _Topic, _Then, true ). 
  230    % setting 3rd to true is a bit presumptious of its uses later on
 debug_message(+Topic, +Mess, +Args)
A wrap around debug/3 that calls it by constructing the term on-the-fly. So that lib(debug) does not create a record by inspecting the term (via expansion). Particularly useful in sending uninstantiated Topics.
author
- nicos angelopoulos
version
- 0.1 2016/11/1

*/

  242debug_message( Topic, Mess, Args ) :-
  243    Call =.. [debug,Topic,Mess,Args],
  244    call( Call ).
 debugging_topic(?Topic)
A wrap around debugging/1 that calls it by constructing the term on-the-fly. So that lib(debug) does not create a record by inspecting the term (via expansion). Particularly useful in sending uninstantiated Topics.
author
- nicos angelopoulos
version
- 0.1 2016/11/1

*/

  256debugging_topic( Topic ) :-
  257    Call =.. [debugging,Topic],
  258    call( Call ).
 debugging_status(+Topic, -Status)
Status == true iff debugging(Topic) succeeds. Else, it is false. Similar to debugging/2, but does not fail for undefined Topic.
 ?- debug( something ).
 true.
 ?- debugging_status( something, Some ).
 Some = true.
 ?- debugging_status( some_else, Else ).
 Else = false.
author
- nicos angelopoulos
version
- 0.1 2014/7/23
  275debugging_status( Topic, Status ) :-
  276    debugging_topic( Topic ),
  277    !,
  278    Status = true.
  279debugging_status( _Topic, false ).
 debug_set(+Prior, +Topic)
Reset Topic according to Prior: true sets Topic to on and false turns Topic off.
 ?- nodebug( chained ).
 true.
 ?- debug( testo ).
 Warning: testo: no matching debug topic (yet)
 true.
 ?- debug( chained, 'debugs chains 1', [] ).
 true.
 ?- debug_chain( testo, chained, Prior ).
 Prior = false.
 ?- debug( chained, 'debugs chains 2', [] ).
 % debugs chains 2
 true.
 ?- Prior = false, debug_set( Prior, chained ).
 Prior = false.
 ?- debug( chained, 'debugs chains 3', [] ).
 true
author
- nicos angelopoulos
version
- 0.1 2014/7/23
- 0.2 2016/8/22, Prior == true used to do nothing, now it turns topic on. also renmaed from debug_set/2.
See also
- debug_chain/3
  308debug_set( false, Topic ) :-
  309    nodebug( Topic ).
  310debug_set( true, Topic ) :-
  311    debug( Topic ).
 debug_topic(+Topic, +Opts, -Restore)
Start debugging Topic if options(debug(true),Opts), with Restore being instantiated to a term that can be used to restore the original debug state of Topic (see options_restore/2). If options(debug(false),Opts) then Topic is stopped from being debugged (Restore still holds the correct term for restoring debugging state for topic to precall status).
?- assert( ( on_t(I,Topic) :- (debugging(Topic) -> write(I-y(Topic)) ; write(I-n(Topic))), nl ) ).
?- T = options, debug(T), on_t(1,T), debug_topic(T,[debug(false)],R), on_t(2,T), debug_set(R,T), on_t(3,T).
1-y(options)
2-n(options)
3-y(options)
T = options,
R = true.

?- T = options, nodebug(T), on_t(1,T), debug_topic(T,[debug(true)],R), on_t(2,T), debug_set(R,T), on_t(3,T).
1-n(options)
2-y(options)
3-n(options)
T = options,
R = false.
author
- nicos angelopoulos
version
- 0.1 2016/8/22

*/

  342debug_topic( Topic, Opts, Restore ) :-
  343    memberchk( debug(Dbg), Opts ),
  344    Dbg == true,
  345    !,
  346    debug_topic_restore( Topic, Restore ),
  347    debug( Topic ).
  348debug_topic( Topic, _Opts, Restore )  :-        % becomes default under this implementation
  349    debug_topic_restore( Topic, Restore ),
  350    nodebug( Topic ).
  351
  352debug_topic_restore( Topic, Restore ) :- 
  353    debugging_topic( Topic ),
  354    !,
  355    Restore = true.
  356debug_topic_restore( _Topic, false ).
 debug_topic(+Flag, +Topic)
Start debugging Topic if Flag == true, and stop debugging if Flag == false.
 ?- debug_topic( true, example ).
author
- nicos angelopoulos
version
- 0.1 2014/12/10
- 0.2 2016/08/22, added nodebug/1 when Flag == false
See also
- options_append/4
  370debug_topic( true, Topic ) :-
  371    debug( Topic ).
  372debug_topic( false, Topic ) :-
  373    nodebug(Topic).
 debug_on(+Topic)
As debug/1, but do not print warning if topic is not known.
  379debug_on( Topic ) :-
  380    asserta( prolog_debug:debugging(Topic,true,[user_error])).
 debug_portray(+Topic, +Term)
Call portray_clause(Term) if we are debugging Topic.
author
- nicos angelopoulos
version
- 0.1
  389debug_portray( Topic, Term ) :-
  390    debugging_topic( Topic ),
  391    !,
  392    portray_clause( Term ).
  393debug_portray( _Topic, _Term ).
 debug_call(+Topic, +Goal, +Arg)
 debug_call(+Topic, +Goal, +Arg, +Opts)
Automates often used debug calls with emphasis on: (a) avoiding calling things that will not be reported and (b) easy tailoring of the messages.

The main novelty is the introduction of abbreviated Goals, that print bespoke messages for often used debugging information. For example the following code ejects info on the legth of the list. Not only the code for calculating the length only happens if debugging for the topic ex, is on, but the message is also tailored to reporting lengths of lists.

 ?- debug(ex).
 ?- debug_call(ex, length, math_vars/[x,y,z]).
 % Length for list, math_vars: 3

With v1.3 the debuc/n shorthand was introduced. So debuc/1,2,3,4 are shorthands for debug_call/1,2,3,4.

?- Mtx = [h(a,b,c),r(1,2,3),r(4,5,6),r(7,8,9)],
   debuc(ex, dims, mtx/Mtx).

Dimensions for matrix, mtx: nR: 4, nC: 3.

The predicate can work as a replacement to debug/3. That is, if Goal does not match any of the forms below, it will be interpreted as a message.

?- debuc(ex, 'A simple message in a ~a.', [bottle] ).
A simple message in a bottle.

The predicate can be used to call arbitrary Goal and then print a message after it has successfull completed (see below).
When Goal is a known abbreviation from those shown below, the Arg usually qualifies the output generated.

As of v2 the last two arguments of the /4 version of the predicate were switched from Pfx and Arg to Arg and Opts. Opts pass arbitary things to Goal, each abbreviation Goal can demand different options. All debuc Goals can take prefix(Pfx) which corresponds to Pfx in the old /4 version, and pred(Fnc,Ar) or pred(Pid).

 ?- debuc(ex, enum, list_x/[x1,x1,x3], [pred(integral,2),prefix('At')] ).
 % At predicate: integral/2 starting enumeration of list: list_x
 % 1.x1
 % 2.x1
 % 3.x3
 % At predicate: integral/2 ended enumeration of list: list_x

The predicate is relaxed about Opts. It can be a single term, which will be cast into a list.

 ?- debuc(ex, pwd, my_run, pred(bio_db,3) ).

 Predicate: bio_db/3 pwd at, my_run, is: '/home/nicos/pl/packs/private/debug_call/'

Goal in:

call(Goal)
Call Goal before printing debugging message debug(Topic, Mess, MArgS). Goal is called in deterministic context. Goal is called with extra arguments +Arg, -Mess and -MArgS.
call(Goal, Opts)
As above, but Opts are passed as an extra, last argument in the call.
dims
Prints the dimensions of matrix, see mtx_dims/3.
end
Translates to finishing ~Arg or finishing ~Topic if Arg == true.
enum
Print members of lists and arguments of terms, where each item is printed on single line and prefixed by an index number Knows: depth(Depth) (restricts items to print).
goal
Anything that does n't match any of the above is retrived as call(Goal)
info
Print using informational machinery (usually different/green colour, to debug's blue) term should Mess/Args in the debug/3 version
input

At 14:2:30 on 6th of Dec 2025 stop task: talking point Reports reading from a file. Arg should be file specification suitable for locate/3. Either loc(File,Exts) or simply File in which case Exts = ''. As of v2.0 the default is to print the basename, use path(abs) in Opts.

length
Prints the lenghts of a bunch of lists. Args should be ListNames/Lists. uses non list ListNames if debuging the length of a single list, in which case message in the singular is used.
list
Writes contents of list with header and footer. Arg should be of the form Hdr/Ftr/List, else Hdr/List unfolds to Hdr/Hdr/List and List is translated to unknown/unknown/List. Knows: depth(Depth) (restricts items to list).
ns_sel
First argument of Arg is the item selected from second arg which is expected to be a list. The selected argument can be named on the massage via sel_name(Lnm) in Opts.
odir
Output directory (Arg should exist and be a directory)
option
Option selected from options for predicate. Possible options: pred(Fnc,Ar) or pred(Pid), the caller predicate, all(OrigOpts), shows all options, internal(true), shows also '$' starting options.
options
Options used on call to a predicate. Possible options: pred(Func,Ar), pred(Pid), the caller predicate, internal(true), shows also '$' starting options.
pwd
Message about current dir Location (=Arg), (if Arg == false, location is not shown)- see examples.
read
Alias for input.
session
Print info on all loaded code, packs are shown with versions both from packs and info from <Pred>_version/2,3 if available (as per stoics.org.uk packs).
start
Translates to starting ~Arg or starting ~Topic if Arg == true.
task(Wch)
Time of start/stop (Wch) of a task. Other values for Wch are allowed but printed as they come. Arg can be a term (as of Version 1.5). Arg can include formatting tidles, and associated arguments should be passed via farg() option.
term
Report the input term. The term can be named via option term_name(Tnm).
var
Reports variable name (arg(1)) and its current instantiation (arg(2))
version
Reports version of software currently using:
  • predicate name of <Arg>_version/2,3 or <Arg>/2 (1st arg Version, 2nd arg release date),
  • Arg should be a term of arity 3 (Sw/Vers/Date) or arity 2 (Sw/Vrs/Date).
wrote
Reports the writting of output on a file. Arg should be file specification suitable for locate/3. Either loc(File,Exts) or simply File in which case Exts = ''. As of v2.0 the default is to print the basename, use path(abs) in Opts.

As of v2.1 all debuc Goals work with options prefix(Pfx) and pred(Ar,Fn) (also synonymed to pred(Pid)).

v2.2 introduced ability to pass formatting patterns and arguments via farg() option.

See file examples/exo.pl for a test suit including at least one example from each debuc Goal.

 ?- debug(ex).
 
 ?- debuc( ex, (length([a,b,c],L),write(len(L)),nl) ).
 len(3)
 L = 3.

 ?- debug_call(ex, length, list1/[x,y,z]).
 % Length for list, list1: 3
  
 ?- debug_call(ex, length, [list1,list2]/[[x,y,z],[a,b,c]] prefix('some prefix')).
 % some prefix lengths for lists, list1: 3, list2: 3
 
 ?- debuc(ex, wrote, loc(file,csv)).
 % Could not locate wrote on file specified by: file, and extensions: csv

 ?- csv_write_file( 'file.csv', []).
 ?- debuc(ex, wrote, loc(file,csv)).
 % Wrote on file: 'file.csv'

 ?- debuc(ex, wrote, loc(file,csv), path(abs)).
 % Wrote on file: '/home/nicos/pl/lib/src/trace/file.csv'

 ?- debuc(ex, task(stop), 'write on file').
 % At 15:44:1 on 2nd of Jul 2014 finished task: write on file.
    
 ?- debuc( ex, pwd, here ).
 % Pwd at, here, is: '/home/nicos/.local/share/swi-prolog/pack/Downloads/bio_db_repo-publish/bio_db_repo-20.09.14/data/hs/maps/hgnc/'
 true.
 
 ?- debuc( ex, pwd, false ).
 % Pwd: '/home/nicos/.local/share/swi-prolog/pack/Downloads/bio_db_repo-publish/bio_db_repo-20.09.14/data/hs/maps/hgnc/'
 true.
 
 ?-  Etcs = [suv-17.09.26.txg,suv-17.09.21.txg], Etc = suv-17.09.26.txg,
     debuc(suv, ns_sel, c(Etc,Etcs, sel_name('suv file') ).
 Continuing with: suv-17.09.26.txg as the: suv file. From list: [suv-17.09.26.txg,suv-17.09.21.txg]

 ?- assert( (list_avg_mess(List,Mess,Args) :- length(List,Len), sum_list(List,Sum), Avg is Sum / Len, Mess = 'Avg: ~w', Args = Avg) ).
 ?- debuc( ex, call(list_avg_mess), [1,2,3] ).
 Avg: 2

 ?- debuc( ex, call(list_avg_mess), [1,2,3], prefix('By call') ).
 By call avg: 2

 ?- debuc( ex, call(list_avg_mess), [1,2,3], [pred(p1,2),prefix('By call')] ).
 By call predicate: p1/2 avg: 2

At some point around SWI-Prolog 8, behaviour of debug/3 changed in being more strict about messages with no arguments. As of version 1.2 debug_call/3 can act as a replacement of debug/3 but with the old behaviour.

 ?- debug( ex, 'Messaging...', true ).
 Messaging...
 [[ EXCEPTION while printing message 'Messaging...'
       with arguments user:true:
       raised: format('too many arguments')
    ]]
 
 true.
 
 ?- debuc( ex, 'Messaging...', true ).
 % Messaging...
 true.
author
- nicos angelopoulos
version
- 0.1 2014/03/27
- 0.2 2014/04/24 added wrote
- 0.3 2014/07/2 added task
- 0.4 2014/09/22 renamed from debug_call/3
- 0.5 2014/??/?? added ns_sel
- 1.1 2018/03/20 prefer +2 arity in debug_call/2
- 1.2 2020/03/07 now can be used as a replacement for debug/3 (but with old 3rd arg behaviour, allowing eg 'true').
- 1.3 2020/09/14 added debuc Goal info and enum, debuc/2,3,4
- 2.0 2025/10/07 changed last two arguments, new option goal recogniser, pred/1, internal/1 & all/1
- 2.1 2025/10/27 pid(F,A) & prefix() universal; call() fixed; doc; enum terms fix; ns_sel simplify
- 2.2 2025/12/08 farg() option; depth() option in list and enum; debuc Goals: version, session.
See also
- file examples/exo.pl
- debuc/3 shorthand for debug_call/3
  598debug_call( Topic, Goal, Arg ) :-
  599    debug_call( Topic, Goal, Arg, [] ).
  600
  601debug_call( Topic, Goal, Arg, OptsPrv ) :-
  602    debugging_topic( Topic ),
  603    !,
  604    en_list( OptsPrv, Opts ),
  605    debugging_call( Topic, Goal, Arg, Opts ).
  606debug_call( _Topic, _Goal, _Arg, _Opts ).
  607
  608debugging_call( Topic, call(Goal), Arg, Opts) :-
  609    !,
  610    call( Goal, Arg, Gess, Grgs ),
  611    !,
  612    debug_call_message_opts( Gess, Grgs, Mess, Args, Opts ),
  613    debug_message( Topic, Mess, Args ).
  614debugging_call( Topic, call_opts(Goal), Arg, Opts ) :-
  615    !,
  616    call( Goal, Arg, Gess, Grgs, Opts ),
  617    debug_call_message_opts( Gess, Grgs, Mess, Args, Opts ),
  618    debug_message( Topic, Mess, Args ).
  619debugging_call( Topic, Goal, Arg, Opts ) :- 
  620    debug_call_topic( Goal, Arg, Opts, Topic ),
  621    !.
  622debugging_call( Topic, Goal, Mess, Args ) :-
  623    compound( Goal ),
  624    call( Goal ),
  625    !,
  626    debug_message( Topic, Mess, Args ).
  627% 20.03.07: this makes debug_call/3 a replacement for debug/3...
  628debugging_call( Topic, Mess, ArgsPrv, _DbgCallArgs ) :-
  629    % as of SWI-Prolog 8.?.? there is an error thrown when true is used instead of [] as 3rd arg of debug/3
  630    atomic( Mess ),
  631    !,
  632    ( ArgsPrv == true -> Args = []; en_list(ArgsPrv,Args) ),
  633    debug( Topic, Mess, Args ).
  634debugging_call( Topic, Goal, Mess, Args ) :-
  635    Called = debug_call(Topic,Goal,Mess,Args),
  636    message_report( 'failure ignored on: ~w', Called, warning ).
 debug_consec(+Topic, +Mess, +Args)
 debug_consec(+Topic, +Clrs, +Mess, +Args)
Alternate the colours of printing messages on Topic, from those in Clrs. When missing these are [blue,magenta]. As of v0.2 Clrs can be a single colour.
 ?- debug( dbg ).
 ?- debug_consec( dbg, 'what:~w', when ).
 % what: when            <- in blue

 ?- debug_consec( dbg, 'what:~w', when ).
 % what: when            <- in magenta

 ?- debug_consec( dbg, [blue,green], 'what:~w', when ).
 % what: when            <- in blue

 ?- debug_consec( dbg, [blue,green], 'what:~w', when ).
 % what: when            <- in green

Version 0.2

 ?- debug_consec( dbg, magenta, 'what:~w', when ).
 % what: when            <- in magenta
author
- nicos angelopoulos
version
- 0.2 2019/12/29
- 0.1 2014/7/24
  670debug_consec( Topic, Mess, Args ) :-
  671    Clrs = [blue,magenta],
  672    debug_consec( Topic, Clrs, Mess, Args ).
  673
  674debug_consec( Topic, ClrS, Mess, Args ) :-
  675    debugging_topic( Topic ),
  676    !,
  677    ( is_list(ClrS) -> Clrs = ClrS; Clrs = [ClrS] ),
  678    debug_consec_topic( Topic, Clrs, Mess, Args ).
  679debug_consec( _Topic, _Clrs, _Mess, _Args ).
  680
  681debug_consec_topic( Topic, Clrs, Mess, Args ) :-
  682    with_output_to( atom(Topicat), write_term(Topic,[]) ),
  683    ( nb_current(Topicat,Value) -> true; Value = 1 ),
  684    ( nth1(Value, Clrs, Clr) -> true; Clrs = [Clr|_] ),
  685    debug_consec_color( Topic, Clr, Mess, Args ),
  686    length( Clrs, Len ),
  687    ( Value < Len -> Next is Value + 1; Next is 1 ),
  688    nb_setval( Topicat, Next ).
  689
  690debug_consec_color( Topic, Clr, Mess, Args ) :-
  691    user:message_property( debug(_), color(Attrs) ),
  692    !,
  693    retractall( debug_call_message_property(debug(_),color(_)) ),
  694    assert( debug_call_message_property(debug(_),color(fg(Clr))) ),
  695    debug_message( Topic, Mess, Args ),
  696    retractall( debug_call_message_property(debug(_),color(_)) ),
  697    assert( debug_call_message_property(debug(_),color(Attrs)) ).
  698debug_consec_color( Topic, Clr, Mess, Args ) :-
  699    assert( debug_call_message_property(debug(_),color(fg(Clr))) ),
  700    debug_message( Topic, Mess, Args ),
  701    retractall( debug_call_message_property(debug(_),color(_)) ).
  702
  703debug_call_topic( info, Arg, Bogs, _Topic ) :-
  704     ( (\+ var(Arg),Arg = Mess/Args) ->
  705          true
  706          ;
  707          % fixme: not sure what to do here ?
  708          Mess = Arg,
  709          Args = []
  710     ),
  711     debug_call_message_opts( Mess, Args, Prefixed, Prgs, Bogs ),
  712	phrase('$messages':translate_message(debug(Prefixed,Prgs)), Lines),
  713	print_message_lines(current_output, kind(informational), Lines).
  714debug_call_topic( dims, NamesPrv/MtxsPrv, Bogs, Topic ) :-
  715    ( is_list(NamesPrv) -> Names=NamesPrv, MtxsPrv=Mtxs, With = 'Dimensions for matrices, '
  716                           ; [NamesPrv] = Names, [MtxsPrv]=Mtxs, With = 'Dimensions for matrix, ' 
  717    ),
  718    maplist( debug_mtx_dims, Mtxs, NRows, NCols ),
  719    findall( PartM, (member(_,Names),PartM='~w: nR: ~d, nC: ~d.'), MParts ),
  720    atomic_list_concat( MParts, '', Right ),
  721    findall( [Name,NRow,NCol], (nth1(N,Names,Name),nth1(N,NRows,NRow),nth1(N,NCols,NCol)), NNest ),
  722    flatten( NNest, Vargs ),
  723    atom_concat( With, Right, Vess ),
  724    debug_call_message_opts( Vess, Vargs, Message, Args, Bogs ),
  725    debug_message( Topic, Message, Args ).
  726debug_call_topic( enum, InArg, Bogs, Topic ) :-
  727    ground( InArg ),
  728    ( InArg = Left/Term -> true; Left = unnamed, Term = InArg ),
  729    ( is_list(Term) ->
  730        length( Term, Len ),
  731        number_codes( Len, LenCs ),
  732        length( LenCs, SpcLen ),
  733        debug_call_topic_list_delim( Left, Topic, 'Starting enumeration of list: ~w', Bogs ),
  734        ( memberchk(depth(Depth), Bogs) -> true; Depth = inf ),
  735        debug_call_topic_enum( Term, 1, Depth, SpcLen, Topic ),
  736        debug_call_topic_list_delim( Left, Topic, 'Ended enumeration of list: ~w', Bogs )
  737        ;
  738        Term =.. [Func|Args],
  739        length( Args, Len ),
  740        number_codes( Len, LenCs ),
  741        length( LenCs, SpcLen ),
  742        atomic_list_concat( ['Starting enumeration of term: ~w (func: ',Func,')'], StrMess ),
  743        debug_call_topic_list_delim( Left, Topic, StrMess, Bogs ),
  744        ( memberchk(depth(Depth), Bogs) -> true; Depth = inf ),
  745        debug_call_topic_enum( Args, 1, Depth, SpcLen, Topic ),
  746        atomic_list_concat( ['Ended enumeration of term: ~w (func: ',Func,')'], EndMess ),
  747        debug_call_topic_list_delim( Left, Topic, EndMess, Bogs )
  748    ).
  749debug_call_topic( length, NamesPrv/ListsPrv, Bogs, Topic ) :-
  750    ( is_list(NamesPrv) -> Names=NamesPrv, ListsPrv=Lists, With = 'Lengths for lists, '
  751                           ; [NamesPrv] = Names, [ListsPrv]=Lists, With = 'Length for list, ' 
  752    ),
  753    maplist( length, Lists, Lengths ),
  754    findall( ['~w: ~w',', '], member(_,Lengths), WsNest ),
  755    flatten( WsNest, WsL ),
  756    once( append(WsLComma,[_],WsL) ),
  757    append( WsLComma, ['.'], WsLDot ),
  758    atomic_list_concat( WsLDot, '', Right ),
  759    findall( [Name,Length], (nth1(N,Names,Name),nth1(N,Lengths,Length)), NLNest ),
  760    flatten( NLNest, NLs ),
  761    atom_concat( With, Right, Vess ),
  762    debug_call_message_opts( Vess, NLs, Message, Args, Bogs ),
  763    debug_message( Topic, Message, Args ). % do the messaging
  764debug_call_topic( list, InArg, Bogs, Topic ) :-
  765    ground( InArg ),
  766    ( InArg = Left/List -> 
  767        ( Left = Hdr/Ftr -> true ; Hdr = Left, Ftr = Left )
  768        ;
  769        List = InArg, Hdr = unamed, Ftr = unamed
  770    ),
  771    debug_call_topic_list_delim( Hdr, Topic, 'Starting listing of list: ~w', Bogs),
  772    ( memberchk(depth(Depth),Bogs) -> 
  773          length( Clean, Depth ),
  774          ( append(Clean,[H|T],List) ->
  775                    maplist( debug_message(Topic,'~w'), Clean ),
  776                    length( [H|T], Xen ),
  777                    ( Xen =:= 1 -> 
  778                         Mess = '... + ~d other element'
  779                         ;
  780                         Mess = '... + ~d other elements'
  781                    ),
  782                    debug_message( Topic, Mess, Xen )
  783                    ;
  784                    maplist( debug_message(Topic,'~w'), List )
  785          )
  786          ;
  787          maplist( debug_message(Topic,'~w'), List )
  788    ),
  789    debug_call_topic_list_delim( Ftr, Topic, 'Ended listing of list: ~w', Bogs ).
  790debug_call_topic( odir, Odir, Bogs, Topic ) :-
  791    ( exists_directory(Odir) ->
  792        Mess = 'Output in directory: ~w'
  793        ;
  794        Mess = 'Output (claimed) in (non-existing) directory: ~w'
  795    ),
  796    debug_call_message_opts( Mess, [Odir], Message, Args, Bogs ),
  797    debug_message( Topic, Message, Args ).
  798debug_call_topic( option, Opt, Bogs, Topic ) :-
  799    Ness = 'Option selected: ~w',
  800    ( (memberchk(all(OrgOpts),Bogs),is_list(OrgOpts)) ->
  801               ( memberchk(internal(true),Bogs) ->
  802                    RdcOpts = OrgOpts
  803                    ;
  804                    findall( R, (member(R,OrgOpts),functor(R,F,_),\+(atom_concat('$',_,F))), RdcOpts )
  805               ),
  806               atom_concat( Ness, ' from options: ~w', Mess ),
  807               Mrgs = [Opt,RdcOpts]
  808               ;
  809               atom_concat( Ness, '.', Mess ),
  810               [Opt] = Mrgs
  811    ),
  812    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  813    debug_message( Topic, Message, Args ).
  814debug_call_topic( options, RepOpts, Bogs, Topic ) :-
  815    Ness = 'Options: ~w',
  816    ( memberchk(internal(true),Bogs) -> 
  817               RepOpts = RdcOpts
  818               ;
  819               findall( R, (member(R,RepOpts),functor(R,F,_),\+(atom_concat('$',_,F))), RdcOpts )
  820    ),
  821    debug_call_message_opts( Ness, [RdcOpts], Message, Args, Bogs ),
  822    debug( Topic,  Message, Args ).
  823debug_call_topic( term, Derm, Bogs, Topic ) :-
  824    ( memberchk(term_name(Tnm),Bogs) -> 
  825          Mess = 'Reporting term (~w): ~w',
  826          Mrgs = [Tnm,Derm]
  827          ; 
  828          Mess = 'Reporting term: ~w',
  829          Mrgs = [Derm]
  830    ),
  831    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  832    debug_message( Topic, Message, Args ).
  833debug_call_topic( var, DbgTerm, Bogs, Topic ) :-
  834    arg( 1, DbgTerm, Var ),
  835    arg( 2, DbgTerm, Val ),
  836    Mess = 'Variable: ~a, value: ~w',
  837    debug_call_message_opts( Mess, [Var,Val], Message, Args, Bogs ),
  838    debug_message( Topic, Message, Args ).
  839debug_call_topic( session, _Derm, Bogs, Topic ) :-
  840     ( memberchk(in_module(Mod), Bogs) -> true; Mod = user),
  841     current_prolog_flag( version_data, Swi ),  % Swi = swi(9, 3, 34, []).
  842     Swi  = swi(Mj,Mn,Fx,Inc),
  843     ( Inc == [] -> 
  844          atomic_list_concat( [Mj,Mn,Fx], ':', Vers )
  845          ;
  846          atomic_list_concat( [Mj,Mn,Fx,Inc], ':',Vers )
  847     ),
  848     debug_message( Topic, 'Session Info', [] ),
  849     ( current_prolog_flag(version_git, Git) -> % Git = '9.3.34-41-g8cf975236'.
  850          atomic_list_concat( ['Interpreter is SWI-Prolog ',Vers,', [Git: ',Git,'].'], Mess )
  851          ;
  852          atomic_list_concat( ['Interpreter is SWI-Prolog ',Vers,'.'], Mess )
  853     ),
  854     debug_call_message_opts( Mess, [], Message, Args, Bogs ),
  855     debug_message( Topic, Message, Args ),
  856     % find where alias pack points to
  857     once( (file_search_path(pack,PackPath),atomic(PackPath)) ),
  858     debug_call_topic_session_predicate_file_prefixed( PackPath, Mod, pack, Lacks ),
  859     findall( APack-ItsVers, (member(APack,Lacks),pack_property(APack,version(ItsVers))), PVs ),
  860     findall( Stoic-VersInfo, (  Mod:predicate_property(P,file(_)),
  861                                 functor(P,Fun,Ari),
  862                                 atom_concat(Stoic,'_version',Fun),
  863                                 ( Mod:predicate_property(P,imported_from(Stoic)) ->
  864                                    true
  865                                    ;
  866                                    Mod:predicate_property(P,exported)
  867                                 ),
  868                                 ( Ari =:= 3 -> 
  869                                        G =.. [Fun,Ser,Sdt,_],
  870                                        call(Mod:G)
  871                                        ;  % defaulty 2
  872                                        Ari =:= 2,
  873                                        G =.. [Fun,Ser,Sdt],
  874                                        call(Mod:G)
  875                                  ),
  876                                  VersInfo = (Ser @< Sdt)
  877                              ),
  878                                 SVs ),
  879     ( SVs == [] ->
  880          true
  881          ;
  882          ( SVs == [_] ->
  883               debug_message( Topic, 'Pack with predicated version info.', [] )
  884               ;
  885               debug_message( Topic, 'Packs with predicated version info.', [] )
  886          ),
  887          debug_call_topic_versions_predicated( SVs, PVs, Topic, RemPVs )
  888     ),
  889     ( RemPVs = [] -> 
  890          true
  891          ;
  892          ( RemPVs = [_] ->
  893               debug_message( Topic, 'Pack with version from pack file only.', [] )
  894               ;
  895               debug_message( Topic, 'Packs with version from pack file only.', [] )
  896          ),
  897          findall( _, (member(P-V,RemPVs),debug_message(Topic,'~w-~w',[P,V])), _ )
  898     ),
  899     once( (file_search_path(swi,SwiPath),atomic(SwiPath)) ),
  900     debug_call_topic_session_predicate_file_prefixed( SwiPath, Mod, boot, Boots ),
  901     debug_message( Topic, 'System boot files loaded.', [] ),
  902     findall( _, (member(Boot,Boots),debug_message(Topic,'~w',[Boot])), _ ),
  903     directory_file_path( SwiPath, library, LibPath ),
  904     debug_call_topic_session_predicate_file_prefixed( LibPath, Mod, rel, Libs ),
  905     ( Libs = [] ->
  906          debug_message( Topic, 'No system libraries found loaded.', [] )
  907          ;
  908          ( Libs =[_] ->
  909               debug_message( Topic, 'System library loaded.', [] )
  910               ;
  911               debug_message( Topic, 'System libraries loaded.', [] )
  912          ),
  913          findall( _, (member(Lib,Libs),debug_message(Topic,'~w',[Lib])), _ )
  914     ),
  915     findall( AppF, (   Mod:predicate_property(_,file(AppF)),
  916                        ( atom_concat(PackPath,PackPsfx,AppF) ->
  917                                            % fixme: check PackTop below, against loaded ?
  918                                   catch( atomic_list_concat([_Empty,_PackTop,TopSub|_],'/',PackPsfx),_,fail),
  919                                   \+ memberchk(TopSub,[prolog,src])
  920                                   ;
  921                                   true
  922                        ),
  923                        \+atom_concat(SwiPath,_,AppF)
  924                    ),
  925                         AppFsL ),
  926     sort( AppFsL, AppFs ),
  927     ( AppFs = [] ->
  928          debug_message( Topic, 'There where no application files loaded.', [] )
  929          ;
  930          ( AppFs = [_] ->
  931               debug_message( Topic, 'There is one application file loaded.', [] )
  932               ;
  933               debug_message( Topic, 'Application files loaded.', [] )
  934          ),
  935          findall( AnAF, (member(AnAF,AppFs),debug_message(Topic,'~w',[AnAF])), _ )
  936     ),
  937     debug_message( Topic, 'Session Info End', [] ).
  938debug_call_topic( version, Derm, Bogs, Topic ) :-
  939     ( atomic(Derm) -> 
  940          atom_concat( Derm, '_version', Verm ),
  941          ( current_predicate(Verm/2) ->
  942               Goal =.. [Verm,V,D],
  943               once(Goal)
  944               ;
  945               ( current_predicate(Verm/3) ->
  946                    Goal =.. [Verm,V,D,_],
  947                    once(Goal)
  948                    ;
  949                    ( pack_property(Derm,version(V)) ->
  950                         D = no_date
  951                         ;
  952                         ( current_predicate(Derm/2) -> 
  953                              Goal =.. [Derm,V,D],
  954                              once(Goal)
  955                              ;
  956                              V = no_vers, D = no_date
  957                         )
  958                    )
  959               )
  960          ),
  961          Mrgs = [Derm,V,D]
  962          ;
  963          ( functor(Derm,_,2) ->
  964               arg( 1, Derm, Sw ),
  965               arg( 2, Derm, V ),
  966               Mrgs = [Sw,V,no_date]
  967               ;
  968               ( functor(Derm,_,3) ->
  969                    arg( 1, Derm, Sw ),
  970                    arg( 2, Derm, V ),
  971                    arg( 3, Derm, D ),
  972                    Mrgs = [Sw,V,D]
  973                    ;
  974                    Mrgs = [Derm,no_vers,no_date]
  975               )
  976          )
  977     ),
  978     ( D == no_date ->
  979          (   V == no_vers ->
  980               Mess = 'Using ~w (no version or publication date available).',
  981               Mrgs = [A|_],
  982               Crgs = [A]
  983               ;
  984               Mess = 'Using ~w, at version: ~w.',
  985               Mrgs = [A,B|_],
  986               Crgs = [A,B]
  987          )
  988          ;
  989          Mess = 'Using ~w, at version: ~w (published on: ~w).',
  990          Mrgs = Crgs
  991     ),
  992     debug_call_message_opts( Mess, Crgs, Message, Args, Bogs ),
  993     debug_message( Topic, Message, Args ).
  994debug_call_topic( wrote, ForLoc, Bogs, Topic ) :-
  995    ( ForLoc = loc(Spec,Ext) -> true; Spec=ForLoc, Ext = '' ),
  996    catch( locate(Spec,Ext,Loc), Excp, true ),
  997    MessW = 'Wrote on file: ~p',
  998    debug_call_location_exception_message( Excp, write, Loc, MessW, Mess, Bogs, Mrgs ),
  999    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
 1000    debug_message( Topic, Message, Args ).
 1001debug_call_topic( read, ForLoc, Bogs, Topic ) :-
 1002     debug_call_topic( input, ForLoc, Bogs, Topic ).
 1003debug_call_topic( input, ForLoc, Bogs, Topic ) :-
 1004    ( ForLoc = loc(Spec,Ext) -> true; Spec=ForLoc, Ext = '' ),
 1005    catch( locate(Spec,Ext,Loc), Excp, true ),
 1006    MessW = 'Input from file: ~p',
 1007    debug_call_location_exception_message( Excp, input, Loc, MessW, Mess, Bogs, Mrgs ),
 1008    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
 1009    debug_message( Topic, Message, Args ).
 1010debug_call_topic( task(Whc), Task, Bogs, Topic ) :-
 1011    datime_readable( Readable ),
 1012    debug_call_topic_time_which_readable( Whc, Whcable ),
 1013    atomic_list_concat( [Readable,' ',Whcable,' task: ', Task], Mess ),
 1014    debug_call_message_opts( Mess, [], Message, Args, Bogs ),
 1015    debug_message( Topic, Message, Args ).
 1016debug_call_topic( start, Arg, Bogs, Topic ) :-
 1017    Mess = 'Starting: ~w',
 1018    ( Arg == true -> Rep = Topic; Rep = Arg ),
 1019    debug_call_message_opts( Mess, [Rep], Message, Args, Bogs ),
 1020    debug_message( Topic, Message, Args ).
 1021debug_call_topic( end, Arg, Bogs, Topic ) :-
 1022    Mess = 'Finished: ~w',
 1023    ( Arg == true -> Rep = Topic; Rep = Arg ),
 1024    debug_call_message_opts( Mess, [Rep], Message, Args, Bogs ),
 1025    debug_message( Topic, Message, Args ).
 1026debug_call_topic( pwd, Stage, Bogs, Topic ) :-
 1027    working_directory( Pwd, Pwd ),
 1028    ( Stage == false -> 
 1029        Mess = 'Pwd: ~p', Mrgs = [Pwd]
 1030        ;
 1031        Mess = 'Pwd at, ~w, is: ~p', Mrgs = [Stage,Pwd]
 1032    ),
 1033    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
 1034    debug_message( Topic, Message, Args ).
 1035debug_call_topic( ns_sel, Term, Bogs, Topic ) :-
 1036    arg( 1, Term, Fst ),
 1037    arg( 2, Term, Sec ),
 1038    ( memberchk(sel_name(Trd),Bogs) ->
 1039          Mess = 'Continuing with: ~w as the: ~w. From list: ~w',
 1040          MArgs= [Fst,Trd,Sec]
 1041          ;
 1042          Mess = 'Continuing with: ~w from list: ~w',
 1043          MArgs= [Fst,Sec]
 1044    ),
 1045    debug_call_message_opts( Mess, MArgs, Message, Args, Bogs ),
 1046    debug_message( Topic, Message, Args ).
 1047
 1048debug_call_topic_session_predicate_file_prefixed( Path, Mod, Iface, Lacks ) :-
 1049     findall( APack, ( Mod:predicate_property(_Pead, file(File)), 
 1050                             atom_concat(Path, Psfx, File), 
 1051                             ( Iface == pack -> 
 1052                                   atomic_list_concat(['',APack|_], '/', Psfx)
 1053                                   ;
 1054                                   ( atom_concat('/',APack,Psfx) -> 
 1055                                        ( Iface == boot ->
 1056                                             \+ atom_concat( library, _, APack )
 1057                                             ;
 1058                                             true
 1059                                        )
 1060                                        ;
 1061                                        Psfx = APack
 1062                                   )
 1063                             )
 1064                           ),
 1065                              AllPacks ),
 1066     sort( AllPacks, Lacks ).
 1067
 1068debug_call_topic_versions_predicated( [], PVs, _Topic, RemPVs ) :-
 1069     PVs = RemPVs.
 1070debug_call_topic_versions_predicated( [Pack-SVers|T], PVs, Topic, RemPVs ) :-
 1071     ( select(Pack-InfoVer,PVs,NxtPVs) ->
 1072          debug_message( Topic, '~w-~w (Pack file version: ~w)', [Pack,SVers,InfoVer] )
 1073          ;
 1074          debug_message( Topic, '~w-~w', [Pack,SVers] ),
 1075          PVs = NxtPVs
 1076     ),
 1077     debug_call_topic_versions_predicated( T, NxtPVs, Topic, RemPVs ).
 1078
 1079debug_call_topic_enum( [], _I, _Depth, _Len, _Topic ).
 1080debug_call_topic_enum( [H|T], I, Depth, Len, Topic ) :-
 1081    ( I > Depth -> 
 1082          Rem = [],
 1083          length( [H|T], HTen ),
 1084          ( HTen =:= 1 -> 
 1085               Mess = '... + ~d other element'
 1086               ;
 1087               Mess = '... + ~d other elements'
 1088          ),
 1089          debug_message( Topic, Mess, HTen )
 1090          ;
 1091          T = Rem,
 1092          number_codes( I, ICs ),
 1093          length( ICs, ICsLen ),
 1094          PadLen is Len - ICsLen,
 1095          findall( ' ', between(1,PadLen,_), Spcs ),
 1096          atomic_list_concat( Spcs, '', Pad ),
 1097          atomic_list_concat( [Pad,'~d.~w'], '', Mess ),
 1098          debug_message( Topic, Mess, [I,H] )
 1099    ),
 1100    J is I + 1,
 1101    debug_call_topic_enum( Rem, J, Depth, Len, Topic ).
 1102
 1103debug_call_topic_list_delim( ListName, Topic, Std, Bogs ) :-
 1104     debug_call_message_opts( Std, [ListName], Mess, Args, Bogs ), 
 1105     debug_message( Topic, Mess, Args ).
 1106
 1107debug_call_topic_time_which_readable( Wch, Wchable ) :-
 1108    debug_call_topic_time_which_readable_known( Wch, Wchable ),
 1109    !.
 1110debug_call_topic_time_which_readable( Wch, Wch ).
 1111
 1112debug_call_topic_time_which_readable_known( start, starting ).
 1113debug_call_topic_time_which_readable_known( finish, finished ).
 1114
 1115debug_call_location_exception_message( Var, _Dir, Loc, MessI, MessO, Opts, Args ) :-
 1116    var(Var),
 1117    !,
 1118    MessI = MessO,
 1119    ( memberchk(path(abs),Opts) ->
 1120               Args = [Loc]
 1121               ;
 1122               file_base_name( Loc, Arg ),
 1123               Args = [Arg]
 1124    ).
 1125debug_call_location_exception_message( locate(cannot_locate(Spec,Ext)), Dir, _Loc, _MessI, Mess, _Opts, Args ) :-
 1126    atomic_list_concat( ['Could not locate',Dir,'file specified by: ~w, and extensions: ~w'], ' ', Mess ),
 1127    Args = [Spec,Ext].
 1128debug_call_location_exception_message( Error, _Dir, _Loc, _MessI, _Mess, _Opts, _Args ) :-
 1129    % fixme:
 1130    throw( debug_call_caught(Error) ).
 1131
 1132debug_mtx_dims( [], 0, 0 ) :-
 1133    !.
 1134debug_mtx_dims( Rows, NRows, NCols ) :-
 1135    length( Rows, NRows ),
 1136    Rows = [Hdr|_],
 1137    ( is_list(Hdr) -> length(Hdr,NCols); functor(Hdr,_,NCols) ).
 1138
 1139debug_message_prefixed( [], Standard, Standard ) :- !.
 1140debug_message_prefixed( '', Standard, Standard ) :- !.
 1141debug_message_prefixed( prefix(Pfx), Standard, Prefixed ) :-
 1142     !,
 1143     debug_message_prefixed( [prefix(Pfx)], Standard, Prefixed ).
 1144debug_message_prefixed( [H|T], Standard, Prefixed ) :-
 1145    memberchk( prefix(Pfx), [H|T] ),
 1146    !,
 1147    debug_message_prefixed_atom( Pfx, Standard, Prefixed ).
 1148debug_message_prefixed( _, Standard, Standard ).
 1149
 1150debug_call_message_opts( Std, Srgs, Mess, Args, Opts ) :-
 1151     debug_call_pred_in_opts_mess( Std, Srgs, Pess, Args, Opts ),
 1152     debug_message_prefixed( Opts, Pess, Mess ).
 1153
 1154debug_call_pred_in_opts_mess( Std, Opt, Prefixed, Prgs, Bogs ) :-
 1155     en_list( Opt, Opts ),
 1156     ( debug_call_pred_in_opts(Pid, Bogs)  ->
 1157          Pfx = 'Predicate: ~w',
 1158          debug_message_prefixed_atom( Pfx, Std, Prefixed ),
 1159          PrgsPrv = [Pid|Opts]
 1160          ;
 1161          Prefixed = Std,
 1162          PrgsPrv = Opts
 1163     ),
 1164     debug_call_pred_in_opts_mess_format_args( PrgsPrv, Prgs, Bogs ).
 1165
 1166debug_call_pred_in_opts( Pid, Opts ) :-
 1167    memberchk( pred(Fun,Ar), Opts ),
 1168    !,
 1169    Fun/Ar = Pid.
 1170debug_call_pred_in_opts( Pid, Opts ) :-
 1171    memberchk( pred(Pid), Opts ).
 1172
 1173debug_call_pred_in_opts_mess_format_args( PrgsPrv, Prgs, Bogs ) :-
 1174     findall( Farg, member(farg(Farg),Bogs), Fargs ),
 1175     append( PrgsPrv, Fargs, Prgs ).
 1176
 1177debug_message_prefixed_atom( Pfx, Standard, Prefixed ) :-
 1178    sub_atom( Standard, 0, 1, Aft, Fst ),
 1179    downcase_atom( Fst, Low ),
 1180    sub_atom( Standard, 1, Aft, 0, Right ),
 1181    atomic_list_concat( [Pfx,' ',Low,Right], Prefixed )