home *** CD-ROM | disk | FTP | other *** search
/ Power-Programmierung / CD1.mdf / prolog / tutorial / algebra / diffsv.pro < prev    next >
Text File  |  1987-04-11  |  3KB  |  97 lines

  1. /* -----------------------------------------------------------------
  2.  
  3.                               DIFFSV.PRO
  4.  
  5.                              (version 1.0)
  6.  
  7.                         Copyright 1987 S.Vaghi
  8.  
  9.  
  10.               Program for the symbolic differentiation of
  11.                            algebraic functions.
  12.  
  13.               ...........................................
  14.  
  15.  
  16.      Example of how to use the program:
  17.  
  18.          to find the derivative, DY, of the function
  19.                                                        y = x^2
  20.          with respect to x, one can
  21.  
  22.                  a) simply enter
  23.                                                 d( x^2, x, DY).
  24.                     after the Prolog prompt,
  25.          or
  26.                  b) enter
  27.                                                  Y = x^2 ,
  28.                                                  d( Y, x, DY).
  29.                     after the prompt,
  30.          or
  31.                  c) enter the complete sequence including
  32.                     simplification, that is
  33.                                                   Y = x^2 ,
  34.                                                   d( Y, x, Z),
  35.                                                   s( Z, DY).
  36.  
  37.          Method c) is always recommended, in which case the
  38.          program is used in combination with SIMPSV.PRO
  39.  
  40.  
  41.    ----------------------------------------------------------------- */
  42.  
  43.  
  44.  
  45.                   /*  definition of operators */
  46.  
  47.  
  48. ?-op(11, yfx,  '^').                 /*  exponentiation     */
  49. ?-op( 9,  fx,  '~').                 /*  minus sign         */
  50. ?-op(11,  fx, 'ln').                 /*  natural logarithm  */
  51.  
  52.  
  53.  
  54. d(X,X,1).
  55.  
  56. d(C,X,0) :- atomic(C), C \= X.
  57.  
  58. d(~U,X,~D) :- d(U,X,D).
  59.  
  60.  
  61.     d(C+U,X,D) :- atomic(C), C \= X, d(U,X,D), ! .
  62.     d(U+C,X,D) :- atomic(C), C \= X, d(U,X,D), ! .
  63.  
  64. d(U+V,X,D1+D2) :- d(U,X,D1), d(V,X,D2).
  65.  
  66.  
  67.     d(C-U,X,~D) :- atomic(C), C \= X, d(U,X,D), ! .
  68.     d(U-C,X, D) :- atomic(C), C \= X, d(U,X,D), ! .
  69.  
  70. d(U-V,X,D1-D2) :- d(U,X,D1), d(V,X,D2).
  71.  
  72.  
  73.     d(C*U,X,C*D) :- atomic(C), C \= X, d(U,X,D), ! .
  74.     d(U*C,X,C*D) :- atomic(C), C \= X, d(U,X,D), ! .
  75.  
  76. d(U*V, X, D2*U+D1*V) :- d(U,X,D1), d(V,X,D2).
  77.  
  78.  
  79.     d(1/U,X, ~D/(U^2) ) :- d(U,X,D), ! .
  80.     d(C/U,X, C*DD) :- atomic(C), C \= X, d(1/U,X,DD), ! .
  81.     d(U/C,X,  D/C) :- atomic(C), C \= X, d(U,X,D), ! .
  82.  
  83. d(U/V, X, (V*D1-U*D2)/(V^2) ) :- d(U,X,D1), d(V,X,D2).
  84.  
  85.  
  86.     d( U^C, X, C*D*U^(C-1) ) :- atomic(C), C \= X, d(U,X,D), ! .
  87.         d(U^~C, X,            Z) :-  d( 1/(U^C), X, Z), ! .
  88.         d( U^(A/B),X, (A/B)*D*U^(A/B-1) ) :- atomic(A), atomic(B),
  89.                                              A \= X, B \= X,
  90.                                              d(U,X,D), ! .
  91.         d(U^~(A/B),X,                  Z) :- d(1/U^(A/B) , X, Z), ! .
  92.  
  93. d(U^V, X, U^V*(V*D1/U+D2*ln(U) )) :- d(U,X,D1), d(V,X,D2).
  94.  
  95.  
  96.  
  97.