subroutine aptetrv (vx, vy, vz, ax, ay, az, bx, by, bz,
     &                    dvc, iunit, angac, angbc, tol,
     &                    cx, cy, cz, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTETRV
c
c     call aptetrv (vx, vy, vz, ax, ay, az, bx, by, bz, dvc, iunit,
c    &              angac, angbc, tol, cx, cy, cz, nerr)
c
c     Version:  aptetrv  Updated    2001 March 28 10:30.
c               aptetrv  Originated 2001 March 26 14:30.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  Given points v = (vx, vy, vz), a = (ax, ay, az) and
c               b = (bx, by, bz), to find point c = (cx, cy, cz) at distance
c               dvc from point "v", at angle angac from line va and at angle
c               angbc from line vb.  Angles angac and angbc are in
c               degrees (iunit = 0) or in radians (iunit = 1).
c               These points may represent the vertices of a polyhedron.
c
c               No solution is possible if any of the points "v", "a" and "b"
c               coincide, if all three are colinear, or if the angles angac and
c               angbc are too close to zero or 180 degrees (zero or pi radians),
c               relative to the angle between lines va and vb.
c
c               Otherwise, two solutions are possible, with point "c" on either
c               side of the plane containing lines va and vb.  The solution
c               returned here (for positive dvc) is that for which the vectors
c               va, vb and vc firm a positive triple, like the thumb, first
c               finger and middle finger of the right hand, respectively.
c               To get the other solution, exchange points "a" and "b" and
c               exchange angles angac and angbc.  A negative value of dvc also
c               puts point "c" on the other side of the plane, but with angles
c               angac and angbc replaced by 180 - angac and 180 - angbc degrees
c               (or pi - angab and pi - angbc radians).
c            
c
c               Flag nerr indicates any input error.
c
c     Input:    angac, angbc, ax, ay, az, bx, by, bz, dvc, iunit, tol,
c               vx, vy, vz.
c
c     Output:   cx, cy, cz, nerr.
c
c     Calls: aptetru, aptvadd, aptvdis 
c
c     Glossary:
c
c     angac     Input    The angle between line va and line vc,
c                          in degrees (iunit = ) or in radians (iunit = 1).
c
c     angbc     Input    The angle between line vb and line vc,
c                          in degrees (iunit = ) or in radians (iunit = 1).
c
c     ax,ay,az  Input    The x, y, z coordinates of point "a".
c
c     bx,by,bz  Input    The x, y, z coordinates of point "b".
c
c     cx,cy,cz  Output   The x, y, z coordinates of point "c".
c                          Vectors va, vb and vc form a positive triple,
c                          i.e,: va cross vb dot vc > 0.
c
c     dvc       Input    Length of line vc.
c
c     nerr      Output   Indicates an input error, if not 0.
c                          1 if points "v" and "a" coincide.
c                          2 if points "v" and "b" coincide.
c                          3 if lines va and vb are colinear.
c                          4 if angles angac and angbc are impossible.
c
c     tol       Input    Numerical tolerance limit.
c                          On computers with 64-bit floating point numbers,
c                          recommend 1.e-5 to 1.e-11.
c
c     vx,vy,vz  Input    The x, y, z coordinates of point "v".  If point "v"
c                          is at the origin, you could call subroutine aptetru
c                          with vectors "a" and "b", multiply the output unit
c                          vector by dvc.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

      implicit none

      integer iunit                   ! Unit for angles, 0 for degrees.
      integer nerr                    ! Error indicator.
      integer nerra                   ! Error indicator.

      real    angac                   ! Angle between line va and line vc.
      real    angbc                   ! Angle between line vb and line vc.
      real    ax                      ! Coordinate x of point "a".
      real    ay                      ! Coordinate y of point "a".
      real    az                      ! Coordinate z of point "a".
      real    bx                      ! Coordinate x of point "b".
      real    by                      ! Coordinate y of point "b".
      real    bz                      ! Coordinate z of point "b".
      real    cx                      ! Coordinate x of point "c".
      real    cy                      ! Coordinate y of point "c".
      real    cz                      ! Coordinate z of point "c".
      real    dlen                    ! Distance of point "c" from origin.
      real    dva                     ! Length of vector va.
      real    dvb                     ! Length of vector vb.
      real    dvc                     ! Length of line vc.
      real    tol                     ! Precision constant.
      real    ucx                     ! Component x of vector uc.
      real    ucy                     ! Component y of vector uc.
      real    ucz                     ! Component z of vector uc.
      real    vax                     ! Component x of vector va.
      real    vay                     ! Component y of vector va.
      real    vaz                     ! Component z of vector va.
      real    vbx                     ! Component x of vector vb.
      real    vby                     ! Component y of vector vb.
      real    vbz                     ! Component z of vector vb.
      real    vx                      ! Coordinate x of point "v".
      real    vy                      ! Coordinate y of point "v".
      real    vz                      ! Coordinate z of point "v".

cbugc***DEBUG begins.
cbug 9901 format (/ 'aptetrv finding a vertex edge.  tol = ',1pe22.14 /
cbug     &  '  vx,vy,vz  =',1p3e22.14 /
cbug     &  '  ax,ay,az  =',1p3e22.14 /
cbug     &  '  bx,by,bz  =',1p3e22.14 /
cbug     &  '  dvc       =',1pe22.14 /
cbug     &  '  iunit     =',i3 /
cbug     &  '  angac,bc  =',1p2e22.14 )
cbug      write (3, 9901) tol, vx, vy, vz, ax, ay, az, bx, by, bz,
cbug     &  dvc, iunit, angac, angbc
cbugc***DEBUG ends.

c.... initialize.

      nerr = 0

      cx   = -1.e99
      cy   = -1.e99
      cz   = -1.e99

c.... Find the vectors parallel to sides va and vb.

      call aptvdis (vx, vy, vz, ax, ay, az, 1, tol,
     &              vax, vay, vaz, dva, nerra)

      call aptvdis (vx, vy, vz, bx, by, bz, 1, tol,
     &              vbx, vby, vbz, dvb, nerra)

c.... Find the unit vector parallel to edge "vc".

      call aptetru (vax, vay, vaz, vbx, vby, vbz, iunit, angac, angbc,
     &              tol, ucx, ucy, ucz, nerr)

      if (nerr .ne. 0) go to 140

c.... Find point "c" = v + dvc * uc

      call aptvadd (vx, vy, vz, 1., dvc, ucx, ucy, ucz, 1, tol,
     &              cx, cy, cz, dlen, nerra)

c.... Truncate small coordinates to zero.

      if (abs (cx) .le. tol * dlen) cx = 0.0
      if (abs (cy) .le. tol * dlen) cy = 0.0
      if (abs (cz) .le. tol * dlen) cz = 0.0

  140 continue
cbugc***DEBUG begins.
cbug 9902 format (/ 'aptetrv results.  nerr = ',i3 /
cbug     &  '  cx,cy,cz  =',1p3e22.14 )
cbug      write ( 3, 9902) nerr, cx, cy, cz
cbugc***DEBUG ends.

  210 return

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

UCRL-WEB-209832