***************************************************************************
  * All the software  contained in this library  is protected by copyright. *
  * Permission  to use, copy, modify, and  distribute this software for any *
  * purpose without fee is hereby granted, provided that this entire notice *
  * is included  in all copies  of any software which is or includes a copy *
  * or modification  of this software  and in all copies  of the supporting *
  * documentation for such software.                                        *
  ***************************************************************************
  * THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR IMPLIED *
  * WARRANTY. IN NO EVENT, NEITHER  THE AUTHORS, NOR THE PUBLISHER, NOR ANY *
  * MEMBER  OF THE EDITORIAL BOARD OF  THE JOURNAL  "NUMERICAL ALGORITHMS", *
  * NOR ITS EDITOR-IN-CHIEF, BE  LIABLE FOR ANY ERROR  IN THE SOFTWARE, ANY *
  * MISUSE  OF IT  OR ANY DAMAGE ARISING OUT OF ITS USE. THE ENTIRE RISK OF *
  * USING THE SOFTWARE LIES WITH THE PARTY DOING SO.                        *
  ***************************************************************************
  * ANY USE  OF THE SOFTWARE  CONSTITUTES  ACCEPTANCE  OF THE TERMS  OF THE *
  * ABOVE STATEMENT.                                                        *
  ***************************************************************************

   AUTHOR:

       Z. DA ROCHA
          UNIVERSITY OF LILLE - FRANCE

   REFERENCE:

       IMPLEMENTATION OF THE RECURRENCE RELATIONS OF BIORTHOGONALITY
       NUMERICAL ALGORITHMS, 3 (1992) PP. 173-183

   SOFTWARE REVISION DATE:

       SEPTEMBER, 1992

   SOFTWARE REQUIRED:
 
       MATHEMATICA

  ***************************************************************************


(*____________________________
_________INTRODUCTION_________
_____________________________*)
   
   (* Here are the three packages GPADETYPE.M , BE.M , 
 BIF.M , written in Mathematica Version 2.0 , and the
 Mathematica session that produce , in a Macintosh SE/30,
 the results of the article 
 "Z. DA ROCHA.Implementation of the recurrence relations
 of biorthogonality. In C. Brezinski, P. Gonzalez-Vera
 and N. Hayek-Calil, eds., Extrapolation and Rational 
 Approximation. Tenerife 1992, volume 3 of Numerical
 Algorithms, pp. 173-183, Basel 1992. J. C. Baltzer.".
  
    Each package must be in a separate file which name
 is formed by the package's name with the suffix .M.

    GPADETYPE.M contains the definition of the 
 function tablegpt that calculates a sequence of the
 generalized Pade-type approximants defined in the article. 
 It calls the packages BE.M and BIF.M .
 
    It is supposed that the user gives in BE.M the 
 definitions of the series of functions ( series ) , the
 generating function ( g ) , and the moments ( c )  of
 the examples he wants to test , and that he gives in 
 BIF.M the definitions of the initial functionals 
 ( initialf ) he wants to utilize . Several definitions
 can be given.
 
    It is obvious that only one definition of series, g ,
 c  and initialf  is valid at each time , the others are put
 under the form of comments.
 
   When the user wants to change one and more 
definitions , he only have to put the characters (* and
*) around the old definitions , to remove these characters
around the new ones , and to save and read again the 
packages to which the definitions belong.

   SUGGESTION: The user can give a maximal value to the
 argument  k  of the function tablegpt  , and interrupt the
 calculations , using the option ABORT CALCULATION of the
 menu , as soon as he is not interested in obtaining more
 results. *)


(**********************************)
(******* Package GPADETYPE.M *******)
(**********************************)

BeginPackage["GPADETYPE`","BE`","BIF`"]


GPADETYPE::usage="is a package that contains the
definition of the function tablegpt.
It calls the packages BE and BIF."

tablegpt::usage="
tablegpt[ k , t  , toption  , coption  ,
                resultprec  , reoption  , reprec  , cprec  , aroption ]
