subroutine aptrksl (au, abu, cu, du, dintmn, dintmx, np, tol,
     &                    nint, dint, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTRKSL
c
c     call aptrksl (au, abu, cu, du, dintmn, dintmx, np, tol,
c    &              nint, cu, dint, nerr)
c
c     Version:  aptrksl  Updated    1990 December 3 14:20.
c               aptrksl  Originated 1990 January 11 15: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, any intersection
c               of the linear track through point a = (au) in the direction of
c               the unit vector ab = (abu, abv, abw), with the vw plane through
c               the point c = (cu), with the normal vector d = (du), for which
c               (1) the distance dint from point "a" to the intersection is
c               between the limits dintmn and dintmx, and (2) the direction
c               vector abu has the same sign as du.  This is equivalent to a
c               zone exit in 1-D slab geometry, if du has the sign of the
c               direction out of the zone at point cu.
c               Flag nint indicates the type of intersection found.
c               Flag nerr indicates any input error.
c
c               To find a zone exit in 1-D slab geometry.
c
c     Input:    au, abu, cu, du, dintmn, dintmx, np, tol.
c
c     Output:   nint, dint, nerr.
c
c     Calls: aptvdil 
c
c     Glossary:
c
c     abu       Input    The u component of the unit direction vector "ab" along
c                          the track in uvw space.  Size np.
c                          An acceptable intersection can only occur if abu has
c                          the same sign as du.
c
c     au        Input    The u coordinate of point "a".  The v and w coordinates
c                          are zero.  Directions u, v and w are orthogonal.
c                          Size np.
c
c     cu        Input    The u coordinate of point "c".  Size np.
c
c     dint      Output   The distance of the point of intersection of the track
c                          from point "a" to the uv plane through point "c".
c                          Positive if in the same direction as vector "ab".
c                          Size np.
c
c     dintmn    Input    Minimum allowed value of distance to intersection dint.
c                          Size np.
c
c     dintmx    Input    Maximum allowed value of distance to intersection dint.
c                          Size np.
c
c     du        Input    The u component of the outward normal vector of the vw
c                          plane at point "c".  Size np.
c                          An acceptable intersection can only occur if abu has
c                          the same sign as du.
c
c     nerr      Output   Indicates an input error, if not 0.
c                          1 if np is not positive.
c
c     nint      Output   Number of acceptable intersections found.  Size np.
c                          0 if none.
c                          1 if an acceptable intersection was found.
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---- Coordinate u of point "a".
      dimension au      (1)
c---- Component u of vector "ab".
      dimension abu     (1)
c---- Coordinate u of point "c".
      dimension cu      (1)
c---- Distance to intersection.
      dimension dint    (1)
c---- Minimum distance to intersection.
      dimension dintmn  (1)
c---- Maximum distance to intersection.
      dimension dintmx  (1)
c---- Component u of outward normal at "c".
      dimension du      (1)
c---- Number of acceptable intersections.
      dimension nint    (1)

c.... Local variables.

c---- Distance from au to cu.
      common /laptrksl/ acu     (64)

c---- A very small number.
      common /laptrksl/ fuz

c---- Index in arrays.
      common /laptrksl/ n
c---- First index of subset of data.
      common /laptrksl/ n1
c---- Last index of subset of data.
      common /laptrksl/ n2
c---- Index in external array.
      common /laptrksl/ nn
c---- Size of current subset of data.
      common /laptrksl/ ns
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptrksl finding 1-D exit in slab geometry:' /
cbug     &  (i3,' au=    ',1pe22.14,' abu=   ',1pe22.14 /
cbug     &  '    cu=    ',1pe22.14,' du=    ',1pe22.14 /
cbug     &  '    dintmn=',1pe22.14,' dintmx=',1pe22.14))
cbug      write ( 3, 9901) (n, au(n), abu(n), cu(n), du(n),
cbug     &  dintmn(n), dintmx(n), n = 1, np)
cbugc***DEBUG ends.

c.... Initialize.

c---- A very small number.
      fuz = 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 distance from point "a" to point "c".

      call aptvdil (au(n1), cu(n1), ns, tol, acu, nerr)

c.... Find the distance to the intersection.

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

        nn = n + n1 - 1
        dint(nn) = acu(n) / (abu(nn) + fuz)

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

c.... Test the intersection for acceptability (a zone exit)

c---- Loop over subset of data.
      do 150 nn = n1, n2

        if ((dint(nn) .ge. dintmn(nn)) .and.
     &      (dint(nn) .le. dintmx(nn)) .and.
     &      ((abu(nn) * du(nn)) .gt. 0.0)    ) then
          nint(nn) = 1
        else
          nint(nn) = 0
        endif

c---- End of loop over subset of data.
  150 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 (/ 'aptrksl results:' /
cbug     &  (i3,' dint=  ',1pe22.14,' nint=',i2))
cbug      write ( 3, 9902) (n, dint(n), nint(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832