subroutine aptvaxb (ax, ay, az, bx, by, bz, np, tol,
& cx, cy, cz, vlen, nerr)
ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c SUBROUTINE APTVAXB
c
c call aptvaxb (ax, ay, az, bx, by, bz, np, tol,
c & cx, cy, cz, vlen, nerr)
c
c Version: aptvaxb Updated 1990 November 26 10:00.
c aptvaxb Originated 1989 November 2 14:10.
c
c Author: Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c Purpose: To find the vector products c = (cx, cy, cz) of the np vector
c pairs a = (ax, ay, az) and b = (bx, by, bz), and the magnitudes
c vlen of the vectors "c". Any components of vector "c" less than
c the estimated error in their calculation, based on tol, will be
c truncated to zero.
c Flag nerr indicates any input error.
c
c With no truncation,
c cx = ay * bz - az * by
c cy = az * bx - ax * bz
c cz = ax * by - ay * bx.
c
c Input: ax, ay, az, bx, by, bz, np, tol.
c
c Output: cx, cy, cz, vlen, nerr.
c
c Glossary:
c
c ax,ay,az Input The x, y, z components of input vector "a". Size np.
c
c bx,by,bz Input The x, y, z components of input vector "b". Size np.
c
c cx,cy,cz Output The x, y, z components of output vector "c". Size np.
c Vector (cross) product of vectors "a" and "b".
c Truncated to zero if less than the estimated error in
c their calculation. See tol.
c
c nerr Output Indicates an input error, if not 0.
c 1 if np is not positive.
c
c np Input Size of arrays ax, ay, az, bx, by, bz, cx, cy, cz.
c
c tol Input Numerical tolerance limit.
c On Cray computers, recommend 1.e-5 to 1.e-11.
c
c vlen Output Magnitude of the vector product "c". Size np.
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.
c.... Dimensioned arguments.
c---- Component x of input vector "a".
dimension ax (1)
c---- Component y of input vector "a".
dimension ay (1)
c---- Component z of input vector "a".
dimension az (1)
c---- Component x of input vector "b".
dimension bx (1)
c---- Component y of input vector "b".
dimension by (1)
c---- Component z of input vector "b".
dimension bz (1)
c---- Component x of output vector "c".
dimension cx (1)
c---- Component y of output vector "c".
dimension cy (1)
c---- Component z of output vector "c".
dimension cz (1)
c---- Magnitude of vector "c".
dimension vlen (1)
c.... Local variables.
c---- Index, 1 to np.
common /laptvaxb/ n
c---- Estimated error in cx.
common /laptvaxb/ cxerr
c---- Estimated error in cy.
common /laptvaxb/ cyerr
c---- Estimated error in cz.
common /laptvaxb/ czerr
cbugc***DEBUG begins.
cbug 9901 format (/ 'aptvaxb finding vector product of vectors:' /
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.... Find the vector products.
c---- Loop over vectors.
do 110 n = 1, np
cx(n) = ay(n) * bz(n) - az(n) * by(n)
cy(n) = az(n) * bx(n) - ax(n) * bz(n)
cz(n) = ax(n) * by(n) - ay(n) * bx(n)
c---- End of loop over vectors.
110 continue
c---- Truncate small components to zero.
if (tol .gt. 0.0) then
c---- Loop over vectors.
do 120 n = 1, np
cxerr = 2.0 * tol * (abs (ay(n) * bz(n)) +
& abs (az(n) * by(n)))
if (abs (cx(n)) .lt. cxerr) then
cx(n) = 0.0
endif
cyerr = 2.0 * tol * (abs (az(n) * bx(n)) +
& abs (ax(n) * bz(n)))
if (abs (cy(n)) .lt. cyerr) then
cy(n) = 0.0
endif
czerr = 2.0 * tol * (abs (ax(n) * by(n)) +
& abs (ay(n) * bx(n)))
if (abs (cz(n)) .lt. czerr) then
cz(n) = 0.0
endif
c---- End of loop over vectors.
120 continue
c---- Tested tol.
endif
c---- Loop over vectors.
do 130 n = 1, np
vlen(n) = sqrt (cx(n)**2 + cy(n)**2 + cz(n)**2)
c---- End of loop over vectors.
130 continue
cbugc***DEBUG begins.
cbug 9902 format (/ 'aptvaxb results:' /
cbug & (i3,' vlen= ',1pe22.14 /
cbug & ' cx,cy,cz=',1p3e22.14))
cbug write ( 3, 9902) (n, vlen(n), cx(n), cy(n), cz(n),
cbug & n = 1, np)
cbugc***DEBUG ends.
210 return
c.... End of subroutine aptvaxb. (+1 line.)
end
UCRL-WEB-209832