calculates the (k+1) first generalized Pade-type
approximants in the point t .
The argument t  can be a symbolic expression 
(toption  == \"VAR\") , or a numerical expression
(toption  == \"SCL\") .  In the first case we obtain symbolic
results ,  in the second case we obtain numerical results.
If coption  == \"EC\" ,  we do exact calculus.
If coption  == \"AC\" , we do approximate
calculus with precision cprec  . This means that we use
the function N[- , cprec]  to do all the intermediate
computations. If cprec < = \"machine precision\", we do 
low precision computations.  If cprec > \"machine precision\",
we do high precision computations.
If coption == \"AC\", the numerical results or the numerical
part of the symbolic results are printed with resultprec 
decimal digits of precision.
The default values of cprec  and resultprec  are the machine
precision ( given for example by Precision[1.0]  ).
If resultprec  or cprec  are greather than  Precision[1.0]  ,
 we must have  resultprec  < = cprec .
If toption  == \"SCL\" , given a non zero value to reoption ,
relative errors with respect to the series are calculated with
precision cprec , and are written with  reprec  decimal digits
of precision.
The default values of reoption  and reprec  are 0 and 2
respectively.
If toption  == \"VAR\" or reoption  is zero , relative errors
are not calculated. 
If toption  == \"SCL\" and coption  == \"EC\", we obtain
the exact numerical expressions of the approximants in
the point t .  If reoption  is not  zero , relative errors of
these exact expressions are calculated with precision
cprec . We should take a sufficiently big value to cprec 
in order that these errors could be correctly calculated.
If toption  == \"SCL\" and coption  == \"EC\" , given a non
zero value to aroption , approximate values of the exacts
expressions of the approximants are calculated with 
precision  resultprec . If aroption  is zero , these approximate
values are not calculated. 
The default value of aroption  is zero.
We must give the first four arguments of tablegpt ,
however the last five can be omitted taking their default
values.

Reference:  
 Z. DA ROCHA.Implementation of the recurrence relations
 of biorthogonality. In C. Brezinski, P. Gonzalez-Vera
 and N. Hayek-Calil, eds., Extrapolation and Rational 
 Approximation. Tenerife 1992, volume 3 of Numerical
 Algorithms, pp. 173-183, Basel 1992. J. C. Baltzer."
                 
Begin["`Private`"]

(*__________________________________________________ 
______________ERROR MESSAGES OF TABLEGPT______________
___________________________________________________*)

tablegpt::badarg1=
        "wrong value to the first argument  
                  k  must be a non negative integer  
                  try again"
                                        
tablegpt::badarg3=
        "wrong value to the third argument
                  toption  must be equal to \"SCL\" or \"VAR\"  
                  try again"
                  
tablegpt::badarg4=
        "wrong value to the fourth argument 
                  coption  must be equal to \"AC\" or \"EC\"  
                  try again"
                  
tablegpt::badarg5=
        "wrong value to the fifth argument 
                  resultprec  must be a non negative integer  
                  try again"                 
                  
tablegpt::badarg7=
        "wrong value to the seventh argument 
                  reprec  must be a non negative integer  
                  try again"     
                  
tablegpt::badarg8=
        "wrong value to the eighth argument 
                  cprec  must be a non negative integer  
                  try again"
                   
tablegpt::badarg58=
      "wrong values to the fifth and/or the 
              eighth arguments.
              We must have resultprec < = cprec  ,
              if at least one of these arguments are greather
              than the machine precision.
              Try again."  
                                          
(*__________________________________________________
__________DEFINITIONS OF THE PRIVATE FUNCTIONS__________
____________________OF TABLEGPT______________________
___________________________________________________*)
                         
functionalc[ poly_, var_ ]:=
Block[{n},
         Sum[ Coefficient[ poly ,var ,n ]*cm[[n+1]] ,
            {n,0,Exponent[ poly ,var ]}
                ]/; PolynomialQ[ poly,var ]
         ] ;

u[ i_ ,j_ ,0, var_ ]:= var^j ;

(*__________________________________________________
________________DEFINITION OF TABLEGPT________________
___________________________________________________*)
        
tablegpt[ k_ , t_ , toption_ , coption_ ,
                resultprec_:(Precision[1.0]) ,
                reoption_:0 , reprec_:2 ,
                cprec_:(Precision[1.0]) ,
                aroption_:0 ]:=
 
Block[ { cm, wn1, wn2, wf1, wf2, w3, wl, wc,
              wx, xarray, larray, n, m, i} ,
 (*________________________________________________
 ________________CONTROL OF ARGUMENTS_______________
 _________________________________________________*)
             
 If [ Or[ Not[ IntegerQ[k] ] ,  k < 0€] ,  
      Return[ Message[tablegpt::badarg1] ]     
     ];         
     
 If [ And [ toption != "SCL" , toption != "VAR" ] ,     
      Return[ Message[tablegpt::badarg3] ]     
    ];         
    
 If[ And [ coption != "EC",  coption != "AC" ] ,
      Return[ Message[tablegpt::badarg4] ]  
    ] ;
 
If [ Or[ Not[ IntegerQ[ resultprec ] ] ,  resultprec < 0€] ,   
      Return[ Message[tablegpt::badarg5] ]     
    ];      
    
If [ Or[ Not[ IntegerQ[ reprec ] ] ,  reprec < 0€] ,   
      Return[ Message[tablegpt::badarg7] ]     
    ];      
    
If [ Or[ Not[ IntegerQ[ cprec ] ] ,  cprec < 0 ] , 
      Return[ Message[tablegpt::badarg8] ]     
    ];        

If [ And[ resultprec  >  cprec ,
              Or[ resultprec > (Precision[1.0]) ,
                    cprec > (Precision[1.0])
                  ]
             ] ,
         Return [ Message [tablegpt::badarg58 ] ]
     ]; 
               
(*_______________________________________________
 _________computation of the first approximant _______
________________________________________________
________________________________________________
______________computation of c(X[0,0,0,x])___________
_____________computation of L[0,0,0,g[x,t],x]__________
________________________________________________*)
If[ coption == "AC"  , 

     cm={ N[ c[0] , cprec ] };
     wx={ N[ u[0,0,0,x] , cprec ] };
     wc={ N[ functionalc[ wx[[1]] , x ], cprec ] };
     wl={ N[ initialf[ 0, wx[[1]], x ] , cprec ] };
     larray={ { N[ (initialf[ 0, g[x,t], x ] / wl[[1]] ), cprec ] } } 
     
 ,  (*coption == "EC" *)
 
     cm={ c[0] };
     wx={ u[0,0,0,x] };  
     wc={ functionalc[ wx[[1]] , x ] };
     wl={ initialf[ 0, wx[[1]], x ] };
     larray={ {  initialf[ 0, g[x,t], x ] / wl[[1]]  } } 
     
    ] ; (* end of If *)
    
    xarray={ Append[ wc, wl[[1]]  ] };
(*_________________________________________________
_____________xarray[[1,1]]=c(X[0,0,0,x])________________
____________larray[[1,1]]=L[0,0,0,g[x,t],x]_______________
__________________________________________________
___________printing of the first approximant____________
__________________________________________________*)

  If[ toption == "SCL" ,
  
      If[  coption == "EC" ,
      
            wf1= xarray[[1,1]]*larray[[1,1]] ;
            Print[ "fgpt[", 0, "]=", Expand[ wf1] ] ;
            wn1=wf1;
            If[  aroption != 0 ,
                   Print[ "ngpt[",0,"]=", N[ wn1 , resultprec ] ]
                ]
         , (* coption == "AC" *)
         
            wn1=N[ xarray[[1,1]]*larray[[1,1]] , cprec ] ;
            Print[ "ngpt[",0,"]=", N[ wn1 , resultprec ] ]
            
        ]; (* end of If [ coption ] *)
      
      If[ reoption !=0 ,     
            Print[ "re[", 0, "]=",
             N[ N[ Abs[ (wn1-series[t]) / series[t] ] , cprec ]
               , reprec ]
                    ] (* end of Print *)
           ]; (* end of If *)
      
     , (* toption == "VAR" *)
     
       If[ coption == "EC",
       
            wf1= xarray[[1,1]]*larray[[1,1]] ;
            Print[ "fgpt[", 0, "]=", Together[ wf1]  ] ; 
            
           , (* coption == "AC" *)
           
             wn1=N[ xarray[[1,1]]*larray[[1,1]]  
                        , cprec ];                   
             Print["ngpt[",0,"]=", N[ Together[wn1], resultprec ]  ] ;
             
            ]   (* end of If [ coption ] *)               
        
    ];  (* end of If [ toption ] *) 
     Print[" "];       
(*_______________________________________________*)
Do[(*{i,2,k+1}*)
(*________________________________________________
____________computation of the i-th approximant________
_________________________________________________*)
 If[ coption == "AC" , 
 
      AppendTo[ cm, N[ c[i-1] , cprec ] ];
      AppendTo[ wx, N[ u[0,i-1,0,x]  , cprec ] ]; 
      AppendTo[ wc, N[ functionalc[ wx[[i]], x], cprec ] ];
      AppendTo[ wl, N[ initialf[ i-1, wx[[1]], x], cprec ] ]
      
     , (* coption == "EC" *)
     
     AppendTo[ cm, c[i-1] ];
     AppendTo[ wx, u[0,i-1,0,x] ];
     AppendTo[ wc, functionalc[ wx[[i]], x ]  ];
     AppendTo[ wl, initialf[ i-1, wx[[1]], x ]  ]
      
    ]; (* end of If *)
(*_________________________________________________
_____________computation of c(X[0,0,i-1,x])______________
____________computation of L[0,0,i-1,g[x,t],x]____________
__________________________________________________
_________computation of the new elements of the_________ 
____________arrays X1 and L1 of the row i______________
___________________(  first part )_____________________
______________simultaneous computation________________ 
_________of the new column of the array X1 and__________
______________the new row of the array L1 _____________
__________________________________________________*)
  AppendTo[ xarray , { wc[[i]] } ];
  Do[ (* {n,2,i} *)
     If[ coption == "AC"  , 
     
             w3=N[ initialf[ n-2, wx[[i]], x ] , cprec ];
             If[ n == 2 , 
                xarray[[ i-1, 2]]= N[ w3/ xarray[[i-1,2]] , cprec ]
                ]; (* end of If *)
              AppendTo[ xarray[[i]] , w3 ];
              AppendTo[ larray[[n-1]] , N[ w3/ wl[[n-1]] , cprec ] ]
                 
         , (* coption == "EC" *)
          
             w3=initialf[ n-2, wx[[i]], x ] ;
             If[ n == 2 , 
                xarray[[i-1, 2]]= w3/ xarray[[i-1,2]] 
                ]; (* end of If *)
              AppendTo[ xarray[[i]] , w3 ];
              AppendTo[ larray[[n-1]] , w3/ wl[[n-1]]  ]    
               
          ] (* end of If *)
        
     ,{n,2,i}
    ];(*end of Do*)
    
(* _________________________________________________
__________________( second part )_____________________
______________simultaneous computation________________ 
_________of the new column of the array L1 and__________
_____________the new row of the array X1______________
__________________________________________________*)
 If[ coption == "AC"  ,
      AppendTo[ larray ,
              { N[ initialf[ i-1, g[x,t], x ]/ wl[[i]] , cprec ] } 
                     ]       
    , (* coption == "EC" *)
      AppendTo[ larray , { initialf[ i-1, g[x,t], x ]/ wl[[i]] } ]
     ]; (* end of If *)
    
   AppendTo[ xarray[[1]] , wl[[i]] ]; 
   
   Do[ (* {n,2,i} *)
        If[ coption == "AC"  ,
        
             w4= N[ initialf[ i-1, wx[[n]], x ] , cprec ] ;
             AppendTo[ larray[[i]] , N[ w4/ wl[[i]] , cprec ] ] ;
             If[ n==2 , 
                  larray[[i-1,2]]=N[ larray[[i,2]]-larray[[i-1,2]] , cprec ]
                ] ; (* end of If *)
              AppendTo[ xarray[[n]], w4 ]
              
             , (* coption == "EC" *)
              
             w4=initialf[ i-1, wx[[n]], x ] ;
             AppendTo[ larray[[i]] , w4/ wl[[i]] ] ;
             If[ n==2 , 
                  larray[[i-1,2]]=larray[[i,2]]-larray[[i-1,2]] 
                ] ; (* end of If *)
              AppendTo[ xarray[[n]], w4 ]
              
             ] ; (* end of If *)
             
           ,{n,2,i}
          ] ; (* end of Do *)
 
(*________________________________________________*)
Do[(*{m,2,i}*)
(*________________________________________________
_________computation of the new elements of the_______
_________arrays Xm and Lm of the  row i (m,i >=2)________
___________________( first part )_____________________
_____________computation of the new row______________
______________of the arrays Xm and Lm _______________
_________________________________________________*)
  Block[{n1}, 
   Do[(* {n,1,i-m} *)
        n1=n+1;
        If[ coption == "AC"  , 
        
             xarray[[n,i]]= N[ xarray[[n1,i]]-
                                         xarray[[n,m]]*
                                         xarray[[n,i]] 
                                       , cprec ] ;
             larray[[n,i]]=N[ ( larray[[n1,i]]-
                                         larray[[n,i]] ) / 
                                         larray[[n,m]]
                                     , cprec ]
                                     
           , (* coption == "EC" *)
           
            xarray[[n,i]]= xarray[[n1,i]]-
                                   xarray[[n,m]]*
                                   xarray[[n,i]] ;
            larray[[n,i]]= ( larray[[n1,i]]-
                                    larray[[n,i]] ) / 
                                    larray[[n,m]]     
                                                                                  
         ] (* end of If *)
         
      ,{n,1,i-m}
     ] (* end of Do *)
     
   ];(* end of Block *)
   
(*_________________________________________________
__________________ (second part) _____________________
_____________computation of the new column____________
_______________of the arrays Xm and Lm _______________
__________________________________________________*)

 Block[{n1,n2,n3,m1},
 
       n1=i-m+1; n2=n1+1; n3=n1-1; m1=m+1;
       If[ coption  == "AC" ,     
         
              xarray[[n1,1]]=N[ xarray[[n2,1]]-
                                            xarray[[n1,m]]*
                                            xarray[[n1,1]] 
                                          , cprec ];
             larray[[n1,1]]=N[( larray[[n2,1]]-
                                           larray[[n1,1]] )/
                                           larray[[n1,m]]
                                        , cprec ]
                                         
           , (* coption == "EC" *)
           
             xarray[[n1,1]]=xarray[[n2,1]]-
                                      xarray[[n1,m]]*
                                      xarray[[n1,1]] ;
             larray[[n1,1]]=( larray[[n2,1]]-
                                       larray[[n1,1]] )/
                                       larray[[n1,m]] 
                                                                    
             ] ;(* end of If *)
        Do[ (*{n,m1,i}*)
              If[ coption == "AC"  , 
              
                    xarray[[n1,n]]=N[ xarray[[n2,n]]-
                                                  xarray[[n1,m]]*
                                                  xarray[[n1,n]]
                                                , cprec ] ;
                   larray[[n1,n]]=N[( larray[[n2,n]]-
                                                 larray[[n1,n]] )/
                                                 larray[[n1,m]]
                                              , cprec ]
                                              
                 ,  (* coption == "EC" *)
                 
                   xarray[[n1,n]]=xarray[[n2,n]]-
                                            xarray[[n1,m]]*
                                            xarray[[n1,n]] ;
                   larray[[n1,n]]=( larray[[n2,n]]-
                                             larray[[n1,n]] )/
                                             larray[[n1,m]]
  
                ]; (* end of If *)
                                
            If[ n == m1 ,
            
                 If[ coption == "AC"  ,
                 
                      xarray[[n3,m1]]=N[ xarray[[n1,m1]] /
                                                      xarray[[n3,m1]]
                                                    , cprec ] ;    
                      larray[[n3,m1]]= N[ larray[[n1,m1]]-
                                                       larray[[n3,m1]] 
                                                    , cprec ]
                                                    
                  ,   (* coption == "EC" *)       
                                     
                     xarray[[n3,m1]]=xarray[[n1,m1]] /
                                                  xarray[[n3,m1]] ;    
                     larray[[n3,m1]]= larray[[n1,m1]]-
                                                 larray[[n3,m1]]  
                                                 
                   ] (* end of If [ coption ] *)
                   
               ]  (*end of If*)  
                          
           ,{n,m1,i}
          ](* end of Do *)
          
     ] (*end of Block*)
         
,{m,2,i}
]; (*end of Do *)
(*________________________________________________
________end of the computation of c(X[0,0,i-1,x]) and ______    
_________________L[0,0,i-1,g[x,t],x]___________________
______________xarray[[1,1]]=c(X[0,0,i-1,x])____________
____________larray[[1,1]]=L[0,0,i-1,g[x,t],x]_____________
__________________________________________________
___________printing of the i-th approximant_____________
__________________________________________________*)

If[ toption == "SCL"  ,

      If[  coption == "EC" ,
      
            wf2= wf1 + xarray[[1,1]]*larray[[1,1]] ;
            Print["fgpt[",i-1,"]=", Expand[ wf2 ] ] ;
            wn2= wf2 ;
            If[ aroption != 0 ,
                  Print[ "ngpt[", i-1, "]=", N[ wn2 , resultprec ] ]
               ]
         , (* coption == "AC" *)
       
            wn2=N[ wn1 + xarray[[1,1]]*larray[[1,1]] , cprec ] ;
            Print[ "ngpt[", i-1, "]=", N[ wn2 , resultprec ] ]
            
          ]; (* end of If[ coption ] *)
      
      If[ reoption!=0 ,         
            Print[ "re[", i-1, "]=",
               N[ N[ Abs[ (wn2-series[t]) / series[t] ] , cprec  ] 
                 , reprec ]
                    ] (* end of Print *)
           ]; (* end of If *)
      
     , (* toption == "VAR" *)
     
      If[ coption == "EC" ,
      
            wf2 = wf1 + xarray[[1,1]]*larray[[1,1]] ;             
            Print[ "fgpt[", i-1, "]=", Together[ wf2]  ] ; 

         , (* coption == "AC" *)
         
            wn2=N[ wn1 + xarray[[1,1]]*larray[[1,1]]
                        , cprec ] ;
            Print["ngpt[",i-1,"]=", N[ Together[wn2] , resultprec ] ] ;
            
         ](* end of If [ coption ]*)
         
    ] ;  (* end of If[ toption ]*)    
    Print[" "] ; 
        
 If[ coption == "EC",  
      wf1=wf2
      , 
      wn1=wn2
     ]
 
,{i,2,k+1}
](* end of Do *)

(*________________________________________________*)
](* end of Block *)


End[ ]

Protect[ tablegpt ]

EndPackage[ ]  

(******************************)
(******** Package BE.M ********)
(******************************)
                   
BeginPackage["BE`"]

Clear[ series, g, c ]

BE::usage="is a package that contains the definitions of:

- the series of functions
- the generating function
- the moments

, that the package GPADETYPE.M needs"

series::usage="series[t] is the closed form of the
                          series of functions"

g::usage="g[x,t] is the closed form of the generating
                  function"

c::usage="c[i] is the moment of order i of the functional c"


Begin["`Private`"]

(* EXAMPLE 1 *)
series[t_]:=Log[1+t]/t ;  
g[x_,t_]:=1/(1-x*t) ;    
c[i_]:=(-1)^i/(i+1) ; 


(* EXAMPLE 2 *)
(*series[t_]:=Log[1+t]/t ; 
g[x_,t_]:=Log[1+x*t]/t ;
c[i_]:=1 ; *)
            
                                        
End[ ]

EndPackage[ ]


(*******************************)
(******** Package BIF.M ********)
(*******************************)

BeginPackage["BIF`"]

Clear[ initialf ]

BIF::usage="is a package that contains the definitions 
of the initial functionals, that the package GPADETYPE.M 
needs"

initialf::usage="initialf[ i, body, var]  is the definition of
the i-th initial functional applied to Function[ var, body ]"

Begin["`Private`"]


(*  CHOICE A  *)
initialf[ i_ ,body_ ,var_ ] := 
             Function[ var, body ][ -1/(i + 1) ] ; 
   
                        
                                                             
(*  CHOICE B  *)
(*initialf[ i_ ,body_ ,var_ ] :=    
          Integrate[ body, {var,-1/(i+1),-1/(i+2)} ] ;*)
                  
                                                  
End[ ]

EndPackage[ ]                



(*______________________________
______Mathematica SESSION_______
________________________________

WE GIVE BELOW SOME EXAMPLES TO SHOW THE CAPABILITIES 
OF THE FUNCTION tablegpt, AND ALSO THE TYPE OF 
RESULTS THAT CAN BE OBTAINED, IF THE ARGUMENTS
        TOPTION AND COPTION ARE WRONG.

______________________________*)
<<GPADETYPE.M

series[t]

Log[1 + t]
----------
    t
g[x,t]

   1
-------
1 - t x
c[i]

    i
(-1)
-----
1 + i
initialf[i,f[x],x]

      1
f[-(-----)]
    1 + i
(*______________________________________________
   Let's remark that the series, the generating
   function, the moments and the initials 
   functionals are defined in an exact way.
  _____________________________________________*)

tablegpt[3,t,"VAR","EC"]
fgpt[0]=1/(1 + t)
 
fgpt[1]=2/(2 + t)
 
fgpt[2]=(6 + 5 t)/(2 (1 + t) (3 + t))
 
                            2       3
fgpt[3]=(144 + 228 t + 108 t  + 19 t )/
 
   (6 (1 + t) (2 + t) (3 + t) (4 + t))
 
(*______________________________________________
   t is a symbolic expression, then we should 
   take toption == "VAR". Taking coption == "EC",
   we get the formal expressions of the
   approximants in the variable t.           
  ______________________________________________*)
tablegpt[3,t,"VAR","AC",19,0,0,30]
ngpt[0]=1./(1. + t)
 
ngpt[1]=(2. + 2. t)/((1. + t) (2. + 1. t))
 
                          2
ngpt[2]=(6. + 8. t + 2.5 t )/
 
   ((1. + t) (2. + 1. t) (3. + 1. t))
 
                            2                         3
ngpt[3]=(24. + 38. t + 18. t  + 3.166666666666666666 t )/
 
   ((1. + t) (2. + 1. t) (3. + 1. t) (4. + 1. t))
 
(*______________________________________________
  coption == "AC" and cprec == 30, then
  the intermediate calculations are made with
  precision 30, using the function N[-,30].
  
  resultprec == 19, then the results are printed 
  with 19 decimal digits of precision.
  
  As toption == "VAR", relatives errors are not
  calculated, and the sixth and the seventh
  arguments are not employed.
  ______________________________________________*)
(*____________________MISTAKE___________________*)
tablegpt[3,t,"SCL","EC"]
fgpt[0]=1/(1 + t)
  
fgpt[1]=1/(1 + t/2)
  
fgpt[2]=3/(4 (1 + t/3)) + 1/(4 (1 + t))
  
fgpt[3]=16/(9 (1 + t/4)) - 9/(4 (1 + t/3)) + 
 
   4/(3 (1 + t/2)) + 5/(36 (1 + t))
  
(*______________________________________________
  TOPTION SHOULD BE EQUAL TO "VAR", NOT TO "SCL"
  
  In spite of the error, we obtain the exact 
  expressions of the approximants in the point t.
  
  The missing arguments take their default values.
  In particular reoption  == 0 and aroption == 0,
  then the relative errors, and the numerical
  approximations of the exact expressions of the
  approximants are not calculated.
  ______________________________________________*)
 
(*___________________MISTAKE____________________*)
tablegpt[3,t,"SCL","EC",19,0,0,0,1]
fgpt[0]=1/(1 + t)
ngpt[0]=1/(1. + t)
  
fgpt[1]=1/(1 + t/2)
ngpt[1]=1/(1. + 0.5 t)
  
fgpt[2]=3/(4 (1 + t/3)) + 1/(4 (1 + t))
ngpt[2]=1/(1. + 0.5 t) + 
 
   0.125 (6. (1/(1. + 0.3333333333333333333 t) - 
 
         1./(1. + 0.5 t)) - 
 
      2. (1/(1. + 0.5 t) - 1./(1. + t)))
  
fgpt[3]=16/(9 (1 + t/4)) - 9/(4 (1 + t/3)) + 
 
   4/(3 (1 + t/2)) + 5/(36 (1 + t))
ngpt[3]=1/(1. + 0.5 t) + 
 
   0.125 (6. (1/(1. + 0.3333333333333333333 t) - 
 
         1./(1. + 0.5 t)) - 
 
      2. (1/(1. + 0.5 t) - 1./(1. + t))) + 
 
   0.03703703703703703704 
 
    (4. (12. (1/(1. + 0.25 t) - 
 
            1./(1. + 0.3333333333333333333 t)) - 
 
         6. (1/(1. + 0.3333333333333333333 t) - 
 
            1./(1. + 0.5 t))) - 
 
      1.5 (6. (1/(1. + 0.3333333333333333333 t) - 
 
            1./(1. + 0.5 t)) - 
 
         2. (1/(1. + 0.5 t) - 1./(1. + t))))
  
(*______________________________________________
  TOPTION SHOULD BE EQUAL TO "VAR", NOT TO "SCL"
  
  aroption == 1, then the numerical approximations
  of the exact expressions of the approximants are
  calculated with precision resultprec == 19.
  
(*___________________MISTAKE____________________*)
tablegpt[3,t,"SCL","AC",25,0,0,30]
ngpt[0]=1./(1. + t)
  
ngpt[1]=1./(1. + t) + 1. (1./(1. + 0.5 t) - 1./(1. + t))
  
ngpt[2]=1./(1. + t) + 1. 
 
    (1./(1. + 0.5 t) - 1./(1. + t)) + 
 
   0.125 (6. (1./(1. + 0.3333333333333333333333333 t) - 
 
         1./(1. + 0.5 t)) - 
 
      2. (1./(1. + 0.5 t) - 1./(1. + t)))
  
ngpt[3]=1./(1. + t) + 1. 
 
    (1./(1. + 0.5 t) - 1./(1. + t)) + 
 
   0.125 (6. (1./(1. + 0.3333333333333333333333333 t) - 
 
         1./(1. + 0.5 t)) - 
 
      2. (1./(1. + 0.5 t) - 1./(1. + t))) + 
 
   0.03703703703703703703703704 
 
    (4. (12. (1./(1. + 0.25 t) - 
 
            1./(1. + 0.3333333333333333333333333 t)) - 
 
         6. (1./(1. + 0.3333333333333333333333333 t) - 
 
            1./(1. + 0.5 t))) - 
 
      1.5 (6. (1./(1. + 0.3333333333333333333333333 t) - 
 
            1./(1. + 0.5 t)) - 
 
         2. (1./(1. + 0.5 t) - 1./(1. + t))))
  
(*_____________________________________________
  TOPTION SHOULD BE EQUAL TO "VAR", NOT TO "SCL"
  
  coption == "AC" and cprec == 30, then the
  intermediate calculations are made with
  precision 30, using the function N[-,30].
  
  resultprec == 25, then the results are printed 
  with 25 digits of precision.
  
  We make reoption == 0, then relative errors
  are not calculated.
  ______________________________________________*)

tablegpt[3,1/10,"SCL","EC",19,0,0,19,1]
fgpt[0]=10/11
ngpt[0]=0.9090909090909090909
  
fgpt[1]=20/21
ngpt[1]=0.9523809523809523809
  
fgpt[2]=325/341
ngpt[2]=0.9530791788856304985
  
fgpt[3]=839495/880803
ngpt[3]=0.9531018854386281609
  
(*______________________________________________ 
  1/10 is a numerical expression, then we should 
  take toption == "SCL".                
 
  As 1/10 is exact, and the definitions of g,
  ci and initialf are exacts, we can obtain the
  exact numerical expressions of the approximants
  taking coption == "EC".
  
  aroption == 1, then the numerical approximations
  of the exact expressions of the approximants
  are calculated with precision resultprec. 
  In this case resultprec == 19.
  
  We make reoption == 0, then relatives errors 
  are not calculated.
 _______________________________________________*)
   
tablegpt[3,1/10,"SCL","EC",19,1,2,19,1]
fgpt[0]=10/11
ngpt[0]=0.9090909090909090909
re[0]=0.046
  
fgpt[1]=20/21
ngpt[1]=0.9523809523809523809
re[1]=0.00076
  
fgpt[2]=325/341
ngpt[2]=0.9530791788856304985
re[2]=0.000024
  
fgpt[3]=839495/880803
ngpt[3]=0.9531018854386281609
            -8
re[3]=9.2 10
  
(*_______________________________________________ 
   If reoption == 1, then relative errors are 
   calculated with precision cprec == 19, and are
   written with reprec == 2 decimal digits of
   precision.
  ______________________________________________*)
tablegpt[3,1/10,"SCL","AC",30,1,2,40]
ngpt[0]=0.909090909090909090909090909091
re[0]=0.046
  
ngpt[1]=0.952380952380952380952380952381
re[1]=0.00076
  
ngpt[2]=0.953079178885630498533724340176
re[2]=0.000024
  
ngpt[3]=0.953101885438628160894093230836
            -8
re[3]=9.2 10
  
(*_______________________________________________
  
  coption == "AC" and cprec == 40, then the 
  intermediate calculations are done with 
  precision 40, using the function N[-,40].
  
  resultprec == 30, then the results are printed
  with 30 decimal digits of precision.
  
  This is possible, because the precision of 
  1/10 is greather than 40.
  (Precision[1/10] == Infinity)
  
  ______________________________________________*)
tablegpt[3,0.1,"SCL","AC",30,1,2,40]
ngpt[0]=0.9090909090909090909
re[0]=0.046
  
ngpt[1]=0.952380952380952381
re[1]=0.00076
  
ngpt[2]=0.9530791788856304986
re[2]=0.000024
  
ngpt[3]=0.953101885438628161
            -8
re[3]=9.2 10
  
(*_______________________________________________
  If we replace 1/10 by 0.1, which is a low
  precision number, calculations are done in
  the machine precision, and the results can
  not have more than 19 decimal digits of
  precision.
  
  Precision[1/10]=Infinity , Precision[0.1]=19
  
  Thus, we should ask for:
  _______________________________________________*)
tablegpt[3,0.1,"SCL","AC",19,1,2]
ngpt[0]=0.9090909090909090909
re[0]=0.046
  
ngpt[1]=0.952380952380952381
re[1]=0.00076
  
ngpt[2]=0.9530791788856304986
re[2]=0.000024
  
ngpt[3]=0.953101885438628161
            -8
re[3]=9.2 10
  
(*___________________MISTAKE____________________*)
tablegpt[3,1/10,"VAR","EC",19,1,2,19,1]
fgpt[0]=10/11
 
fgpt[1]=20/21
 
fgpt[2]=325/341
 
fgpt[3]=839495/880803
 
(*_______________________________________________
  TOPTION SHOULD BE EQUAL TO "SCL", NOT TO "VAR"
  
  We get only the exact expressions of the
  approximants.
  
  reoption == 1 and aroption == 1, but the
  relatives errors and the numerical approximations
  of the approximants are not calculated, because
  toption == "VAR".
  
  The values of resultprec and cprec are not 
  employed.
 _______________________________________________*)
(*___________________MISTAKE____________________*)
tablegpt[3,1/10,"VAR","AC",30,1,2,40]
ngpt[0]=0.909090909090909090909090909091
 
ngpt[1]=0.952380952380952380952380952381
 
ngpt[2]=0.953079178885630498533724340176
 
ngpt[3]=0.953101885438628160894093230836
 
(*_______________________________________________
  TOPTION SHOULD BE EQUAL TO "SCL", NOT TO "VAR"
  
  coption == "AC" and cprec == 40, then the 
  intermediate calculations are done with
  precision 40, using the function N[-,40].
  
  resultprec == 30, then the results are printed
  with 30 decimal digits of precision.
  
  reoption == 1, but relatives errors are not
  calculated, because toption == "VAR".
  
  Remark: Precision[1/10] >= 40.
________________________________________________*)
(*______________________________________________
___ WE GIVE BELOW THE RESULTS OF THE ARTICLE ___
________________________________________________

The numerical results presented in the article are obtained 
taking  coption == "AC"  and  cprec == 19 .  This means that
the calculations are made in the fixed machine precision , 
using the function  N[ -, 19 ] .  In other words , we do low
precision calculations .

We remember that the precision of the Macintosh SE/30
is 19 . 
 
__________________________________________________*)
Timing[tablegpt[10,t,"VAR","EC"]]
fgpt[0]=1/(1 + t)
 
fgpt[1]=2/(2 + t)
 
fgpt[2]=(6 + 5 t)/(2 (1 + t) (3 + t))
 
                            2       3
fgpt[3]=(144 + 228 t + 108 t  + 19 t )/
 
   (6 (1 + t) (2 + t) (3 + t) (4 + t))
 
                             2        3       4
fgpt[4]=(720 + 1284 t + 768 t  + 203 t  + 18 t )/
 
   (6 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t))
 
                                  2         3         4
fgpt[5]=(21600 + 42120 t + 29460 t  + 9930 t  + 1555 t  + 
 
          5
     159 t )/
 
   (30 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t) (6 + t))
 
                                     2           3
fgpt[6]=(302400 + 632880 t + 496680 t  + 197940 t  + 
 
            4         5        6
     41630 t  + 5336 t  - 211 t )/
 
   (60 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t) (6 + t) 
 
     (7 + t))
 
                                           2
