subroutine aptvdic (au, av, bu, bv, np, tol, du, dv, dab, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTVDIC
c
c     call aptvdic (au, av, bu, bv, np, tol, du, dv, dab, nerr)
c
c     Version:  aptvdic  Updated    1990 November 26 10:00.
c               aptvdic  Originated 1989 December 29 15:50.
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 2-D vector
c               d = (du, dv) from point a = (au, av) to point b = (bu, bv),
c               and its magnitude dab, the distance from "a" to "b", all in the
c               uv plane.  Directions u, v and w are orthogonal.
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               With no truncation, (du, dv) = (bu, bv) - (au, av),
c               and distance dab = sqrt (du**2 + dv**2).
c
c     Input:    au, av, bu, bv, np, tol.
c
c     Output:   du, dv, dab, nerr.
c
c     Glossary:
c
c     au, av    Input    The u and v coordinates of point "a".  Size np.
c                          The w coordinates are zero.  Directions u, v and w
c                          are orthogonal.
c
c     bu, bv    Input    The u and v coordinates of point "b".  Size np.
c                          The w coordinates are zero.
c
c     dab       Output   Distance between points "a" and "b", equal to
c                          the length of 2-D vector d = (du, dv).  May be
c                          truncated to zero, if less than the estimated error
c                          in its calculation.  See tol.  Size np.
c
c     du, dv    Output   The u and v components of 2-D vector "d".  Size np.
c                          The w coordinates are zero.
c                          May 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    The size of arrays au, av, bu, bv, dab, du, dv.
c
c     tol       Input    Numerical tolerance limit.  Used to truncate
c                          the components of 2-D vector d = (du, dv).
c                          On Cray computers, recommend 1.e-5 to 1.e-11.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

c.... Dimensioned arguments.

c---- Coordinate u of point "a".
      dimension au      (1)
c---- Coordinate v of point "a".
      dimension av      (1)
c---- Coordinate u of point "b".
      dimension bu      (1)
c---- Coordinate v of point "b".
      dimension bv      (1)
c---- the distance from "a" to "b".
      dimension dab     (1)
c---- Component u of vector "d".
      dimension du      (1)
c---- Component v of vector "d".
      dimension dv      (1)

c.... Local variables.

c---- Estimated error in du.
      common /laptvdic/ duerr
c---- Estimated error in dv.
      common /laptvdic/ dverr
c---- Index in "a", "b", "d", dab.
      common /laptvdic/ n
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvdic finding distance between points:' /
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.

      nerr = 0

c.... Test for input errors.

      if (np .le. 0) then
        nerr = 1
        go to 210
      endif

c.... Find the components of the distance vectors.

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

        du(n)  = bu(n) - au(n)
        dv(n)  = bv(n) - av(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 du, dv.
      if (tol .gt. 0.0) then

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

          duerr  = tol * (abs (au(n)) + abs (bu(n)))
          if (abs (du(n)) .lt. duerr) then
            du(n) = 0.0
          endif

          dverr  = tol * (abs (av(n)) + abs (bv(n)))
          if (abs (dv(n)) .lt. dverr) then
            dv(n) = 0.0
          endif

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

c---- Tested tol.
      endif

c.... Find the magnitudes of the distance vectors.

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

        dab(n) = sqrt (du(n)**2 + dv(n)**2)

c---- End of loop over points or vectors.
  130 continue
cbugc***DEBUG begins.
cbug 9902 format (/ 'aptvdic results:' /
cbug     &  (i3,' du,dv,dab=',1p3e22.14))
cbug      write ( 3, 9902) (n, du(n), dv(n), dab(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832