% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \subsection{library(pengines): Pengines: Web Logic Programming Made Easy} \label{sec:pengines} \begin{tags} \tag{author} Torbjörn Lager and Jan Wielemaker \end{tags} The \file{library(pengines)} provides an infrastructure for creating Prolog engines in a (remote) pengine server and accessing these engines either from Prolog or JavaScript.\vspace{0.7cm} \begin{description} \predicate[det]{pengine_create}{1}{:Options} Creates a new pengine. Valid options are: \begin{description} \termitem{id}{-ID} \arg{ID} gets instantiated to the id of the created pengine. \arg{ID} is atomic. \termitem{alias}{+Name} The pengine is named \arg{Name} (an atom). A slave pengine (child) can subsequently be referred to by this name. \termitem{application}{+Application} \arg{Application} in which the pengine runs. See \predref{pengine_application}{1}. \termitem{server}{+URL} The pengine will run in (and in the Prolog context of) the pengine server located at \arg{URL}. \termitem{src_list}{+List_of_clauses} Inject a list of Prolog clauses into the pengine. \termitem{src_text}{+Atom_or_string} Inject the clauses specified by a source text into the pengine. \termitem{src_url}{+URL} Inject the clauses specified in the file located at \arg{URL} into the pengine. \termitem{src_predicates}{+List} Send the local predicates denoted by \arg{List} to the remote pengine. \arg{List} is a list of predicate indicators. \end{description} Remaining options are passed to \predref{http_open}{3} (meaningful only for non-local pengines) and \predref{thread_create}{3}. Note that for \predref{thread_create}{3} only options changing the stack-sizes can be used. In particular, do not pass the detached or alias options.. Successful creation of a pengine will return an \textit{event term} of the following form: \begin{description} \termitem{create}{ID, Term} \arg{ID} is the id of the pengine that was created. \arg{Term} is not used at the moment. \end{description} An error will be returned if the pengine could not be created: \begin{description} \termitem{error}{ID, Term} \arg{ID} is invalid, since no pengine was created. \arg{Term} is the exception's error term. \end{description} \predicate[det]{pengine_ask}{3}{+NameOrID, @Query, +Options} Asks pengine \arg{NameOrID} a query \arg{Query}. \arg{Options} is a list of options: \begin{description} \termitem{template}{+Template} \arg{Template} is a variable (or a term containing variables) shared with the query. By default, the template is identical to the query. \termitem{chunk}{+Integer} Retrieve solutions in chunks of \arg{Integer} rather than one by one. 1 means no chunking (default). Other integers indicate the maximum number of solutions to retrieve in one chunk. \termitem{bindings}{+Bindings} Sets the global variable '\$variable_names' to a list of \verb$Name = Var$ terms, providing access to the actual variable names. \end{description} Any remaining options are passed to \predref{pengine_send}{3}. Note that the predicate \predref{pengine_ask}{3} is deterministic, even for queries that have more than one solution. Also, the variables in \arg{Query} will not be bound. Instead, results will be returned in the form of \textit{event terms}. \begin{description} \termitem{success}{ID, Terms, Projection, Time, More} \arg{ID} is the id of the pengine that succeeded in solving the query. \arg{Terms} is a list holding instantiations of \arg{Template}. \arg{Projection} is a list of variable names that should be displayed. \arg{Time} is the CPU time used to produce the results and finally, \arg{More} is either \const{true} or \const{false}, indicating whether we can expect the pengine to be able to return more solutions or not, would we call \predref{pengine_next}{2}. \termitem{failure}{ID} \arg{ID} is the id of the pengine that failed for lack of a solutions. \termitem{error}{ID, Term} \arg{ID} is the id of the pengine throwing the exception. \arg{Term} is the exception's error term. \termitem{output}{ID, Term} \arg{ID} is the id of a pengine running the query that called \predref{pengine_output}{1}. \arg{Term} is the term that was passed in the first argument of \predref{pengine_output}{1} when it was called. \termitem{prompt}{ID, Term} \arg{ID} is the id of the pengine that called \predref{pengine_input}{2} and \arg{Term} is the prompt. \end{description} Defined in terms of \predref{pengine_send}{3}, like so: \begin{code} pengine_ask(ID, Query, Options) :- partition(pengine_ask_option, Options, AskOptions, SendOptions), pengine_send(ID, ask(Query, AskOptions), SendOptions). \end{code} \predicate[det]{pengine_next}{2}{+NameOrID, +Options} Asks pengine \arg{NameOrID} for the next solution to a query started by \predref{pengine_ask}{3}. Defined options are: \begin{description} \termitem{chunk}{+Count} Modify the chunk-size to \arg{Count} before asking the next set of solutions. \end{description} Remaining options are passed to \predref{pengine_send}{3}. The result of re-executing the current goal is returned to the caller's message queue in the form of \textit{event terms}. \begin{description} \termitem{success}{ID, Terms, Projection, Time, More} See \predref{pengine_ask}{3}. \termitem{failure}{ID} \arg{ID} is the id of the pengine that failed for lack of more solutions. \termitem{error}{ID, Term} \arg{ID} is the id of the pengine throwing the exception. \arg{Term} is the exception's error term. \termitem{output}{ID, Term} \arg{ID} is the id of a pengine running the query that called \predref{pengine_output}{1}. \arg{Term} is the term that was passed in the first argument of \predref{pengine_output}{1} when it was called. \termitem{prompt}{ID, Term} \arg{ID} is the id of the pengine that called \predref{pengine_input}{2} and \arg{Term} is the prompt. \end{description} Defined in terms of \predref{pengine_send}{3}, as follows: \begin{code} pengine_next(ID, Options) :- pengine_send(ID, next, Options). \end{code} \predicate[det]{pengine_stop}{2}{+NameOrID, +Options} Tells pengine \arg{NameOrID} to stop looking for more solutions to a query started by \predref{pengine_ask}{3}. \arg{Options} are passed to \predref{pengine_send}{3}. Defined in terms of \predref{pengine_send}{3}, like so: \begin{code} pengine_stop(ID, Options) :- pengine_send(ID, stop, Options). \end{code} \predicate[det]{pengine_abort}{1}{+NameOrID} Aborts the running query. The pengine goes back to state `2', waiting for new queries. \begin{tags} \tag{See also} \predref{pengine_destroy}{1}. \end{tags} \predicate[det]{pengine_destroy}{1}{+NameOrID} \nodescription \predicate[det]{pengine_destroy}{2}{+NameOrID, +Options} Destroys the pengine \arg{NameOrID}. With the option \verb$force(true)$, the pengine is killed using \predref{abort}{0} and \predref{pengine_destroy}{2} succeeds. \predicate[det]{pengine_self}{1}{-Id} True if the current thread is a pengine with \arg{Id}. \predicate[det]{pengine_application}{1}{+Application} Directive that must be used to declare a pengine application module. The module must not be associated to any file. The default application is \verb$pengine_sandbox$. The example below creates a new application \verb$address_book$ and imports the API defined in the module file \verb$adress_book_api.pl$ into the application. \begin{code} :- pengine_application(address_book). :- use_module(address_book:adress_book_api). \end{code} \predicate[nondet]{current_pengine_application}{1}{?Application} True when \arg{Application} is a currently defined application. \begin{tags} \tag{See also} \predref{pengine_application}{1} \end{tags} \predicate[nondet]{pengine_property}{2}{?Pengine, ?Property} True when \arg{Property} is a property of the given \arg{Pengine}. Enumerates all pengines that are known to the calling Prolog process. Defined properties are: \begin{description} \termitem{self}{ID} Identifier of the pengine. This is the same as the first argument, and can be used to enumerate all known pengines. \termitem{alias}{Name} \arg{Name} is the alias name of the pengine, as provided through the \const{alias} option when creating the pengine. \termitem{thread}{Thread} If the pengine is a local pengine, \arg{Thread} is the Prolog thread identifier of the pengine. \termitem{remote}{Server} If the pengine is remote, the URL of the server. \termitem{application}{Application} \arg{Pengine} runs the given application \termitem{module}{Module} Temporary module used for running the \arg{Pengine}. \termitem{destroy}{Destroy} \arg{Destroy} is \const{true} if the pengines is destroyed automatically after completing the query. \termitem{parent}{Queue} Message queue to which the (local) pengine reports. \termitem{source}{?SourceID, ?Source} \arg{Source} is the source code with the given \arg{SourceID}. May be present if the setting \verb$debug_info$ is present. \termitem{detached}{?Time} \arg{Pengine} was detached at \arg{Time}. \end{description} \predicate[det]{pengine_output}{1}{+Term} Sends \arg{Term} to the parent pengine or thread. \predicate[det]{pengine_debug}{2}{+Format, +Args} Create a message using \predref{format}{3} from \arg{Format} and \arg{Args} and send this to the client. The default JavaScript client will call \verb$console.log(Message)$ if there is a console. The predicate \predref{pengine_rpc}{3} calls \verb$debug(pengine(debug), '~w', [Message])$. The debug topic \verb$pengine(debug)$ is enabled by default. \begin{tags} \mtag{See also}- \predref{debug}{1} and \predref{nodebug}{1} for controlling the \verb$pengine(debug)$ topic \\- \predref{format}{2} for format specifications \end{tags} \qpredicate[det,multifile]{thread_pool}{create_pool}{1}{+Application}On demand creation of a thread pool for a pengine application. \predicate[det]{pengine_done}{0}{} Called from the pengine thread \verb$at_exit$ option. Destroys \textit{child} pengines using \predref{pengine_destroy}{1}. Cleaning up the Pengine is synchronised by the \verb$pengine_done$ mutex. See \predref{read_event}{6}. \predicate[semidet,multifile]{prepare_module}{3}{+Module, +Application, +Options} Hook, called to initialize the temporary private module that provides the working context of a pengine. This hook is executed by the pengine's thread. Preparing the source consists of three steps: \begin{enumerate} \item Add \arg{Application} as (first) default import module for \arg{Module} \item Call this hook \item Compile the source provided by the the \verb$src_text$ and \verb$src_url$ options \end{enumerate} \begin{arguments} \arg{Module} & is a new temporary module (see \predref{in_temporary_module}{3}) that may be (further) prepared by this hook. \\ \arg{Application} & (also a module) associated to the pengine. \\ \arg{Options} & is passed from the environment and should (currently) be ignored. \\ \end{arguments} \predicate[semidet,multifile]{prepare_goal}{3}{+Goal0, -Goal1, +Options} Pre-preparation hook for running \arg{Goal0}. The hook runs in the context of the pengine. Goal is the raw goal given to \textit{ask}. The returned \arg{Goal1} is subject to goal expansion (\predref{expand_goal}{2}) and sandbox validation (\predref{safe_goal}{1}) prior to execution. If this goal fails, \arg{Goal0} is used for further processing. \begin{arguments} \arg{Options} & provides the options as given to \textit{ask} \\ \end{arguments} \predicate[semidet,multifile]{not_sandboxed}{2}{+User, +Application} This hook is called to see whether the Pengine must be executed in a protected environment. It is only called after \predref{authentication_hook}{3} has confirmed the authentity of the current user. If this hook succeeds, both loading the code and executing the query is executed without enforcing sandbox security. Typically, one should: \begin{enumerate} \item Provide a safe user authentication hook. \item Enable HTTPS in the server or put it behind an HTTPS proxy and ensure that the network between the proxy and the pengine server can be trusted. \end{enumerate} \predicate[det]{pengine_pull_response}{2}{+Pengine, +Options} Pulls a response (an event term) from the slave \arg{Pengine} if \arg{Pengine} is a remote process, else does nothing at all. \predicate[det]{pengine_input}{2}{+Prompt, -Term} Sends \arg{Prompt} to the master (parent) pengine and waits for input. Note that \arg{Prompt} may be any term, compound as well as atomic. \predicate[det]{pengine_respond}{3}{+Pengine, +Input, +Options} Sends a response in the form of the term \arg{Input} to a slave (child) pengine that has prompted its master (parent) for input. Defined in terms of \predref{pengine_send}{3}, as follows: \begin{code} pengine_respond(Pengine, Input, Options) :- pengine_send(Pengine, input(Input), Options). \end{code} \predicate[det]{pengine_event_loop}{2}{:Closure, +Options} Starts an event loop accepting event terms sent to the current pengine or thread. For each such event E, calls \verb$ignore(call(Closure, E))$. A closure thus acts as a \textit{handler} for the event. Some events are also treated specially: \begin{description} \termitem{create}{ID, Term} The \arg{ID} is placed in a list of active pengines. \termitem{destroy}{ID} The \arg{ID} is removed from the list of active pengines. When the last pengine \arg{ID} is removed, the loop terminates. \termitem{output}{ID, Term} The predicate \predref{pengine_pull_response}{2} is called. \end{description} Valid options are: \begin{description} \termitem{autoforward}{+To} Forwards received event terms to slaves. \arg{To} is either \const{all}, \verb$all_but_sender$ or a Prolog list of NameOrIDs. [not yet implemented] \end{description} \predicate[nondet]{pengine_rpc}{2}{+URL, +Query} \nodescription \predicate[nondet]{pengine_rpc}{3}{+URL, +Query, +Options} Semantically equivalent to the sequence below, except that the query is executed in (and in the Prolog context of) the pengine server referred to by \arg{URL}, rather than locally. \begin{code} copy_term_nat(Query, Copy), % attributes are not copied to the server call(Copy), % executed on server at URL Query = Copy. \end{code} Valid options are: \begin{description} \termitem{chunk}{+Integer} Can be used to reduce the number of network roundtrips being made. See \predref{pengine_ask}{3}. \termitem{timeout}{+Time} Wait at most \arg{Time} seconds for the next event from the server. The default is defined by the setting \verb$pengines:time_limit$. \end{description} Remaining options (except the server option) are passed to \predref{pengine_create}{1}. \predicate[semidet,multifile]{prompt}{3}{+ID, +Prompt, -Term} Hook to handle \predref{pengine_input}{2} from the remote pengine. If the hooks fails, \predref{pengine_rpc}{3} calls \predref{read}{1} using the current prompt. \predicate[semidet,multifile]{output}{2}{+ID, +Term} Hook to handle \predref{pengine_output}{1} from the remote pengine. If the hook fails, it calls \predref{print}{1} on \arg{Term}. \predicate[det]{portray_blob}{2}{+Blob, +Options} Portray non-text blobs that may appear in output terms. Not really sure about that. Basically such terms need to be avoided as they are meaningless outside the process. The generated error is hard to debug though, so now we send them as \verb|'$BLOB'(Type)|. Future versions may include more info, depending on \arg{Type}. \predicate[semidet,multifile]{write_result}{3}{+Lang, +Event, +Dict} Hook that allows for different output formats. The core Pengines library supports \const{prolog} and various JSON dialects. The hook \predref{event_to_json}{3} can be used to refine the JSON dialects. This hook must be used if a completely different output format is desired. \predicate{add_error_details}{3}{+Error, +JSON0, -JSON} Add format error code and location information to an error. Also used by \file{pengines_io.pl}. \predicate[semidet,multifile]{event_to_json}{3}{+Event, -JSONTerm, +Lang} Hook that translates a Pengine event structure into a term suitable for \predref{reply_json}{1}, according to the language specification \arg{Lang}. This can be used to massage general Prolog terms, notably associated with \verb$success(ID, Bindings, Projection, Time, More)$ and \verb$output(ID, Term)$ into a format suitable for processing at the client side. \predicate[semidet,multifile]{authentication_hook}{3}{+Request, +Application, -User} This hook is called from the =/pengine/create= HTTP handler to discover whether the server is accessed by an authorized user. It can react in three ways: \begin{itemize} \item Succeed, binding \arg{User} to a ground term. The authentity of the user is available through \predref{pengine_user}{1}. \item Fail. The =/create= succeeds, but the pengine is not associated with a user. \item Throw an exception to prevent creation of the pengine. Two meaningful exceptions are: \begin{shortlist} \item \verb$throw(http_reply(authorise(basic(Realm))))$ Start a normal HTTP login challenge (reply 401) \item \verb$throw(http_reply(forbidden(Path)))$) Reject the request using a 403 repply. \end{shortlist} \end{itemize} \begin{tags} \tag{See also} \predref{http_authenticate}{3} can be used to implement this hook using default HTTP authentication data. \end{tags} \predicate[semidet]{pengine_user}{1}{-User} True when the pengine was create by an HTTP request that authorized \arg{User}. \begin{tags} \tag{See also} \predref{authentication_hook}{3} can be used to extract authorization from the HTTP header. \end{tags} \predicate[det]{pengine_event}{1}{?EventTerm} \nodescription \predicate[det]{pengine_event}{2}{?EventTerm, +Options} Examines the pengine's event queue and if necessary blocks execution until a term that unifies to Term arrives in the queue. After a term from the queue has been unified to Term, the term is deleted from the queue. Valid options are: \begin{description} \termitem{timeout}{+Time} \arg{Time} is a float or integer and specifies the maximum time to wait in seconds. If no event has arrived before the time is up \arg{EventTerm} is bound to the atom \const{timeout}. \termitem{listen}{+Id} Only listen to events from the pengine identified by \arg{Id}. \end{description} \end{description}