subroutine aptvsuc (noptf, fa, au, av, fb, bu, bv, np, tol,
     &                    cu, cv, clen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVSUC
c
c     call aptvsuc (noptf, fa, au, av, fb, bu, bv, np, tol,
c    &              cu, cv, clen, nerr)
c
c     Version:  aptvsuc  Updated    1990 November 26 10:00.
c               aptvsuc  Originated 1989 April 3 17:10.
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 = (cu, cv) of the vectors a = (au, av) and b = (bu, bv):
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, au, av, fb, bu, bv, np, tol.
c
c     Output:   cu, cv, clen, nerr.
c
c     Glossary:
c
c     au,av     Input    The u and v components of vector "a".  Size np.
c
c     bu,bv     Input    The u and v 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     cu,cv     Output   The u and v 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 u of vector "a".
      dimension au      (1)
c---- Component v of vector "a".
      dimension av      (1)
c---- Component u of vector "b".
      dimension bu      (1)
c---- Component v of vector "b".
      dimension bv      (1)
c---- Magnitude of vector "c".
      dimension clen    (1)
c---- Component u of vector "c".
      dimension cu      (1)
c---- Component v of vector "c".
      dimension cv      (1)
c---- Weight of vector "a".
      dimension fa      (1)
c---- Weight of vector "b".
      dimension fb      (1)

c.... Local variables.

c---- Estimated error in cu.
      common /laptvsuc/ cuerr
c---- Initial value of cu.
      common /laptvsuc/ cuu     (64)
c---- Estimated error in cv.
      common /laptvsuc/ cverr
c---- Initial value of cv.
      common /laptvsuc/ cvv     (64)
c---- Weight of vector "a".
      common /laptvsuc/ faa     (64)
c---- Weight of vector "b".
      common /laptvsuc/ fbb     (64)
c---- Index in arrays.
      common /laptvsuc/ n
c---- First index of subset of data.
      common /laptvsuc/ n1
c---- Last index of subset of data.
      common /laptvsuc/ n2
c---- Index in external array.
      common /laptvsuc/ nn
c---- Size of current subset of data.
      common /laptvsuc/ ns
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvsuc finding vector sum fa * a + fb * c.',
cbug     &  '  noptf=',i2,' tol=',1pe22.14)
cbug 9902 format ('  fa,fb=  ',1p2e22.14)
cbug 9903 format (i3,' au,av=',1p2e22.14 /
cbug     &  '    bu,bv=',1p2e22.14)
cbug 9904 format (i3,' fa=   ',1pe22.14 /
cbug     &  '    au,av=',1p2e22.14 /
cbug     &  '    fb=   ',1pe22.14 /
cbug     &  '    bu,bv=',1p2e22.14)
cbug      write ( 3, 9901) noptf, tol
cbug      if (noptf .eq. 0) then
cbug        write ( 3, 9902) fa, fb
cbug        write ( 3, 9903) (n, au(n), av(n),
cbug     &    bu(n), bv(n), n = 1, np)
cbug      else
cbug        write ( 3, 9904) (n, fa(n), au(n), av(n),
cbug     &    fb(n), bu(n), bv(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
        cuu(n) = faa(n) * au(nn) + fbb(n) * bu(nn)
        cvv(n) = faa(n) * av(nn) + fbb(n) * bv(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

          cuerr = tol * (abs (faa(n) * au(nn)) + abs (fbb(n) * bu(nn)))
          cverr = tol * (abs (faa(n) * av(nn)) + abs (fbb(n) * bv(nn)))

          if (abs (cuu(n)) .lt. cuerr) then
            cuu(n) = 0.0
          endif

          if (abs (cvv(n)) .lt. cverr) then
            cvv(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
        cu(nn) = cuu(n)
        cv(nn) = cvv(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 nn = n1, n2

        clen(nn) = sqrt (cu(nn)**2 + cv(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 (/ 'aptvsuc results:' /
cbug     &  (i3,' cu,cv=',1p2e22.14 /
cbug     &  '    clen= ',1pe22.14))
cbug      write ( 3, 9905) (n, cu(n), cv(n), clen(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832