1:- module(
    2       da_frame,
    3       [
    4           da_frame_stack/3,
    5           da_hidden_frame/1,
    6           da_frame_parent/2,
    7           da_frame_clause/2,
    8           da_frame_predicate_indicator/2,
    9           da_alternative/2,
   10           da_frame_alternative_frame/2,
   11           da_frame_parent_pc/2,
   12           da_frame_pc_stack/4,
   13           da_frame_pc_source_span/3,
   14           da_frame_clause_source_span/2,
   15           da_frame_port_source_span/3,
   16           da_frame_scopes/4,
   17           da_frame_evaluate/4,
   18           da_frame_variables_mapping/2,
   19           da_referenced_variables/2,
   20           da_frame_step_in_targets/4
   21       ]
   22   ).   23
   24:- use_module(source).   25:- use_module(clause).

DAP library module for reasoning about Prolog frames

This module contains predicates for retrieving information about Prolog frames for debugging purposes. A Prolog frame is a runtime artifact that encapsulates the execution of a single goal.

Each frame has a unique temporarly ID represented as an integer. The predicates in this module generally take a frame ID as their first argument and unify their second argument with information about the denoted frame which is relevant for debugging purposes.

See also
- prolog_frame_attribute/3
- da_frame_stack/2 */
   43:- meta_predicate da_frame_stack(+, 3, -).   44:- meta_predicate da_frame_pc_stack(+, +, 3, -).
 da_frame_stack(+FrameId, :Goal, -Frames) is det
Frames is unified with a list of StackFrame terms acquired by meta-calling Goal as call(Goal,Id, PC, StackFrame) for every non-hidden frame in the current execution stack starting after FrameId, with the frame's ID and saved PC as the first and second argument to Goal respectively.
See also
- da_frame_parent/2
- da_frame_parent_pc/2
   56:- det(da_frame_stack/3).   57da_frame_stack(Frame, Goal, Frames) :-
   58    da_frame_parent(Frame, Parent),
   59    da_frame_parent_pc(Frame, PC),
   60    da_frame_pc_stack(Parent, PC, Goal, Frames).
   61
   62da_frame_pc_stack(null, _, _, []) :- !.
   63da_frame_pc_stack(FrameId, _, Goal, Frames) :-
   64    da_hidden_frame(FrameId),
   65    !,
   66    da_frame_stack(FrameId, Goal, Frames).
   67da_frame_pc_stack(Frame, PC, Goal, [Head|Frames]) :-
   68    call(Goal, Frame, PC, Head),
   69    da_frame_stack(Frame, Goal, Frames).
 da_frame_parent(+Frame, -Parent) is det
Parent is unified with the parent frame of Frame, or with the atom null in case Frame is the top frame.
   77:- det(da_frame_parent/2).   78da_frame_parent(Frame, Parent) :-
   79    prolog_frame_attribute(Frame, parent, Parent),
   80    !.
   81da_frame_parent(_, null).
   82
   83
   84:- det(da_frame_non_hidden_parent/2).   85da_frame_non_hidden_parent(null, null) :- !.
   86da_frame_non_hidden_parent(FrameId, ParentFrameId) :-
   87    da_frame_parent(FrameId, ParentFrameId0),
   88    da_frame_parent_non_hidden_parent(ParentFrameId0, ParentFrameId).
   89
   90da_frame_parent_non_hidden_parent(null, null) :- !.
   91da_frame_parent_non_hidden_parent(ParentFrameId0, ParentFrameId) :-
   92    da_hidden_frame(ParentFrameId0),
   93    !,
   94    da_frame_non_hidden_parent(ParentFrameId0, ParentFrameId).
   95da_frame_parent_non_hidden_parent(ParentFrameId, ParentFrameId).
 da_frame_parent_pc(+Frame, -PC) is det
PC is unified with the program counter saved by Frame on behalf of the parent frame of Frame, or with the atom null in case Frame does not specify a saved program counter.

The saved program counter determines from which point in the parent frame execution will resume once Frame is finished.

See also
- da_frame_parent/2
- prolog_frame_attribute/3 section on the pc option for information regarding for which frames the saved program counter is not available.
  110:- det(da_frame_parent_pc/2).  111da_frame_parent_pc(Frame, PC) :-
  112    prolog_frame_attribute(Frame, pc, PC),
  113    da_frame_parent(Frame, Parent),
  114    \+ da_hidden_frame(Parent),
  115    !.
  116da_frame_parent_pc(_, null).
 da_hidden_frame(+Frame) is semidet
