[ library(constraint_pools) | The ECLiPSe Libraries | Reference Manual | Alphabetic Index ]
create_constraint_pool(+PoolName, +NTypes, ++SpecList)
Create a "constraint pool" module
- PoolName
 
- Atom - the name of the pool to create
 
- NTypes
 
- Integer - the number of constraint types
 
- SpecList
 
- List of terms of the form Atom/Integer->Spec
 
Description
	Create a special type of module, called a "constraint pool".
	The module will contain:
	
	- simple definitions for the predicates listed in SpecList.
	    These definitions will just store or forward every call.
	
 - a logical store which can be used to store and retrieve
	    constraints, indexed by pool name and type. NTypes is the number
	    of different constraint types that this pool will support.
	
 - a logical store for one additional data item, for example
	    a solver handle.
	
 
	The possible specifications in SpecList are:
	
	- N/A -> store_as(Type)
 - 
	    will generate a definition for the predicate N/A such that every
	    call to N/A will be stored in the pool for the given Type.
	    
 
	- N/A -> ImplN/ImplA
 - 
	    will generate a definition for the predicate N/A such that every
	    call to N/A gets augmented with an additional argument (the pool
	    name), and mapped into a call to the implementation predicate
	    ImplN/ImplA. The implementation predicate must be visible from
	    where create_constraint_pool/3 is invoked.  The implementation
	    predicate's arity ImplA must be one higher than the the arity A
	    of the newly defined predicate.
	    
 
	
	Since a pool is a module, the pool name should normally not refer
	to an existing module. If it does, the existing module gets augmented
	with the pool predicates and pool stores.
    
Examples
    % We assume the implementation predicate:
    d(Data, Pool) :- writeln(d(Data, Pool)).
    % Create the pool:
    ?- create_constraint_pool(pool, 1, [c/2->store_as(1),d/1->d/2]).
    Yes (0.00s cpu)
    % Call the just created pool constraint d/1,
    % which leads to d/2 being invoked:
    ?- pool:d(hello).
    d(hello, pool)
    Yes (0.00s cpu)
    % Call the just created pool constraint c/2,
    % which will be stored. Then retrieve the store:
    ?- pool:c(a,b), collect_all_pool_constraints(pool, C).
    C = [c(a, b)]
    Yes (0.00s cpu)
    
See Also
is_constraint_pool / 1, pool_is_empty / 1, post_typed_pool_constraint / 3, collect_typed_pool_constraints / 3, collect_all_pool_constraints / 2, set_pool_item / 2, get_pool_item / 2