subroutine aptvsum (noptf, fa, ax, ay, az, fb, bx, by, bz, np,
     &                    tol, cx, cy, cz, clen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVSUM
c
c     call aptvsum (noptf, fa, ax, ay, az, fb, bx, by, bz, np, tol,
c    &              cx, cy, cz, clen, nerr)
c
c     Version:  aptvsum  Updated    1990 November 26 10:00.
c               aptvsum  Originated 1989 April 3 16:00.
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 weighted
c               sum c = (cx, cy, cz) of the vectors a = (ax, ay, az) and
c               b = (bx, by, bz):
c                 c(n) = fa * a(n) + fb * b(n), n = 1, np  (noptf = 0), or
c                 c(n) = fa(n) * a(n) + fb(n) * b(n), n = 1, np (noptf = 1),
c               and to find clen, the magnitude of vector "c".
c               Any component of vector "c" 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               Special cases:
c                 sum:            c = a + b  (noptf = 0, fa = 1.0, fb =  1.0).
c                 difference:     c = a - b  (noptf = 0, fa = 1.0, fb = -1.0).
c                 interpolation:  c = fa * a + (1.0 - fa) * b  (noptf = 0),
c                                 c = (1.0 - fb) * a + fb * b  (noptf = 0).
c
c     Input:    noptf, fa, ax, ay, az, fb, bx, by, bz, np, tol.
c
c     Output:   cx, cy, cz, clen, nerr.
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
c     clen      Output   Magnitude of vector "c".  May be truncated to zero,
c                          if less than the estimated error in its calculation.
c                          See tol.  Size np.
c
c     cx,cy,cz  Output   The x, y, z components of vector "c".  Size np.
c                          Will be truncated to zero if less than the estimated
c                          numerical error in their calculation based on tol.
c
c     fa        Input    Coefficient of vector "a".  Size 1 (noptf = 0) or
c                          np (noptf = 1).
c
c     fb        Input    Coefficient of vector "b".  Size 1 (noptf = 0) or
c                          np (noptf = 1).
c
c     nerr      Output   Indicates an input error, if not 0.
c                          1 if np is not positive.
c                          2 if noptf is not 0 or 1.
c
c     noptf     Input    Size option for fa, fb:
c                          0 if fa and fb are scalars.
c                          1 if fa and fb are arrays with size np.
c
c     np        Input    Size of arrays.
c
c     tol       Input    Numerical tolerance limit.  Used to truncate
c                          the components of vector "c".
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---- Weight of vector "a".
      dimension fa      (1)
c---- Weight of vector "b".
      dimension fb      (1)

c.... Local variables.

c---- Initial value of cx.
      common /laptvsum/ cxx     (64)
c---- Initial value of cy.
      common /laptvsum/ cyy     (64)
c---- Initial value of cz.
      common /laptvsum/ czz     (64)
c---- Estimated error in cx.
      common /laptvsum/ cxerr
c---- Estimated error in cy.
      common /laptvsum/ cyerr
c---- Estimated error in cz.
      common /laptvsum/ czerr
c---- Weight of vector "a".
      common /laptvsum/ faa     (64)
c---- Weight of vector "b".
      common /laptvsum/ fbb     (64)
c---- Index in arrays.
      common /laptvsum/ n
c---- First index of subset of data.
      common /laptvsum/ n1
c---- Last index of subset of data.
      common /laptvsum/ n2
c---- Index in external array.
      common /laptvsum/ nn
c---- Size of current subset of data.
      common /laptvsum/ ns
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvsum finding vector sum fa * a + fb * c.',
cbug     &  '  noptf=',i2,' tol=',1pe22.14)
cbug 9902 format ('  fa,fb=     ',1p2e22.14)
cbug 9903 format (i3,' ax,ay,az=',1p3e22.14 /
cbug     &  '    bx,by,bz=',1p3e22.14)
cbug 9904 format (i3,' fa=      ',1pe22.14 /
cbug     &  '    ax,ay,az=',1p3e22.14 /
cbug     &  '    fb=      ',1pe22.14 /
cbug     &  '    bx,by,bz=',1p3e22.14)
cbug      write ( 3, 9901) noptf, tol
cbug      if (noptf .eq. 0) then
cbug        write ( 3, 9902) fa, fb
cbug        write ( 3, 9903) (n, ax(n), ay(n), az(n),
cbug     &    bx(n), by(n), bz(n), n = 1, np)
cbug      else
cbug        write ( 3, 9904) (n, fa(n), ax(n), ay(n), az(n),
cbug     &    fb(n), bx(n), by(n), bz(n), n = 1, np)
cbug      endif
cbugc***DEBUG ends.

c.... Initialize.

      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)

c.... Loop over subsets of data.

  110 ns = n2 - n1 + 1

c.... Find the weights of vectors "a" and "b".

c---- Weights fa and fb are scalars.
      if (noptf .eq. 0) then

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

          faa(n) = fa(1)
          fbb(n) = fb(1)

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

c---- Weights fa and fb are arrays.
      elseif (noptf .eq. 1) then

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

          faa(n) = fa(n)
          fbb(n) = fb(n)

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

      else
        nerr = 2
        go to 210
      endif

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

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

        nn     = n + n1 - 1
        cxx(n) = faa(n) * ax(nn) + fbb(n) * bx(nn)
        cyy(n) = faa(n) * ay(nn) + fbb(n) * by(nn)
        czz(n) = faa(n) * az(nn) + fbb(n) * bz(nn)

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

c.... See if small components of vector "c" should be truncated to zero.

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

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

          nn    = n + n1 - 1

          cxerr = tol * (abs (faa(n) * ax(nn)) + abs (fbb(n) * bx(nn)))
          cyerr = tol * (abs (faa(n) * ay(nn)) + abs (fbb(n) * by(nn)))
          czerr = tol * (abs (faa(n) * az(nn)) + abs (fbb(n) * bz(nn)))

          if (abs (cxx(n)) .lt. cxerr) then
            cxx(n) = 0.0
          endif

          if (abs (cyy(n)) .lt. cyerr) then
            cyy(n) = 0.0
          endif

          if (abs (czz(n)) .lt. czerr) then
            czz(n) = 0.0
          endif

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

c---- Tested tol.
      endif

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

        nn     = n + n1 - 1
        cx(nn) = cxx(n)
        cy(nn) = cyy(n)
        cz(nn) = czz(n)

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

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

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

        nn       = n + n1 - 1
        clen(nn) = sqrt (cx(nn)**2 + cy(nn)**2 + cz(nn)**2)

c---- End of loop over subset of data.
  170 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 9905 format (/ 'aptvsum results:' /
cbug     &  (i3,' cx,cy,cz=',1p3e22.14 /
cbug     &  '    clen=    ',1pe22.14))
cbug      write ( 3, 9905) (n, cx(n), cy(n), cz(n), clen(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832