True when Frame ought to be hidden during debugging.
  122da_hidden_frame(Frame) :-
  123    prolog_frame_attribute(Frame, hidden, true), !.
  124da_hidden_frame(Frame) :-
  125    prolog_frame_attribute(Frame, goal, Goal),
  126    da_hidden_predicate(Goal), !.
  127
  128da_hidden_predicate(Goal) :- predicate_property(Goal, nodebug), !.
  129da_hidden_predicate(Goal) :- predicate_property(Goal, hidden), !.
  130da_hidden_predicate(swipl_debug_adapter:_).
 da_frame_predicate_indicator(+FrameId, -PredicateIndicator) is det
PredicateIndicator is unified with the qualified predicate indicator of the goal executed in frame FrameId.
  138:- det(da_frame_predicate_indicator/2).  139da_frame_predicate_indicator(FrameId, PredicateIndicator) :-
  140    prolog_frame_attribute(FrameId, predicate_indicator, PredicateIndicator).
 da_alternative(+ChoicePoint, -Alternative) is det
Alternative is unified with a term describing the location from which execution will be resumed in case the current goal fails, which is one of the following:
frame(AlternativeFrameId)
If ChoicePoint refers to an alternative frame, where AlternativeFrameId is the ID of the frame from which execution will resume in case the goal associated with the current frame fails,
jump(PC)
If ChoicePoint is an in-clause choice point, where PC is the program counter in the frame from which execution will resume is case the current goal fails or
clause(Clause)
If ChoicePoint refers to an alternative clause Clause
null
If ChoicePoint is none
  158:- det(da_alternative/2).  159da_alternative(ChoicePoint, Alternative) :-
  160    prolog_choice_attribute(ChoicePoint, type, Type),
  161    da_alternative(Type, ChoicePoint, Alternative).
  162
  163:- det(da_alternative/3).  164da_alternative(jump, ChoicePoint, jump(PC)) :-
  165    !,
  166    prolog_choice_attribute(ChoicePoint, pc, PC).
  167da_alternative(clause, ChoicePoint, clause(Clause)) :-
  168    !,
  169    prolog_choice_attribute(ChoicePoint, clause, Clause).
  170da_alternative(none, _, null) :- !.
  171da_alternative(debug, _, null) :- !.
  172da_alternative(catch, _, null) :- !.
  173da_alternative(top, _, null) :- !.
  174da_alternative(_, ChoicePoint, frame(Frame)) :-
  175    !,
  176    prolog_choice_attribute(ChoicePoint, frame, Frame).
 da_frame_alternative_frame(+FrameId, -AlternativeFrameId) is det
AlternativeFrameId is unified with the ID of the frame that will be tried if FrameId fails, or with the atom null if FrameId does not have an alternative frame.
  184:- det(da_frame_alternative_frame/2).  185da_frame_alternative_frame(FrameId, frame(AlternativeFrameId)) :-
  186    prolog_frame_attribute(FrameId, alternative, AlternativeFrameId),
  187    !.
  188da_frame_alternative_frame(_, null).
 da_frame_clause(+Frame, -ClauseRef) is det
