InputForm bug in formal derivative

33 views
Skip to first unread message

Martin R

unread,
Feb 16, 2019, 5:41:35 PM2/16/19
to FriCAS - computer algebra system
Hi there!

I'm afraid that there is a slight bug in the InputForm of formal derivatives in 1.3.5.

I guess the problem is that evaluation does not commute with differentiation.

Best wishes,

Martin

(1) -> f := operator 'f

   (1)  f
                                                          Type: BasicOperator
(2) -> unparse(eval(D(f(x,y), x, 1), x=y)::INFORM)

   (2)  "D(f(y,y),y::Symbol)"
                                                                 Type: String
(3) -> D(f(y,y),y::Symbol)

   (3)  f  (y,y) + f  (y,y)
         ,2         ,1
                                                    Type: Expression(Integer)

or a bit more complicated:

(1) -> f := operator 'f

   (1)  f
                                                          Type: BasicOperator
(2) -> ex := eval(D(f(x,y), [x, y], [1, 1]), x=x+y)

   (2)  f    (y + x,y)
         ,1,2
                                                    Type: Expression(Integer)
(3) -> iex := ex::INFORM

   (3)
   (D (eval (D (f %F y) (:: %F Symbol)) (:: %F Symbol) (+ y x)) (:: y Symbol))
                                                              Type: InputForm
(4) -> unparse(iex)

   (4)  "D(eval(D(f(%F,y),%F::Symbol),%F::Symbol,y+x),y::Symbol)"
                                                                 Type: String
(5) -> D(eval(D(f(%F,y),%F::Symbol),%F::Symbol,y+x),y::Symbol)

   (5)  f    (y + x,y) + f    (y + x,y)
         ,1,1             ,1,2
                                                    Type: Expression(Integer)

Martin R

unread,
Feb 17, 2019, 2:33:58 AM2/17/19
to FriCAS - computer algebra system
I am going to prepare a fix today...

Martin

Martin R

unread,
Feb 17, 2019, 6:37:56 AM2/17/19
to FriCAS - computer algebra system
Here is a proposed fix:

diff --git a/src/algebra/fspace.spad b/src/algebra/fspace.spad
index 3e6d3dda..29031e32 100644
--- a/src/algebra/fspace.spad
+++ b/src/algebra/fspace.spad
@@ -593,37 +593,26 @@ FunctionSpace(R : Comparable) : Category == Definition where
       error concat("Unknown operator 4: ",string(name(op)))$String
 
     if R has ConvertibleTo InputForm then
-      INP==>InputForm
-      import from MakeUnaryCompiledFunction(%, %, %)
-      indiff : List % -> INP
-      pint  : List INP-> INP
 