fgpt[7]=(16934400 + 37558080 t + 32244240 t  + 
 
               3            4           5          6
     14561400 t  + 3716860 t  + 590226 t  + 25536 t  + 
 
            7
     19771 t )/
 
   (420 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t) (6 + t) 
 
     (7 + t) (8 + t))
 
                                              2
fgpt[8]=(152409600 + 354957120 t + 327756240 t  + 
 
                3             4            5
     163296840 t  + 48013140 t  + 9028894 t  + 
 
             6           7           8
     820050 t  + 203475 t  - 117605 t )/
 
   (420 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t) (6 + t) 
 
     (7 + t) (8 + t) (9 + t))
 
                                                 2
fgpt[9]=(1524096000 + 3701980800 t + 3632519520 t  + 
 
                 3              4              5
     1960724640 t  + 643428240 t  + 138302080 t  + 
 
               6            7           8           9
     17229394 t  + 2854800 t  - 972575 t  + 909115 t )/
 
   (420 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t) (6 + t) 
 
     (7 + t) (8 + t) (9 + t) (10 + t))
 
                                                     2
fgpt[10]=(16765056000 + 42245884800 t + 43659695520 t  + 
 
                  3               4               5
     25200490560 t  + 9038435280 t  + 2164751120 t  + 
 
                6             7            8
     327825414 t  + 48632194 t  - 7843525 t  + 
 
              9            10
     9027690 t  - 7756313 t  )/
 
   (420 (1 + t) (2 + t) (3 + t) (4 + t) (5 + t) (6 + t) 
 
     (7 + t) (8 + t) (9 + t) (10 + t) (11 + t))
 
