Accessing coefficients in a numerical expression (clpr)

53 Views Asked by At

I have some clauses where the head represents the names and values of a set of variables in a linear equation and the body the actual equation. Like so:

:-use_module(library(clpr)).    
relation(
        independents([
            var(x1, X1),
            var(x2, X2),
            var(x3, X3)
        ]),
        dependent(
            var(y, Y)
        )
    ):- {Y = 3 + 0.5 * X1 + 0.6 * X2 + 0.7 * X3}.

Is there a straightforward way to (indirectly) get the coefficients for this equation? I.e. a rule which returns coefficient(VARNAME, COEFFICIENT) e.g. coefficient(x1, 0.5), coefficient(x2, 0.6) and so on.

I know this might seem like a stupid question given that it would be easy to just put all coefficients in the head of the clause. But in my application i want the head of these clauses to strictly show the values of each variable (and not their coefficients). I.e. to avoid ambiguity.

My current solution is a convoluted and unelegant one involving member/2, subtract/3, maplist/2 and setting X1, X2, X3 to one or zero to figure out each slope.

Related question: Representing linear functions in prolog

Thanks!

/JC

1

There are 1 best solutions below

2
On BEST ANSWER

This is my first use of clpr so if this is unhelpful to you I plead insanity, but to me, the key here seems to be using dump/3 to convert the constraint back into a Prolog expression and then traversing it like any other structure. So I obtain the constraint again by doing this:

?- relation(independents([var(x1,X1),var(x2,X2),var(x3,X3)]),
            dependent(var(y,Y))), 
   dump([X1,X2,X3,Y],[x1,x2,x3,y], [y=Eqn]).
Eqn = 3.0+0.5*x1+0.6*x2+0.7*x3

I think it's worth remembering what this looks like under the hood using write_canonical:

+(+(+(3.0,*(0.5,x1)),*(0.6,x2)),*(0.7,x3))

Traversing a polynomial you should be covered by only a few simple cases; the following may actually be overkill:

coefficient(X=Y, Var, Coeff) :-
    coefficient(X, Var, Coeff) ; coefficient(Y, Var, Coeff).
coefficient(X+Y, Var, Coeff) :-
    coefficient(X, Var, Coeff) ; coefficient(Y, Var, Coeff).
coefficient(X-Y, Var, Coeff) :-
    coefficient(X, Var, Coeff) ; coefficient(Y, Var, Coeff).
coefficient(X*Y, X, Y) :-
    atomic(X), atomic(Y).
coefficient(X*Y, Var, Coeff) :-
    coefficient(X, Var, Coeff) ; coefficient(Y, Var, Coeff).

Your base case really is the X*Y case where they are both atomic. The rest of the clauses are really just there to unwrap nesting. This appears to do what you want:

?- relation(independents([var(x1,X1),var(x2,X2),var(x3,X3)]),
            dependent(var(y,Y))), 
   dump([X1,X2,X3,Y],[x1,x2,x3,y], [y=Eqn]), 
   coefficient(Eqn, Var, Coeff).

Eqn = 3.0+0.5*x1+0.6*x2+0.7*x3,
Var = 0.5,
Coeff = x1,
{Y=3.0+0.5*X1+0.6*X2+0.7*X3} ;
Eqn = 3.0+0.5*x1+0.6*x2+0.7*x3,
Var = 0.6,
Coeff = x2,
{Y=3.0+0.5*X1+0.6*X2+0.7*X3} ;
Eqn = 3.0+0.5*x1+0.6*x2+0.7*x3,
Var = 0.7,
Coeff = x3,
{Y=3.0+0.5*X1+0.6*X2+0.7*X3} ;
false.

To really generalize this you probably will need to use maplist et. al. to convert your independents/dependents lists into the variables you will need to pass to dump/3 and then handle the case where you have multiple equations in the result, but I don't think this will be very challenging for you.

Hope this helps!