
pengines.pl -- Pengines: Web Logic Programming Made EasyThe library(pengines) provides an infrastructure for creating Prolog engines in a (remote) pengine server and accessing these engines either from Prolog or JavaScript.
pengine_create(:Options) is detRemaining options are passed to http_open/3 (meaningful only for non-local pengines) and thread_create/3. Note that for 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 event term of the following form:
An error will be returned if the pengine could not be created:
translate_local_sources(+OptionsIn, -Options, +Module) is det[private]src_predicates and src_list options into
src_text. We need to do that anyway for remote pengines. For
local pengines, we could avoid this step, but there is very
little point in transferring source to a local pengine anyway as
local pengines can access any Prolog predicate that you make
visible to the application.
Multiple sources are concatenated to end up with a single src_text option.
pengine_send(+NameOrID, +Term) is det[private]pengine_send(NameOrID, Term, []).
pengine_send(+NameOrID, +Term, +Options) is det[private]Any remaining options are passed to http_open/3.
pengine_request(-Request) is det[private]idle_limit setting while using thread_idle/2 to minimis
resources.
pengine_reply(+Event) is det[private]
pengine_reply(+Queue, +Event) is det[private]
If the message cannot be sent within the idle_limit setting of
the pengine, abort the pengine.
pengine_ask(+NameOrID, @Query, +Options) is detOptions is a list of options:
false, the
Pengine goal is not executed using findall/3 and friends and
we do not backtrack immediately over the goal. As a result,
changes to backtrackable global state are retained. This is
similar that using set_prolog_flag(toplevel_mode, recursive).Name = Var terms, providing access to the actual variable
names.Any remaining options are passed to pengine_send/3.
Note that the predicate pengine_ask/3 is deterministic, even for queries that have more than one solution. Also, the variables in Query will not be bound. Instead, results will be returned in the form of event terms.
true or false, indicating whether we can expect the
pengine to be able to return more solutions or not, would we call
pengine_next/2.Defined in terms of pengine_send/3, like so:
pengine_ask(ID, Query, Options) :-
partition(pengine_ask_option, Options, AskOptions, SendOptions),
pengine_send(ID, ask(Query, AskOptions), SendOptions).
pengine_next(+NameOrID, +Options) is detchunk(false).Remaining options are passed to pengine_send/3. The result of re-executing the current goal is returned to the caller's message queue in the form of event terms.
Defined in terms of pengine_send/3, as follows:
pengine_next(ID, Options) :-
pengine_send(ID, next, Options).
pengine_stop(+NameOrID, +Options) is detDefined in terms of pengine_send/3, like so:
pengine_stop(ID, Options) :-
pengine_send(ID, stop, Options).
pengine_abort(+NameOrID) is det
pengine_destroy(+NameOrID) is det
pengine_destroy(+NameOrID, +Options) is detforce(true), the pengine
is killed using abort/0 and pengine_destroy/2 succeeds.thread(ThreadId)remote(URL)
pengine_register_local(+Id, +Thread, +Queue, +URL, +App, +Destroy) is det[private]
pengine_unregister(+Id) is det[private]
pengine_unregister(+Id)[private]http and the queue is the
message queue used to send events to the HTTP workers.
pengine_self(-Id) is det
protect_pengine(+Id, :Goal) is semidet[private]This also runs Goal if the Pengine no longer exists. This deals with Pengines terminated through destroy_or_continue/1.
pengine_application(+Application) is detpengine_sandbox. The example below creates a new application
address_book and imports the API defined in the module file
adress_book_api.pl into the application.
:- pengine_application(address_book). :- use_module(address_book:adress_book_api).
current_pengine_application(?Application) is nondet
pengine_property(?Pengine, ?Property) is nondetalias option when creating the pengine.true if the pengines is destroyed automatically
after completing the query.debug_info is present.
pengine_output(+Term) is det
pengine_debug(+Format, +Args) is detconsole.log(Message) if there is a console. The predicate
pengine_rpc/3 calls debug(pengine(debug), '~w', [Message]). The debug
topic pengine(debug) is enabled by default.
local_pengine_create(+Options)[private]
thread_pool:create_pool(+Application) is det[multifile]
create(+Queue, -Child, +Options, +URL, +Application) is det[private]
pengine_done is detat_exit option. Destroys child
pengines using pengine_destroy/1. Cleaning up the Pengine is
synchronised by the pengine_done mutex. See read_event/6.
pengine_main(+Parent, +Options, +Application)[private]
fix_streams is det[private]
pengine_prepare_source(:Application, +Options) is det[private]
prepare_module(+Module, +Application, +Options) is semidet[multifile]src_text and
src_url options
guarded_main_loop(+Pengine) is det[private]
solve(+Chunk, +Template, :Goal, +ID) is det[private]
set_projection(:Goal, +Bindings)[private]
filter_template(+Template0, +Bindings, -Template) is det[private]
more_solutions(+Pengine, +Choice, +State, +Time)[private]chunk solutions.next, but sets the new chunk-size to Count.
ask(+Pengine, :Goal, +Options)[private]chunk(N) option.
prepare_goal(+Pengine, +GoalIn, -GoalOut, +Options) is det[private]
Note that expand_goal(Module:GoalIn, GoalOut) is what we'd like
to write, but this does not work correctly if the user wishes to
expand X:Y while interpreting X not as the module in which
to run Y. This happens in the CQL package. Possibly we should
disallow this reinterpretation?
prepare_goal(+Goal0, -Goal1, +Options) is semidet[multifile]
pengine_not_sandboxed(+Pengine) is semidet[private]not_sandboxed(User, Application) must succeed.
not_sandboxed(+User, +Application) is semidet[multifile]
pengine_pull_response(+Pengine, +Options) is det
pengine_input(+Prompt, -Term) is det
pengine_respond(+Pengine, +Input, +Options) is detDefined in terms of pengine_send/3, as follows:
pengine_respond(Pengine, Input, Options) :-
pengine_send(Pengine, input(Input), Options).
send_error(+Error) is det[private]
replace_blobs(Term0, Term) is det[private]
remote_send_rec(+Server, +Action, +ID, +Params, -Reply, +Options)[private]
pengine_event(?EventTerm) is det[private]
pengine_event(?EventTerm, +Options) is det[private]Valid options are:
timeout.
pengine_event_loop(:Closure, +Options) is detignore(call(Closure, E)). A
closure thus acts as a handler for the event. Some events are also
treated specially:
Valid options are:
all,
all_but_sender or a Prolog list of NameOrIDs. [not yet
implemented]
pengine_rpc(+URL, +Query) is nondet
pengine_rpc(+URL, +Query, +Options) is nondetcopy_term_nat(Query, Copy), % attributes are not copied to the server call(Copy), % executed on server at URL Query = Copy.
Valid options are:
pengines:time_limit.Remaining options (except the server option) are passed to pengine_create/1.
prompt(+ID, +Prompt, -Term) is semidet[multifile]
output(+ID, +Term) is semidet[multifile]
http_pengine_create(+Request)[private]application/json and as
www-form-encoded. Accepted parameters:
| Parameter | Default | Comment |
|---|---|---|
| format | prolog | Output format |
| application | pengine_sandbox | Pengine application |
| chunk | 1 | Chunk-size for results |
| collate | 0 (off) | Join output events |
| solutions | chunked | If all, emit all results |
| ask | - | The query |
| template | - | Output template |
| src_text | "" | Program |
| src_url | - | Program to download |
| disposition | - | Download location |
Note that solutions=all internally uses chunking to obtain the results from the pengine, but the results are combined in a single HTTP reply. This is currently only implemented by the CSV backend that is part of SWISH for downloading unbounded result sets with limited memory resources.
Using chunk=false simulates the recursive toplevel. See
pengine_ask/3.
http_pengine_create(+Request, +Application, +Format, +OptionsDict)[private]
wait_and_output_result(+Pengine, +Queue, +Format, +TimeLimit, +Collate) is det[private]time_limit,
Pengine is aborted and the result is error(time_limit_exceeded,
_).
collect_events(+Pengine, +CollateTime, +Queue, +Deadline, +Max, -Events)[private]
create_wait_and_output_result(+Pengine, +Queue, +Format, +TimeLimit, +Dict) is det[private]disposition key to denote the
download location.
time_limit_exceeded(+Pengine, +Format)[private]
destroy_queue_from_http(+Pengine, +Event, +Queue) is semidet[private]
gc_abandoned_queues[private]
sync_destroy_queue_from_http(+Pengine, +Queue) is det[private]
sync_destroy_queue_from_pengine(+Pengine, +Queue)[private]pengine held.
read_event(+Pengine, +Request, +Format, +EventString, -Event) is det[private]pengine_done mutex.
event parameter or as a posted document.
discard_post_data(+Request) is det[private]
fix_bindings(+Format, +EventIn, +Bindings, -Event) is det[private]json(-s) Format from the variables in
the asked Goal. Variables starting with an underscore, followed
by an capital letter are ignored from the template.
json_lang(+Format) is semidet[private]
http_pengine_pull_response(+Request)[private]
http_pengine_abort(+Request)[private]
http_pengine_detach(+Request)[private]
http_pengine_destroy_all(+Request)[private]
http_pengine_ping(+Request)[private]status(Pengine, Stats) is created, where Stats
is the return of thread_statistics/2.
http_pengine_list(+Request)[private]
output_result(+Pengine, +Format, +EventTerm) is det[private]prolog, json or json-s.
portray_blob(+Blob, +Options) is det'$BLOB'(Type).
Future versions may include more info, depending on Type.
abort_pending_output(+Pengine) is det[private]
write_result(+Lang, +Event, +Dict) is semidet[multifile]prolog and various JSON dialects. The hook
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.
disable_client_cache[private]
add_error_details(+Error, +JSON0, -JSON)
add_error_code(+Error, +JSON0, -JSON) is det[private]code field to JSON0 of Error is an ISO error term. The error
code is the functor name of the formal part of the error, e.g.,
syntax_error, type_error, etc. Some errors carry more
information:
add_error_location(+Error, +JSON0, -JSON) is det[private]location property if the error can be associated with a
source location. The location is an object with properties file
and line and, if available, the character location in the line.
event_to_json(+Event, -JSONTerm, +Lang) is semidet[multifile]success(ID, Bindings, Projection, Time, More) and output(ID,
Term) into a format suitable for processing at the client side.
allowed(+Request, +Application) is det[private]forbidden header if contact is not allowed.
authenticate(+Request, +Application, -UserOptions:list) is det[private][user(User)], [] or
an exception.
authentication_hook(+Request, +Application, -User) is semidet[multifile]throw(http_reply(authorise(basic(Realm))))
Start a normal HTTP login challenge (reply 401)throw(http_reply(forbidden(Path))))
Reject the request using a 403 repply.
pengine_user(-User) is semidet
reply_options(+Request, +Methods) is semidet[private]
pengine_src_text(+SrcText, +Module) is det[private]
pengine_src_url(+URL, +Module) is det[private]The following predicates are exported, but not or incorrectly documented.
pengine_destroy(Arg1, Arg2)
pengine_event(Arg1, Arg2)
pengine_rpc(Arg1, Arg2, Arg3)