subroutine aptvadd (ax, ay, az, bmult, b, cx, cy, cz, np, tol,
     &                    dx, dy, dz, vlen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVADD
c
c     call aptvadd (ax, ay, az, bmult, b, cx, cy, cz, np, tol,
c    &              dx, dy, dz, vlen, nerr)
c
c     Version:  aptvadd  Updated    1990 November 26 10:00.
c               aptvadd  Originated 1989 November 20 13:20.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To find, for each of the np sets of input data, the vector sum
c               d(n) = a(n) + bmult * b(n) * c(n), where d = (dx, dy, dz),
c               a = (ax, ay, az), and c = (cx, cy, cz), and to find vlen, the
c               magnitude of vector "d".
c               Any component of vector "d" less than the estimated error in
c               its calculation, based on tol, will be truncated to zero.
c               Flag nerr indicates any input error.
c
c     History:  1990 February 22.  Deleted truncation of vector components to
c               zero based on vector magnitude.
c
c     Input:    ax, ay, az, bmult, b, cx, cy, cz, np, tol.
c
c     Output:   dx, dy, dz, vlen, nerr.
c
c     Glossary:
c
c     ax,ay,az  Input    The x, y, z components of vector "a".  Size np.
c
c     b         Input    Coefficient of vector "c", when multiplied by bmult.
c                          Size np.
c
c     bmult     Input    Multiplier of term b(n) * c(n).  Not an array.
c
c     cx,cy,cz  Input    The x, y, z components of vector "c".  Size np.
c
c     dx,dy,dz  Output   The x, y, z components of vector "d".  Size np.
c                          Will be truncated to zero if less than the estimated
c                          numerical error in their calculation based on tol.
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     tol       Input    Numerical tolerance limit.  Used to truncate
c                          the components of vector d = (dx, dy, dz).
c                          On Cray computers, recommend 1.e-5 to 1.e-11.
c
c     vlen      Output   Magnitude of vector "d".  May be truncated to zero,
c                          if less than the estimated error in its calculation.
c                          See tol.  Size np.
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---- A scalar multiplier.
      dimension b       (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---- Component x of vector "d".
      dimension dx      (1)
c---- Component y of vector "d".
      dimension dy      (1)
c---- Component z of vector "d".
      dimension dz      (1)
c---- The distance from "a" to "c".
      dimension vlen    (1)

c.... Local variables.

c---- Estimated error in dx.
      common /laptvadd/ dxerr
c---- Estimated error in dy.
      common /laptvadd/ dyerr
c---- Estimated error in dz.
      common /laptvadd/ dzerr
c---- An array index.
      common /laptvadd/ n
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvadd finding vector sum a + b * c:' /
cbug     &  '  bmult=',1pe22.14 /
cbug     &  (i3,' ax,ay,az=',1p3e22.14 /
cbug     &  '    b=       ',1pe22.14 /
cbug     &  '    cx,cy,cz=',1p3e22.14))
cbug      write ( 3, 9901) bmult, (n, ax(n), ay(n), az(n), b(n),
cbug     &  cx(n), cy(n), cz(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

c.... Find the components of vector "d".

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

        dx(n)   = ax(n) + bmult * b(n) * cx(n)
        dy(n)   = ay(n) + bmult * b(n) * cy(n)
        dz(n)   = az(n) + bmult * b(n) * cz(n)

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

c.... See if the truncation error option is to be used.

c---- Test and adjust dx, dy, dz.
      if (tol .gt. 0.0) then

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

          dxerr = tol * (abs (ax(n)) + abs (bmult * b(n) * cx(n)))
          if (abs (dx(n)) .lt. dxerr) then
            dx(n) = 0.0
          endif

          dyerr = tol * (abs (ay(n)) + abs (bmult * b(n) * cy(n)))
          if (abs (dy(n)) .lt. dyerr) then
            dy(n) = 0.0
          endif

          dzerr = tol * (abs (az(n)) + abs (bmult * b(n) * cz(n)))
          if (abs (dz(n)) .lt. dzerr) then
            dz(n) = 0.0
          endif

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

c---- Tested tol.
      endif

c.... Find the magnitudes of vector "d".

c---- Loop over points or vectors.
      do 130 n = 1, np

        vlen(n) = sqrt (dx(n)**2 + dy(n)**2 + dz(n)**2)

c---- End of loop over points or vectors.
  130 continue
cbugc***DEBUG begins.
cbug 9902 format (/ 'aptvadd results:' /
cbug     &  (i3,' vlen=    ',1pe22.14 /
cbug     &  '    dx,dy,dz=',1p3e22.14))
cbug      write ( 3, 9902) (n, vlen(n), dx(n), dy(n), dz(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832