subroutine apttrid (ax, ay, az, bx, by, bz, cx, cy, cz, np, tol,
& dab, dbc, dca, areat, gx, gy, gz, nerr)
ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c SUBROUTINE APTTRID
c
c call apttrid (ax, ay, az, bx, by, bz, cx, cy, cz, np, tol,
c & dab, dbc, dca, areat, gx, gy, gz, nerr)
c
c Version: apttrid Updated 1990 December 3 16:20.
c apttrid Originated 1990 May 8 13:00.
c
c Author: Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c Purpose: To find the edge lengths dab, dbc and dca, the areas areat, and
c the centers of gravity g = (gx, gy, gz) of np triangles with
c vertices a = (ax, ay, az), b = (bx, by, bz), and
c c = (cx, cy, cz) in 3-D space.
c Flag nerr indicates any input error.
c
c Input: ax, ay, az, bx, by, bz, cx, cy, cz, np, tol.
c
c Output: dab, dbc, dca, areat, gx, gy, gz, nerr.
c
c Calls: aptvdis, aptvaxb
c
c
c Glossary:
c
c areat Output Area of the triangle. Size np.
c
c ax,ay,az Input The x, y, z coordinates of vertex "a" of triangle.
c Size np.
c
c bx,by,bz Input The x, y, z coordinates of vertex "b" of triangle.
c Size np.
c
c cx,cy,cz Input The x, y, z coordinates of vertex "c" of triangle.
c Size np.
c
c dab Output The length of edge "ab" of the triangle. Size np.
c
c dbc Output The length of edge "bc" of the triangle. Size np.
c
c dca Output The length of edge "ca" of the triangle. Size np.
c
c gx,gy,gz Output Center of gravity or centroid of triangle. Size np.
c Coordinates may be truncated to zero, if less than
c the estimated error in their calculation, based on
c 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 external 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---- Area of triangle "abc".
dimension areat (1)
c---- Coordinate x of vertex "a".
dimension ax (1)
c---- Coordinate y of vertex "a".
dimension ay (1)
c---- Coordinate z of vertex "a".
dimension az (1)
c---- Coordinate x of vertex "b".
dimension bx (1)
c---- Coordinate y of vertex "b".
dimension by (1)
c---- Coordinate z of vertex "b".
dimension bz (1)
c---- Coordinate x of vertex "c".
dimension cx (1)
c---- Coordinate y of vertex "c".
dimension cy (1)
c---- Coordinate z of vertex "c".
dimension cz (1)
c---- Length of edge "ab".
dimension dab (1)
c---- Length of edge "bc".
dimension dbc (1)
c---- Length of edge "ca".
dimension dca (1)
c---- Cooodinate x of centroid of triangle.
dimension gx (1)
c---- Coordinate y of centroid of triangle.
dimension gy (1)
c---- Coordinate z of centroid of triangle.
dimension gz (1)
c.... Local variables.
c---- Component x of edge vector "ab".
common /lapttrid/ abx (64)
c---- Component y of edge vector "ab".
common /lapttrid/ aby (64)
c---- Component z of edge vector "ab".
common /lapttrid/ abz (64)
c---- Component x of edge vector "bc".
common /lapttrid/ bcx (64)
c---- Component y of edge vector "bc".
common /lapttrid/ bcy (64)
c---- Component z of edge vector "bc".
common /lapttrid/ bcz (64)
c---- Component x of edge vector "ca".
common /lapttrid/ cax (64)
c---- Component y of edge vector "ca".
common /lapttrid/ cay (64)
c---- Component z of edge vector "ca".
common /lapttrid/ caz (64)
c---- Component x of ab X bc.
common /lapttrid/ dx (64)
c---- Component y of ab X bc.
common /lapttrid/ dy (64)
c---- Component z of ab X bc.
common /lapttrid/ dz (64)
c---- Estimated error in gx.
common /lapttrid/ gxerr
c---- Estimated error in gy.
common /lapttrid/ gyerr
c---- Estimated error in gz.
common /lapttrid/ gzerr
c---- Index in local array.
common /lapttrid/ n
c---- First index of subset of data.
common /lapttrid/ n1
c---- Last index of subset of data.
common /lapttrid/ n2
c---- Index in external array.
common /lapttrid/ nn
c---- Size of current subset of data.
common /lapttrid/ ns
cbugc***DEBUG begins.
cbug 9901 format (/ 'apttrid finding triangle data:' /
cbug & (i3,' ax,ay,az=',1p3e22.14 /
cbug & ' bx,by,bz=',1p3e22.14 /
cbug & ' cx,cy,cz=',1p3e22.14))
cbug write (3, 9901) (n, ax(n), ay(n), az(n), bx(n), by(n), bz(n),
cbug & cx(n), cy(n), cz(n), 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)
110 ns = n2 - n1 + 1
c.... Find the edge vectors of the triangle, "ab", "bc" and "ca",
c.... and the edge lengths, dab, dbc and dca.
call aptvdis (ax(n1), ay(n1), az(n1), bx(n1), by(n1), bz(n1),
& ns, tol, abx, aby, abz, dab, nerr)
call aptvdis (bx(n1), by(n1), bz(n1), cx(n1), cy(n1), cz(n1),
& ns, tol, bcx, bcy, bcz, dbc, nerr)
call aptvdis (cx(n1), cy(n1), cz(n1), ax(n1), ay(n1), az(n1),
& ns, tol, cax, cay, caz, dca, nerr)
c.... Find twice the area of the triangle.
call aptvaxb (abx, aby, abz, bcx, bcy, bcz, ns, tol,
& dx, dy, dz, areat(n1), nerr)
c.... Find the area and the coordinates of the center of gravity.
c---- Loop over subset of data.
do 120 n = 1, ns
nn = n + n1 - 1
areat(nn) = 0.5 * abs (areat(nn))
gx(nn) = (ax(nn) + bx(nn) + cx(nn)) / 3.0
gy(nn) = (ay(nn) + by(nn) + cy(nn)) / 3.0
gz(nn) = (az(nn) + bz(nn) + cz(nn)) / 3.0
c---- End of loop over subset of data.
120 continue
c.... See if truncation allowed.
c---- Truncation to zero allowed.
if (tol .gt. 0.0) then
c---- Loop over subset of data.
do 130 n = 1, ns
nn = n + n1 - 1
gxerr = tol * (abs (ax(nn)) + abs (bx(nn)) +
& abs (cx(nn))) / 3.0
gyerr = tol * (abs (ay(nn)) + abs (by(nn)) +
& abs (cy(nn))) / 3.0
gzerr = tol * (abs (az(nn)) + abs (bz(nn)) +
& abs (cz(nn))) / 3.0
if (abs (gx(nn)) .lt. gxerr) then
gx(nn) = 0.0
endif
if (abs (gy(nn)) .lt. gyerr) then
gy(nn) = 0.0
endif
if (abs (gz(nn)) .lt. gzerr) then
gz(nn) = 0.0
endif
c---- End of loop over subset of data.
130 continue
c---- Tested tol.
endif
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 (/ 'apttrid results:' /
cbug & (i3,' areat= ',1pe22.14 /
cbug & ' d(ab,bc,ca)=',1p3e22.14 /
cbug & ' gx,gy,gz=',1p3e22.14))
cbug
cbug write ( 3, 9902) (n, areat(n), dab(n), dbc(n), dca(n),
cbug & gx(n), gy(n), gz(n), n = 1, np)
cbugc***DEBUG ends.
210 return
c.... End of subroutine apttrid. (+1 line.)
end
UCRL-WEB-209832