subroutine aptvplp (ax, ay, az, bx, by, bz, np, tol,
     &                    cx, cy, cz, clen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVPLP
c
c     call aptvplp (ax, ay, az, bx, by, bz, np, tol,
c    &              cx, cy, cz, clen, nerr)
c
c     Version:  aptvplp  Updated    1990 November 26 10:00.
c               aptvplp  Originated 1990 April 5 14:30.
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 projection
c               c = (cx, cy, cz) of the vector a = (ax, ay, az) on the plane
c               with normal vector b = (bx, by, bz), and clen, the magnitude
c               of vector "c".  If the magnitude of vector "b" is too small,
c               the orientation of the plane is indeterminate, and the
c               returned value of clen will be -1.e+99.  The components of
c               vector "c" may be truncated to zero, if less than the estimated
c               error in their calculation, based on tol.
c               Flag nerr indicates any input error.
c
c     Input:    ax, ay, az, bx, by, bz, np, tol.
c
c     Output:   cx, cy, cz, clen, nerr.
c
c     Calls: aptvadd, aptvdot, aptvunb 
c               
c
c     Glossary:
c
c     ax,ay,az  Input    The x, y, z components of vector "a".  Size np.
c
c     bx,by,bz  Input    The x, y, z components of vector "b".  Size np.
c                          Normal to the projection plane.  If too small,
c                          based on tol, to determine the orientation of the
c                          plane, clen will be returned as -1.e+99.
c
c     clen      Output   The magnitude of vector "c".  Size np.
c                          Zero if vector "a" is perpendicular to the plane.
c                          Will be -1.e+99 if vector "b" is too small.
c
c     cx,cy,cz  Output   The x, y, z components of vector "c".  Size np.
c                          The projection of vector "a" in the plane with
c                          normal vector "b".  Each component may be truncated
c                          to zero, if less than the estimated error in its
c                          calculation, based on tol.  If vector "b" is too
c                          small, based on tol, vector "c" will be equal to
c                          vector "a", but clen will be -1.e+99.
c
c     nerr      Output   Indicates an input error, if not 0.  See clen.
c                          1 if np is not positive.
c
c     np        Input    Size of arrays.
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---- Component x of vector "a".
      dimension ax      (1)
c---- Component y of vector "a".
      dimension ay      (1)
c---- Component z of vector "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---- Magnitude of vector "c".
      dimension clen    (1)
c---- Component x of vector "c".
      dimension cx      (1)
c---- Component y of vector "c".
      dimension cy      (1)
c---- Component z of vector "c".
      dimension cz      (1)

c.... Local variables.

c---- Component of vector "a" prll to "b".
      common /laptvplp/ ahb     (64)

c---- A very big number.
      common /laptvplp/ big

c---- Magnitude of normal vector "b".
      common /laptvplp/ blen    (64)
c---- Component x of unit normal vector.
      common /laptvplp/ hbx     (64)
c---- Component y of unit normal vector.
      common /laptvplp/ hby     (64)
c---- Component z of unit normal vector.
      common /laptvplp/ hbz     (64)
c---- Index in local array.
      common /laptvplp/ n
c---- First index of subset of data.
      common /laptvplp/ n1
c---- Last index of subset of data.
      common /laptvplp/ n2
c---- Index in external array.
      common /laptvplp/ nn
c---- Size of current subset of data.
      common /laptvplp/ ns
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvplp finding projection of A on plane with',
cbug     &  ' normal B:' /
cbug     &  (i3,' ax,ay,az=',1p3e22.14 /
cbug     &  '    bx,by,bz=',1p3e22.14))
cbug      write ( 3, 9901) (n, ax(n), ay(n), az(n),
cbug     &  bx(n), by(n), bz(n), n = 1, np)
cbugc***DEBUG ends.

c.... Initialize.

c---- A very big number.
      big = 1.e+99

      nerr = 0

c.... Test for input errors.

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

c.... Set up the indices of the first subset of data.

      n1 = 1
      n2 = min (np, 64)

  110 ns = n2 - n1 + 1

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

      call aptvunb (bx(n1), by(n1), bz(n1), ns, 0.,
     &              hbx, hby, hbz, blen, nerr)

c.... Find the component of vector "a" perpendicular to the plane.

      call aptvdot (ax(n1), ay(n1), az(n1), hbx, hby, hbz, ns, tol,
     &              ahb, nerr)

c.... Find the components of vector "a" in the plane.

      call aptvadd (ax(n1), ay(n1), az(n1), -1., ahb,
     &              hbx, hby, hbz, ns, tol,
     &              cx(n1), cy(n1), cz(n1), clen(n1), nerr)

c.... See if vector "b" is too small to define plane.

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

        nn = n + n1 - 1

        if (blen(n) .le. tol) then
          clen(nn) = -big
        endif

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

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 9902 format (/ 'aptvplp results:' /
cbug     &  (i3,' clen=    ',1pe22.14 /
cbug     &  '    cx,cy,cz=',1p3e22.14))
cbug      write ( 3, 9902) (n, clen(n), cx(n), cy(n), cz(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832