1% Stache :-{ Stash That Actually Can Handle Existentials
    2
    3:- module(stache, [
    4   stash/1,
    5   unstash/1,
    6   rummage/1,
    7   rummage_lazy/1
    8]).    9
   10:- use_module(library(chr)).   11
   12% TODO we only use these constraints with term_state/2, so it would be more
   13% efficient to inline, e.g. stash/2, rummage/2, etc.
   14% But if term expansion cooperates with CHR that would be even better.
   15:- chr_constraint
   16   stash/1, % Assume
   17   unstash/1, % Retract
   18   rummage/1, % Greedy lookup
   19   rummage_lazy/1. % Lazy lookup
   20
   21% Retract a single assumption (uses ==, not =)
   22unstash(A), stash(A) <=> true.
   23% unstash(_) <=> fail. % Optionally disallow preemptive retraction.
   24
   25% Greedy rummage: stack solutions up-front to avoid choice point.
   26rummage(A), stash(B) <=> unifiable(A,B,_) | (rummage(A) ; A=B), stash(B).
   27rummage(_)           <=> fail.
   28
   29% Lazy rummage: lower latency and space usage, but leaves choice point.
   30rummage_lazy(A), stash(B) <=> (A=B ; rummage_lazy(A)), stash(B).
   31rummage_lazy(_)