54 interfacesfelemtract, &
55 interfacesfnumelems, interfacesfnumnodes, &
56 interfacesfelemconn, &
57 mapnodesf,lwrbnd,uppbnd,coor,disp)
64 INTEGER :: lwrbnd,uppbnd
67 INTEGER :: interfacesfnumelems,interfacesfnumnodes
68 INTEGER,
DIMENSION(1:UppBnd,1:InterfaceSFNumElems) :: interfacesfelemconn
69 INTEGER,
DIMENSION(1:InterfaceSFNumNodes) :: mapnodesf
70 REAL*8,
DIMENSION(1:3, 1:InterfaceSFNumElems) :: interfacesfelemtract
71 REAL*8,
DIMENSION(1:3*NumNp) :: disp
74 REAL*8,
DIMENSION(1:3*numnp) :: r_ex
79 INTEGER,
DIMENSION(1:3) :: triconn
80 REAL*8,
DIMENSION(1:3) :: uniftract
83 REAL*8,
DIMENSION(1:3,1:numnp) :: coor
92 REAL*8 :: x1x0, y1y0, z1z0
93 REAL*8 :: x2x0, y2y0, z2z0
96 REAL*8 :: xnorm, area,
at
100 DO i = 1, interfacesfnumelems
104 triconn(1:3) = interfacesfelemconn(1:3,
i)
110 x0p = coor(1,mapnodesf(triconn(1))) + disp(3*mapnodesf(triconn(1))-2)
111 y0p = coor(2,mapnodesf(triconn(1))) + disp(3*mapnodesf(triconn(1))-1)
112 z0p = coor(3,mapnodesf(triconn(1))) + disp(3*mapnodesf(triconn(1)))
114 x1p = coor(1,mapnodesf(triconn(2))) + disp(3*mapnodesf(triconn(2))-2)
115 y1p = coor(2,mapnodesf(triconn(2))) + disp(3*mapnodesf(triconn(2))-1)
116 z1p = coor(3,mapnodesf(triconn(2))) + disp(3*mapnodesf(triconn(2)))
118 x2p = coor(1,mapnodesf(triconn(3))) + disp(3*mapnodesf(triconn(3))-2)
119 y2p = coor(2,mapnodesf(triconn(3))) + disp(3*mapnodesf(triconn(3))-1)
120 z2p = coor(3,mapnodesf(triconn(3))) + disp(3*mapnodesf(triconn(3)))
136 x3p = y1y0 * z2z0 - z1z0 * y2y0
137 y3p = z1z0 * x2x0 - x1x0 * z2z0
138 z3p = x1x0 * y2y0 - y1y0 * x2x0
142 xnorm =
sqrt( x3p*x3p + y3p*y3p + z3p*z3p )
148 uniftract(1:3) = interfacesfelemtract(1:3,
i)*area/3.d0
152 triconn(1:3) = interfacesfelemconn(lwrbnd:uppbnd,
i)
155 nz = mapnodesf(triconn(
j))*3
158 r_ex(nx) = r_ex(nx) + uniftract(1)
159 r_ex(ny) = r_ex(ny) + uniftract(2)
160 r_ex(nz) = r_ex(nz) + uniftract(3)
subroutine tractloaddef(R_ex, numnp, InterfaceSFElemTract, InterfaceSFNumElems, InterfaceSFNumNodes, InterfaceSFElemConn, MapNodeSF, LwrBnd, UppBnd, coor, Disp)