subroutine aptvcvc (au, av, bu, bv, np, tol, cu, cv, clen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVCVC
c
c     call aptvcvc (au, av, bu, bv, np, tol, cu, cv, clen, nerr)
c
c     Version:  aptvcvc  Updated    1990 November 26 10:00.
c               aptvcvc  Originated 1990 April 5 16:40.
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 = (cu, cv) of the vector a = (au, av) in the direction of the
c               vector b = (bu, bv), and clen, the magnitude of vector "c".
c               If the magnitude of vector "b" is too small, its orientation is
c               indeterminate, and the returned value of clen will be -1.e+99.
c               The components of vector "c" may be truncated to zero, if less
c               than the estimated error in their calculation, based on tol.
c               Flag nerr indicates any input error.
c
c     Input:    au, av, bu, bv, np, tol.
c
c     Output:   cu, cv, clen, nerr.
c
c     Calls: aptvdoc, aptvubc 
c               
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                          If too small, based on tol, to determine the
c                          orientation of the line, clen will be returned
c                          as -1.e+99.
c
c     clen      Output   The magnitude of vector "c".  Size np.
c                          Zero if vector "a" is perpendicular to vector "b".
c                          Will be -1.e+99 if vector "b" is too small.
c
c     cu, cv    Output   The u and v components of vector "c".  Size np.
c                          The projection of vector "a" in the direction of
c                          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 zero,
c                          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 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.... Local variables.

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

c---- First index of subset of data.
      common /laptvcvc/ n1
c---- Last index of subset of data.
      common /laptvcvc/ n2
c---- Index in local array.
      common /laptvcvc/ n
c---- Index in external array.
      common /laptvcvc/ nn
c---- Size of current subset of data.
      common /laptvcvc/ ns
c---- Magnitude of vector "b".
      common /laptvcvc/ blen    (64)
c---- Component u of unit vector "hb".
      common /laptvcvc/ hbu     (64)
c---- Component v of unit vector "hb".
      common /laptvcvc/ hbv     (64)
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvcvc finding projection of A on vector B:' /
cbug     &  (i3,' au,av=',1p2e22.14 /
cbug     & '    bu,bv=',1p2e22.14))
cbug      write ( 3, 9901) (n, au(n), av(n), bu(n), bv(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" parallel to vector "b", and
c....   blen, the magnitude of vector "b".

      call aptvubc (bu(n1), bv(n1), ns, 0.,
     &              hbu, hbv, blen, nerr)

c.... Find the magnitude of vector "c".

      call aptvdoc (au(n1), av(n1), hbu, hbv, ns, tol,
     &              clen(n1), nerr)

c.... Find the components of vector "a" parallel to vector "b".

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

        nn = n + n1 - 1
        cu(nn)   = clen(nn) * hbu(n)
        cv(nn)   = clen(nn) * hbv(n)

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

  210 return

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

UCRL-WEB-209832