:- module(attrmod, [domain/2]). :- use_module(library(atts)). :- use_module(library(clpz)). :- attribute a/1. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ?- attrmod:put_atts(X,a(test)). attrmod:put_atts(X,a(test)). ?- attrmod:put_atts(X, a(n(1))), attrmod:put_atts(Y, a(n(2))), X = Y. X = Y, attrmod:put_atts(Y,a(n(3))). ?- attrmod:put_atts(X, a(n(1))), X = a. caught: error(type_error(variable,a),get_atts/2) ?- attrmod:put_atts(X, a(n(1))), X = 1. X = 1. ?- attrmod:put_atts(X, a(n(1))), X = 3. false. ?- attrmod:put_atts(X, a(n(1))), attrmod:put_atts(Y, a(n(2))), X = Y, X = 3. X = 3, Y = 3. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ %verify_attributes(X, Y, _) :- throw(cannot_unify(X,Y)). %verify_attributes(_, _, _) :- false. % verify_attributes(Var, Value, []) :- % get_atts(Var, a(n(A))), % get_atts(Value, a(n(B))), % step (1) % C #= A + B, % step (2) % put_atts(Value, a(n(C))). % step (3) % verify_attributes(Var, Value, []) :- % get_atts(Var, a(n(A))), % ( integer(Value) -> % Value =:= A % ; get_atts(Value, a(n(B))), % C #= A + B, % put_atts(Var, -a(n(_))), % put_atts(Value, a(n(C))) % ). :- use_module(library(ordsets)). :- use_module(library(dif)). :- attribute domain/1. verify_attributes(Var, Other, []) :- ( get_atts(Var, domain(Dom1)) -> ( var(Other), get_atts(Other, domain(Dom2)) -> ord_intersection(Dom1, Dom2, Dom), dif(Dom, []), ( Dom = [Value] -> Other = Value ; put_atts(Other, domain(Dom)) ) ; ord_memberchk(Other, Dom1) ) ; true ). domain(X, List) :- list_to_ord_set(List, Dom), put_atts(X, domain(Dom)).