1:- module( store,
    2	[	store_new/1
    3	,	store_add//2
    4	,	store_get//2
    5	,	store_set//2
    6	,	store_upd//3
    7	,	store_apply//2
    8   ,  store_contains//2
    9	]).   10
   11:- meta_predicate store_apply(+,2,+,-).
   27:- use_module(library(rbtrees)).
   31store_new(store(0,A)) :- rb_empty(A).
   35store_add(V, N1, store(N1,T1), store(N2,T2)) :- rb_insert_new(T1,N1,V,T2), succ(N1,N2).
   39store_get(Ref, V, store(N,T), store(N,T)) :- rb_lookup(Ref,V,T).
   43store_contains(Ref, V, store(N,T), store(N,T)) :- rb_in(Ref,V,T).
   47store_set(Ref, V, store(N,T1), store(N,T2)) :- rb_update(T1,Ref,V,T2).
   53store_upd(Ref, V1, V2, store(N,T1), store(N,T2)) :- rb_update(T1,Ref,V1,V2,T2).
   59store_apply(Ref, Op, store(N,T1), store(N,T2)) :- rb_apply(T1,Ref,Op,T2).
   60
   61user:portray(store(N,_)) :- format('<store|~w items>',[N])
 
Supply of references to storage cells
This module provides a sort of store data structure - terms can be added to the store and then accessed using a reference term which is returned by store_add//2.
The type
ref(A)denotes the type of store references that point to terms of type A.All predicates except store_new/1 take store input and output arguments at the end so they can easily be used in a DCG with the store as threaded state variable. */