% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(intercept): Intercept and signal interface} \label{sec:intercept} This library allows for creating an execution context (goal) which defines how calls to \predref{send_signal}{1} are handled. This library is typically used to fetch values from the context or process results depending on the context. For example, assume we parse a (large) file using a grammar (see \predref{phrase_from_file}{3}) that has some sort of \textit{record} structure. What should we do with the recognised records? We can return them in a list, but if the input is large this is a huge overhead if the records are to be asserted or written to a file. Using this interface we can use \begin{code} document --> record(Record), !, { send_signal(record(Record)) }, document. document --> []. \end{code} Given the above, we can assert all records into the database using the following query: \begin{code} ..., intercept(phrase_from_file(File, document), record(Record), assertz(Record)). \end{code} Or, we can collect all records in a list using \predref{intercept_all}{4}: \begin{code} ..., intercept_all(Record, phrase_from_file(File, document), record(Record), Records). \end{code} \vspace{0.7cm} \begin{description} \predicate{intercept}{3}{:Goal, ?Ball, :Handler} Run \arg{Goal} as \predref{call}{1}. If somewhere during the execution of \arg{Goal} \predref{send_signal}{1} is called with a \textit{Signal} that unifies with \arg{Ball}, run \arg{Handler} and continue the execution. This predicate is related to \predref{catch}{3}, but rather than aborting the execution of \arg{Goal} and running \arg{Handler} it continues the execution of \arg{Goal}. This construct is also related to \textit{delimited continuations} (see \predref{reset}{3} and \predref{shift}{1}). It only covers one (common) use case for delimited continuations, but does so with a simpler interface, at lower overhead and without suffering from poor interaction with the cut. Note that \arg{Ball} and \arg{Handler} are \textit{copied} before calling the (copy) of \arg{Handler} to avoid instantiation of \arg{Ball} and/or \arg{Handler} which can make a subsequent signal fail. \begin{tags} \tag{See also} \predref{intercept}{4}, \predref{reset}{3}, \predref{catch}{4}, \predref{broadcast_request}{1}. \tag{Compatibility} Ciao \end{tags} \predicate{intercept}{4}{:Goal, ?Ball, :Handler, +Arg} Similar to \predref{intercept}{3}, but the copy of \arg{Handler} is called as \verb$call(Copy,Arg)$, which allows passing large context arguments or arguments subject to unification or \textit{destructive assignment}. For example: \begin{code} ?- intercept(send_signal(x), X, Y=X). true. ?- intercept(send_signal(x), X, =(X), Y). Y = x. \end{code} \predicate{intercept_all}{4}{+Template, :Goal, ?Ball, -List} True when \arg{List} contains all instances of \arg{Template} that have been sent using \predref{send_signal}{1} where the argument unifies with \arg{Ball}. Note that backtracking in \arg{Goal} resets the \arg{List}. For example, given \begin{code} enum(I, Max) :- I =< Max, !, send_signal(emit(I)), I2 is I+1, enum(I2, Max). enum(_, _). \end{code} Consider the following queries \begin{code} ?- intercept_all(I, enum(1,6), emit(I), List). List = [1, 2, 3, 4, 5, 6]. ?- intercept_all(I, (between(1,3,Max),enum(1,Max)), emit(I), List). Max = 1, List = [1] ; Max = 2, List = [1, 2] ; Max = 3, List = [1, 2, 3]. \end{code} \begin{tags} \tag{See also} \predref{nb_intercept_all}{4} \end{tags} \predicate{nb_intercept_all}{4}{+Template, :Goal, ?Ball, -List} As \predref{intercept_all}{4}, but backtracing inside \arg{Goal} does not reset \arg{List}. Consider this program and the subsequent queries \begin{code} enum_b(F, T) :- forall(between(F, T, I), send_signal(emit(I))). \end{code} \begin{code} ?- intercept_all(I, enum_b(1, 6), emit(I), List). List = []. ?- nb_intercept_all(I, enum_b(1, 6), emit(I), List). List = [1, 2, 3, 4, 5, 6]. \end{code} \predicate{send_signal}{1}{+Signal} If this predicate is called from a sub-goal of \predref{intercept}{3}, execute the associated \textit{Handler} of the \predref{intercept}{3} environment. \begin{tags} \tag{Errors} \verb$unintercepted_signal(Signal)$ if there is no matching intercept environment. \end{tags} \predicate{send_silent_signal}{1}{+Signal} As \predref{send_signal}{1}, but succeed silently if there is no matching intercept environment. \end{description}