subroutine aptvxun (ax, ay, az, bx, by, bz, np, tol,
     &                    ux, uy, uz, vlen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVXUN
c
c     call aptvxun (ax, ay, az, bx, by, bz, np, tol,
c    &              ux, uy, uz, vlen, nerr)
c
c     Version:  aptvxun  Updated    1990 November 26 10:00.
c               aptvxun  Originated 1989 November 10 11:20.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To find the vector products "a" x "b" of the np vector pairs
c               a = (ax, ay, az) and b = (bx, by, bz), and divide by their
c               magnitudes vlen, to produce the unit vectors u = (ux, uy, uz),
c               parallel to "a" x "b".  Any components of vector "u" less than
c               the estimated error in their calculation, based on tol, will be
c               truncated to zero.  If all are zero, or are truncated to zero,
c               the output vector "u" will be zero, and vlen will be zero.
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:    ax, ay, az, bx, by, bz, np, tol.
c
c     Output:   ux, uy, uz, vlen, nerr.
c
c     Calls: aptvuna 
c
c     Glossary:
c
c     ax,ay,az  Input    The x, y, z components of input vector "a".  Size np.
c
c     bx,by,bz  Input    The x, y, z components of input vector "b".  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 ax, ay, az, bx, by, bz, ux, uy, uz,
c                          vlen.
c
c     tol       Input    Numerical tolerance limit.
c                          On Cray computers, recommend 1.e-5 to 1.e-11.
c
c     ux,uy,uz  Output   The x, y, z components of output vector "u".  Size np.
c                          Vector (cross) product of vectors "a" and "b",
c                          normalized to unit magnitude.  A component will be
c                          truncated to zero if less than the estimated error
c                          in its calculation, based on tol.
c
c     vlen      Output   Magnitude of the vector product "a" x "b", after any
c                          truncation of components has been done.  Will be
c                          zero if all components of vector "u" are zero.
c                          Size np.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

c.... Dimensioned arguments.

c---- Component x of input vector "a".
      dimension ax      (1)
c---- Component y of input vector "a".
      dimension ay      (1)
c---- Component z of input vector "a".
      dimension az      (1)
c---- Component x of input vector "b".
      dimension bx      (1)
c---- Component y of input vector "b".
      dimension by      (1)
c---- Component z of input vector "b".
      dimension bz      (1)
c---- Component x of output vector "u".
      dimension ux      (1)
c---- Component y of output vector "u".
      dimension uy      (1)
c---- Component z of output vector "u".
      dimension uz      (1)
c---- Magnitude of vector "a" x "b".
      dimension vlen    (1)

c.... Local variables.

c---- Index, 1 to np.
      common /laptvxun/ n
c---- Estimated error in ux.
      common /laptvxun/ uxerr
c---- Estimated error in uy.
      common /laptvxun/ uyerr
c---- Estimated error in uz.
      common /laptvxun/ uzerr
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvxun finding vector product of vectors:' /
cbug     &  (i3,' ax,ay,az=',1p3e22.14 /
cbug     &  '    bx,by,bz=',1p3e22.14))
cbug      write ( 3, 9901) (n, ax(n), ay(n), az(n), bx(n), by(n), bz(n),
cbug     &  n = 1, np)
cbugc***DEBUG ends.

c.... Initialize.

      nerr = 0

c.... Test for input errors.

      if (np .le. 0) then
        nerr = 1
cbugc***DEBUG begins.
cbug        write ( 3, '(/ "aptvxun fatal.  bad np=",i3)') np
cbugc***DEBUG ends.
        go to 210
      endif

c.... Find the vector products.

c---- Loop over vectors.
      do 110 n = 1, np

        ux(n)   = ay(n) * bz(n) - az(n) * by(n)
        uy(n)   = az(n) * bx(n) - ax(n) * bz(n)
        uz(n)   = ax(n) * by(n) - ay(n) * bx(n)

c---- End of loop over vectors.
  110 continue

c---- Truncate small components to zero.
      if (tol .gt. 0.0) then

c---- Loop over vectors.
        do 120 n = 1, np

          uxerr   = 2.0 * tol * (abs (ay(n) * bz(n)) +
     &                           abs (az(n) * by(n)))
          if (abs (ux(n)) .lt. uxerr) then
            ux(n) = 0.0
          endif

          uyerr   = 2.0 * tol * (abs (az(n) * bx(n)) +
     &                           abs (ax(n) * bz(n)))
          if (abs (uy(n)) .lt. uyerr) then
            uy(n) = 0.0
          endif

          uzerr   = 2.0 * tol * (abs (ax(n) * by(n)) +
     &                           abs (ay(n) * bx(n)))
          if (abs (uz(n)) .lt. uzerr) then
            uz(n) = 0.0
          endif

c---- End of loop over vectors.
  120   continue

c---- Tested tol.
      endif

c.... Find the vector lengths and unit vectors.

      call aptvuna (ux, uy, uz, np, 0., vlen, nerr)

cbugc***DEBUG begins.
cbug 9902 format (/ 'aptvxun results:' /
cbug     &  (i3,' vlen=    ',1pe22.14 /
cbug     &  '    ux,uy,uz=',1p3e22.14))
cbug      write ( 3, 9902) (n, vlen(n), ux(n), uy(n), uz(n),
cbug     &  n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832