Version 8.1.9 introduces a uniform mechanism to listen to events that happen in the Prolog engine. It replaces and generalises prolog_event_hook/1 , a hook that was introduced to support the graphical debugger. The current implementation deals with debug, thread and dynamic database events. We expect this mechanism to deal with more hooks in the future.
first
(default) or last
and determines whether the new handler is expected as first or last.
Defined channels are described below. The Channel argument is the name of the term listed below. The arguments are added as additional arguments to the given Closure.
gc
thread.
This specific channel is used by clause_info/5
to reclaim source layout of reclaimed clauses. User applications should
typically use the PredicateIndicator channel.library(prolog_breakpoints)
thread_exit
channel that is
also used by the at_exit(Closure)
option of
thread_create/3.incremental
and monotonic
dynamic
predicates. Below is an example illustrating events from changing a
dynamic predicate.
:- dynamic p/1. :- prolog_listen(p/1, updated(p/1)). updated(Pred, Action, Context) :- format('Updated ~p: ~p ~p~n', [Pred, Action, Context]).
?- assert(p(a)). Updated p/1: assertz <clause>(0x55db261709d0) ?- retractall(p(_)). Updated p/1: retractall start(user:p(_12294)) Updated p/1: retract <clause>(0x55db261719c0) Updated p/1: retractall end(user:p(_12294))
retractall
. The
context argument is start(Head)
or end(Head)
.
asserta
,
assertz
or retract
. Context is the involved
clause. See transaction/1
and snapshot/1.