subroutine aptpbln (ax, ay, az, bx, by, bz, np, tol,
     &                    cx, cy, cz, abx, aby, abz, ablen, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTPBLN
c
c     call aptpbln (ax, ay, az, bx, by, bz, np, tol,
c    &              cx, cy, cz, abx, aby, abz, ablen, nerr)
c
c     Version:  aptpbln  Updated    1990 April 5 8:30.
c               aptpbln  Originated 1990 April 5 8:30.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To find the plane which perpendicularly bisects the line through
c               points a = (ax, ay, az) and b = (bx, by, bz), by passing through
c               the point c = (cx, cy, cz) on the midpoint of line "ab", with
c               normal vector ab = (abx, aby, abz) parallel to the line "ab".
c               The length of line "ab", ablen, is also returned.
c               The components of vector "ab" will be truncated to zero, if less
c               than the estimated numerical error in their calculation, based
c               on tol.  Flag nerr indicates any input error, if not zero.
c
c     Input:    ax, ay, az, bx, by, bz, np, tol.
c
c     Output:   cx, cy, cz, abx, aby, abz, ablen, nerr.
c
c     Calls: aptvsum 
c
c     Glossary:
c
c     ablen     Output   The magnitude of the normal vector "ab".  Size np.
c                          Zero if points "a" and "b" are congruent, and the
c                          orientation of the bisecting plane is indeterminate.
c
c     abx,y,z   Output   The x, y, z components of vector "ab" parallel to line
c                          "ab".  Vector "ab" is normal to the plane that
c                          perpendicularly bisects the line "ab".  Size np.
c                          Each component may be truncated to zero, if less than
c                          the estimated error in its calculation.  See tol.
c
c     ax,ay,az  Input    The x, y, z coordinates of point "a".  Size np.
c
c     bx,by,bz  Input    The x, y, z coordinates of point "b".  Size np.
c
c     cx,cy,cz  Output   The x, y, z coordinates of point "c" on the midpoint
c                          of line "ab".  Size np.
c
c     nerr      Output   Indicates an input error, if not 0.
c                          1 if np is not positive.
c
c     np        Input    The number of lines "ab" for which the bisecting plane
c                          is to be found.  Must be positive.
c
c     tol       Input    Numerical tolerance limit for abx, aby, abz.
c                          On Cray computers, recommend 1.e-5 to 1.e-11.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

c.... Dimensioned arguments.

c---- Magnitude of normal vector "ab".
      dimension ablen   (1)
c---- Component x of normal vector "ab".
      dimension abx     (1)
c---- Component y of normal vector "ab".
      dimension aby     (1)
c---- Component z of normal vector "ab".
      dimension abz     (1)
c---- Coordinate x of input point "a".
      dimension ax      (1)
c---- Coordinate y of input point "a".
      dimension ay      (1)
c---- Coordinate z of input point "a".
      dimension az      (1)
c---- Coordinate x of input point "b".
      dimension bx      (1)
c---- Coordinate y of input point "b".
      dimension by      (1)
c---- Coordinate z of input point "b".
      dimension bz      (1)
c---- Coordinate x of center point "c".
      dimension cx      (1)
c---- Coordinate y of center point "c".
      dimension cy      (1)
c---- Coordinate z of center point "c".
      dimension cz      (1)

c.... Local variables.

c---- Distance of point "c" from origin.
      common /laptpbln/ clen    (64)
c---- First index of subset of data.
      common /laptpbln/ n1
c---- Last index of subset of data.
      common /laptpbln/ n2
c---- Size of current subset of data.
      common /laptpbln/ ns
cbugc***DEBUG begins.
cbugc---- Index in arrays.
cbug      common /laptpbln/ n
cbug 9901 format (/ 'aptpbln finding plane perpendicularly bisecting line',
cbug     &  ' through points:' /
cbug     &  (i3,' ax,ay,az=',1p3e22.14 /
cbug     &  '    bx,by,bz=',1p3e22.14))
cbug      write ( 3, 9901) (n, ax(n), ay(n), az(n), bx(n), by(n), bz(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 vector parallel to line "ab", and its length.

      call aptvsum (0, -1.0, ax(n1), ay(n1), az(n1),
     &                  1.0, bx(n1), by(n1), bz(n1), ns, tol,
     &              abx(n1), aby(n1), abz(n1), ablen(n1), nerr)

c.... Find the midpoint of line "ab".

      call aptvsum (0, 0.5, ax(n1), ay(n1), az(n1),
     &                 0.5, bx(n1), by(n1), bz(n1), ns, tol,
     &              cx(n1), cy(n1), cz(n1), clen, 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 9902 format (/ 'aptpbln results:' /
cbug     &  (i3,' ablen=   ',1pe22.14 /
cbug     &  '    cx,cy,cz=',1p3e22.14 /
cbug     &  '    abx,y,z= ',1p3e22.14))
cbug      write ( 3, 9902) (n, ablen(n), cx(n), cy(n), cz(n),
cbug     &  abx(n), aby(n), abz(n), n = 1, np)
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832