subroutine aptvanc (au, av, bu, bv, np, tol, costh, sinth, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVANC
c
c     call aptvanc (au, av, bu, bv, np, tol, costh, sinth, nerr)
c
c     Version:  aptvanc  Updated    1990 March 14 16:00.
c               aptvanc  Originated 1990 January 8 16:40.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To find the cosine costh and sine sinth of the angle between the
c               pair of 2-D vectors a = (au, av) and b = (bu, bv), measured
c               counterclockwise in the uv plane, from vector "a" to vector "b",
c               for each of np sets of input data.  The values of costh and
c               sinth will be truncated to zero, if less than the estimated
c               error in their calculation, based on tol.  Flag nerr indicates
c               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:    au, av, bu, bv, np, tol.
c
c     Output:   costh, sinth, nerr.
c
c     Calls: aptvaxc, aptvdoc, aptvubc 
c               
c
c     Glossary:
c
c     au, av    Input    The u and v components of a 2-D vector.  Size np.
c
c     bu, bv    Input    The u and v components of a 2-D vector.  Size np.
c
c     costh     Output   Cosine of the angle between the 2-D vectors "a" and
c                          "b".  Will be truncated to zero, if less than the
c                          estimated error in its calculation, based on tol.
c                          Meaningless if the magnitude of "a" or "b" is zero.
c                          The angle is measured counterclockwise in the uv
c                          plane, from vector "a" to 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 au, av, bu, bv, costh, sinth.
c
c     sinth     Output   Sine of the angle between the 2-D vectors "a" and
c                          "b".  Will be truncated to zero, if less than the
c                          estimated error in its calculation, based on tol.
c                          Meaningless if the magnitude of "a" or "b" is zero.
c                          The angle is measured counterclockwise in the uv
c                          plane, from vector "a" to vector "b".  Size np.
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 input vector "a".
      dimension au      (1)
c---- Component v of input vector "a".
      dimension av      (1)
c---- Component u of input vector "b".
      dimension bu      (1)
c---- Component v of input vector "b".
      dimension bv      (1)
c---- Cosine of angle between "a" and "b".
      dimension costh   (1)
c---- Sine of angle between "a" and "b".
      dimension sinth   (1)

c.... Local variables.

c---- Component u of unit vector "ha".
      common /laptvanc/ hau     (64)
c---- Component v of unit vector "ha".
      common /laptvanc/ hav     (64)
c---- Component u of unit vector "hb".
      common /laptvanc/ hbu     (64)
c---- Component v of unit vector "hb".
      common /laptvanc/ hbv     (64)
c---- Index in arrays.
      common /laptvanc/ n
c---- First index of subset of data.
      common /laptvanc/ n1
c---- Last index of subset of data.
      common /laptvanc/ n2
c---- Size of current subset of data.
      common /laptvanc/ ns
c---- Magnitude of input vector "a".
      common /laptvanc/ vlena   (64)
c---- Magnitude of input vector "b".
      common /laptvanc/ vlenb   (64)
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvanc finding angles.',
cbug     &  '  np=',i3,', tol=',1pe13.5)
cbug 9902 format (i3,' au,av=',1p2e22.14 /
cbug     &  '    bu,bv=',1p2e22.14)
cbug      write ( 3, 9901) np, tol
cbug      write ( 3, 9902) (n, au(n), av(n), bu(n), bv(n),
cbug     &  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.... 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 unit vectors parallel to vectors "a" and "b".

      call aptvubc (au(n1), av(n1), ns, 0.,
     &              hau, hav, vlena, nerr)

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

c.... Find the cosine of the angle between vectors "a" and "b".

      call aptvdoc (hau, hav, hbu, hbv, ns, tol, costh(n1), nerr)

c.... Find the sine of the angle between vectors "a" and "b".

      call aptvaxc (hau, hav, hbu, hbv, ns, tol, sinth(n1), nerr)

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 9903 format (/ 'aptvanc cosines and sines:')
cbug 9904 format (i3,' costh=',1pe22.14,' sinth=',1pe22.14)
cbug      write ( 3, 9903)
cbug      write ( 3, 9904) (n, costh(n), sinth(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832