{346.9 Second, Null}

(* EXAMPLE 1 / CHOICE A / t=1/10 *)

Timing[tablegpt[18,1/10,"SCL","AC",19,1,2,19]]
ngpt[0]=0.9090909090909090909
re[0]=0.046
  
ngpt[1]=0.9523809523809523809
re[1]=0.00076
  
ngpt[2]=0.9530791788856304985
re[2]=0.000024
  
ngpt[3]=0.9531018854386281611
            -8
re[3]=9.2 10
  
ngpt[4]=0.9531017741319958195
            -8
re[4]=2.5 10
  
ngpt[5]=0.953101799312840515
            -9
re[5]=1.3 10
  
ngpt[6]=0.9531017979533113538
            -11
re[6]=9.4 10
  
ngpt[7]=0.9531017980496206312
            -12
re[7]=6.7 10
  
ngpt[8]=0.9531017980427756454
           -13
re[8]=5. 10
  
ngpt[9]=0.9531017980431676873
            -14
re[9]=8.5 10
  
ngpt[10]=0.9531017980392848927
             -12
re[10]=4.2 10
  
ngpt[11]=0.9531017979081451278
             -10
re[11]=1.4 10
  
ngpt[12]=0.9531017930245871805
             -9
re[12]=5.3 10
  
ngpt[13]=0.9531016007674931718
             -7
re[13]=2.1 10
  
ngpt[14]=0.9530940770413426088
             -6
re[14]=8.1 10
  
ngpt[15]=0.9528104393613031248
re[15]=0.00031
  
ngpt[16]=0.9422785871535768974
re[16]=0.011
  
ngpt[17]=0.535593077066076859
re[17]=0.44
  
ngpt[18]=-16.08206884403569196
re[18]=18.
  
{105.367 Second, Null}

(* EXAMPLE 1 / CHOICE A / t=5/10 *)

Timing[tablegpt[18,5/10,"SCL","AC",19,1,2,19]]
ngpt[0]=0.6666666666666666667
re[0]=0.18
  
ngpt[1]=0.8
re[1]=0.013
  
ngpt[2]=0.8095238095238095238
re[2]=0.0017
  
ngpt[3]=0.8109347442680776014
            -6
re[3]=5.6 10
  
ngpt[4]=0.8109026775693442359
re[4]=0.000034
  
ngpt[5]=0.8109367176033842679
           -6
re[5]=8. 10
  
ngpt[6]=0.8109280184835740259
            -6
re[6]=2.7 10
  
ngpt[7]=0.8109309547180695183
            -7
re[7]=9.1 10
  
ngpt[8]=0.810929955569791207
            -7
re[8]=3.2 10
  
ngpt[9]=0.8109303111616713609
            -7
re[9]=1.2 10
  
ngpt[10]=0.81093018067630991
             -8
re[10]=4.4 10
  
ngpt[11]=0.8109302297899225965
             -8
re[11]=1.7 10
  
ngpt[12]=0.8109302083555396209
             -9
re[12]=9.7 10
  
ngpt[13]=0.8109300972258040342
             -7
re[13]=1.5 10
  
ngpt[14]=0.8109255247104956377
             -6
re[14]=5.8 10
  
ngpt[15]=0.8107880723123342286
re[15]=0.00018
  
ngpt[16]=0.8089713950037241565
re[16]=0.0024
  
ngpt[17]=0.9545179237449895502
re[17]=0.18
  
ngpt[18]=16.7493991583511504
re[18]=20.
  
{106.067 Second, Null}

<<BIF.M

(* THE DEFINITION OF INITIALF IS CHANGED *)

Timing[ tablegpt[10,t,"VAR","EC"] ]
Syntax::bktwrn: 
   Warning: "c (a X + b)" should probably be "c [a X + b]"
    . (line 385 of "Integrate`table`")
    
fgpt[0]=(2 (Log[-1 - t] - Log[-1 - t/2]))/t
 
fgpt[1]=(Log[-1 - t] + 8 Log[-1 - t/2] - 9 Log[-1 - t/3])/
 
   (2 t)
 
fgpt[2]=(7 Log[-1 - t] - 24 Log[-1 - t/2] + 
 
     81 Log[-1 - t/3] - 64 Log[-1 - t/4])/(6 t)
 
fgpt[3]=(23 Log[-1 - t] + 64 Log[-1 - t/2] - 
 
     486 Log[-1 - t/3] + 1024 Log[-1 - t/4] - 
 
     625 Log[-1 - t/5])/(24 t)
 
fgpt[4]=(121 Log[-1 - t] - 160 Log[-1 - t/2] + 
 
     2430 Log[-1 - t/3] - 10240 Log[-1 - t/4] + 
 
     15625 Log[-1 - t/5] - 7776 Log[-1 - t/6])/(120 t)
 
fgpt[5]=(719 Log[-1 - t] + 384 Log[-1 - t/2] - 
 
     10935 Log[-1 - t/3] + 81920 Log[-1 - t/4] - 
 
     234375 Log[-1 - t/5] + 279936 Log[-1 - t/6] - 
 
     117649 Log[-1 - t/7])/(720 t)
 
fgpt[6]=(5041 Log[-1 - t] - 896 Log[-1 - t/2] + 
 
     45927 Log[-1 - t/3] - 573440 Log[-1 - t/4] + 
 
     2734375 Log[-1 - t/5] - 5878656 Log[-1 - t/6] + 
 
     5764801 Log[-1 - t/7] - 2097152 Log[-1 - t/8])/
 
   (5040 t)
 
fgpt[7]=(40319 Log[-1 - t] + 2048 Log[-1 - t/2] - 
 
     183708 Log[-1 - t/3] + 3670016 Log[-1 - t/4] - 
 
     27343750 Log[-1 - t/5] + 94058496 Log[-1 - t/6] - 
 
     161414428 Log[-1 - t/7] + 134217728 Log[-1 - t/8] - 
 
     43046721 Log[-1 - t/9])/(40320 t)
 
fgpt[8]=(362881 Log[-1 - t] - 4608 Log[-1 - t/2] + 
 
     708588 Log[-1 - t/3] - 22020096 Log[-1 - t/4] + 
 
     246093750 Log[-1 - t/5] - 1269789696 Log[-1 - t/6] + 
 
     3389702988 Log[-1 - t/7] - 
 
     4831838208 Log[-1 - t/8] + 
 
     3486784401 Log[-1 - t/9] - 1000000000 Log[-1 - t/10])
 
    /(362880 t)
 
fgpt[9]=(3628799 Log[-1 - t] + 10240 Log[-1 - t/2] - 
 
     2657205 Log[-1 - t/3] + 125829120 Log[-1 - t/4] - 
 
     2050781250 Log[-1 - t/5] + 
 
     15237476352 Log[-1 - t/6] - 
 
     59319802290 Log[-1 - t/7] + 
 
     128849018880 Log[-1 - t/8] - 
 
     156905298045 Log[-1 - t/9] + 
 
     100000000000 Log[-1 - t/10] - 
 
     25937424601 Log[-1 - t/11])/(3628800 t)
 
fgpt[10]=(39916801 Log[-1 - t] - 22528 Log[-1 - t/2] + 
 
     9743085 Log[-1 - t/3] - 692060160 Log[-1 - t/4] + 
 
     16113281250 Log[-1 - t/5] - 
 
     167612239872 Log[-1 - t/6] + 
 
     913524955266 Log[-1 - t/7] - 
 
     2834678415360 Log[-1 - t/8] + 
 
     5177874835485 Log[-1 - t/9] - 
 
     5500000000000 Log[-1 - t/10] + 
 
     3138428376721 Log[-1 - t/11] - 
 
     743008370688 Log[-1 - t/12])/(39916800 t)
 
