subroutine aptscap (np, au, av, aw, pm, bu, bv, bw, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTSCAP
c
c     call aptscap (np, au, av, aw, pm, bu, bv, bw, nerr)
c
c     Version:  aptscap  Updated    1992 June 4 10:00.
c               aptscap  Originated 1990 January 10 10:30.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To randomly sample np unit direction vectors b = (bu, bv, bw)
c               from a cosine**pm distribution in 3-D space, centered on an
c               axis in the direction of unit vector a = (au, av, aw).
c               Flag nerr indicates any input error.
c
c               If "ba" is the expected value of the component of unit vector
c               "b" in the direction of unit vector "a", then:
c
c                 ba = (pm + 1.0) / (pm + 2.0).  (ba .ge. 0.5).
c                 pm = (2.0 * ba - 1.0) / (1.0 - ba).  (pm .ge. 0.0).
c                 pm = 0.0:  isotropic in half-space.
c                 pm = 1.0:  cosine distribution in half-space.
c
c     History:  1990 May 1 10:20.  Switched from rejection to trig method.
c               1990 May 3 9:40.  Changed vector rotation method.
c               1990 May 7 10::40.  Removed arguments tolx, toly, tolz.
c                 This option may be exercized by calling aptvlim or aptvtol.
c               1992 June 4 10:0.  Move rotm calculation out of loop 170.
c
c     Input:    np, au, av, aw, pm.
c
c     Output:   bu, bv, bw, nerr.
c
c     Glossary:
c
c     au,av,aw  Input    The u, v and w components of a unit vector in the
c                          direction of the center of a cosine**pm distribution.
c
c     bu,bv,bw  Output   The u, v, w components of a unit vector representing a
c                          direction chosen randomly from a cosine**pm
c                          distribution in 3-D space, centered in the direction
c                          of unit vector "a".  Coordinates u, v and w may
c                          be any 3 orthogonal coordinates.  Size np.
c
c     nerr      Output   Indicates an input error, if not 0.
c                          1 if np is not positive.
c                          2 if pm is -1.0 or less.
c
c     np        Input    Size of arrays.
c
c     pm        Input    Power used for the cosine**pm spatial distribution
c                          from which unit vector "b" is to be chosen.
c                          Must be greater than -1.0.
c                          pm = 0.0:  isotropic in half-space.
c                          pm = 1.0:  cosine distribution in half-space.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

c.... Dimensioned arguments.

c---- Component u of random unit vector.
      dimension bu      (1)
c---- Component v of random unit vector.
      dimension bv      (1)
c---- Component w of random unit vector.
      dimension bw      (1)

c.... Local variables.

c---- Cosine of angle phi.
      common /laptscap/ cosph
c---- Cosine of angle theta.
      common /laptscap/ costh
c---- Component u of unit vector "c".
      common /laptscap/ cu      (64)
c---- Component v of unit vector "c".
      common /laptscap/ cv      (64)
c---- Component w of unit vector "c".
      common /laptscap/ cw      (64)
c---- Function 1.0 / (1.0 + aw + fuz).
      common /laptscap/ faw

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

c---- Index in unit vector array.
      common /laptscap/ n
c---- First index of subset of data.
      common /laptscap/ n1
c---- Last index of subset of data.
      common /laptscap/ n2
c---- Index in external array.
      common /laptscap/ nn
c---- Size of current subset of data.
      common /laptscap/ ns

c---- Numerical constant pi.
      common /laptscap/ pi

c---- Random number (0.0 to 1.0).
      common /laptscap/ ranfp1  (64)
c---- Random number (0.0 to 1.0).
      common /laptscap/ ranfp2  (64)
c---- Rotation matrix.
      common /laptscap/ rotm   (3,3)
c---- Sine of angle phi.
      common /laptscap/ sinph
c---- Sine of angle of "a" from w axis.
      common /laptscap/ sinr
c---- Function sinr + fuz.
      common /laptscap/ sinr1
c---- Sine of angle theta.
      common /laptscap/ sinth
c---- Angle from v axis in vw plane.
      common /laptscap/ theta
cbugc***DEBUG begins.
cbug      common /laptscap/ avgu, avgv, avgw, devu, devv, devw
cbug      common /laptscap/ avgu2, avgv2, avgw2, sumsqs
cbug 9901 format (/ 'aptscap finding cos**pm random directions.' /
cbug     &  '  np=',i3,'  pm=',1pe22.14 /
cbug     &  '  au,av,aw=',1p3e22.14)
cbug      write (3, 9901) np, pm, au, av, aw
cbugc***DEBUG ends.

c.... initialize.

c---- A very small number.
      fuz = 1.e-99

c++++ Dimensionless.    18 digits.
      pi       = 3.14159265358979323

      nerr = 0

c.... Test for input errors.

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

      if (pm .le. -1.0) then
        nerr = 2
        go to 210
      endif

c.... Set up the indices of the first subset of data.

      n1 = 1
      n2 = min (np, 64)

c.... Loop over the data subsets.

  110 ns = n2 - n1 + 1

c.... Generate the needed random numbers.

c---- Loop over subset of data.
      do 120 n = 1, ns
        ranfp1(n) = ranf( )
c---- End of loop over subset of data.
  120 continue

c---- Loop over subset of data.
      do 130 n = 1, ns
        ranfp2(n) = ranf( )
c---- End of loop over subset of data.
  130 continue

c.... Find unit vectors "c" with the w component sampled from a cos**pm
c....   distribution.

c---- Isotropic distribution in half-space.
      if (pm .eq. 0.0) then

c---- Loop over vectors.
        do 140 n = 1, ns

          cosph = ranfp1(n)
          sinph = sqrt (1.0 - cosph**2)
          theta = 2.0 * pi * ranfp2(n)
          costh = cos (theta)
          sinth = sin (theta)

          cu(n) = costh * sinph
          cv(n) = sinth * sinph
          cw(n) = cosph

c---- End of loop over vectors.
  140   continue

c---- Cosine distribution in half-space.
      elseif (pm .eq. 1.0) then

c---- Loop over vectors.
        do 150 n = 1, ns

          cosph = sqrt (ranfp1(n))
          sinph = sqrt (1.0 - cosph**2)
          theta = 2.0 * pi * ranfp2(n)
          costh = cos (theta)
          sinth = sin (theta)

          cu(n) = costh * sinph
          cv(n) = sinth * sinph
          cw(n) = cosph

c---- End of loop over vectors.
  150   continue

c---- Cosine**pm distribution in half-space.
      else

c---- Loop over vectors.
        do 160 n = 1, ns

          cosph = ranfp1(n)**(1.0 / (1.0 + pm))
          sinph = sqrt (1.0 - cosph**2)
          theta = 2.0 * pi * ranfp2(n)
          costh = cos (theta)
          sinth = sin (theta)

          cu(n) = costh * sinph
          cv(n) = sinth * sinph
          cw(n) = cosph

c---- End of loop over vectors.
  160   continue

c---- Tested pm.
      endif

c.... Rotate all the unit vectors "c" by the angle required to align the
c....   vector (0., 0., 1.) with the unit vector a = (au, av, aw).

        sinr      = sqrt (au**2 + av**2)
        sinr1     = sinr + fuz
        faw       = (1.0 - aw) / sinr1**2

        rotm(1,1) =  av**2 * faw + aw
        rotm(1,2) = -au * av * faw
        rotm(1,3) =  au * sinr / sinr1

        rotm(2,1) = -au * av * faw
        rotm(2,2) =  au**2 * faw + aw
        rotm(2,3) =  av * sinr / sinr1

        rotm(3,1) = -au * sinr / sinr1
        rotm(3,2) = -av * sinr / sinr1
        rotm(3,3) =  aw

c---- Loop over vectors.
      do 170 n = 1, ns

        nn     = n + n1 - 1

        bu(nn) = cu(n) * rotm(1,1) + cv(n) * rotm(1,2) +
     &           cw(n) * rotm(1,3)
        bv(nn) = cu(n) * rotm(2,1) + cv(n) * rotm(2,2) +
     &           cw(n) * rotm(2,3)
        bw(nn) = cu(n) * rotm(3,1) + cv(n) * rotm(3,2) +
     &           cw(n) * rotm(3,3)

c---- End of loop over vectors.
  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
cbug 9902 format (/ 'aptscap results:')
cbug 9903 format (i3,' bu,bv,bw=',1p3e22.14 /
cbug     &  '    sumsq=   ',1pe22.14)
cbug 9904 format (/ 'aptscap mean and deviation:' /
cbug     &  '  avg(u,v,w)=',1p3e22.14 /
cbug     &  '  dev(u,v,w)=',1p3e22.14)
cbug
cbug      write ( 3, 9902)
cbug
cbug      avgu  = 0.0
cbug      avgv  = 0.0
cbug      avgw  = 0.0
cbug      avgu2 = 0.0
cbug      avgv2 = 0.0
cbug      avgw2 = 0.0
cbug
cbug      do 180 n = 1, np
cbug        avgu   = avgu + bu(n)
cbug        avgv   = avgv + bv(n)
cbug        avgw   = avgw + bw(n)
cbug        avgu2  = avgu2 + bu(n)**2
cbug        avgv2  = avgv2 + bv(n)**2
cbug        avgw2  = avgw2 + bw(n)**2
cbug        sumsqs = bu(n)**2 + bv(n)**2 + bw(n)**2
cbug        write ( 3, 9903) n, bu(n), bv(n), bw(n), sumsqs
cbug  180 continue
cbug
cbug      avgu  = avgu / np
cbug      avgv  = avgv / np
cbug      avgw  = avgw / np
cbug      avgu2 = avgu2 / np
cbug      avgv2 = avgv2 / np
cbug      avgw2 = avgw2 / np
cbug      devu  = sqrt (avgu2 - avgu**2)
cbug      devv  = sqrt (avgv2 - avgv**2)
cbug      devw  = sqrt (avgw2 - avgw**2)
cbug
cbug      write ( 3, 9904) avgu, avgv, avgw, devu, devv, devw
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832