Solutions for Session 10

CLPR

The first exercises are simple 'type and see'-exercises. You can try them yourself.

The non-CLP program for the mortgage-problem looks as follows:

mg(P,0,_,_,P).
mg(P,T,I,MP,B) :-
	T>0,
        T1 is T-1,
        mg(P,T1,I,MP,B1),
	B is B1*(1+I)-MP.

The CLP program looks as follows:

:- use_module(library(clpr)).

mg_clp(P,T,_,_,B) :-
        {
            T = 0,
            B = P
        }.
mg_clp(P,T,I,MP,B) :-
        {
            T>0,
            T1 = T - 1,
	    B = B1*(1+I)-MP
        },
        mg_clp(P,T1,I,MP,B1).
Here are some queries:
?-  mg_clp(100,4,0.1,20,B).
B = 53.590000000000046 ? 
yes
?- mg(100,4,0.1,20,B).
B = 53.590000000000046 ? 
yes
As expected, there is no difference between both predicates when used with all arguments except B instantiated. Now what happens if we try to compute MP given all other arguments?
?- mg_clp(100,4,0.1,MP,0).
MP = 31.547080370609795 ? 
yes
?- mg(100,4,0.1,MP,0).
! Instantiation error in argument 2 of is/2
The CLP-predicate works fine. With the pure prolog predicate, however, we get an error. This is because of the line B is B1*(1+I)-MP: 'is' only works if all variables occuring in the right hand side are already instantiated and here MP is not instantiated yet. As a consequence, CLP-predicates are often more flexible (with respect to which arguments should be instantiated and which not) than pure prolog predicates.

CLPFD

:- use_module(library(clpfd)).

exactly(_El, [], 0).
exactly(El, [H|List], N) :-
    El #= H #<=> B,
    N #= M+B,
    exactly(El, List, M).