{1322.8 Second, Null}

(* EXAMPLE 1 / CHOICE B / t=1/10 *)

Timing[tablegpt[18,1/10,"SCL","AC",19,1,2,19] ]

ngpt[0]=0.9304003126978571612 + 0. I
re[0]=0.024
  
ngpt[1]=0.9526154387643152494 + 0. I
re[1]=0.00051
  
ngpt[2]=0.9530929357373173121 + 0. I
            -6
re[2]=9.3 10
  
ngpt[3]=0.9531016594990221988 + 0. I
            -7
re[3]=1.5 10
  
ngpt[4]=0.9531017961560421776 + 0. I
           -9
re[4]=2. 10
  
ngpt[5]=0.9531017980205204763 + 0. I
            -11
re[5]=2.4 10
  
ngpt[6]=0.9531017980430070554 + 0. I
            -13
re[6]=2.5 10
  
ngpt[7]=0.9531017980432356399 + 0. I
            -14
re[7]=1.4 10
  
ngpt[8]=0.9531017980432846559 + 0. I
            -14
re[8]=3.8 10
  
ngpt[9]=0.9531017980431149106 + 0. I
            -13
re[9]=1.4 10
  
ngpt[10]=0.9531017980435545993 + 0. I
             -13
re[10]=3.2 10
  
ngpt[11]=0.9531017980433808646 + 0. I
             -13
re[11]=1.4 10
  
ngpt[12]=0.9531017980408155513 + 0. I
             -12
re[12]=2.6 10
  
ngpt[13]=0.9531017980413931785 + 0. I
             -12
re[13]=1.9 10
  
ngpt[14]=0.9531017981194427825 + 0. I
            -11
re[14]=8. 10
  
ngpt[15]=0.9531017975688508125 + 0. I
            -10
re[15]=5. 10
  
ngpt[16]=0.9531018001032914474 + 0. I
             -9
re[16]=2.2 10
  
ngpt[17]=0.9531017902184169881 + 0. I
             -9
re[17]=8.2 10
  
ngpt[18]=0.9531018272524060622 + 0. I
             -8
re[18]=3.1 10
  
{198.867 Second, Null}

(* EXAMPLE 1 / CHOICE B / t=5/10 *)

Timing[tablegpt[18,5/10,"SCL","AC",19,1,2,19] ]

ngpt[0]=0.7292862271758185047 + 0. I
re[0]=0.1
  
ngpt[1]=0.8032574001765176901 + 0. I
re[1]=0.0095
  
ngpt[2]=0.8103004364051660181 + 0. I
re[2]=0.00078
  
ngpt[3]=0.8108850424152741188 + 0. I
re[3]=0.000056
  
ngpt[4]=0.8109273550473686867 + 0. I
            -6
re[4]=3.5 10
  
ngpt[5]=0.8109300544066455737 + 0. I
           -7
re[5]=2. 10
  
ngpt[6]=0.8109302079622129344 + 0. I
           -8
re[6]=1. 10
  
ngpt[7]=0.8109302158331711878 + 0. I
            -10
re[7]=4.7 10
  
ngpt[8]=0.8109302162000442809 + 0. I
           -11
re[8]=2. 10
  
ngpt[9]=0.8109302162155757041 + 0. I
            -13
re[9]=9.3 10
  
ngpt[10]=0.8109302162166090232 + 0. I
             -13
re[10]=3.5 10
  
ngpt[11]=0.8109302162160694845 + 0. I
             -13
re[11]=3.2 10
  
ngpt[12]=0.8109302162142455786 + 0. I
             -12
re[12]=2.6 10
  
ngpt[13]=0.8109302162303289475 + 0. I
             -11
re[13]=1.7 10
  
ngpt[14]=0.8109302161587919064 + 0. I
             -11
re[14]=7.1 10
  
ngpt[15]=0.8109302164174791966 + 0. I
             -10
re[15]=2.5 10
  
ngpt[16]=0.8109302155461385625 + 0. I
             -10
re[16]=8.3 10
  
ngpt[17]=0.8109302184751786312 + 0. I
             -9
re[17]=2.8 10
  
ngpt[18]=0.8109302078896959859 + 0. I
            -8
re[18]=1. 10
  
{198.083 Second, Null}

<<BE.M

(* THE DEFINITIONS OF THE GENERATING FUNCTION G
   AND THE MOMENTS Ci ARE CHANGED *)

g[x,t]

Log[1 + t x]
------------
     t
c[i]

1

(* EXAMPLE 2 / CHOICE B / t=1/10 *)

Timing[ tablegpt[13,1/10,"SCL","AC",19,1,2,19] ]

ngpt[0]=-0.7808331152258671109
re[0]=1.8
  
ngpt[1]=1.083499342005201791
re[1]=0.14
  
ngpt[2]=0.9412129219466011686
re[2]=0.012
  
ngpt[3]=0.9542485780911726024
re[3]=0.0012
  
ngpt[4]=0.9529886775784329004
re[4]=0.00012
  
ngpt[5]=0.9531130724518763377
re[5]=0.000012
  
ngpt[6]=0.9531006666029636968
            -6
re[6]=1.2 10
  
ngpt[7]=0.9531019914757284546
           -7
re[7]=2. 10
  
ngpt[8]=0.953098361446182256
            -6
re[8]=3.6 10
  
ngpt[9]=0.9532006850731807849
re[9]=0.0001
  
ngpt[10]=0.9535019673510525734
re[10]=0.00042
  
ngpt[11]=0.6939102521456232009
re[11]=0.27
  
ngpt[12]=20.22503775691232666
re[12]=20.
  
ngpt[13]=-1018.437274602137056
re[13]=1100.
  
NumberForm::sigz: 
   Requested number format may result in trailing zeros
     which are not significant digits.

{108.033 Second, Null}

<<BIF.M

(* THE DEFINITION OF INITIALF IS CHANGED *)

initialf[i,f[x],x]

      1
f[-(-----)]
    1 + i

(* EXAMPLE 2 / CHOICE A / t=1/10 *)

Timing[ tablegpt[13,1/10,"SCL","AC",19,1,2,19] ]

ngpt[0]=-1.053605156578263013
re[0]=2.1
  
ngpt[1]=1.1090836942327677
re[1]=0.16
  
ngpt[2]=0.9388043121126286463
re[2]=0.015
  
ngpt[3]=0.9544763924291553613
re[3]=0.0014
  
ngpt[4]=0.9529670353515125909
re[4]=0.00014
  
ngpt[5]=0.9531151363963682564
re[5]=0.000014
  
ngpt[6]=0.9531004710085092535
            -6
re[6]=1.4 10
  
ngpt[7]=0.9531019304663106517
            -7
re[7]=1.4 10
  
ngpt[8]=0.9531017846104010524
            -8
re[8]=1.4 10
  
ngpt[9]=0.9531018094421660127
            -8
re[9]=1.2 10
  
ngpt[10]=0.9531015237720669914
             -7
re[10]=2.9 10
  
ngpt[11]=0.9531069149587972882
             -6
re[11]=5.4 10
  
ngpt[12]=0.952994232040929374
re[12]=0.00011
  
ngpt[13]=0.9603178184280040616
re[13]=0.0076
  
{52. Second, Null}

(*______________________________


   Let us repeat these calculations taking  coption == "EC" ,
   reoption != 0  and  resultprec == 19 .
   
   The value of cprec is adapted to each case.

______________________________*)

<<BE.M

(* THE DEFINITIONS OF THE GENERATING FUNCTION G
   AND THE MOMENTS Ci ARE CHANGED *)

g[x,t]

   1
-------
1 - t x
c[i]

    i
(-1)
-----
1 + i
initialf[i,f[x],x]

      1
f[-(-----)]
    1 + i

(* EXEMPLE 1 / CHOICE A / t= 1/10 *)

(* cprec == 30  ,  aroption  == 1 *)

Timing[tablegpt[18,1/10,"SCL","EC",19,1,2,30,1] ]

fgpt[0]=10/11
ngpt[0]=0.9090909090909090909
re[0]=0.046
  
fgpt[1]=20/21
ngpt[1]=0.9523809523809523809
re[1]=0.00076
  
fgpt[2]=325/341
ngpt[2]=0.9530791788856304985
re[2]=0.000024
  
fgpt[3]=839495/880803
ngpt[3]=0.9531018854386281609
            -8
re[3]=9.2 10
  
fgpt[4]=6116320/6417279
ngpt[4]=0.9531017741319958195
            -8
re[4]=2.5 10
  
fgpt[5]=2611668709/2740178133
ngpt[5]=0.9531017993128405131
            -9
re[5]=1.3 10
  
fgpt[6]=41206328461/43233921654
ngpt[6]=0.9531017979533113395
            -11
re[6]=9.4 10
  
fgpt[7]=210275894157731/220622702200362
ngpt[7]=0.9531017980496205578
            -12
re[7]=6.7 10
  
fgpt[8]=19135106368216145/20076665900232942
ngpt[8]=0.9531017980427779875
            -13
re[8]=4.9 10
  
fgpt[9]=2880247009226315/3021972065459802
ngpt[9]=0.9531017980432843238
            -14
re[9]=3.7 10
  
fgpt[10]=2648440462891067927/2778759276635944602
ngpt[10]=0.9531017980432458244
             -15
re[10]=2.9 10
  
fgpt[11]=285531014744749821876937/299580816373397823486222
ngpt[11]=0.9531017980432488205
             -16
re[11]=2.3 10
  
fgpt[12]=56106844397343326002317140/
 
   58867630417372672315042623
ngpt[12]=0.9531017980432485828
             -17
re[12]=1.9 10
  
fgpt[13]=205687691560660637264609466155/
 
   215808733110088216706946255918
ngpt[13]=0.9531017980432486019
             -18
re[13]=1.5 10
  
fgpt[14]=62117682851319512351568226223695/
 
   65174237399246641445497769287236
ngpt[14]=0.9531017980432486004
             -19
re[14]=1.3 10
  
fgpt[15]=46952802530809584459944858562163/
 
   49263155968444644472887985235892
ngpt[15]=0.9531017980432486005
             -20
re[15]=1.1 10
  
fgpt[16]=13054671195264713700496171088310871/
 
   13697037632356177752946557910281636
ngpt[16]=0.9531017980432486005
             -22
re[16]=8.9 10
  
fgpt[17]=228789923829811637017260753724668144983/
 
   240047730787545853126172573407899730884
ngpt[17]=0.9531017980432486005
             -23
re[17]=7.6 10
  
fgpt[18]=1005074135384362521416743369142993521334315/
 
   1054529681349688932783276114980903517773412
ngpt[18]=0.9531017980432486005
             -24
re[18]=6.5 10
  
{271.417 Second, Null}

(* EXEMPLE 1 / CHOICE A / t= 5/10 *)

(* cprec == 19 , aroption == 1 *)

Timing[tablegpt[18,5/10,"SCL","EC",19,1,2,19,1] ]

fgpt[0]=2/3
ngpt[0]=0.6666666666666666667
re[0]=0.18
  
fgpt[1]=4/5
ngpt[1]=0.8
re[1]=0.013
  
fgpt[2]=17/21
ngpt[2]=0.8095238095238095238
re[2]=0.0017
  
fgpt[3]=2299/2835
ngpt[3]=0.8109347442680776014
            -6
re[3]=5.6 10
  
fgpt[4]=25288/31185
ngpt[4]=0.8109026775693442361
re[4]=0.000034
  
fgpt[5]=234827/289575
ngpt[5]=0.8109367176033842701
           -6
re[5]=8. 10
  
fgpt[6]=49313141/60810750
ngpt[6]=0.8109280184835740391
            -6
