subroutine aptptpl (px, py, pz, ax, ay, az, bx, by, bz, np, tol,
     &                    dpmin, cx, cy, cz, itrun, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTPTPL
c
c     call aptptpl (px, py, pz, ax, ay, az, bx, by, bz, np, tol,
c    &              dpmin, cx, cy, cz, itrun, nerr)
c
c     Version:  aptptpl  Updated    1990 November 29 10:50.
c               aptptpl  Originated 1989 November 2 14:10.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To find, for each of np sets of input data, the minimum distance
c               dpmin to the point p = (px, py, pz), from the plane through
c               the point a = (ax, ay, az) with normal vector b = (bx, by, bz),
c               and the coordinates c = (cx, cy, cz) of the point in the plane
c               nearest point "p".
c               Flag itrun indicates truncation of dpmin to zero (1) or
c               too small a magnitude of vector "b" (2).
c               Flag nerr indicates any input error.
c
c     History:  1990 March 14.  Changed tol to 0.0 in call to unit vector
c               subroutine.  Allows small magnitudes.
c
c     Input:    px, py, pz, ax, ay, az, bx, by, bz, np, tol.
c
c     Output:   dpmin, cx, cy, cz, itrun, nerr.
c
c     Calls: aptvadd, aptvdis, aptvdot, aptvunb 
c               
c
c     Glossary:
c
c     ax,ay,az  Input    The x, y, z coordinates of point "a" in the plane.
c                          Size np.
c
c     bx,by,bz  Input    The x, y, z components of vector "b" normal to the
c                          plane.  Magnitude must exceed tol.  Size np.
c
c     cx,cy,cz  Output   The x, y, z coordinates of the point in the plane
c                          nearest point "p".  Size np.
c                          Returned as point "p" if normal vector "b" is too
c                          short, based on tol (itrun = 2).
c
c     dpmin     Output   The perpendicular distance to point "p" from the
c                          plane through point "a" with normal vector "b".
c                          Positive if point "p" is in the same direction
c                          from the plane as the normal vector "b".
c                          Truncated to zero if less than the estimated error
c                          in its calculation, based on tol (itrun = 1).
c                          Returned as zero if normal vector "b" is too short,
c                          based on tol (itrun = 2).  Size np.
c
c     itrun     Output   Indicates a special result for one data set:
c                          1 if the value of dpmin is truncated to zero, when
c                            less than the estimated error in its calculation,
c                            based on tol.
c                          2 if normal vector "b" is too short, based on tol.
c                            The orientation of the plane is unknown, and
c                            dpmin and point "c" cannot be calculated.
c                          Size np.
c
c     nerr      Output   Indicates an input error, if not 0.
c                          1 if np is not positive.
c
c     np        Input    Size of arrays.
c
c     px,py,pz  Input    The x, y, z coordinates of point "p".  Size np.
c
c     tol       Input    Numerical tolerance limit.
c                          On Cray computers, recommend 1.e-5 to 1.e-11.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

c.... Dimensioned arguments.

c---- Coordinate x of point "a".
      dimension ax      (1)
c---- Coordinate y of point "a".
      dimension ay      (1)
c---- Coordinate z of point "a".
      dimension az      (1)
c---- Component x of vector "b".
      dimension bx      (1)
c---- Component y of vector "b".
      dimension by      (1)
c---- Component z of vector "b".
      dimension bz      (1)
c---- Coordinate x of point "c".
      dimension cx      (1)
c---- Coordinate y of point "c".
      dimension cy      (1)
c---- Coordinate z of point "c".
      dimension cz      (1)
c---- Distance from plane to point "p".
      dimension dpmin   (1)
c---- 1 if dpmin truncated to zero.
      dimension itrun   (1)
c---- Coordinate x of point "p".
      dimension px      (1)
c---- Coordinate y of point "p".
      dimension py      (1)
c---- Coordinate z of point "p".
      dimension pz      (1)


c.... Local variables.

c---- Component x of vector "ap".
      common /laptptpl/ apx     (64)
c---- Component y of vector "ap".
      common /laptptpl/ apy     (64)
c---- Component z of vector "ap".
      common /laptptpl/ apz     (64)
c---- Index in arrays.
      common /laptptpl/ n
c---- First index of subset of data.
      common /laptptpl/ n1
c---- Last index of subset of data.
      common /laptptpl/ n2
c---- Index in external array.
      common /laptptpl/ nn
c---- Size of current subset of data.
      common /laptptpl/ ns
c---- Component x of unit normal vector.
      common /laptptpl/ ubx     (64)
c---- Component y of unit normal vector.
      common /laptptpl/ uby     (64)
c---- Component z of unit normal vector.
      common /laptptpl/ ubz     (64)
c---- Magnitude of a vector.
      common /laptptpl/ vlen    (64)
c---- Magnitude of normal vector "b".
      common /laptptpl/ vlenb   (64)
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptptpl finding distance to the point:')
cbug 9902 format (i3,' px,py,pz=',1p3e22.14 /
cbug     &  '    from the plane through:' /
cbug     &  '    ax,ay,az=',1p3e22.14 /
cbug     &  '    with normal vector:' /
cbug     &  '    bx,by,bz=',1p3e22.14)
cbug      write ( 3, 9901)
cbug      write ( 3, 9902) (n, px(n), py(n), pz(n), ax(n), ay(n), az(n),
cbug     &  bx(n), by(n), bz(n), n = 1, np)
cbugc***DEBUG ends.

c.... Initialize.

      nerr = 0

c.... Test for input errors.

      if (np .le. 0) then
        nerr = 1
        go to 210
      endif

      n1 = 1
      n2 = min (np, 64)

  110 ns = n2 - n1 + 1

c.... Find the unit vector normal to the plane.

      call aptvunb (bx(n1), by(n1), bz(n1), ns, 0.,
     &              ubx, uby, ubz, vlenb, nerr)

c.... Find the vector "ap" from point "a" to point "p".

      call aptvdis (ax(n1), ay(n1), az(n1), px(n1), py(n1), pz(n1), ns,
     &              tol, apx, apy, apz, vlen, nerr)

c.... Find the perpendicular distance from the plane to point "p".

      call aptvdot (apx, apy, apz, ubx, uby, ubz, ns, tol,
     &              dpmin(n1), nerr)

c---- Loop over subset of data.
      do 120 n = 1, ns

        nn = n + n1 - 1
        if (abs (dpmin(nn)) .gt. 0.0) then
          itrun(nn) = 0
        else
          itrun(nn) = 1
        endif
        if (vlenb(n) .le. tol) then
          itrun(nn) = 2
        endif
        if (vlenb(n) .le. tol) then
          dpmin(nn) = 0.0
        endif

c---- End of loop over subset of data.
  120 continue

c.... Find the coordinates of the point of intersection.

      call aptvadd (px(n1), py(n1), pz(n1), -1., dpmin(n1),
     &              ubx, uby, ubz, ns, tol,
     &              cx(n1), cy(n1), cz(n1), vlen, nerr)

c.... See if all data subsets are done.

c---- Do another subset of data.
      if (n2 .lt. np) then
        n1 = n2 + 1
        n2 = min (np, n1 + 63)
        go to 110
      endif
cbugc***DEBUG begins.
cbug 9903 format (/ 'aptptpl results:' /
cbug     &  (i3,' dpmin=   ',1pe22.14,' itrun=',i2 /
cbug     &  '    cx,cy,cz=',1p3e22.14))
cbug      write ( 3, 9903) (n, dpmin(n), itrun(n), cx(n), cy(n), cz(n),
cbug     &  n = 1, np)
cbugc***DEBUG ends.

  210 return

c.... End of subroutine aptptpl.      (+1 line.)
      end

UCRL-WEB-209832