-      pint l  == convert concat(convert('D)@INP, l)
+      import from MakeUnaryCompiledFunction(%, %, %)
+      indiff : List % -> InputForm
       indiff l ==
-          a3 : % := third(l)
-          do_eval := false
-          s : SY :=
-              (su := retractIfCan(a3)@Union(SY, "failed")) case SY =>
-                  su::SY
-              do_eval := true
-              new()$SY
-          -- Ugly, but otherwise interpreter may have trouble
-          -- evaluating result
-          si := convert([convert("::"::SY)@INP, convert(s)@INP,
-                         convert('Symbol)@INP])@INP
-          ne := eval(first l, retract(second l)@K, (do_eval => s::%; a3))
-          d1 := pint([convert(ne)@INP, si])
-          do_eval =>
-              convert([convert('eval)@INP, d1, si, convert(third(l))@INP])
-          d1
+          -- l is a triple [function at dummy variable, dummy variable, evaluated at]
+          fun : InputForm := convert(first(l))@InputForm
+          dmy : InputForm := convert(second(l))@InputForm
+          evl : InputForm := convert(third(l))@InputForm
+          dff : InputForm := convert([convert('D)$InputForm, fun, dmy])$InputForm
+
+          dmy = evl => dff
+          convert([convert('eval)$InputForm, dff, dmy, evl])$InputForm
+
+      setProperty(opdiff, SPECIALINPUT, indiff@(List % -> InputForm) pretend None)
 
       eval(f : %, s : OP, g : %, x : SY) == eval(f, [s], [g], x)
 
       eval(f : %, ls : List OP, lg : List %, x : SY) ==
         eval(f, ls, [compiledFunction(g, x) for g in lg])
 
-      setProperty(opdiff, SPECIALINPUT, indiff@(List % -> InputForm) pretend None)
-
     variables(lx : List(%)) ==
       l := empty()$List(SY)
       for k in tower lx repeat
diff --git a/src/input/bugs2019.input b/src/input/bugs2019.input
index f3268439..e71890f2 100644
--- a/src/input/bugs2019.input
+++ b/src/input/bugs2019.input
@@ -14,6 +14,10 @@ di2 := D(f(x, y^2), [x, y], [2, 1])
 idi2 := di2::InputForm
 testEquals("interpret(idi2) - di2", "0")
 
+di2 := eval(D(f(x,y), x, 1), x=y)
+idi2 := di2::InputForm
+testEquals("interpret(idi2) - di2", "0")
+
 testcase "'*' and 'gcd' in Factored"
 
 testEquals("factor(x-1)*0", "0")

Kurt Pagani

unread,
Feb 17, 2019, 11:47:00 AM2/17/19
to FriCAS - computer algebra system
Hi Martin
I suppose this problem is even more involved:

f:=operator 'f
g(x,y) == D(f(x,y), x)
G(x,y) == eval(D(f(t,s), t),[t=x,s=y])

expr:=D(f(x,y), x, 1)
function(expr, h, [x,y])

Then G(q,q) is what I had expected, but neither g nor h may be considered as functions.
The problem seems to be that we here deal with a kind of "macro", i.e. G,g,h are not functions as long as 'f' is not concrete.

Even unparse(G(q,q)::INFORM) yields "D(f(q,q),q::Symbol)" :(

I guess this requires some fundamental changes?

Best
Kurt



(8) -> [G(x,x),g(x,x),h(x,x)]
   Compiling function g with type (Variable(x), Variable(x)) ->
      Expression(Integer)
   Compiling function h with type (Variable(x), Variable(x)) ->
      Expression(Integer)

   (8)  [f  (x,x), f  (x,x) + f  (x,x), f  (x,x) + f  (x,x)]
          ,1        ,2         ,1        ,2         ,1
                                              Type: List(Expression(Integer))

Martin R

unread,
Feb 17, 2019, 12:46:48 PM2/17/19
to FriCAS - computer algebra system
Hi Kurt!

I'm not sure I understand the problem.  With the patch applied, I obtain:

(1) -> f:=operator 'f

   (1)  f
                                                          Type: BasicOperator
(2) -> g(x,y) == D(f(x,y), x)
                                                                   Type: Void
(3) -> G(x,y) == eval(D(f(t,s), t),[t=x,s=y])
                                                                   Type: Void
(4) -> expr:=D(f(x,y), x, 1);

                                                    Type: Expression(Integer)
(5) -> function(expr, h, [x,y]);

                                                                 Type: Symbol
(6) -> [G(x,x), g(x,x), h(x,x)]

   (6)  [f  (x,x), f  (x,x) + f  (x,x), f  (x,x)]
          ,1        ,2         ,1        ,1
                                              Type: List(Expression(Integer))

(7) -> [interpret(G(x,x)::INFORM), interpret(g(x,x)::INFORM), interpret(h(x,x)::INFORM)]

   (7)  [f  (x,x), f  (x,x) + f  (x,x), f  (x,x)]
          ,1        ,2         ,1        ,1
                                                              Type: List(Any)


I think that this is OK, let's look at it in detail.

* G(x,y) == eval(D(f(t,s), t),[t=x,s=y])

D(f(t,s), t) means "consider f as a bivariate function and compute the derivative with respect to the first variable"
G then evaluates this expression at t=x and s=x.

* g(x,y) == D(f(x,y), x)

g(x,x) means "compute D(f(x,x), x)"

* function(expr, h, [x,y])

I admit that I am not completely sure about the semantics of "function", but I think it should be roughly equivalent to G.

Maybe you could say what result you would expect?

Best wishes,

Martin

Kurt Pagani

unread,
Feb 17, 2019, 2:30:15 PM2/17/19
to FriCAS - computer algebra system
On Sunday, 17 February 2019 18:46:48 UTC+1, Martin R wrote:
Hi Kurt!

I'm not sure I understand the problem.  With the patch applied, I obtain:


You do, your patch is certainly a partial solution (now G and h are correct). What I actually wanted to say/ask is that/whether g and G ought to be identical.

Semantically g(x,y)=D(f(x,y), x) => g(x,x)=D(f(x,x), x), but is that really the answer the user expects? It might be a source of confusion. If you hadn't pointed out the issue, I certainly would have made the mistake using g instead of G ;) 

 
What is the general opinion?
BTW thanks for the patch.
Kurt

Kurt Pagani

unread,
Feb 17, 2019, 2:40:00 PM2/17/19
to FriCAS - computer algebra system
Oh, just recogniced that I mixed up 'syntactical' & 'semantical' :(
Should read "syntactically g(x,y)=D(f(x,y), x) => g(x,x)=D(f(x,x), x)", of course.
So, what shall be the semantics of g(x,y) in fricas? As is or the actually a partial function?



Waldek Hebisch

unread,
Feb 18, 2019, 12:03:58 PM2/18/19
to fricas...@googlegroups.com
Martin R wrote:

> Here is a proposed fix:

Could you say more how it is supposed to work? AFAICS
obiously correct method would introduce new symbols and
use eval. Other cases are optimizations to get simpler/
nicer output. You change several things, most seem
to be irrelevant, but curcialy I do not see creation
of new symbols.

--
Waldek Hebisch

Martin R

unread,
Feb 18, 2019, 12:08:52 PM2/18/19
to FriCAS - computer algebra system
The symbol is actually provided in the internal representation of diff.  That's why I added

-- l is a triple [function at dummy variable, dummy variable, evaluated at]

Martin

Waldek Hebisch

unread,
Feb 18, 2019, 12:19:34 PM2/18/19
to fricas...@googlegroups.com
Martin R wrote:
>
> The symbol is actually provided in the internal representation of diff.
> That's why I added
>
> -- l is a triple [function at dummy variable, dummy variable, evaluated at]

But are you sure we can reuse it? In the past such reuse lead
to unitended capture and bugs. In fact, the bug you are trying
to fix is just example of unintended capture -- I missed checks
that y is used only once.

--
Waldek Hebisch

Martin R

unread,
Feb 18, 2019, 2:21:56 PM2/18/19
to FriCAS - computer algebra system
I find it hard to be sure, but I think it is quite safe, because
otherwise the differentiation operator wouldn't work either.

Do you have an idea how to try to break it?

(1) -> f := operator 'f

   (1)  f
                                                          Type: BasicOperator
(2) -> ex := D(f(x,y), x)

   (2)  f  (x,y)
         ,1
                                                    Type: Expression(Integer)
(3) -> a := argument(first kernels ex)$Kernel EXPR INT

   (3)  [f(%A,y), %A, x]
                                              Type: List(Expression(Integer))
(4) -> %A := "hi"

   (4)  "hi"
                                                                 Type: String
(5) -> a := argument(first kernels ex)$Kernel EXPR INT

   (5)  [f(%A,y), %A, x]
                                              Type: List(Expression(Integer))
(6) -> ex::INFORM

   (6)  (eval (D (f %A y) %A) %A x)
                                                              Type: InputForm

Martin

Kurt Pagani

unread,
Feb 18, 2019, 6:01:18 PM2/18/19
to FriCAS - computer algebra system
It's certainly better than before. Nevertheless, IMO there is still a mess concerning the usage of "eval". In LISP eval/apply macro/function are properly defined, but it seems to me that "eval" here is used more like "subst" and moreover, "=="  behaves like "==>" reagrding "D". I have a conceptional problem in accepting the possibility g(x,x) <> eval(g(x,y), y=x), when g is a function (else if g was defined as a macro). Am I barking up the wrong tree?


Before
======
g(x,y) == D(f(x,y),x)

 interpret(g(x,x)::INFORM)

   (1)  2 f  (x,x) + 2 f  (x,x)
            ,2           ,1
                                                    Type: Expression(Integer)

g(x,x)::INFORM

   (2)  (+ (D (f x x) (:: x Symbol)) (D (f x x) (:: x Symbol)))
                                                              Type: InputForm

but

(3) -> g(x,x)

   (3)  f  (x,x) + f  (x,x)
          ,2         ,1
                                                    Type: Expression(Integer)

After patch
========
(1) -> interpret(g(x,x)::INFORM)

   (1)  f  (x,x) + f  (x,x)
         ,2         ,1
                                                    Type: Expression(Integer)



$ patch fspace.spad  fspace.diff

; compiling file "C:/msys64/home/kfp/patches/FS2.NRLIB/FS2.lsp" (written 18 FEB 2019 10:26:58 PM):

; wrote C:/msys64/home/kfp/patches/FS2.NRLIB/FS2.fasl
; compilation finished in 0:00:00.018
------------------------------------------------------------------------
   FunctionSpaceFunctions2 is now explicitly exposed in frame initial
   FunctionSpaceFunctions2 will be automatically loaded when needed
      from /msys64/home/kfp/patches/FS2.NRLIB/FS2

(1) ->  f:=operator 'f

   (1)  f
                                                          Type: BasicOperator
(2) -> g(x,y) == D(f(x,y),x)
                                                                   Type: Void
(3) -> g(x,y)
   Compiling function g with type (Variable(x), Variable(y)) ->
      Expression(Integer)

   (3)  f  (x,y)
         ,1
                                                    Type: Expression(Integer)
(4) -> g(x,x)

   Compiling function g with type (Variable(x), Variable(x)) ->
      Expression(Integer)

   (4)  f  (x,x) + f  (x,x)
         ,2         ,1
                                                    Type: Expression(Integer)
(5) -> g(x,x)::INFORM

   (5)  (+ (eval (D (f x %C) %C) %C x) (eval (D (f %B x) %B) %B x))
                                                              Type: InputForm
(6) -> eval(g(x,y),x=y)

   (6)  f  (y,y)
         ,1
                                                    Type: Expression(Integer)
(8) -> h(x,y) == x^2*sin(y)
                                                                   Type: Void
(9) -> h1(x,y) == D(h(x,y),x)
                                                                   Type: Void
(10) -> h1(x,y)
   Compiling function h with type (Variable(x), Variable(y)) ->
      Expression(Integer)
   Compiling function h1 with type (Variable(x), Variable(y)) ->
      Expression(Integer)

   (10)  2 x sin(y)
                                                    Type: Expression(Integer)
(11) -> h1(x,x)

   Compiling function h with type (Variable(x), Variable(x)) ->
      Expression(Integer)
   Compiling function h1 with type (Variable(x), Variable(x)) ->
      Expression(Integer)

                       2
   (11)  2 x sin(x) + x cos(x)
                                                    Type: Expression(Integer)
(12) -> eval(h1(x,y),x=y)

   (12)  2 y sin(y)
                                                    Type: Expression(Integer)
(13) -> eval(h1(x,y),y=x)

   (13)  2 x sin(x)
                                                    Type: Expression(Integer)
(14) -> h1(s,s)
   Compiling function h with type (Variable(s), Variable(s)) ->
      Expression(Integer)
   Compiling function h1 with type (Variable(s), Variable(s)) ->
      Expression(Integer)

                       2
   (14)  2 s sin(s) + s cos(s)
                                                    Type: Expression(Integer)
(15) -> h1(s,t)
   Compiling function h with type (Variable(s), Variable(t)) ->
      Expression(Integer)
   Compiling function h1 with type (Variable(s), Variable(t)) ->
      Expression(Integer)

   (15)  2 s sin(t)
                                                    Type: Expression(Integer)

Martin R

unread,
Feb 19, 2019, 1:28:07 AM2/19/19
to FriCAS - computer algebra system
Dear Kurt!

As far as I can see, eval, D, == and := are behaving exactly as specified.  With

f(x,y) == D(f(x,y),x)

the symbol "f" is a FriCAS function, and NOT a function in the usual mathematical sense!
In particular, f(a,b) returns the expression (in the pre-calculus sense)

f_1(a,b),

first derivative of with respect to the first argument, evaluated at a and b.
Note that it is somewhat sloppy to write f_x(a,b) in calculus, because it is
unclear what x refers to.

Therefore, eval(f(a,b), b=a) must return f_1(a,a).

On the other hand, f(a,a) should return the expression D(f(a,a), a), which
is the derivative of f(a,a) with respect to a.

Maybe the confusion comes from the difference between D and f_1:

f_1(a,b) is the *result* of D(f(a,b), a). 

D is a FriCAS function, whereas f_1(a,b) is an expression.

Martin

Kurt Pagani

unread,
Feb 19, 2019, 10:37:07 AM2/19/19
to FriCAS - computer algebra system
Hi Martin
Thanks for the explanations. I really don't want to be nit-picking, however, you hit the nail:


> Maybe the confusion comes from the difference between D and f_1:
> f_1(a,b) is the *result* of D(f(a,b), a).
> D is a FriCAS function, whereas f_1(a,b) is an expression.
 

F(x,y)==D(y*sin(x),x)
-> InputForm (* y (cos x))

That is, the information that y*cos(x) comes from a derivative is lost (although not really because F(y,y)::INFORM -> (+ (sin y) (* y (cos y))) (before your patch).

So why not expecting F(u,v)==D(f(u,v),u) as f_1(u,v)? Then F(u,u)=f_1(u,u) naturally. On the other hand when using macro (==>):

F(x,y) ==> D(y*sin(x),x)

it's clear to me that we have a substitution F(x,x)->D(x*sin(x),x). But you are right of course, one may/should see it as you mentioned:


> D is a FriCAS function, whereas f_1(a,b) is an expression.

Again, thanks for the trouble!
Kurt
Reply all
Reply to author
Forward
0 new messages