re[6]=2.7 10
  
fgpt[7]=177826819/219287250
ngpt[7]=0.810930954718069564
            -7
re[7]=9.1 10
  
fgpt[8]=5309394197/6547290750
ngpt[8]=0.8109299555697904511
            -7
re[8]=3.2 10
  
fgpt[9]=260160429733/320817246750
ngpt[9]=0.8109303111616458008
            -7
re[9]=1.2 10
  
fgpt[10]=17951066763101/22136390025750
ngpt[10]=0.8109301806762325677
             -8
re[10]=4.4 10
  
fgpt[11]=2961926195431493/3652504354248750
ngpt[11]=0.8109302298260242143
             -8
re[11]=1.7 10
  
fgpt[12]=599790040578376352/739632131735371875
ngpt[12]=0.810930210902426415
             -9
re[12]=6.6 10
  
fgpt[13]=26602452631541800019/32804860431086493750
ngpt[13]=0.8109302183262094558
             -9
re[13]=2.6 10
  
fgpt[14]=28038984971301224664911/34576322894365164412500
ngpt[14]=0.8109302153662697054
            -9
re[14]=1. 10
  
fgpt[15]=71175885032208528128299/87770665808773109662500
ngpt[15]=0.8109302165632443957
             -10
re[15]=4.3 10
  
fgpt[16]=4626432524297387065348171/
 
   5705093277570252128062500
ngpt[16]=0.8109302160731266838
             -10
re[16]=1.8 10
  
fgpt[17]=4074036481915723088426254549/
 
   5023905140228364023971837500
ngpt[17]=0.8109302162760453318
             -11
re[17]=7.4 10
  
fgpt[18]=264812371296814677589826687017/
 
   326553834114843661558169437500
ngpt[18]=0.8109302161911976887
             -11
re[18]=3.1 10
  
{267.817 Second, Null}

<<BIF.M

(* THE DEFINITION OF INITIALF IS CHANGED *)

(* EXAMPLE 1 / CHOICE B / t=1/10 *)

(* cprec == 50 , aroption == 0 *)
Syntax::bktwrn: 
   Warning: "c (a X + b)" should probably be "c [a X + b]".
     (line 385 of "Integrate`table`")

Timing[ tablegpt[15,1/10,"SCL","EC",19,1,2,50]]

fgpt[0]=-20 Log[21/2] + 20 Log[11]
re[0]=0.024
  
fgpt[1]=-45 Log[31/3] + 40 Log[21/2] + 5 Log[11]
re[1]=0.00051
  
fgpt[2]=(-320 Log[41/4])/3 + 135 Log[31/3] - 
 
   40 Log[21/2] + (35 Log[11])/3
            -6
re[2]=9.3 10
  
fgpt[3]=(-3125 Log[51/5])/12 + (1280 Log[41/4])/3 - 
 
   (405 Log[31/3])/2 + (80 Log[21/2])/3 + (115 Log[11])/12
            -7
re[3]=1.5 10
  
fgpt[4]=-648 Log[61/6] + (15625 Log[51/5])/12 - 
 
   (2560 Log[41/4])/3 + (405 Log[31/3])/2 - 
 
   (40 Log[21/2])/3 + (121 Log[11])/12
           -9
re[4]=2. 10
  
fgpt[5]=(-117649 Log[71/7])/72 + 3888 Log[61/6] - 
 
   (78125 Log[51/5])/24 + (10240 Log[41/4])/9 - 
 
   (1215 Log[31/3])/8 + (16 Log[21/2])/3 + 
 
   (719 Log[11])/72
            -11
re[5]=2.4 10
  
fgpt[6]=(-262144 Log[81/8])/63 + (823543 Log[71/7])/72 - 
 
   11664 Log[61/6] + (390625 Log[51/5])/72 - 
 
   (10240 Log[41/4])/9 + (729 Log[31/3])/8 - 
 
   (16 Log[21/2])/9 + (5041 Log[11])/504
            -13
re[6]=2.6 10
  
fgpt[7]=(-4782969 Log[91/9])/448 + 
 
   (2097152 Log[81/8])/63 - (5764801 Log[71/7])/144 + 
 
   23328 Log[61/6] - (1953125 Log[51/5])/288 + 
 
   (8192 Log[41/4])/9 - (729 Log[31/3])/16 + 
 
   (32 Log[21/2])/63 + (40319 Log[11])/4032
            -15
re[7]=2.5 10
  
fgpt[8]=(-15625000 Log[101/10])/567 + 
 
   (43046721 Log[91/9])/448 - (8388608 Log[81/8])/63 + 
 
   (40353607 Log[71/7])/432 - 34992 Log[61/6] + 
 
   (1953125 Log[51/5])/288 - (16384 Log[41/4])/27 + 
 
   (2187 Log[31/3])/112 - (8 Log[21/2])/63 + 
 
   (362881 Log[11])/36288
            -17
re[8]=2.2 10
  
fgpt[9]=(-25937424601 Log[111/11])/362880 + 
 
   (156250000 Log[101/10])/567 - 
 
   (387420489 Log[91/9])/896 + (67108864 Log[81/8])/189 - 
 
   (282475249 Log[71/7])/1728 + (209952 Log[61/6])/5 - 
 
   (9765625 Log[51/5])/1728 + (65536 Log[41/4])/189 - 
 
   (6561 Log[31/3])/896 + (16 Log[21/2])/567 + 
 
   (3628799 Log[11])/362880
            -19
re[9]=1.8 10
  
fgpt[10]=(-71663616 Log[121/12])/385 + 
 
   (285311670611 Log[111/11])/362880 - 
 
   (781250000 Log[101/10])/567 + 
 
   (1162261467 Log[91/9])/896 - 
 
   (134217728 Log[81/8])/189 + 
 
   (1977326743 Log[71/7])/8640 - (209952 Log[61/6])/5 + 
 
   (48828125 Log[51/5])/12096 - (32768 Log[41/4])/189 + 
 
   (2187 Log[31/3])/896 - (16 Log[21/2])/2835 + 
 
   (39916801 Log[11])/3991680
             -21
re[10]=1.4 10
  
fgpt[11]=(-23298085122481 Log[131/13])/47900160 + 
 
   (859963392 Log[121/12])/385 - 
 
   (3138428376721 Log[111/11])/725760 + 
 
   (7812500000 Log[101/10])/1701 - 
 
   (10460353203 Log[91/9])/3584 + 
 
   (1073741824 Log[81/8])/945 - 
 
   (13841287201 Log[71/7])/51840 + 
 
   (1259712 Log[61/6])/35 - (244140625 Log[51/5])/96768 + 
 
   (131072 Log[41/4])/1701 - (6561 Log[31/3])/8960 + 
 
   (32 Log[21/2])/31185 + (479001599 Log[11])/47900160
             -24
re[11]=9.7 10
  
fgpt[12]=(-221460595216 Log[141/14])/173745 + 
 
   (302875106592253 Log[131/13])/47900160 - 
 
   (5159780352 Log[121/12])/385 + 
 
   (34522712143931 Log[111/11])/2177280 - 
 
   (19531250000 Log[101/10])/1701 + 
 
   (94143178827 Log[91/9])/17920 - 
 
   (4294967296 Log[81/8])/2835 + 
 
   (13841287201 Log[71/7])/51840 - 
 
   (944784 Log[61/6])/35 + 
 
   (1220703125 Log[51/5])/870912 - 
 
   (262144 Log[41/4])/8505 + (19683 Log[31/3])/98560 - 
 
   (16 Log[21/2])/93555 + (6227020801 Log[11])/622702080
             -26
re[12]=6.4 10
  
fgpt[13]=(-24027099609375 Log[151/15])/7175168 + 
 
   (3100448333024 Log[141/14])/173745 - 
 
   (3937376385699289 Log[131/13])/95800320 + 
 
   (20639121408 Log[121/12])/385 - 
 
   (379749833583241 Log[111/11])/8709120 + 
 
   (39062500000 Log[101/10])/1701 - 
 
   (282429536481 Log[91/9])/35840 + 
 
   (34359738368 Log[81/8])/19845 - 
 
   (96889010407 Log[71/7])/414720 + 
 
   (629856 Log[61/6])/35 - 
 
   (1220703125 Log[51/5])/1741824 + 
 
   (1048576 Log[41/4])/93555 - (19683 Log[31/3])/394240 + 
 
   (32 Log[21/2])/1216215 + 
 
   (87178291199 Log[11])/8717829120
             -28
re[13]=3.9 10
  
fgpt[14]=(-1125899906842624 Log[161/16])/127702575 + 
 
   (360406494140625 Log[151/15])/7175168 - 
 
   (21703138331168 Log[141/14])/173745 + 
 
   (51185893014090757 Log[131/13])/287400960 - 
 
   (61917364224 Log[121/12])/385 + 
 
   (4177248169415651 Log[111/11])/43545600 - 
 
   (195312500000 Log[101/10])/5103 + 
 
   (2541865828329 Log[91/9])/250880 - 
 
   (34359738368 Log[81/8])/19845 + 
 
   (678223072849 Log[71/7])/3732480 - 
 
   (1889568 Log[61/6])/175 + 
 
   (6103515625 Log[51/5])/19160064 - 
 
   (1048576 Log[41/4])/280665 + 
 
   (59049 Log[31/3])/5125120 - (32 Log[21/2])/8513505 + 
 
   (1307674368001 Log[11])/130767436800
             -30
re[14]=2.3 10
  
fgpt[15]=(-48661191875666868481 Log[171/17])/
 
    2092278988800 + (18014398509481984 Log[161/16])/
 
    127702575 - (5406097412109375 Log[151/15])/14350336 + 
 
   (303843936636352 Log[141/14])/521235 - 
 
   (665416609183179841 Log[131/13])/1149603840 + 
 
   (743008370688 Log[121/12])/1925 - 
 
   (45949729863572161 Log[111/11])/261273600 + 
 
   (1953125000000 Log[101/10])/35721 - 
 
   (22876792454961 Log[91/9])/2007040 + 
 
   (274877906944 Log[81/8])/178605 - 
 
   (4747561509943 Log[71/7])/37324800 + 
 
   (11337408 Log[61/6])/1925 - 
 
   (30517578125 Log[51/5])/229920768 + 
 
   (4194304 Log[41/4])/3648645 - 
 
   (177147 Log[31/3])/71751680 + 
 
   (64 Log[21/2])/127702575 + 
 
   (20922789887999 Log[11])/2092278988800

{46118.2 Second, Null}

(* EXAMPLE 1 / CHOICE B / t= 5/10 *)

(* cprec == 40 , aroption == 0 *)

Timing[ tablegpt[15,5/10,"SCL","EC",19,1,2,40]]

fgpt[0]=-4 Log[5/2] + 4 Log[3]
re[0]=0.1
 
fgpt[1]=-9 Log[7/3] + 8 Log[5/2] + Log[3]
re[1]=0.0095
 
fgpt[2]=(-64 Log[9/4])/3 + 27 Log[7/3] - 8 Log[5/2] + 
 
   (7 Log[3])/3
re[2]=0.00078
 
fgpt[3]=(-625 Log[11/5])/12 + (256 Log[9/4])/3 - 
 
   (81 Log[7/3])/2 + (16 Log[5/2])/3 + (23 Log[3])/12
re[3]=0.000056
 
fgpt[4]=(-648 Log[13/6])/5 + (3125 Log[11/5])/12 - 
 
   (512 Log[9/4])/3 + (81 Log[7/3])/2 - (8 Log[5/2])/3 + 
 
   (121 Log[3])/60
            -6
re[4]=3.5 10
 
