6.1 Attributed variables

Attributed variables provide a technique for extending the Prolog unification algorithm Holzbaur, 1990 by hooking the binding of attributed variables. There is little consensus in the Prolog community on the exact definition and interface to attributed variables. The SWI-Prolog interface is identical to the one realised by Bart Demoen for hProlog Demoen, 2002.

Binding an attributed variable schedules a goal to be executed at the first possible opportunity. In the current implementation the hooks are executed immediately after a successful unification of the clause-head or successful completion of a foreign language (built-in) predicate. Each attribute is associated to a module and the hook (attr_unify_hook/2) is executed in this module. The example below realises a very simple and incomplete finite domain reasoner.

:- module(domain,
          [ domain/2                    % Var, ?Domain
          ]).
:- use_module(library(ordsets)).

domain(X, Dom) :-
        var(Dom), !,
        get_attr(X, domain, Dom).
domain(X, List) :-
        list_to_ord_set(List, Domain),
        put_attr(Y, domain, Domain),
        X = Y.

%       An attributed variable with attribute value Domain has been
%       assigned the value Y

attr_unify_hook(Domain, Y) :-
        (   get_attr(Y, domain, Dom2)
        ->  ord_intersection(Domain, Dom2, NewDomain),
            (   NewDomain == []
            ->  fail
            ;   NewDomain = [Value]
            ->  Y = Value
            ;   put_attr(Y, domain, NewDomain)
            )
        ;   var(Y)
        ->  put_attr( Y, domain, Domain )
        ;   ord_memberchk(Y, Domain)
        ).

%       Translate attributes from this module to residual goals

attribute_goals(X) -->
        { get_attr(X, domain, List) },
        [domain(X, List)].

Before explaining the code we give some example queries:

?- domain(X, [a,b]), X = cfail
?- domain(X, [a,b]), domain(X, [a,c]).X = a
?- domain(X, [a,b,c]), domain(X, [a,c]).domain(X, [a, c])

The predicate domain/2 fetches (first clause) or assigns (second clause) the variable a domain, a set of values it can be unified with. In the second clause first associates the domain with a fresh variable and then unifies X to this variable to deal with the possibility that X already has a domain. The predicate attr_unify_hook/2 is a hook called after a variable with a domain is assigned a value. In the simple case where the variable is bound to a concrete value we simply check whether this value is in the domain. Otherwise we take the intersection of the domains and either fail if the intersection is empty (first example), simply assign the value if there is only one value in the intersection (second example) or assign the intersection as the new domain of the variable (third example). The nonterminal attribute_goals/3 is used to translate remaining attributes to user-readable goals that, when executed, reinstate these attributes.

attvar(@Term)
Succeeds if Term is an attributed variable. Note that var/1 also succeeds on attributed variables. Attributed variables are created with put_attr/3.
put_attr(+Var, +Module, +Value)
If Var is a variable or attributed variable, set the value for the attribute named Module to Value. If an attribute with this name is already associated with Var, the old value is replaced. Backtracking will restore the old value (i.e. an attribute is a mutable term. See also setarg/3). This predicate raises a representation error if Var is not a variable and a type error if Module is not an atom.
get_attr(+Var, +Module, -Value)
Request the current value for the attribute named Module. If Var is not an attributed variable or the named attribute is not associated to Var this predicate fails silently. If Module is not an atom, a type error is raised.
del_attr(+Var, +Module)
Delete the named attribute. If Var loses its last attribute it is transformed back into a traditional Prolog variable. If Module is not an atom, a type error is raised. In all other cases this predicate succeeds regardless whether or not the named attribute is present.
attr_unify_hook(+AttValue, +VarValue)
Hook that must be defined in the module an attributed variable refers to. Is is called after the attributed variable has been unified with a non-var term, possibly another attributed variable. AttValue is the attribute that was associated to the variable in this module and VarValue is the new value of the variable. Normally this predicate fails to veto binding the variable to VarValue, forcing backtracking to undo the binding. If VarValue is another attributed variable the hook often combines the two attribute and associates the combined attribute with VarValue using put_attr/3.
attr_portray_hook(+AttValue, +Var)
Called by write_term/2 and friends for each attribute if the option attributes(portray) is in effect. If the hook succeeds the attribute is considered printed. Otherwise Module = ... is printed to indicate the existence of a variable.
attribute_goals(+Var, -Gs, +GsRest)
This nonterminal, if it is defined in a module, is used by copy_term/3 to project attributes of that module to residual goals. It is also used by the toplevel to obtain residual goals after executing a query.

6.1.1 Special purpose predicates for attributes

Normal user code should deal with put_attr/3, get_attr/3 and del_attr/2. The routines in this section fetch or set the entire attribute list of a variables. Use of these predicates is anticipated to be restricted to printing and other special purpose operations.

get_attrs(+Var, -Attributes)
Get all attributes of Var. Attributes is a term of the form att(Module, Value, MoreAttributes), where MoreAttributes is [] for the last attribute.
put_attrs(+Var, -Attributes)
Set all attributes of Var. See get_attrs/2 for a description of Attributes.
copy_term(+Term, -Copy, -Gs)
Create a regular term Copy as a copy of Term (without any attributes), and a list Gs of goals that when executed reinstate all attributes onto Copy. The nonterminal attribute_goals/3, as defined in the modules the attributes stem from, is used to convert attributes to lists of goals.
copy_term_nat(+Term, -Copy)
As copy_term/2. Attributes however, are not copied but replaced by fresh variables.