
prolog_clause.pl -- Get detailed source-information about a clauseThis module started life as part of the GUI tracer. As it is generally useful for debugging purposes it has moved to the general Prolog library.
The tracer library library(trace/clause) adds caching and dealing with
dynamic predicates using listing to XPCE objects to this. Note that
clause_info/4 as below can be slow.
clause_info(+ClauseRef, -File, -TermPos, -VarOffsets) is semidet
clause_info(+ClauseRef, -File, -TermPos, -VarOffsets, +Options) is semidet
Note that positions are character positions, i.e., not
bytes. Line endings count as a single character, regardless of
whether the actual ending is \n or =|\r\n|_.
Defined options are:
unify_term(+T1, +T2)
NOTE: Called directly from library(trace/clause) for the GUI
tracer.
read_term_at_line(+File, +Line, +Module, -Clause, -TermPos, -VarNames) is semidet[private]
open_source(+File, -Stream) is semidet[multifile]clause_property(ClauseRef, file(File)), prolog_clause:open_source(File, Stream)
make_varnames(+ReadClause, +DecompiledClause, +Offsets, +Names, -Term) is detvarnames(...) where each argument contains the name
of the variable at that offset. If the read Clause is a DCG rule,
name the two last arguments <DCG_list> and <DCG_tail>
This predicate calles the multifile predicate make_varnames_hook/5 with the same arguments to allow for user extensions. Extending this predicate is needed if a compiler adds additional arguments to the clause head that must be made visible in the GUI tracer.
unify_clause(+Read, +Decompiled, +Module, +ReadTermPos, -RecompiledTermPos)[private]This predicate calls the multifile predicate unify_clause_hook/5 with the same arguments to support user extensions.
unify_clause2(+Read, +Decompiled, +Module, +TermPosIn, -TermPosOut)[private]
inlined_unification(+BodyRead, +BodyCompiled, -BodyReadOut, -BodyCompiledOut, +HeadRead, +BodyPosIn, -BodyPosOut) is det[private]
inlineable_head_var(+Head, -Var) is nondet[private]
expand_failed(+Exception, +Term)[private]
unify_body(+Read, +Decompiled, +Module, +Pos0, -Pos)[private]Pos0 and Pos still include the term-position of the head.
does_not_dcg_after_binding(+ReadBody, +ReadPos) is semidet[private]
unify_goal(+Read, +Decompiled, +Module, +TermPosRead, -TermPosDecompiled) is semidet[multifile]
ubody(+Read, +Decompiled, +Module, +TermPosRead, -TermPosForDecompiled)[private]
conj(+GoalTerm, +PositionTerm, -GoalList, -PositionList)[private]
mkconj(+Decompiled, +Module, -Position, +ReadGoals, +ReadPositions)[private]
argpos(+N, +PositionTerm, -ArgPositionTerm) is det[private]
initialization_layout(+SourceLocation, ?InitGoal, -ReadGoal, -TermPos) is semidet
predicate_name(:Head, -PredName:string) is det
clause_name(+Ref, -Name)The following predicates are exported, but not or incorrectly documented.
clause_info(Arg1, Arg2, Arg3, Arg4, Arg5)