54 interfacenumelems, interfacenumnodes, &
56 mapnode,lwrbnd,uppbnd, coor, disp, mapsfelvolel,&
57 elconnvol,ieltype,numelvol,tractpress)
68 INTEGER :: lwrbnd,uppbnd
70 INTEGER :: ieltype,numelvol
71 INTEGER,
DIMENSION(1:iElType,1:NumElVol) :: elconnvol
73 INTEGER :: interfacenumelems,interfacenumnodes
74 INTEGER,
DIMENSION(1:UppBnd,1:InterfaceNumElems) :: interfaceelemconn
75 INTEGER,
DIMENSION(1:InterfaceNumNodes) :: mapnodesf
79 REAL*8,
DIMENSION(1:3*NumNp) :: disp
81 INTEGER,
DIMENSION(1:InterfaceNumNodes) :: mapnode
83 REAL*8,
DIMENSION(1:3*numnp) :: r_ex
88 INTEGER,
DIMENSION(1:3) :: triconn
89 REAL*8,
DIMENSION(1:3) :: uniftract,normvect
91 INTEGER,
DIMENSION(1:NumElVol) :: mapsfelvolel
94 REAL*8,
DIMENSION(1:3,1:numnp) :: coor
103 REAL*8 :: x1x0, y1y0, z1z0
104 REAL*8 :: x2x0, y2y0, z2z0
106 REAL*8 :: xnorm, area
108 DO i = 1, interfacenumelems
112 triconn(1:3) = interfaceelemconn(1:3,
i)
118 x0p = coor(1,mapnode(triconn(1))) + disp(3*mapnode(triconn(1))-2)
119 y0p = coor(2,mapnode(triconn(1))) + disp(3*mapnode(triconn(1))-1)
120 z0p = coor(3,mapnode(triconn(1))) + disp(3*mapnode(triconn(1)))
122 x1p = coor(1,mapnode(triconn(2))) + disp(3*mapnode(triconn(2))-2)
123 y1p = coor(2,mapnode(triconn(2))) + disp(3*mapnode(triconn(2))-1)
124 z1p = coor(3,mapnode(triconn(2))) + disp(3*mapnode(triconn(2)))
126 x2p = coor(1,mapnode(triconn(3))) + disp(3*mapnode(triconn(3))-2)
127 y2p = coor(2,mapnode(triconn(3))) + disp(3*mapnode(triconn(3))-1)
128 z2p = coor(3,mapnode(triconn(3))) + disp(3*mapnode(triconn(3)))
142 x3p = y1y0 * z2z0 - z1z0 * y2y0
143 y3p = z1z0 * x2x0 - x1x0 * z2z0
144 z3p = x1x0 * y2y0 - y1y0 * x2x0
148 xnorm =
sqrt( x3p*x3p + y3p*y3p + z3p*z3p )
161 normvect(1) = x3p/xnorm
162 normvect(2) = y3p/xnorm
163 normvect(3) = z3p/xnorm
167 uniftract(1:3) = - normvect(1:3)*tractpress*area/3.d0
171 triconn(1:3) = interfaceelemconn(lwrbnd:uppbnd,
i)
174 nz = mapnode(triconn(
j))*3
177 r_ex(nx) = r_ex(nx) + uniftract(1)
178 r_ex(ny) = r_ex(ny) + uniftract(2)
179 r_ex(nz) = r_ex(nz) + uniftract(3)
subroutine tractpressloaddef(R_ex, numnp, InterfaceNumElems, InterfaceNumNodes, InterfaceElemConn, MapNode, LwrBnd, UppBnd, coor, Disp, MapSFElVolEl, ElConnVol, iElType, NumElVol, TractPress)