Previous: fittsv Up: ../plot79_f.html Next: fitvbv


FITTTR

       SUBROUTINE  FITTTR (P,N,ITR,NTR,OT,ACT,JP,IP,KP,DIST,MP,MTR,MBDRY,
      X                    IERROR)
 C$    (Triangulate)
 C$    Determine an optimal triangulation  of an arbitrary set  of
 C$    3-D data points representing a surface.  The  triangulation
 C$    will subsequently be used for computation of gradients  and
 C$    surface interpolation  using  routines FITTGR  and  FITTSV.
 C$    Thus, for  a given  surface, FITTTR  will be  called  once,
 C$    followed by a single call to FITTGR, and then FITTSV can be
 C$    called to interpolate a surface value as often as required.
 C$    The other routines in the  package, named FITT** (** =  AP,
 C$    C1, C2, DE, DO,  EV, FT, IN,  OP, PR, SR,  and SS) are  for
 C$    internal use  only  by  FITTTR, FITTGR,  and  FITTSV.   The
 C$    mnemonic phrase  present  in their  leading  comment  lines
 C$    flags them as internal.  The arguments are:
 C$
 C$    P(3,MP)...........(X,Y,Z)   coordinates  of  surface   data
 C$                      points.  In order to avoid underflow  and
 C$                      overflow, it is advisable to  renormalize
 C$                      the X and Y coordinates so that they  are
 C$                      of the order of one in magnitude.
 C$    N.................Number of data points (.LE. MP)
 C$    ITR(6,MTR)........Output triangle parameters.
 C$    NTR...............Output number of triangles (.LE. MTR).
 C$    OT(MTR)...........REAL scratch array.
 C$    ACT(MTR)..........LOGICAL scratch array.
 C$    JP(MP)............INTEGER scratch array.
 C$    IP(3,MBDRY).......INTEGER scratch array.
 C$    KP(3,MBDRY).......INTEGER scratch array.
 C$    DIST(MP)..........REAL scratch array.
 C$    MP................Maximum number of points and maximum
 C$                      dimension of P(3,*), JP(*), and DIST(*).
 C$                      (MP .GE. N).
 C$    MTR...............Maximum  number of triangles  and maximum
 C$                      dimension of ITR(6,*), OT(*), and ACT(*).
 C$                      A reasonable estimate  is 1.5*N +  MBDRY.
 C$                      If too few are allocated, an error return
 C$                      will occur.
 C$    MBDRY.............Maximum number of boundary values and
 C$                      maximum dimension of IP(3,*) and KP(3,*).
 C$                      A reasonable estimate  lies somewhere  in
 C$                      between 4*SQRT(N) and 3*CUBEROOT(N).   If
 C$                      too few  are allocated,  an error  return
 C$                      will occur.
 C$    IERROR............0 - Triangulation successful.
 C$                      1 - Insufficient work space (MTR too
 C$                          small).
 C$                      2 - Insufficient work space (MBDRY too
 C$                          small).
 C$                      3 - All data points colinear, so that a
 C$                          surface cannot be defined.
 C$                      4 - Too few data points (N .LT. 3)
 C$                      5 - Too many data points (N .GT. MP)
 C$
 C$    In order  to  save space  in  the calling  program,  it  is
 C$    possible to  share  storage  between some  of  the  scratch
 C$    arrays in this routine and in routine FITTGR:
 C$
 C$    DIST(*) may overlap (IP(*,*),KP(*,*)) or (OT(*),ACT(*)),
 C$    JP(*) may overlap (OT(*),ACT(*)),
 C$    (IP(*,*),JP(*,*)) may overlap (OT(*),ACT(*)),
 C$    GRAD(*,*) in routine FITTGR may overlap DIST(*) or
 C$    JP(*) or (IP(*,*),KP(*,*)) or (OT(*),ACT(*)).
 C$
 C$    P(*,*) and  ITR(*,*),  as well  as  GRAD(*,*) (once  it  is
 C$    calculated in routine FITTGR) must be preserved in order to
 C$    be able to perform surface interpolation later.
 C$
 C$    Several routines  contain  floating  point  constants  with
 C$    names like BIGNUM, SMALL, and ATAD (a Tad).  The values  of
 C$    these are fairly arbitrary.  BIGNUM should be close to  the
 C$    largest floating-point number on the host machine; a  value
 C$    1.0E+22 should be adequate  on every known machine.   SMALL
 C$    and ATAD are given  values small relative  to 1.0, and  are
 C$    simply tolerances  used to  avoid  division by  zero.   All
 C$    floating point constants are  given obvious symbolic  names
 C$    and defined in DATA statements.
 C$
 C$    The  entire  collection  of   routines  passes  the   Pfort
 C$    Verifier.  There  is one  potential machine  dependence  in
 C$    routine FITTSV, where a flag is used to remember whether  a
 C$    given triangle has  already been processed.   On a  machine
 C$    where local  variables  are  allocated  on  a  stack,  this
 C$    variable may be reinitialized  on entry, and  consequently,
 C$    extra unnecessary processing  may be  done.  The  execution
 C$    should nevertheless be correct.
 C$
 C$    This routine and its  related routines have been  developed
 C$    by Frank Little, Computer-Aided Design Group, Department of
 C$    Mathematics, University Of Utah, Salt Lake City, UT  84112.
 C$
 C$    (03-APR-82)