ClauseRef is unified with a reference to the clause which Frame is executing, or with the atom null in case Frame is executing a foreign predicate.
  196:- det(da_frame_clause/2).  197da_frame_clause(Frame, ClauseRef) :-
  198    (   prolog_frame_attribute(Frame, clause, ClauseRef)
  199    ->  true
  200    ;   prolog_frame_attribute(Frame, goal, Goal),
  201        qualified(Goal, Module, UGoal),
  202        (   predicate_property(Module:UGoal, interpreted)
  203        ->  (   clause(Module:UGoal, _Body, ClauseRef)
  204            ->  true
  205            ;   functor(UGoal, Functor, Arity),
  206                functor(UGoalTemplate, Functor, Arity),
  207                clause(Module:UGoalTemplate, _Body, ClauseRef), !
  208            )
  209        ;   ClauseRef = null
  210        )
  211    ).
  212
  213:- det(da_frame_pc_source_span/3).  214da_frame_pc_source_span(_, null, null) :- !.
  215da_frame_pc_source_span(FrameId, PC, SourceSpan) :-
  216    da_frame_clause(FrameId, ClauseRef),
  217    da_clause_source_span(ClauseRef, SourceSpan, [pc(PC)]).
  218
  219:- det(da_frame_port_source_span/3).  220da_frame_port_source_span(FrameId, Port, SourceSpan) :-
  221    da_port_parent_pc(Port, PC),
  222    !,
  223    da_frame_parent_port_source_span(FrameId, FrameId, PC, Port, SourceSpan).
  224da_frame_port_source_span(FrameId, Port, SourceSpan) :-
  225    da_frame_parent_pc(FrameId, ParentPC),
  226    da_frame_parent_pc_source_span(FrameId, ParentPC, Port, SourceSpan).
  227
  228da_port_parent_pc(cut_call(PC), PC) :- !.
  229da_port_parent_pc(cut_exit(PC), PC) :- !.
  230da_port_parent_pc(redo(0)     , _ ) :- !, false.
  231da_port_parent_pc(redo(PC)    , PC) :- !.
  232
  233da_frame_parent_pc_source_span(FrameId, null, Port, SourceSpan) :-
  234    !,
  235    da_frame_port_clause_source_span(FrameId, Port, SourceSpan).
  236da_frame_parent_pc_source_span(FrameId, ParentPC, Port, SourceSpan) :-
  237    da_frame_parent(FrameId, ParentFrameId),
  238    da_frame_parent_port_source_span(FrameId, ParentFrameId, ParentPC, Port, SourceSpan).
  239
  240da_frame_port_clause_source_span(FrameId, Port, SourceSpan) :-
  241    da_frame_clause(FrameId, ClauseRef),
  242    da_clause_source_span(ClauseRef, SourceSpan, [port(Port)]).
  243
  244da_frame_clause_source_span(FrameId, SourceSpan) :-
  245    da_frame_clause(FrameId, ClauseRef),
  246    da_clause_source_span(ClauseRef, SourceSpan).
  247
  248:- det(da_frame_parent_port_source_span/5).  249da_frame_parent_port_source_span(FrameId, null, _ParentPC, Port, SourceSpan) :-
  250    !,
  251    da_frame_port_clause_source_span(FrameId, Port, SourceSpan).
  252da_frame_parent_port_source_span(FrameId, _ParentFrameId, _ParentPC, unify, SourceSpan) :-
  253    !,
  254    da_frame_clause(FrameId, ClauseRef),
  255    da_clause_source_span(ClauseRef, SourceSpan, [port(unify)]).
  256da_frame_parent_port_source_span(_FrameId, ParentFrameId, ParentPC, Port, SourceSpan) :-
  257    da_frame_clause(ParentFrameId, ParentClauseRef),
  258    da_clause_source_span(ParentClauseRef, SourceSpan, [pc(ParentPC), port(Port)]).
  259
  260
  261:- det(da_frame_scopes/4).  262da_frame_scopes(ActiveFrameId, ActiveFrameId, Port, Scopes) :-
  263    !,
  264    da_active_frame_scopes(ActiveFrameId, Port, Scopes).
  265da_frame_scopes(FrameId, _ActiveFrameId, _Port, Scopes) :-
  266    da_stack_frame_scopes(FrameId, Scopes).
  267
  268da_stack_frame_scopes(FrameId, [ scope(Name, ArgumentsRef, SourceSpan),
  269                                 scope("Local Bindings", LocalsRef, SourceSpan)
  270                               ]
  271                     ) :-
  272    da_frame_variables_reference_type(FrameId, ArgumentsRef, arguments),
  273    da_frame_variables_reference_type(FrameId, LocalsRef, locals),
  274    da_frame_clause_source_span(FrameId, SourceSpan),
  275    da_frame_predicate_indicator(FrameId, PI),
  276    format(string(Name), "~w Arguments", PI).
  277
  278da_active_frame_scopes(FrameId, unify, Scopes) :-
  279    !,
  280    da_stack_frame_scopes(FrameId, Scopes).
  281da_active_frame_scopes(FrameId, Port, [ scope(Name, ArgumentsRef, ArgumentsSpan),
  282					scope("Local Bindings", LocalsRef, LocalsSpan)
  283                                      ]
  284                      ) :-
  285    !,
  286    da_frame_non_hidden_parent(FrameId, ParentFrameId),
  287    (   ParentFrameId == null
  288    ->  da_frame_variables_reference_type(FrameId, LocalsRef, locals),
  289        da_frame_port_source_span(FrameId, Port, LocalsSpan)
  290    ;   da_frame_variables_reference_type(ParentFrameId, LocalsRef, locals),
  291        da_frame_clause_source_span(ParentFrameId, LocalsSpan)
  292    ),
  293    da_frame_variables_reference_type(FrameId, ArgumentsRef, arguments),
  294    da_frame_port_source_span(FrameId, Port, ArgumentsSpan),
  295    da_frame_predicate_indicator(FrameId, PI),
  296    format(string(Name), "~w Arguments", PI).
  297
  298
  299:- use_module(library(clpfd)).  300
  301:- det(da_frame_variables_reference_type/3).  302da_frame_variables_reference_type(FrameId, VariablesRef, Type) :-
  303    da_variables_reference_frame_type_id(VariablesRef, FrameId, TypeId),
  304    da_scope_type_id(Type, TypeId).
  305
  306da_variables_reference_frame_type_id(VariablesRef, FrameId, TypeId) :-
  307    TypeId in 0..2,
  308    VariablesRef #= (FrameId * 4) + TypeId.
  309
  310da_scope_type_id(arguments, 0) :- !.
  311da_scope_type_id(locals, 1) :- !.
  312da_scope_type_id(cached, 2).
  313
  314:- det(da_referenced_variables/2).  315da_referenced_variables(VariablesRef, Variables) :-
  316    da_frame_variables_reference_type(FrameId, VariablesRef, Type),
  317    (   Type == cached
  318    ->  da_variables_compound_arguments(Variables0, FrameId),
  319        indexed_arguments(1, Variables0, Variables)
  320    ;   da_frame_clause(FrameId, ClauseRef),
  321        (   ClauseRef == null
  322        ->  da_frame_goal_arity(FrameId, Arity),
  323            findall('_', between(1, Arity, _), Args),
  324            compound_name_arguments(VarNames, varnames, Args)
  325        ;   da_clause_variable_names(ClauseRef, VarNames)
  326        ),
  327        da_frame_variables(FrameId, Type, VarNames, Variables)
  328    ).
  329
  330:- thread_local da_variables_compound_arguments/2.  331
  332da_tracer_cached_compound_arguments(Arguments, Ref) :-
  333    (   da_variables_compound_arguments(_, Ref0)
  334    ->  succ(Ref0, Ref)
  335    ;   Ref = 1
  336    ),
  337    asserta(da_variables_compound_arguments(Arguments, Ref)).
  338
  339:- det(indexed_arguments/3).  340indexed_arguments(_, [], []) :- !.
  341indexed_arguments(I0, [H0|T0], [variable(Name, H, ChildrenReference)|T]) :-
  342    indexed_argument_name(I0, Name),
  343    da_term_factorized(H0, ChildrenReference, H),
  344    succ(I0, I1),
  345    indexed_arguments(I1, T0, T).
  346
  347indexed_argument_name(I, N) :-
  348    format(atom(N), "arg(~w)", [I]).
  349
  350da_term_factorized(Var, 0, Name) :-
  351    var(Var), format(string(Name), "~w", [Var]),
  352    !.
  353da_term_factorized([], 0, "[]") :- !.
  354da_term_factorized(List, Ref, "[...]") :-
  355    is_list(List),
  356    !,
  357    da_tracer_cached_compound_arguments(List, Ref0),
  358    Ref is (Ref0 << 2) + 2.
  359da_term_factorized(Compound, Ref, Name) :-
  360    compound(Compound),
  361    !,
  362    compound_name_arguments(Compound, Functor, Arguments),
  363    length(Arguments, Arity),
  364    format(atom(Name), '~w/~w', [Functor, Arity]),
  365    da_tracer_cached_compound_arguments(Arguments, Ref0),
  366    Ref is (Ref0 << 2) + 2.
  367da_term_factorized(Term0, 0, Term) :-
  368    term_string(Term0, Term).
  369
  370:- det(da_frame_variables/4).  371da_frame_variables(Frame, Type, VarNames, Variables) :-
  372    da_frame_goal_arity(Frame, Arity),
  373    da_frame_arity_variables(Frame, Arity, Type, VarNames, Variables).
  374
  375:- det(da_frame_goal_arity/2).  376da_frame_goal_arity(FrameId, Arity) :-
  377    prolog_frame_attribute(FrameId, predicate_indicator, PI),
  378    qualified(PI, _, _Functor/Arity).
  379
  380da_frame_arity_variables(_, _, _, varnames, []) :-
  381    % clause has no variables at all, hence VarNames is an atom
  382    !.
  383da_frame_arity_variables(_, 0, arguments, _, []) :- !.
  384da_frame_arity_variables(Frame, Arity, arguments, VarNames, Variables) :-
  385    !,
  386    da_frame_arguments(Frame, 1, Arity, VarNames, Variables).
  387da_frame_arity_variables(Frame, Arity, locals, VarNames, Variables) :-
  388    !,
  389    succ(Arity, I),
  390    da_frame_locals(Frame, I, VarNames, Variables).
  391
  392:- det(da_frame_arguments/5).  393da_frame_arguments(Frame, I, Arity, VarNames, Variables) :-
  394    (   I =< Arity
  395    ->  arg(I, VarNames, Name0),
  396        (   Name0 == '_'
  397        ->  indexed_argument_name(I, Name)
  398        ;   Name = Name0
  399        ),
  400        prolog_frame_attribute(Frame, argument(I), Value0),
  401        da_term_factorized(Value0, ChildrenReference, Value),
  402        Variables = [variable(Name, Value, ChildrenReference)|T],
  403        NI is I + 1,
  404        da_frame_arguments(Frame, NI, Arity, VarNames, T)
  405    ;   Variables = []
  406    ).
  407
  408da_frame_locals(Frame, I, VarNames, Variables) :-
  409    (   arg(I, VarNames, Name0)
  410    ->  (   Name0 == '_'
  411        ->  indexed_argument_name(I, Name)
  412        ;   Name = Name0
  413        ),
  414        (   prolog_frame_attribute(Frame, argument(I), Value0)
  415        ->  da_term_factorized(Value0, ChildrenReference, Value)
  416        ;   da_term_factorized(_, ChildrenReference, Value)
  417        ),
  418        Variables = [variable(Name, Value, ChildrenReference)|T],
  419        NI is I + 1,
  420        da_frame_locals(Frame, NI, VarNames, T)
  421    ;   Variables = []
  422    ).
  423
  424
  425:- det(da_frame_evaluate/4).  426da_frame_evaluate(FrameId, SourceTerm, Result, Bindings) :-
  427    read_term_from_atom(SourceTerm, Goal, [variable_names(Bindings)]),
  428    da_frame_clause(FrameId, ClauseRef),
  429    da_clause_variable_names(ClauseRef, ClauseVarNames),
  430    da_frame_unify_variables(FrameId, ClauseVarNames, Bindings),
  431    da_evaluate(Goal, Result).
  432
  433
  434:- det(da_evaluate/2).  435da_evaluate(Goal, Result) :-
  436    catch(Goal, Result, true),
  437    !,
  438    (   var(Result)
  439    ->  Result = true
  440    ;   true
  441    ).
  442da_evaluate(_, false).
  443
  444
  445:- det(da_frame_unify_variables/3).  446da_frame_unify_variables(_FrameId, _ClauseVarNames, [               ]) :- !.
  447da_frame_unify_variables( FrameId,  ClauseVarNames, [VarName=Value|T]) :- !,
  448    (   arg(I, ClauseVarNames, VarName)
  449    ->  prolog_frame_attribute(FrameId, argument(I), Value),
  450        da_frame_unify_variables(FrameId, ClauseVarNames, T)
  451    ;   true
  452    ),
  453    da_frame_unify_variables(FrameId, ClauseVarNames, T).
  454
  455
  456da_frame_variables_mapping(FrameId, Map) :-
  457    da_frame_clause(FrameId, ClauseRef),
  458    da_clause_variable_names(ClauseRef, ClauseVarNames),
  459    (   ClauseVarNames == varnames
  460    ->  Map = []
  461    ;   findall(Name=Value,
  462                (   arg(I, ClauseVarNames, Name),
  463                    prolog_frame_attribute(FrameId, argument(I), Value)
  464                ),
  465                Map)
  466    ).
  467
  468
  469da_frame_step_in_targets(FrameId, FrameId, Choice, [step_in_target(0, null)|Targets]) :-
  470    !,
  471    da_alternative(Choice, Alternative),
  472    da_alternative_step_in_targets(Alternative, Targets).
  473da_frame_step_in_targets(_, _, _, []).
  474
  475
  476da_alternative_step_in_targets(null, []) :- !.
  477da_alternative_step_in_targets(Alt, [step_in_target(1, Alt)])