Back to library index.

Package rcheby (in rcheby.i) -

Index of documented functions or symbols:

rcheby_build

DOCUMENT rfit = rcheby_build(nfit, dfit)
      or rfit = rcheby_build(nfit)
      or rfit = rcheby_build(,dfit)
  build fit suitable for input to rcheby_fit from separate numerator
  and denominator fits in the format returned by cheby_fit.
  You can use rcheby_build in conjunction with cheby_conv to build
  an rfit given the polynomial coefficients for the numerator and
  denominator: rcheby_build(cheby_conv(n), cheby_conv(d)).

SEE ALSO: rcheby_fit, rcheby_eval, rcheby_num, rcheby_den, cheby_conv

rcheby_den

DOCUMENT fit = rcheby_den(rfit)
  extract denominator from rcheby_fit RFIT to a Chebyshev fit suitable
  for input to cheby_eval (not rcheby_eval).

SEE ALSO: cheby_fit, rcheby_fit, rcheby_num, rcheby_build

rcheby_eval

DOCUMENT y = cheby_eval(fit, x)
  evaluates a rational Chebyshev FIT at points X.  The FIT is a 1D
  array of Chebyshev coefficients, as returned by rcheby_fit, namely:
    [m,k, a,b, 2*n0,n1,...nM,d1,...,dK]
  where ni are the coefficients of the Chebyshev polynomials in the
  numerator and di are the coefficients for the denominator (d0=1.0
  is implicit).

SEE ALSO: rcheby_fit, cheby_fit, rcheby_build, rcheby_conv

rcheby_fit

DOCUMENT fit = rcheby_fit(f, interval, m, k)
      or fit = rcheby_fit(f, x, m, k)
  returns a rational Chebyshev fit (for use in rcheby_eval) of
  numerator degree M and denominator degree K, to the function
  F on the INTERVAL (a 2 element array [a,b]). In the second form,
  F and X are arrays; the function to be fit is the piecewise cubic
  function of xp spline(f,x,xp), and the interval of the fit is
  [min(x),max(x)].  You can pass an alternate interpolator using
  the nterp= keyword; it must have the same calling sequence as
  spline or interp.

  The return value is the array [m,k, a,b, 2*n0,n1,...nM,d1,...,dK]
  where [a,b] is the interval over which the fit applies, the ni are
  the coefficients of the Chebyshev polynomials for the numerator
  (note that double the zeroth coefficient is stored), while the di
  are the denominator coefficients, with a zeroth coefficient of
  1.0 assumed.

  The fitting algorithm returns very nearly the minimax error
  rational fit to F, that is, the rational function which minimizes
  the maximum absolute deviation from F for the given degrees.  This
  function (very nearly) has M+K+1 points of maximum deviation from
  F on the interval, which alternate in sign and have equal absolute
  value.  The algorithm is inspired by the discussion in section 5.13
  of Numerical Recipes, which itself is inspired by the well-known
  Remez (or Remes) algorithms.  Note that it may be used with K=0
  to obtain minimax polynomial fits.  (Compare with cheby_fit, the
  standard Chebyshev polynomial fitting algorithm.)

Problem with this algorithm:
Nothing prevents numerator and denominator from having a factor
in common.  This will always happen if the function being fit really
IS a rational function of lower degree in both numerator and
denominator than (m,k); hopefully it is rare in other cases.  But
if you really care about a fit, you would be wise to check.

SEE ALSO: rcheby_eval, cheby_fit, rcheby_build, rcheby_conv, rcheby_trunc

rcheby_num

DOCUMENT fit = rcheby_num(rfit)
  extract numerator from rcheby_fit RFIT to a Chebyshev fit suitable
  for input to cheby_eval (not rcheby_eval).

SEE ALSO: cheby_fit, rcheby_fit, rcheby_den, rcheby_build

rcheby_trunc

DOCUMENT tfit = rcheby_trunc(fit, err)
  truncate rcheby_fit FIT to relative error ERR by dropping
  trailing Chebyshev coefficients smaller than ERR.  (Note that
  this destroys the minimax property of rcheby_fit -- use with
  caution.)  If ERR is omitted, it defaults to 1.e-9.

SEE ALSO: rcheby_fit, cheby_trunc