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 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, 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, 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.

?- 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
See also
- http://stoics.org.uk/~nicos/sware/debug_call/
- debug_call/4 for version information

*/

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:1:0,
D = date(2025,10,27).

*/

  114debug_call_version( 2:1:0, date(2025,10,27) ).
  115
  116:- use_module(library(apply)).   % maplist/4,...
  117:- use_module(library(lists)).   % member/4,...
  118:- use_module(library(debug)).   % debug/1,...
  119:- use_module(library(lib)).  120
  121:- lib(source(debug_call), [homonyms(true),index(false)]).  122:- lib(stoics_lib:locate/3 ).  123:- lib(stoics_lib:en_list/2).  124:- lib(stoics_lib:message_report/3).  125:- lib(stoics_lib:datime_readable/1).  126:- 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
  138debuc( Topic ) :-
  139    debug( Topic ).
  140debuc( Topic, Goal ) :-
  141    debug_call( Topic, Goal ).
  142debuc( Topic, Goal, Arg ) :-
  143    debug_call( Topic, Goal, Arg ).
  144debuc( Topic, Goal, Arg, Opts ) :-
  145    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

 ?- 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],
author
- nicos angelopoulos
version
- 0.2 2018/3/20
  168debug_call( Topic, Goal ) :-
  169    debugging_topic( Topic ),
  170    !,
  171    debug_call_goal( Topic, Goal ).
  172debug_call( _Topic, _Goal ).
  173
  174debug_call_goal( Topic, Moal ) :-
  175    ( Moal = Mod:Goal -> true; Goal = Moal, Mod=user ),
  176    functor( Goal, Functor, Arity ),
  177    Extra is Arity + 2,
  178    current_predicate( Mod:Functor/Extra ),
  179    !,
  180    ( call(Mod:Goal,Mess,Args) ->
  181        debug( Topic, Mess, Args )
  182        ;
  183        true
  184    ).
  185debug_call_goal( _Topic, Goal ) :-
  186    ( 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
  202debug_chain( Topic, Then ) :-
  203    en_list( Then, Thens ),
  204    maplist( debug_chain(Topic), Thens, _Priors ).
  205
  206debug_chain( Topic, Then, Prior ) :-
  207    debugging_topic( Topic ),
  208    !,
  209    debugging_status( Then, Prior ),
  210    debug( Then ).
  211debug_chain( _Topic, _Then, true ). 
  212    % 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

*/

  224debug_message( Topic, Mess, Args ) :-
  225    Call =.. [debug,Topic,Mess,Args],
  226    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

*/

  238debugging_topic( Topic ) :-
  239    Call =.. [debugging,Topic],
  240    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
  257debugging_status( Topic, Status ) :-
  258    debugging_topic( Topic ),
  259    !,
  260    Status = true.
  261debugging_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
  290debug_set( false, Topic ) :-
  291    nodebug( Topic ).
  292debug_set( true, Topic ) :-
  293    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

*/

  324debug_topic( Topic, Opts, Restore ) :-
  325    memberchk( debug(Dbg), Opts ),
  326    Dbg == true,
  327    !,
  328    debug_topic_restore( Topic, Restore ),
  329    debug( Topic ).
  330debug_topic( Topic, _Opts, Restore )  :-        % becomes default under this implementation
  331    debug_topic_restore( Topic, Restore ),
  332    nodebug( Topic ).
  333
  334debug_topic_restore( Topic, Restore ) :- 
  335    debugging_topic( Topic ),
  336    !,
  337    Restore = true.
  338debug_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
  352debug_topic( true, Topic ) :-
  353    debug( Topic ).
  354debug_topic( false, Topic ) :-
  355    nodebug(Topic).
 debug_on(+Topic)
As debug/1, but do not print warning if topic is not known.
  361debug_on( Topic ) :-
  362    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
  371debug_portray( Topic, Term ) :-
  372    debugging_topic( Topic ),
  373    !,
  374    portray_clause( Term ).
  375debug_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
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
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 it is translated as Hdr/''/List or ''/''/List. If Hdr or Ftr are '' then that part of the message is skipped
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
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).
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))
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)).

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 canned calls 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
See also
- file examples/exo.pl
- debuc/3 shorthand for debug_call/3
  567debug_call( Topic, Goal, Arg ) :-
  568    debug_call( Topic, Goal, Arg, [] ).
  569
  570debug_call( Topic, Goal, Arg, OptsPrv ) :-
  571    debugging_topic( Topic ),
  572    !,
  573    en_list( OptsPrv, Opts ),
  574    debugging_call( Topic, Goal, Arg, Opts ).
  575debug_call( _Topic, _Goal, _Arg, _Opts ).
  576
  577debugging_call( Topic, call(Goal), Arg, Opts) :-
  578    !,
  579    call( Goal, Arg, Gess, Grgs ),
  580    !,
  581    debug_call_message_opts( Gess, Grgs, Mess, Args, Opts ),
  582    debug_message( Topic, Mess, Args ).
  583debugging_call( Topic, call_opts(Goal), Arg, Opts ) :-
  584    !,
  585    call( Goal, Arg, Gess, Grgs, Opts ),
  586    debug_call_message_opts( Gess, Grgs, Mess, Args, Opts ),
  587    debug_message( Topic, Mess, Args ).
  588debugging_call( Topic, Goal, Arg, Opts ) :- 
  589    debug_call_topic( Goal, Arg, Opts, Topic ),
  590    !.
  591debugging_call( Topic, Goal, Mess, Args ) :-
  592    compound( Goal ),
  593    call( Goal ),
  594    !,
  595    debug_message( Topic, Mess, Args ).
  596% 20.03.07: this makes debug_call/3 a replacement for debug/3...
  597debugging_call( Topic, Mess, ArgsPrv, _DbgCallArgs ) :-
  598    % as of SWI-Prolog 8.?.? there is an error thrown when true is used instead of [] as 3rd arg of debug/3
  599    atomic( Mess ),
  600    !,
  601    ( ArgsPrv == true -> Args = []; en_list(ArgsPrv,Args) ),
  602    debug( Topic, Mess, Args ).
  603debugging_call( Topic, Goal, Mess, Args ) :-
  604    Called = debug_call(Topic,Goal,Mess,Args),
  605    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
  639debug_consec( Topic, Mess, Args ) :-
  640    Clrs = [blue,magenta],
  641    debug_consec( Topic, Clrs, Mess, Args ).
  642
  643debug_consec( Topic, ClrS, Mess, Args ) :-
  644    debugging_topic( Topic ),
  645    !,
  646    ( is_list(ClrS) -> Clrs = ClrS; Clrs = [ClrS] ),
  647    debug_consec_topic( Topic, Clrs, Mess, Args ).
  648debug_consec( _Topic, _Clrs, _Mess, _Args ).
  649
  650debug_consec_topic( Topic, Clrs, Mess, Args ) :-
  651    with_output_to( atom(Topicat), write_term(Topic,[]) ),
  652    ( nb_current(Topicat,Value) -> true; Value = 1 ),
  653    ( nth1(Value, Clrs, Clr) -> true; Clrs = [Clr|_] ),
  654    debug_consec_color( Topic, Clr, Mess, Args ),
  655    length( Clrs, Len ),
  656    ( Value < Len -> Next is Value + 1; Next is 1 ),
  657    nb_setval( Topicat, Next ).
  658
  659debug_consec_color( Topic, Clr, Mess, Args ) :-
  660    user:message_property( debug(_), color(Attrs) ),
  661    !,
  662    retractall( debug_call_message_property(debug(_),color(_)) ),
  663    assert( debug_call_message_property(debug(_),color(fg(Clr))) ),
  664    debug_message( Topic, Mess, Args ),
  665    retractall( debug_call_message_property(debug(_),color(_)) ),
  666    assert( debug_call_message_property(debug(_),color(Attrs)) ).
  667debug_consec_color( Topic, Clr, Mess, Args ) :-
  668    assert( debug_call_message_property(debug(_),color(fg(Clr))) ),
  669    debug_message( Topic, Mess, Args ),
  670    retractall( debug_call_message_property(debug(_),color(_)) ).
  671
  672debug_call_topic( info, Arg, Bogs, _Topic ) :-
  673     ( (\+ var(Arg),Arg = Mess/Args) ->
  674          true
  675          ;
  676          % fixme: not sure what to do here ?
  677          Mess = Arg,
  678          Args = []
  679     ),
  680     debug_call_message_opts( Mess, Args, Prefixed, Prgs, Bogs ),
  681	phrase('$messages':translate_message(debug(Prefixed,Prgs)), Lines),
  682	print_message_lines(current_output, kind(informational), Lines).
  683debug_call_topic( dims, NamesPrv/MtxsPrv, Bogs, Topic ) :-
  684    ( is_list(NamesPrv) -> Names=NamesPrv, MtxsPrv=Mtxs, With = 'Dimensions for matrices, '
  685                           ; [NamesPrv] = Names, [MtxsPrv]=Mtxs, With = 'Dimensions for matrix, ' 
  686    ),
  687    maplist( debug_mtx_dims, Mtxs, NRows, NCols ),
  688    findall( PartM, (member(_,Names),PartM='~w: nR: ~d, nC: ~d.'), MParts ),
  689    atomic_list_concat( MParts, '', Right ),
  690    findall( [Name,NRow,NCol], (nth1(N,Names,Name),nth1(N,NRows,NRow),nth1(N,NCols,NCol)), NNest ),
  691    flatten( NNest, Vargs ),
  692    atom_concat( With, Right, Vess ),
  693    debug_call_message_opts( Vess, Vargs, Message, Args, Bogs ),
  694    debug_message( Topic, Message, Args ).
  695debug_call_topic( enum, InArg, Bogs, Topic ) :-
  696    ground( InArg ),
  697    ( InArg = Left/Term -> true; Left = unnamed, Term = InArg ),
  698    ( is_list(Term) ->
  699        length( Term, Len ),
  700        number_codes( Len, LenCs ),
  701        length( LenCs, SpcLen ),
  702        debug_call_topic_list_delim( Left, Topic, 'Starting enumeration of list: ~w', Bogs ),
  703        debug_call_topic_enum( Term, 1, SpcLen, Topic ),
  704        debug_call_topic_list_delim( Left, Topic, 'Ended enumeration of list: ~w', Bogs )
  705        ;
  706        Term =.. [Func|Args],
  707        length( Args, Len ),
  708        number_codes( Len, LenCs ),
  709        length( LenCs, SpcLen ),
  710        atomic_list_concat( ['Starting enumeration of term: ~w (func: ',Func,')'], StrMess ),
  711        debug_call_topic_list_delim( Left, Topic, StrMess, Bogs ),
  712        debug_call_topic_enum( Args, 1, SpcLen, Topic ),
  713        atomic_list_concat( ['Ended enumeration of term: ~w (func: ',Func,')'], EndMess ),
  714        debug_call_topic_list_delim( Left, Topic, EndMess, Bogs )
  715    ).
  716debug_call_topic( length, NamesPrv/ListsPrv, Bogs, Topic ) :-
  717    ( is_list(NamesPrv) -> Names=NamesPrv, ListsPrv=Lists, With = 'Lengths for lists, '
  718                           ; [NamesPrv] = Names, [ListsPrv]=Lists, With = 'Length for list, ' 
  719    ),
  720    maplist( length, Lists, Lengths ),
  721    findall( ['~w: ~w',', '], member(_,Lengths), WsNest ),
  722    flatten( WsNest, WsL ),
  723    once( append(WsLComma,[_],WsL) ),
  724    append( WsLComma, ['.'], WsLDot ),
  725    atomic_list_concat( WsLDot, '', Right ),
  726    findall( [Name,Length], (nth1(N,Names,Name),nth1(N,Lengths,Length)), NLNest ),
  727    flatten( NLNest, NLs ),
  728    atom_concat( With, Right, Vess ),
  729    debug_call_message_opts( Vess, NLs, Message, Args, Bogs ),
  730    debug_message( Topic, Message, Args ). % do the messaging
  731debug_call_topic( list, InArg, Bogs, Topic ) :-
  732    ground( InArg ),
  733    ( InArg = Left/List -> 
  734        ( Left = Hdr/Ftr -> true ; Hdr = Left, Ftr = '' )
  735        ;
  736        List = InArg, Hdr = '', Ftr = ''
  737    ),
  738    debug_call_topic_list_delim( Hdr, Topic, 'Starting listing of list: ~w', Bogs),
  739    maplist( debug_message(Topic,'~w'), List ),
  740    debug_call_topic_list_delim( Ftr, Topic, 'Ended listing of list: ~w', Bogs ).
  741debug_call_topic( odir, Odir, Bogs, Topic ) :-
  742    ( exists_directory(Odir) ->
  743        Mess = 'Output in directory: ~w'
  744        ;
  745        Mess = 'Output (claimed) in (non-existing) directory: ~w'
  746    ),
  747    debug_call_message_opts( Mess, [Odir], Message, Args, Bogs ),
  748    debug_message( Topic, Message, Args ).
  749debug_call_topic( option, Opt, Bogs, Topic ) :-
  750    Ness = 'Option selected: ~w',
  751    ( (memberchk(all(OrgOpts),Bogs),is_list(OrgOpts)) ->
  752               ( memberchk(internal(true),Bogs) ->
  753                    RdcOpts = OrgOpts
  754                    ;
  755                    findall( R, (member(R,OrgOpts),functor(R,F,_),\+(atom_concat('$',_,F))), RdcOpts )
  756               ),
  757               atom_concat( Ness, ' from options: ~w', Mess ),
  758               Mrgs = [Opt,RdcOpts]
  759               ;
  760               atom_concat( Ness, '.', Mess ),
  761               [Opt] = Mrgs
  762    ),
  763    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  764    debug_message( Topic, Message, Args ).
  765debug_call_topic( options, RepOpts, Bogs, Topic ) :-
  766    Ness = 'Options: ~w',
  767    ( memberchk(internal(true),Bogs) -> 
  768               RepOpts = RdcOpts
  769               ;
  770               findall( R, (member(R,RepOpts),functor(R,F,_),\+(atom_concat('$',_,F))), RdcOpts )
  771    ),
  772    debug_call_message_opts( Ness, [RdcOpts], Message, Args, Bogs ),
  773    debug( Topic,  Message, Args ).
  774debug_call_topic( term, Derm, Bogs, Topic ) :-
  775    ( memberchk(term_name(Tnm),Bogs) -> 
  776          Mess = 'Reporting term (~w): ~w',
  777          Mrgs = [Tnm,Derm]
  778          ; 
  779          Mess = 'Reporting term: ~w',
  780          Mrgs = [Derm]
  781    ),
  782    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  783    debug_message( Topic, Message, Args ).
  784debug_call_topic( var, DbgTerm, Bogs, Topic ) :-
  785    arg( 1, DbgTerm, Var ),
  786    arg( 2, DbgTerm, Val ),
  787    Mess = 'Variable: ~a, value: ~w',
  788    debug_call_message_opts( Mess, [Var,Val], Message, Args, Bogs ),
  789    debug_message( Topic, Message, Args ).
  790debug_call_topic( wrote, ForLoc, Bogs, Topic ) :-
  791    ( ForLoc = loc(Spec,Ext) -> true; Spec=ForLoc, Ext = '' ),
  792    catch( locate(Spec,Ext,Loc), Excp, true ),
  793    MessW = 'Wrote on file: ~p',
  794    debug_call_location_exception_message( Excp, write, Loc, MessW, Mess, Bogs, Mrgs ),
  795    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  796    debug_message( Topic, Message, Args ).
  797debug_call_topic( read, ForLoc, Bogs, Topic ) :-
  798     debug_call_topic( input, ForLoc, Bogs, Topic ).
  799debug_call_topic( input, ForLoc, Bogs, Topic ) :-
  800    ( ForLoc = loc(Spec,Ext) -> true; Spec=ForLoc, Ext = '' ),
  801    catch( locate(Spec,Ext,Loc), Excp, true ),
  802    MessW = 'Input from file: ~p',
  803    debug_call_location_exception_message( Excp, input, Loc, MessW, Mess, Bogs, Mrgs ),
  804    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  805    debug_message( Topic, Message, Args ).
  806debug_call_topic( task(Whc), Task, Bogs, Topic ) :-
  807    datime_readable( Readable ),
  808    debug_call_topic_time_which_readable( Whc, Whcable ),
  809    atomic_list_concat( [Readable,' ',Whcable,' task: ~w.'], Mess ),
  810    debug_call_message_opts( Mess, [Task], Message, Args, Bogs ),
  811    debug_message( Topic, Message, Args ).
  812debug_call_topic( start, Arg, Bogs, Topic ) :-
  813    Mess = 'Starting: ~w',
  814    ( Arg == true -> Rep = Topic; Rep = Arg ),
  815    debug_call_message_opts( Mess, [Rep], Message, Args, Bogs ),
  816    debug_message( Topic, Message, Args ).
  817debug_call_topic( end, Arg, Bogs, Topic ) :-
  818    Mess = 'Finished: ~w',
  819    ( Arg == true -> Rep = Topic; Rep = Arg ),
  820    debug_call_message_opts( Mess, [Rep], Message, Args, Bogs ),
  821    debug_message( Topic, Message, Args ).
  822debug_call_topic( pwd, Stage, Bogs, Topic ) :-
  823    working_directory( Pwd, Pwd ),
  824    ( Stage == false -> 
  825        Mess = 'Pwd: ~p', Mrgs = [Pwd]
  826        ;
  827        Mess = 'Pwd at, ~w, is: ~p', Mrgs = [Stage,Pwd]
  828    ),
  829    debug_call_message_opts( Mess, Mrgs, Message, Args, Bogs ),
  830    debug_message( Topic, Message, Args ).
  831debug_call_topic( ns_sel, Term, Bogs, Topic ) :-
  832    arg( 1, Term, Fst ),
  833    arg( 2, Term, Sec ),
  834    ( memberchk(sel_name(Trd),Bogs) ->
  835          Mess = 'Continuing with: ~w as the: ~w. From list: ~w',
  836          MArgs= [Fst,Trd,Sec]
  837          ;
  838          Mess = 'Continuing with: ~w from list: ~w',
  839          MArgs= [Fst,Sec]
  840    ),
  841    debug_call_message_opts( Mess, MArgs, Message, Args, Bogs ),
  842    debug_message( Topic, Message, Args ).
  843
  844debug_call_topic_enum( [], _I, _Len, _Topic ).
  845debug_call_topic_enum( [H|T], I, Len, Topic ) :-
  846    number_codes( I, ICs ),
  847    length( ICs, ICsLen ),
  848    PadLen is Len - ICsLen,
  849    findall( ' ', between(1,PadLen,_), Spcs ),
  850    atomic_list_concat( Spcs, '', Pad ),
  851    atomic_list_concat( [Pad,'~d.~w'], '', Mess ),
  852    debug_message( Topic, Mess, [I,H] ),
  853    J is I + 1,
  854    debug_call_topic_enum( T, J, Len, Topic ).
  855
  856debug_call_topic_list_delim( ListName, Topic, Std, Bogs ) :-
  857     debug_call_message_opts( Std, [ListName], Mess, Args, Bogs ), 
  858     debug_message( Topic, Mess, Args ).
  859
  860debug_call_topic_time_which_readable( Wch, Wchable ) :-
  861    debug_call_topic_time_which_readable_known( Wch, Wchable ),
  862    !.
  863debug_call_topic_time_which_readable( Wch, Wch ).
  864
  865debug_call_topic_time_which_readable_known( start, starting ).
  866debug_call_topic_time_which_readable_known( finish, finished ).
  867
  868debug_call_location_exception_message( Var, _Dir, Loc, MessI, MessO, Opts, Args ) :-
  869    var(Var),
  870    !,
  871    MessI = MessO,
  872    ( memberchk(path(abs),Opts) ->
  873               Args = [Loc]
  874               ;
  875               file_base_name( Loc, Arg ),
  876               Args = [Arg]
  877    ).
  878debug_call_location_exception_message( locate(cannot_locate(Spec,Ext)), Dir, _Loc, _MessI, Mess, _Opts, Args ) :-
  879    atomic_list_concat( ['Could not locate',Dir,'file specified by: ~w, and extensions: ~w'], ' ', Mess ),
  880    Args = [Spec,Ext].
  881debug_call_location_exception_message( Error, _Dir, _Loc, _MessI, _Mess, _Opts, _Args ) :-
  882    % fixme:
  883    throw( debug_call_caught(Error) ).
  884
  885debug_mtx_dims( [], 0, 0 ) :-
  886    !.
  887debug_mtx_dims( Rows, NRows, NCols ) :-
  888    length( Rows, NRows ),
  889    Rows = [Hdr|_],
  890    ( is_list(Hdr) -> length(Hdr,NCols); functor(Hdr,_,NCols) ).
  891
  892debug_message_prefixed( [], Standard, Standard ) :- !.
  893debug_message_prefixed( '', Standard, Standard ) :- !.
  894debug_message_prefixed( prefix(Pfx), Standard, Prefixed ) :-
  895     !,
  896     debug_message_prefixed( [prefix(Pfx)], Standard, Prefixed ).
  897debug_message_prefixed( [H|T], Standard, Prefixed ) :-
  898    memberchk( prefix(Pfx), [H|T] ),
  899    !,
  900    debug_message_prefixed_atom( Pfx, Standard, Prefixed ).
  901debug_message_prefixed( _, Standard, Standard ).
  902
  903debug_call_message_opts( Std, Srgs, Mess, Args, Opts ) :-
  904     debug_call_pred_in_opts_mess( Std, Srgs, Pess, Args, Opts ),
  905     debug_message_prefixed( Opts, Pess, Mess ).
  906
  907debug_call_pred_in_opts_mess( Std, Opt, Prefixed, Prgs, Bogs ) :-
  908     en_list( Opt, Opts ),
  909     ( debug_call_pred_in_opts(Pid, Bogs)  ->
  910          Pfx = 'Predicate: ~w',
  911          debug_message_prefixed_atom( Pfx, Std, Prefixed ),
  912          Prgs = [Pid|Opts]
  913          ;
  914          Prefixed = Std,
  915          Prgs = Opts
  916     ).
  917
  918debug_call_pred_in_opts( Pid, Opts ) :-
  919    memberchk( pred(Fun,Ar), Opts ),
  920    !,
  921    Fun/Ar = Pid.
  922debug_call_pred_in_opts( Pid, Opts ) :-
  923    memberchk( pred(Pid), Opts ).
  924
  925debug_message_prefixed_atom( Pfx, Standard, Prefixed ) :-
  926    sub_atom( Standard, 0, 1, Aft, Fst ),
  927    downcase_atom( Fst, Low ),
  928    sub_atom( Standard, 1, Aft, 0, Right ),
  929    atomic_list_concat( [Pfx,' ',Low,Right], Prefixed )