fgpt[5]=(-117649 Log[15/7])/360 + (3888 Log[13/6])/5 - 
 
   (15625 Log[11/5])/24 + (2048 Log[9/4])/9 - 
 
   (243 Log[7/3])/8 + (16 Log[5/2])/15 + (719 Log[3])/360
           -7
re[5]=2. 10
 
fgpt[6]=(-262144 Log[17/8])/315 + (823543 Log[15/7])/360 - 
 
   (11664 Log[13/6])/5 + (78125 Log[11/5])/72 - 
 
   (2048 Log[9/4])/9 + (729 Log[7/3])/40 - 
 
   (16 Log[5/2])/45 + (5041 Log[3])/2520
           -8
re[6]=1. 10
 
fgpt[7]=(-4782969 Log[19/9])/2240 + 
 
   (2097152 Log[17/8])/315 - (5764801 Log[15/7])/720 + 
 
   (23328 Log[13/6])/5 - (390625 Log[11/5])/288 + 
 
   (8192 Log[9/4])/45 - (729 Log[7/3])/80 + 
 
   (32 Log[5/2])/315 + (40319 Log[3])/20160
            -10
re[7]=4.7 10
 
fgpt[8]=(-3125000 Log[21/10])/567 + 
 
   (43046721 Log[19/9])/2240 - (8388608 Log[17/8])/315 + 
 
   (40353607 Log[15/7])/2160 - (34992 Log[13/6])/5 + 
 
   (390625 Log[11/5])/288 - (16384 Log[9/4])/135 + 
 
   (2187 Log[7/3])/560 - (8 Log[5/2])/315 + 
 
   (362881 Log[3])/181440
           -11
re[8]=2. 10
 
fgpt[9]=(-25937424601 Log[23/11])/1814400 + 
 
   (31250000 Log[21/10])/567 - 
 
   (387420489 Log[19/9])/4480 + (67108864 Log[17/8])/945 - 
 
   (282475249 Log[15/7])/8640 + (209952 Log[13/6])/25 - 
 
   (1953125 Log[11/5])/1728 + (65536 Log[9/4])/945 - 
 
   (6561 Log[7/3])/4480 + (16 Log[5/2])/2835 + 
 
   (3628799 Log[3])/1814400
            -13
re[9]=7.9 10
 
fgpt[10]=(-71663616 Log[25/12])/1925 + 
 
   (285311670611 Log[23/11])/1814400 - 
 
   (156250000 Log[21/10])/567 + 
 
   (1162261467 Log[19/9])/4480 - 
 
   (134217728 Log[17/8])/945 + 
 
   (1977326743 Log[15/7])/43200 - (209952 Log[13/6])/25 + 
 
   (9765625 Log[11/5])/12096 - (32768 Log[9/4])/945 + 
 
   (2187 Log[7/3])/4480 - (16 Log[5/2])/14175 + 
 
   (39916801 Log[3])/19958400
             -14
re[10]=2.9 10
 
fgpt[11]=(-23298085122481 Log[27/13])/239500800 + 
 
   (859963392 Log[25/12])/1925 - 
 
   (3138428376721 Log[23/11])/3628800 + 
 
   (1562500000 Log[21/10])/1701 - 
 
   (10460353203 Log[19/9])/17920 + 
 
   (1073741824 Log[17/8])/4725 - 
 
   (13841287201 Log[15/7])/259200 + 
 
   (1259712 Log[13/6])/175 - (48828125 Log[11/5])/96768 + 
 
   (131072 Log[9/4])/8505 - (6561 Log[7/3])/44800 + 
 
   (32 Log[5/2])/155925 + (479001599 Log[3])/239500800
             -16
re[11]=9.8 10
 
fgpt[12]=(-221460595216 Log[29/14])/868725 + 
 
   (302875106592253 Log[27/13])/239500800 - 
 
   (5159780352 Log[25/12])/1925 + 
 
   (34522712143931 Log[23/11])/10886400 - 
 
   (3906250000 Log[21/10])/1701 + 
 
   (94143178827 Log[19/9])/89600 - 
 
   (4294967296 Log[17/8])/14175 + 
 
   (13841287201 Log[15/7])/259200 - 
 
   (944784 Log[13/6])/175 + (244140625 Log[11/5])/870912 - 
 
   (262144 Log[9/4])/42525 + (19683 Log[7/3])/492800 - 
 
   (16 Log[5/2])/467775 + (6227020801 Log[3])/3113510400
             -17
re[12]=3.1 10
 
fgpt[13]=(-4805419921875 Log[31/15])/7175168 + 
 
   (3100448333024 Log[29/14])/868725 - 
 
   (3937376385699289 Log[27/13])/479001600 + 
 
   (20639121408 Log[25/12])/1925 - 
 
   (379749833583241 Log[23/11])/43545600 + 
 
   (7812500000 Log[21/10])/1701 - 
 
   (282429536481 Log[19/9])/179200 + 
 
   (34359738368 Log[17/8])/99225 - 
 
   (96889010407 Log[15/7])/2073600 + 
 
   (629856 Log[13/6])/175 - 
 
   (244140625 Log[11/5])/1741824 + 
 
   (1048576 Log[9/4])/467775 - (19683 Log[7/3])/1971200 + 
 
   (32 Log[5/2])/6081075 + (87178291199 Log[3])/43589145600
             -19
re[13]=9.4 10
 
fgpt[14]=(-1125899906842624 Log[33/16])/638512875 + 
 
   (72081298828125 Log[31/15])/7175168 - 
 
   (21703138331168 Log[29/14])/868725 + 
 
   (51185893014090757 Log[27/13])/1437004800 - 
 
   (61917364224 Log[25/12])/1925 + 
 
   (4177248169415651 Log[23/11])/217728000 - 
 
   (39062500000 Log[21/10])/5103 + 
 
   (2541865828329 Log[19/9])/1254400 - 
 
   (34359738368 Log[17/8])/99225 + 
 
   (678223072849 Log[15/7])/18662400 - 
 
   (1889568 Log[13/6])/875 + 
 
   (1220703125 Log[11/5])/19160064 - 
 
   (1048576 Log[9/4])/1403325 + 
 
   (59049 Log[7/3])/25625600 - (32 Log[5/2])/42567525 + 
 
   (1307674368001 Log[3])/653837184000
             -20
re[14]=2.7 10
 
fgpt[15]=(-48661191875666868481 Log[35/17])/
 
    10461394944000 + (18014398509481984 Log[33/16])/
 
    638512875 - (1081219482421875 Log[31/15])/14350336 + 
 
   (303843936636352 Log[29/14])/2606175 - 
 
   (665416609183179841 Log[27/13])/5748019200 + 
 
   (743008370688 Log[25/12])/9625 - 
 
   (45949729863572161 Log[23/11])/1306368000 + 
 
   (390625000000 Log[21/10])/35721 - 
 
   (22876792454961 Log[19/9])/10035200 + 
 
   (274877906944 Log[17/8])/893025 - 
 
   (4747561509943 Log[15/7])/186624000 + 
 
   (11337408 Log[13/6])/9625 - 
 
   (6103515625 Log[11/5])/229920768 + 
 
   (4194304 Log[9/4])/18243225 - 
 
   (177147 Log[7/3])/358758400 + (64 Log[5/2])/638512875 + 
 
   (20922789887999 Log[3])/10461394944000
             -22
re[15]=7.1 10
 
{34301.1 Second, Null}

(* EXAMPLE 2 / CHOICE B / t= 1/10 *)

(* cprec == 50 , aroption == 0 *)

Timing[tablegpt[15,1/10,"SCL","EC",19,1,2,50]]

fgpt[0]=-10 - 180 Log[9/10] + 190 Log[19/20]
re[0]=1.8
  
fgpt[1]=-10 + 765 Log[9/10] - 3800 Log[19/20] + 
 
   3045 Log[29/30]
re[1]=0.14
  
fgpt[2]=-10 - 1995 Log[9/10] + 31160 Log[19/20] - 
 
   76995 Log[29/30] + 47840 Log[39/40]
re[2]=0.012
  
fgpt[3]=-10 + (8235 Log[9/10])/2 - 
 
   (525920 Log[19/20])/3 + 986580 Log[29/30] - 
 
   1647360 Log[39/40] + (4991875 Log[49/50])/6
re[3]=0.0012
  
fgpt[4]=-10 - (14769 Log[9/10])/2 + 
 
   (2387920 Log[19/20])/3 - 9020160 Log[29/30] + 
 
   30251520 Log[39/40] - (229840625 Log[49/50])/6 + 
 
   16286832 Log[59/60]
re[4]=0.00012
  
fgpt[5]=-10 + 12051 Log[9/10] - (9428864 Log[19/20])/3 + 
 
   (134139645 Log[29/30])/2 - 400957440 Log[39/40] + 
 
   (2861140625 Log[49/50])/3 - 974457216 Log[59/60] + 
 
   (715524411 Log[69/70])/2
re[5]=0.000012
  
fgpt[6]=-10 - (128619 Log[9/10])/7 + 
 
   (33734272 Log[19/20])/3 - (866421603 Log[29/30])/2 + 
 
   4324270080 Log[39/40] - (51492109375 Log[49/50])/3 + 
 
   31595536512 Log[59/60] - (54169952613 Log[69/70])/2 + 
 
   (61258334208 Log[79/80])/7
            -6
re[6]=1.2 10
  
fgpt[7]=-10 + (745155 Log[9/10])/28 - 
 
   (785000960 Log[19/20])/21 + 
 
   (5051324835 Log[29/30])/2 - 40390950912 Log[39/40] + 
 
   (1504357421875 Log[49/50])/6 - 
 
   738935861760 Log[59/60] + 
 
   (2218143069345 Log[69/70])/2 - 
 
   (5735668776960 Log[79/80])/7 + 
 
   (6619815631791 Log[89/90])/28
            -7
re[7]=1.2 10
  
fgpt[8]=-10 - (1036745 Log[9/10])/28 + 
 
   (2465184640 Log[19/20])/21 - 
 
   (190667613555 Log[29/30])/14 + 
 
   339139493888 Log[39/40] - 
 
   (18959650390625 Log[49/50])/6 + 
 
   13976193911040 Log[59/60] - 
 
   (65285535428855 Log[69/70])/2 + 
 
   (289480627978240 Log[79/80])/7 - 
 
   (751906933406109 Log[89/90])/28 + 
 
   (49002250000000 Log[99/100])/7
            -8
re[8]=1.2 10
  
fgpt[9]=-10 + (698277 Log[9/10])/14 - 
 
   (22193361920 Log[19/20])/63 + 
 
   (1933571610045 Log[29/30])/28 - 
 
   (18356952367104 Log[39/40])/7 + 
 
   (106957333984375 Log[49/50])/3 - 
 
   227157274146816 Log[59/60] + 
 
   773937591524265 Log[69/70] - 
 
   (31382504619376640 Log[79/80])/21 + 
 
   (22929929886970773 Log[89/90])/14 - 
 
   (6642570000000000 Log[99/100])/7 + 
 
   (56854318334847671 Log[109/110])/252
            -9
re[9]=1.2 10
  
fgpt[10]=-10 - (10075521 Log[9/10])/154 + 
 
   (64174584832 Log[19/20])/63 - 
 
   (9328176512595 Log[29/30])/28 + 
 
   (132923324891136 Log[39/40])/7 - 
 
   (1106870556640625 Log[49/50])/3 + 
 
   3292100180563968 Log[59/60] - 
 
   15706518443513583 Log[69/70] + 
 
   (909999749925437440 Log[79/80])/21 - 
 
   (997493378312089107 Log[89/90])/14 + 
 
   (481663050000000000 Log[99/100])/7 - 
 
   (9070600438084370713 Log[109/110])/252 + 
 
   (86529991202832384 Log[119/120])/11
             -10
re[10]=1.2 10
  
