Skip to content

Instantly share code, notes, and snippets.

@Anniepoo
Last active October 6, 2019 14:05
Show Gist options
  • Save Anniepoo/19dc2f650228ab8cf13072a4f0fe9f67 to your computer and use it in GitHub Desktop.
Save Anniepoo/19dc2f650228ab8cf13072a4f0fe9f67 to your computer and use it in GitHub Desktop.
:- chr_constraint temp_persist/2, collect_persist/2, get_persist/2.
get_all_persistant(S, Persistant) :-
chr_trace, chr_leash(-all),
get_persist(S, Persistant).
persistant(S, Data), get_persist(S, _) ==> temp_persist(S, Data).
get_persist(S, Persist) <=> collect_persist(S, Persist).
temp_persist(S, Data), collect_persist(S, Persist) <=>
Persist = [Data | Rest],
collect_persist(S, Rest).
collect_persist(_, L) <=> L=[].
====================
:- use_module(library(chr)).
:- chr_constraint foo/1, get_foo/1, recurse_foo/1.
load_it :-
foo(1),
foo(3),
foo(7).
% no backtrack get
foo(X) \ get_foo(Y) <=>
X = Y.
get_foo(_) <=> fail.
/* doesnt work
foo(X), recurse_foo(Y) ==>
Y = [ X | Rest ],
recurse_foo(Rest).
recurse_foo(_) <=> true.
*/
all_foos(L) :-
nb_setval(all_foos_val, []),
af(L).
af(_) :-
find_chr_constraint(foo(X)),
nb_getval(all_foos_val, OldL),
nb_setval(all_foos_val, [X | OldL]),
fail.
af(L) :-
nb_getval(all_foos_val, L).
:- chr_constraint gather_foos_together/1, get_thy_foos/1.
foo(X) \ gather_foos_together(Old) <=> gather_foos_together([X | Old]).
gather_foos_together(Foos), get_thy_foos(Y) ==> Foos = Y.
% get_thy_foos(_) <=> true. don't do this
:- chr_constraint get_foo_list/1.
foo(X), get_foo_list(L) ==>
L=[X|L1], get_foo_list(L1).
get_foo_list(L) <=> L=[].
:- chr_constraint one_foo/1, collect_foo/1.
% copy constraints to be collected
foo(X), get_foo(_) ==> one_foo(X).
get_foo(L) <=> collect_foo(L).
% collect and remove copied constraints
one_foo(X), collect_foo(L) <=>
L=[X|L1], collect_foo(L1).
collect_foo(L) <=> L=[].
Query with
?- halt.
anniepoo@anniesthinkpad:~/prologhelp$ swipl chrtest.pl
Welcome to SWI-Prolog (threaded, 64 bits, version 8.1.0)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.
For online help and background, visit http://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).
?- edit.
true.
?- load_it, collect_foo(X).
X = [],
foo(7),
foo(3),
foo(1).
?-
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment