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 23usermessage_property( Dbg, Property ) :- 24 debug_call_message_property( Dbg, Property ).
?- debug_call_version( -V, -D ). V = 1:5:0, D = date(2022,12,29).
*/
113debug_call_version( 1:5:0, date(2022,12,29) ). 114 115:- use_module(library(apply)). % maplist/4,... 116:- use_module(library(lists)). % member/4,... 117:- use_module(library(debug)). % debug/1,... 118:- use_module(library(lib)). 119 120:- lib(source(debug_call), [homonyms(true),index(false)]). 121:- lib(stoics_lib:locate/3 ). 122:- lib(stoics_lib:en_list/2). 123:- lib(stoics_lib:message_report/3). 124:- lib(stoics_lib:datime_readable/1). 125:- lib(end(debug_call) ).
137debuc( Topic ) :- 138 debug( Topic ). 139debuc( Topic, Goal ) :- 140 debug_call( Topic, Goal ). 141debuc( Topic, Goal, Arg ) :- 142 debug_call( Topic, Goal, Arg ). 143debuc( Topic, Goal, Arg, Opts ) :- 144 debug_call( Topic, Goal, Arg, Opts ).
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],
167debug_call( Topic, Goal ) :- 168 debugging_topic( Topic ), 169 !, 170 debug_call_goal( Topic, Goal ). 171debug_call( _Topic, _Goal ). 172 173debug_call_goal( Topic, Moal ) :- 174 ( Moal = Mod:Goal -> true; Goal = Moal, Mod=user ), 175 functor( Goal, Functor, Arity ), 176 Extra is Arity + 2, 177 current_predicate( Mod:Functor/Extra ), 178 !, 179 ( call(Mod:Goal,Mess,Args) -> 180 debug( Topic, Mess, Args ) 181 ; 182 true 183 ). 184debug_call_goal( _Topic, Goal ) :- 185 ( call(Goal) -> true; true ).
201debug_chain( Topic, Then ) :- 202 en_list( Then, Thens ), 203 maplist( debug_chain(Topic), Thens, _Priors ). 204 205debug_chain( Topic, Then, Prior ) :- 206 debugging_topic( Topic ), 207 !, 208 debugging_status( Then, Prior ), 209 debug( Then ). 210debug_chain( _Topic, _Then, true ). 211 % setting 3rd to true is a bit presumptious of its uses later on
lib(debug)
does not create a record by inspecting the term (via expansion).
Particularly useful in sending uninstantiated Topics.
223debug_message( Topic, Mess, Args ) :-
224 Call =.. [debug,Topic,Mess,Args],
225 call( Call ).
lib(debug)
does not create a record by inspecting the term (via expansion).
Particularly useful in sending uninstantiated Topics.
237debugging_topic( Topic ) :-
238 Call =.. [debugging,Topic],
239 call( Call ).
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.
256debugging_status( Topic, Status ) :- 257 debugging_topic( Topic ), 258 !, 259 Status = true. 260debugging_status( _Topic, false ).
?- 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
289debug_set( false, Topic ) :- 290 nodebug( Topic ). 291debug_set( true, Topic ) :- 292 debug( Topic ).
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.
323debug_topic( Topic, Opts, Restore ) :- 324 memberchk( debug(Dbg), Opts ), 325 Dbg == true, 326 !, 327 debug_topic_restore( Topic, Restore ), 328 debug( Topic ). 329debug_topic( Topic, _Opts, Restore ) :- % becomes default under this implementation 330 debug_topic_restore( Topic, Restore ), 331 nodebug( Topic ). 332 333debug_topic_restore( Topic, Restore ) :- 334 debugging_topic( Topic ), 335 !, 336 Restore = true. 337debug_topic_restore( _Topic, false ).
?- debug_topic( true, example ).
351debug_topic( true, Topic ) :- 352 debug( Topic ). 353debug_topic( false, Topic ) :- 354 nodebug(Topic).
360debug_on( Topic ) :-
361 asserta( prolog_debug:debugging(Topic,true,[user_error])).
portray_clause(Term)
if we are debugging Topic.
370debug_portray( Topic, Term ) :- 371 debugging_topic( Topic ), 372 !, 373 portray_clause( Term ). 374debug_portray( _Topic, _Term ).
The main novelty is the introduction of abbreviated Goals, that print bespoke message 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
Predicate can be used to call arbitrary Goal and then print a message after it has successfull completed.
When Goal is a known abbreviation from those shown below, the Arg usually qualifies the output generated.
When Goal is of the form call(Goal)
, Arg will be passed to debug(Topic,Mess,Arg)
.
As of v2 the last two arguments of the /4 version of the predicate where switched from Pfx and Arg
to Arg and Opts. Opts pass arbitary things to Goal, each abbreviation Goal can demand different options.
All abbreviation Goal them can take =prefix(Pfx)
= which corresponds to Pfx in the old /4 verison.
Opts will be forced to be a list via en_list/2, Goal will know what todo with it.
As of v1.2 it can work as a replacement to debug/3.
With v1.3 the debuc/3 shorthand was introduced.
Goal in:
debug(Topic, Mess, Arg)
. (Goal is called in non-deterministic context.)call(Goal)
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.pred(Pid)
, the caller predicate, all(OrigOpts)
, shows all options,
internal(true)
, shows also '$' starting options.pred(Pid)
, the caller predicate, internal(true)
, shows also '$' starting options.arg(1)
) and its current instantiation (arg(2)
)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.
See file examples/exo.pl
for a test suit including at least one example from each shorthand call.
?- 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,'suv file',true)). Continuing with: suv file, as: suv-17.09.26.txg, from non singleton list: [suv-17.09.26.txg,suv-17.09.21.txg]
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, 'Messagging...', true ). Messagging... [[ EXCEPTION while printing message 'Messagging...' with arguments user:true: raised: format('too many arguments') ]] true. ?- debuc( ex, 'Messagging...', true ). % Messagging... true.
531debug_call( Topic, Goal, Arg ) :- 532 debug_call( Topic, Goal, Arg, [] ). 533 534debug_call( Topic, Goal, Arg, OptsPrv ) :- 535 debugging_topic( Topic ), 536 !, 537 en_list( OptsPrv, Opts ), 538 debugging_call( Topic, Goal, Arg, Opts ). 539debug_call( _Topic, _Goal, _Arg, _Opts ). 540 541debugging_call( Topic, Goal, Arg, Opts ) :- 542 debug_call_topic( Goal, Arg, Opts, Topic ), 543 !. 544debugging_call( Topic, call(Goal), Mess, Args ) :- 545 !, 546 call( Goal ), 547 debug_message( Topic, Mess, Args ). 548debugging_call( Topic, Goal, Mess, Args ) :- 549 compound( Goal ), 550 call( Goal ), 551 !, 552 debug_message( Topic, Mess, Args ). 553% 20.03.07: this makes debug_call/3 a replacement for debug/3... 554debugging_call( Topic, Mess, ArgsPrv, _DbgCallArgs ) :- 555 % as of SWI-Prolog 8.?.? there is an error thrown when true is used instead of [] as 3rd arg of debug/3 556 atomic( Mess ), 557 !, 558 ( ArgsPrv == true -> Args = []; en_list(ArgsPrv,Args) ), 559 debug( Topic, Mess, Args ). 560debugging_call( Topic, Goal, Mess, Args ) :- 561 Called = debug_call(Topic,Goal,Mess,Args), 562 message_report( 'failure ignored on: ~w', Called, warning ).
?- 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
596debug_consec( Topic, Mess, Args ) :- 597 Clrs = [blue,magenta], 598 debug_consec( Topic, Clrs, Mess, Args ). 599 600debug_consec( Topic, ClrS, Mess, Args ) :- 601 debugging_topic( Topic ), 602 !, 603 ( is_list(ClrS) -> Clrs = ClrS; Clrs = [ClrS] ), 604 debug_consec_topic( Topic, Clrs, Mess, Args ). 605debug_consec( _Topic, _Clrs, _Mess, _Args ). 606 607debug_consec_topic( Topic, Clrs, Mess, Args ) :- 608 with_output_to( atom(Topicat), write_term(Topic,[]) ), 609 ( nb_current(Topicat,Value) -> true; Value = 1 ), 610 ( nth1(Value, Clrs, Clr) -> true; Clrs = [Clr|_] ), 611 debug_consec_color( Topic, Clr, Mess, Args ), 612 length( Clrs, Len ), 613 ( Value < Len -> Next is Value + 1; Next is 1 ), 614 nb_setval( Topicat, Next ). 615 616debug_consec_color( Topic, Clr, Mess, Args ) :- 617 user:message_property( debug(_), color(Attrs) ), 618 !, 619 retractall( debug_call_message_property(debug(_),color(_)) ), 620 assert( debug_call_message_property(debug(_),color(fg(Clr))) ), 621 debug_message( Topic, Mess, Args ), 622 retractall( debug_call_message_property(debug(_),color(_)) ), 623 assert( debug_call_message_property(debug(_),color(Attrs)) ). 624debug_consec_color( Topic, Clr, Mess, Args ) :- 625 assert( debug_call_message_property(debug(_),color(fg(Clr))) ), 626 debug_message( Topic, Mess, Args ), 627 retractall( debug_call_message_property(debug(_),color(_)) ). 628 629debug_call_topic( info, Arg, Bogs, _Topic ) :- 630 ( (\+ var(Arg),Arg = Mess/Args) -> 631 true 632 ; 633 % fixme: not sure what to do here ? 634 Mess = Arg, 635 Args = [] 636 ), 637 % lib_message_report( Format, Args, Kind ) :- 638 debug_message_prefixed( Bogs, Mess, Prefixed ), 639 phrase('$messages':translate_message(debug(Prefixed,Args)), Lines), 640 print_message_lines(current_output, kind(informational), Lines). 641debug_call_topic( dims, NamesPrv/MtxsPrv, Bogs, Topic ) :- 642 ( is_list(NamesPrv) -> Names=NamesPrv, MtxsPrv=Mtxs, With = 'Dimensions for matrices, ' 643 ; [NamesPrv] = Names, [MtxsPrv]=Mtxs, With = 'Dimensions for matrix, ' 644 ), 645 debug_message_prefixed( Bogs, With, Prefixed ), 646 maplist( debug_mtx_dims, Mtxs, NRows, NCols ), 647 findall( PartM, (member(_,Names),PartM=' (~w) nR: ~d, nC: ~d.'), MParts ), 648 atomic_list_concat( MParts, '', Right ), 649 findall( [Name,NRow,NCol], (nth1(N,Names,Name),nth1(N,NRows,NRow),nth1(N,NCols,NCol)), NNest ), 650 flatten( NNest, Vars ), 651 atom_concat( Prefixed, Right, Message ), 652 debug_message( Topic, Message, Vars ). % do the messaging ! 653debug_call_topic( enum, InArg, Bogs, Topic ) :- 654 ( memberchk(prefix(Pfx),Bogs) -> true; Pfx = '' ), 655 ground( InArg ), 656 ( InArg = Left/Term -> true; Left = unnamed, Term = InArg ), 657 ( is_list(Term) -> 658 length( Term, Len ), 659 number_codes( Len, LenCs ), 660 length( LenCs, SpcLen ), 661 debug_call_topic_list_delim( Left, Topic, prefix(Pfx), 'Starting enumeration of list: ~w' ), 662 debug_call_topic_enum( Term, 1, SpcLen, Topic ), 663 debug_call_topic_list_delim( Left, Topic, prefix(Pfx), 'Ended enumeration of list: ~w' ) 664 ; 665 Term =.. Args, 666 length( Args, Len ), 667 number_codes( Len, LenCs ), 668 length( LenCs, SpcLen ), 669 debug_call_topic_list_delim( Left, Topic, prefix(Pfx), 'Starting enumeration of list: ~w' ), 670 debug_call_topic_enum( Args, 1, SpcLen, Topic ), 671 debug_call_topic_list_delim( Left, Topic, prefix(Pfx), 'Ended enumeration of list: ~w' ) 672 ). 673debug_call_topic( length, NamesPrv/ListsPrv, Bogs, Topic ) :- 674 ( is_list(NamesPrv) -> Names=NamesPrv, ListsPrv=Lists, With = 'Lengths for lists, ' 675 ; [NamesPrv] = Names, [ListsPrv]=Lists, With = 'Length for list, ' 676 ), 677 debug_message_prefixed( Bogs, With, Prefixed ), 678 maplist( length, Lists, Lengths ), 679 findall( ['~w: ~w',', '], member(_,Lengths), WsNest ), 680 flatten( WsNest, WsL ), 681 once( append(WsLComma,[_],WsL) ), 682 append( WsLComma, ['.'], WsLDot ), 683 atomic_list_concat( WsLDot, '', Right ), 684 atom_concat( Prefixed, Right, Message ), 685 findall( [Name,Length], (nth1(N,Names,Name),nth1(N,Lengths,Length)), NLNest ), 686 flatten( NLNest, NLs ), 687 debug_message( Topic, Message, NLs ). % do the messaging 688debug_call_topic( list, InArg, Bogs, Topic ) :- 689 ground( InArg ), 690 ( InArg = Left/List -> 691 ( Left = Hdr/Ftr -> true ; Hdr = Left, Ftr = '' ) 692 ; 693 List = InArg, Hdr = '', Ftr = '' 694 ), 695 ( memberchk(prefix(Pfx),Bogs) -> true; Pfx = '' ), 696 debug_call_topic_list_delim( Hdr, Topic, Pfx, 'Starting listing of list: ~w' ), 697 maplist( debug_message(Topic,'~w'), List ), 698 debug_call_topic_list_delim( Ftr, Topic, Pfx, 'Ended listing of list: ~w' ). 699debug_call_topic( odir, Odir, Bogs, Topic ) :- 700 ( exists_directory(Odir) -> 701 Mess = 'Output in directory: ~w' 702 ; 703 Mess = 'Output (claimed) in (non-existing) directory: ~w' 704 ), 705 debug_message_prefixed( Bogs, Mess, Prefixed ), 706 debug_message( Topic, Prefixed, [Odir] ). 707debug_call_topic( option, Opt, Bogs, Topic ) :- 708 ( memberchk(pred(Pid),Bogs) -> 709 Pess = 'Predicate: ~w, option selected: ~w', 710 Prgs = [Pid,Opt] 711 ; 712 Pess = 'Option selected: ~w', 713 Prgs = [Opt] 714 ), 715 ( (memberchk(all(OrgOpts),Bogs),is_list(OrgOpts)) -> 716 ( memberchk(internal(true),Bogs) -> 717 RdcOpts = OrgOpts 718 ; 719 findall( R, (member(R,OrgOpts),functor(R,F,_),\+(atom_concat('$',_,F))), RdcOpts ) 720 ), 721 atom_concat( Pess, ' from options: ~w', Mess ), 722 append( Prgs, [RdcOpts], Mrgs ) 723 ; 724 atom_concat( Pess, '.', Mess ), 725 Prgs = Mrgs 726 ), 727 debug_message_prefixed( Bogs, Mess, Prefixed ), 728 debug_message( Topic, Prefixed, Mrgs ). 729debug_call_topic( options, RepOpts, Bogs, Topic ) :- 730 ( memberchk(pred(Pid),Bogs) -> 731 Mess = 'Predicate: ~w, with options: ~w.', 732 Mrgs = [Pid,RdcOpts] 733 ; 734 Mess = 'Options: ~w.', 735 Mrgs = [RdcOpts] 736 ), 737 debug_message_prefixed( Bogs, Mess, Prefixed ), 738 ( memberchk(internal(true),Bogs) -> 739 RepOpts = RdcOpts 740 ; 741 findall( R, (member(R,RepOpts),functor(R,F,_),\+(atom_concat('$',_,F))), RdcOpts ) 742 ), 743 debug( Topic, Prefixed, Mrgs ). 744debug_call_topic( term, DbgTerm, Bogs, Topic ) :- 745 Mess = '~w', 746 debug_message_prefixed( Bogs, Mess, Prefixed ), 747 debug_message( Topic, Prefixed, [DbgTerm] ). 748debug_call_topic( var, DbgTerm, Bogs, Topic ) :- 749 arg( 1, DbgTerm, Var ), 750 arg( 2, DbgTerm, Val ), 751 Mess = 'Variable: ~a, value: ~w', 752 debug_message_prefixed( Bogs, Mess, Prefixed ), 753 debug_message( Topic, Prefixed, [Var,Val] ). 754debug_call_topic( wrote, ForLoc, Bogs, Topic ) :- 755 ( ForLoc = loc(Spec,Ext) -> true; Spec=ForLoc, Ext = '' ), 756 catch( locate(Spec,Ext,Loc), Excp, true ), 757 MessW = 'Wrote on file: ~p', 758 debug_call_location_exception_message( Excp, write, Loc, MessW, Mess, Bogs, Args ), 759 debug_message_prefixed( Bogs, Mess, Prefixed ), 760 debug_message( Topic, Prefixed, Args ). 761debug_call_topic( read, ForLoc, Bogs, Topic ) :- 762 debug_call_topic( input, ForLoc, Bogs, Topic ). 763debug_call_topic( input, ForLoc, Bogs, Topic ) :- 764 ( ForLoc = loc(Spec,Ext) -> true; Spec=ForLoc, Ext = '' ), 765 catch( locate(Spec,Ext,Loc), Excp, true ), 766 MessW = 'Input from file: ~p', 767 debug_call_location_exception_message( Excp, input, Loc, MessW, Mess, Bogs, Args ), 768 debug_message_prefixed( Bogs, Mess, Prefixed ), 769 debug_message( Topic, Prefixed, Args ). 770debug_call_topic( task(Whc), Task, Bogs, Topic ) :- 771 datime_readable( Readable ), 772 debug_call_topic_time_which_readable( Whc, Whcable ), 773 atomic_list_concat( [Readable,' ',Whcable,' task: ~w.'], Mess ), 774 debug_message_prefixed( Bogs, Mess, Prefixed ), 775 debug_message( Topic, Prefixed, [Task] ). 776debug_call_topic( start, Arg, Bogs, Topic ) :- 777 Mess = 'Starting: ~w', 778 debug_message_prefixed( Bogs, Mess, Prefixed ), 779 ( Arg == true -> Rep = Topic; Rep = Arg ), 780 debug_message( Topic, Prefixed, [Rep] ). 781% 25.10.07, use this as an example of how to have back compatibility to the new args order. 782debug_call_topic( end, Arg, Bogs, Topic ) :- 783 Mess = 'Finished: ~w', 784 debug_message_prefixed( Bogs, Mess, Prefixed ), 785 ( Arg == true -> Rep = Topic; Rep = Arg ), 786 debug_message( Topic, Prefixed, [Rep] ). 787debug_call_topic( pwd, Stage, Bogs, Topic ) :- 788 working_directory( Pwd, Pwd ), 789 ( Stage == false -> 790 Mess = 'Pwd: ~p', Args = [Pwd] 791 ; 792 Mess = 'Pwd at, ~w, is: ~p', Args = [Stage,Pwd] 793 ), 794 debug_message_prefixed( Bogs, Mess, Prefixed ), 795 debug_message( Topic, Prefixed, Args ). 796debug_call_topic( ns_sel, Term, Bogs, Topic ) :- 797 % ( Term = [Fst,Sec] -> true; arg(1,Term,Fst),arg(2,Term,Sec) ), 798 arg( 1, Term, Fst ), 799 arg( 2, Term, Sec ), 800 functor( Term, _Tname, Arity ), 801 ( Sec == [] -> 802 true % fixme: it will make more sense to throw an error if Sec = [] 803 ; 804 ( Sec = [_Single] -> 805 ( (Arity>3,arg(4,Term,true)) -> 806 ( (Arity>2,\+ arg(3,Term,false)) -> 807 arg(3,Term,Trd), 808 Mess= 'Continuing with: ~w as: ~w, (only match).', MArgs = [Trd,Fst] 809 ; 810 Mess= 'Continuing with only match: ~w.', MArgs = [Fst,Sec] 811 ) 812 ; 813 Mess = 'Continuing: ~w, from non singleton list: ~w', MArgs = [Fst,Sec] 814 ) 815 ; 816 ( (Arity>2,\+ arg(3,Term,false)) -> 817 arg(3,Term,Trd), 818 Mess = 'Continuing with: ~w, as: ~w, from non singleton list: ~w', MArgs = [Trd,Fst,Sec] 819 ; 820 Mess = 'Continuing: ~w, from non singleton list: ~w', MArgs = [Fst,Sec] 821 ) 822 ), 823 debug_message_prefixed( Bogs, Mess, Prefixed ), 824 debug_message( Topic, Prefixed, MArgs ) 825 ). 826 827debug_call_topic_enum( [], _I, _Len, _Topic ). 828debug_call_topic_enum( [H|T], I, Len, Topic ) :- 829 number_codes( I, ICs ), 830 length( ICs, ICsLen ), 831 PadLen is Len - ICsLen, 832 findall( ' ', between(1,PadLen,_), Spcs ), 833 atomic_list_concat( Spcs, '', Pad ), 834 atomic_list_concat( [Pad,'~d.~w'], '', Mess ), 835 debug_message( Topic, Mess, [I,H] ), 836 J is I + 1, 837 debug_call_topic_enum( T, J, Len, Topic ). 838 839debug_call_topic_list_delim( '', _Topic, _Pfx, _Mess ). 840debug_call_topic_list_delim( ListName, Topic, Pfx, Mess ) :- 841 debug_message_prefixed( Pfx, Mess, Prefixed ), 842 debug_message( Topic, Prefixed, [ListName] ). 843 844debug_call_topic_time_which_readable( Wch, Wchable ) :- 845 debug_call_topic_time_which_readable_known( Wch, Wchable ), 846 !. 847debug_call_topic_time_which_readable( Wch, Wch ). 848 849debug_call_topic_time_which_readable_known( start, starting ). 850debug_call_topic_time_which_readable_known( finish, finished ). 851 852debug_call_location_exception_message( Var, _Dir, Loc, MessI, MessO, Opts, Args ) :- 853 var(Var), 854 !, 855 MessI = MessO, 856 ( memberchk(path(abs),Opts) -> 857 Args = [Loc] 858 ; 859 file_base_name( Loc, Arg ), 860 Args = [Arg] 861 ). 862debug_call_location_exception_message( locate(cannot_locate(Spec,Ext)), Dir, _Loc, _MessI, Mess, _Opts, Args ) :- 863 atomic_list_concat( ['Could not locate',Dir,'file specified by: ~w, and extensions: ~w'], ' ', Mess ), 864 Args = [Spec,Ext]. 865debug_call_location_exception_message( Error, _Dir, _Loc, _MessI, _Mess, _Opts, _Args ) :- 866 % fixme: 867 throw( debug_call_caught(Error) ). 868 869debug_mtx_dims( [], 0, 0 ) :- 870 !. 871debug_mtx_dims( Rows, NRows, NCols ) :- 872 length( Rows, NRows ), 873 Rows = [Hdr|_], 874 ( is_list(Hdr) -> length(Hdr,NCols); functor(Hdr,_,NCols) ). 875 876debug_message_prefixed( [], Standard, Standard ) :- !. 877debug_message_prefixed( '', Standard, Standard ) :- !. 878debug_message_prefixed( prefix(Pfx), Standard, Prefixed ) :- 879 !, 880 debug_message_prefixed( [prefix(Pfx)], Standard, Prefixed ). 881debug_message_prefixed( [H|T], Standard, Prefixed ) :- 882 memberchk( prefix(Pfx), [H|T] ), 883 !, 884 debug_message_prefixed_atom( Pfx, Standard, Prefixed ). 885debug_message_prefixed( _, Standard, Standard ). 886 887debug_message_prefixed_atom( Pfx, Standard, Prefixed ) :- 888 sub_atom( Standard, 0, 1, Aft, Fst ), 889 downcase_atom( Fst, Low ), 890 sub_atom( Standard, 1, Aft, 0, Right ), 891 atomic_list_concat( [Pfx,' ',Low,Right], Prefixed )
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
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
*/
options_debug( Opts, Mess, Args )
only writes if Opts containsdebug(true)
. maybe this should be part ofpack(options)
lib(debug)
's expansions