fgpt[11]=-10 + (3693127 Log[9/10])/44 - 
 
   (282739806208 Log[19/20])/99 + 
 
   (6169916222577 Log[29/30])/4 - 
 
   (390953147826176 Log[39/40])/3 + 
 
   (42743491943359375 Log[49/50])/12 - 
 
   (305186614774751232 Log[59/60])/7 + 
 
   283171337502447254 Log[69/70] - 
 
   (3214765531949170688 Log[79/80])/3 + 
 
   (9912005389615160583 Log[89/90])/4 - 
 
   3545707000000000000 Log[99/100] + 
 
   (110182942861892035223 Log[109/110])/36 - 
 
   (16054291335355564032 Log[119/120])/11 + 
 
   (272701471596625205017 Log[129/130])/924
             -11
re[11]=1.2 10
  
fgpt[12]=-10 - (60441945 Log[9/10])/572 + 
 
   (772287047680 Log[19/20])/99 - 
 
   (303563927341485 Log[29/30])/44 + 
 
   855262458019840 Log[39/40] - 
 
   (1169176068115234375 Log[49/50])/36 + 
 
   (3757317057930147840 Log[59/60])/7 - 
 
   4649091686124773790 Log[69/70] + 
 
   23460563413295431680 Log[79/80] - 
 
   (292986801414969591213 Log[89/90])/4 + 
 
   145576612500000000000 Log[99/100] - 
 
   (6635345570753556606785 Log[109/110])/36 + 
 
   (1582139243906381905920 Log[119/120])/11 - 
 
   (19410332376697913793545 Log[129/130])/308 + 
 
   (15261708472413133359104 Log[139/140])/1287
             -12
re[12]=1.2 10
  
fgpt[13]=-10 + (131019015 Log[9/10])/1001 - 
 
   (26816534773760 Log[19/20])/1287 + 
 
   (659194657345845 Log[29/30])/22 - 
 
   (59452550608322560 Log[39/40])/11 + 
 
   (2540427789306640625 Log[49/50])/9 - 
 
   (43549130493430824960 Log[59/60])/7 + 
 
   (282934725749815987365 Log[69/70])/4 - 
 
   (3263796956940510167040 Log[79/80])/7 + 
 
   1910776100716319086953 Log[89/90] - 
 
   5063856600000000000000 Log[99/100] + 
 
   (158690345329256810590895 Log[109/110])/18 - 
 
   (110080320278004372602880 Log[119/120])/11 + 
 
   (548667346388190675973795 Log[129/130])/77 - 
 
   (3716801733377224395882496 Log[139/140])/1287 + 
 
   (2034541967461468505859375 Log[149/150])/4004
             -13
re[13]=1.2 10
  
fgpt[14]=-10 - (160019737 Log[9/10])/1001 + 
 
   (491778251653120 Log[19/20])/9009 - 
 
   (36284747820977295 Log[29/30])/286 + 
 
   (1091175549910384640 Log[39/40])/33 - 
 
   (233180151153564453125 Log[49/50])/99 + 
 
   (479745009438209114112 Log[59/60])/7 - 
 
   (12122485891579966387345 Log[69/70])/12 + 
 
   (59936300204649066004480 Log[79/80])/7 - 
 
   (315827316295587456797889 Log[89/90])/7 + 
 
   155007457000000000000000 Log[99/100] - 
 
   (6412340030619042579038353 Log[109/110])/18 + 
 
   (6065854857979614650695680 Log[119/120])/11 - 
 
   (131017329477722238384403895 Log[129/130])/231 + 
 
   (477921861719728041910697984 Log[139/140])/1287 - 
 
   (560607520650779937744140625 Log[149/150])/4004 + 
 
   (69468266798051432465432576 Log[159/160])/3003
             -14
re[14]=1.2 10
  
fgpt[15]=-10 + (1544321673 Log[9/10])/8008 - 
 
   (140746681352192 Log[19/20])/1001 + 
 
   (1051915259820327165 Log[29/30])/2002 - 
 
   (2163576353587200000 Log[39/40])/11 + 
 
   (417473024139404296875 Log[49/50])/22 - 
 
   (55664528841491727384576 Log[59/60])/77 + 
 
   (54705072552389584281369 Log[69/70])/4 - 
 
   (9274105384316892316958720 Log[79/80])/63 + 
 
   (27490380372332010423163449 Log[89/90])/28 - 
 
   (29984223060000000000000000 Log[99/100])/7 + 
 
   (25268167873327785250782641 Log[109/110])/2 - 
 
   (281628661871509680848633856 Log[119/120])/11 + 
 
   (5491709757378322462837495305 Log[129/130])/154 - 
 
   (4794234724990503203174744064 Log[139/140])/143 + 
 
   (81344516776606454315185546875 Log[149/150])/4004 - 
 
   (7168067720417619066042187776 Log[159/160])/1001 + 
 
   (6182536502865495354921554813 Log[169/170])/5544
             -15
re[15]=1.3 10
  
{36793.9 Second, Null}

<<BIF.M

(* THE DEFINITIONS OF INITIALF IS CHANGED *)

initialf[i,f[x],x]
      1
f[-(-----)]
    1 + i

(* EXAMPLE 2 / CHOICE A / t= 1/10 *)

(* cprec == 50 , aroption == 0 *)

Timing[tablegpt[15,1/10,"SCL","EC",19,1,2,50]]

fgpt[0]=10 Log[9/10]
re[0]=2.1
  
fgpt[1]=-30 Log[9/10] + 40 Log[19/20]
re[1]=0.16
  
fgpt[2]=60 Log[9/10] - 320 Log[19/20] + 270 Log[29/30]
re[2]=0.015
  
fgpt[3]=-100 Log[9/10] + 1600 Log[19/20] - 
 
   4050 Log[29/30] + 2560 Log[39/40]
re[3]=0.0014
  
fgpt[4]=150 Log[9/10] - 6400 Log[19/20] + 
 
   36450 Log[29/30] - 61440 Log[39/40] + 31250 Log[49/50]
re[4]=0.00014
  
fgpt[5]=-210 Log[9/10] + 22400 Log[19/20] - 
 
   255150 Log[29/30] + 860160 Log[39/40] - 
 
   1093750 Log[49/50] + 466560 Log[59/60]
re[5]=0.000014
  
fgpt[6]=280 Log[9/10] - 71680 Log[19/20] + 
 
   1530900 Log[29/30] - 9175040 Log[39/40] + 
 
   21875000 Log[49/50] - 22394880 Log[59/60] + 
 
   8235430 Log[69/70]
            -6
re[6]=1.4 10
  
fgpt[7]=-360 Log[9/10] + 215040 Log[19/20] - 
 
   8266860 Log[29/30] + 82575360 Log[39/40] - 
 
   328125000 Log[49/50] + 604661760 Log[59/60] - 
 
   518832090 Log[69/70] + 167772160 Log[79/80]
            -7
re[7]=1.4 10
  
fgpt[8]=450 Log[9/10] - 614400 Log[19/20] + 
 
   41334300 Log[29/30] - 660602880 Log[39/40] + 
 
   4101562500 Log[49/50] - 12093235200 Log[59/60] + 
 
   18159123150 Log[69/70] - 13421772800 Log[79/80] + 
 
   3874204890 Log[89/90]
            -8
re[8]=1.4 10
  
fgpt[9]=-550 Log[9/10] + 1689600 Log[19/20] - 
 
   194861700 Log[29/30] + 4844421120 Log[39/40] - 
 
   45117187500 Log[49/50] + 199538380800 Log[59/60] - 
 
   466084160850 Log[69/70] + 590558003200 Log[79/80] - 
 
   383546284110 Log[89/90] + 100000000000 Log[99/100]
            -9
re[9]=1.4 10
  
fgpt[10]=660 Log[9/10] - 4505600 Log[19/20] + 
 
   876877650 Log[29/30] - 33218887680 Log[39/40] + 
 
   451171875000 Log[49/50] - 2873352683520 Log[59/60] + 
 
   9787767377850 Log[69/70] - 18897856102400 Log[79/80] + 
 
   20711499341940 Log[89/90] - 
 
   12000000000000 Log[99/100] + 2853116706110 Log[109/110]
             -10
re[10]=1.4 10
  
fgpt[11]=-780 Log[9/10] + 11714560 Log[19/20] - 
 
   3799803150 Log[29/30] + 215922769920 Log[39/40] - 
 
   4189453125000 Log[49/50] + 37353584885760 Log[59/60] - 
 
   178137366276870 Log[69/70] + 
 
   491344258662400 Log[79/80] - 
 
   807748474335660 Log[89/90] + 
 
   780000000000000 Log[99/100] - 
 
   407995688973730 Log[109/110] + 
 
   89161004482560 Log[119/120]
             -11
re[11]=1.4 10
  
fgpt[12]=910 Log[9/10] - 29818880 Log[19/20] + 
 
   15959173230 Log[29/30] - 1343519457280 Log[39/40] + 
 
   36657714843750 Log[49/50] - 
 
   448243018629120 Log[59/60] + 
 
   2909576982522210 Log[69/70] - 
 
   11006111394037760 Log[79/80] + 
 
   25444076941573290 Log[89/90] - 
 
   36400000000000000 Log[99/100] + 
 
   31415668050977210 Log[109/110] - 
 
   14979048753070080 Log[119/120] + 
 
   3028751065922530 Log[129/130]
             -12
re[12]=1.4 10
  
fgpt[13]=-1050 Log[9/10] + 74547200 Log[19/20] - 
 
   65287526850 Log[29/30] + 8061116743680 Log[39/40] - 
 
   305480957031250 Log[49/50] + 
 
   5042733959577600 Log[59/60] - 
 
   43643654737833150 Log[69/70] + 
 
   220122227880755200 Log[79/80] - 
 
   686990077422478830 Log[89/90] + 
 
   1365000000000000000 Log[99/100] - 
 
   1727861742803746550 Log[109/110] + 
 
   1348114387776307200 Log[119/120] - 
 
   590606457854893350 Log[129/130] + 
 
   111120068255580160 Log[139/140]
             -13
re[13]=1.4 10
  
fgpt[14]=1200 Log[9/10] - 183500800 Log[19/20] + 
 
   261150107400 Log[29/30] - 46901042872320 Log[39/40] + 
 
   2443847656250000 Log[49/50] - 
 
   53789162235494400 Log[59/60] + 
 
   611011166329664100 Log[69/70] - 
 
   4025092166962380800 Log[79/80] + 
 
   16487761858139491920 Log[89/90] - 
 
   43680000000000000000 Log[99/100] + 
 
   76025916683364848200 Log[109/110] - 
 
   86279320817683660800 Log[119/120] + 
 
   61423071616908908400 Log[129/130] - 
 
   24890895289249955840 Log[139/140] + 
 
   4378938903808593750 Log[149/150]
             -14
re[14]=1.4 10
  
fgpt[15]=-1360 Log[9/10] + 445644800 Log[19/20] - 
 
   1024511959800 Log[29/30] + 
 
   265772576276480 Log[39/40] - 
 
   18884277343750000 Log[49/50] + 
 
   548649454802042880 Log[59/60] - 
 
   8078925421470003100 Log[69/70] + 
 
   68426566838360473600 Log[79/80] - 
 
   360375366327906037680 Log[89/90] + 
 
   1237600000000000000000 Log[99/100] - 
 
   2843369283957845322680 Log[109/110] + 
 
   4400245361701866700800 Log[119/120] - 
 
   4524832942445622918800 Log[129/130] + 
 
   2962016539420744744960 Log[139/140] - 
 
   1116629420471191406250 Log[149/150] + 
 
   184467440737095516160 Log[159/160]
             -15
re[15]=1.4 10
  
{16036.5 Second, Null}

(*______________________________
___________ GOOD LUCK __________
_______________________________*)