| Did you know ... | Search Documentation: |
| Pack nan_system_sources -- prolog/nan/system/sources.pl |
Part of Nan.System.Sources (nan/system/sources.pl)
Module sources (nan/system/sources.pl) provides
the predicates that implement Answer Sources in Prolog.
For code docs syntax and meaning see sources_docs.txt.
NOTE:
Ensures destruction of the source even if goal throws an error.
GExe() is nondet.GUse() is nondet.Example:
?- using_source(I, between(1, 2, I), _S,
( repeat,
source_next(_S, answer(_Det, the(I))),
(_Det == last -> !; true)
)).
I = 1 ;
I = 2.
Ensures destruction of the source even if goal throws an error.
GCom(Srcs, Src) is det.GUse() is nondet.Example:
?- [user].
parallel_com(Srcs, Src) :-
GRst = parallel_com__rst,
GNxt = parallel_com__nxt,
source_create_com(Srcs, GRst, GNxt, _, Src).
parallel_com__rst(Srcs, _, _) :-
maplist(source_reset, Srcs).
parallel_com__nxt(Srcs, _, _, Ans) :-
maplist(source_next_begin, Srcs),
foldl(parallel_com__nxt__do, Srcs, [], As),
Ans = answer(more, the(As)).
parallel_com__nxt__do(Src, As0, As) :-
source_next_end(Src, A),
append(As0, [A], As).
^Z
?- using_source(1, sleep(1), _S1,
using_source(2, sleep(1), _S2,
using_source_com([_S1, _S2], parallel_com, _S,
( time(source_next(_S, answer(more, the(Anss))))
)))). % Warm run
% 188 inferences, 0.000 CPU in 1.000 seconds (0% CPU, Infinite Lips)
Anss = [answer(last, the(1)), answer(last, the(2))].
GExe() is nondet.GRst(Srcs, Sta0, Sta1) is det.GNxt(Srcs, Sta0, Sta1, Ans) is det.Enforces determinism on GRst and GNxt.
For an example, see using_source_com/4.
Fails if no source exists.