32 SUBROUTINE i7therm(JLT ,IPARG ,PM ,IXS ,IFORM ,X ,
33 1 XI ,YI ,ZI , X1 ,Y1 ,Z1 ,
34 1 X2 ,Y2 ,Z2 ,X3 ,Y3 ,Z3 ,
35 2 X4 ,Y4 ,Z4 ,IX1 ,IX2 ,IX3 ,
36 3 IX4 ,RSTIF ,TEMPI ,IELES ,
37 4 PHI ,TINT ,AREAS ,IELECI ,FRAD ,DRAD ,
38 5 GAPV ,FNI ,IFUNCTK,XTHE ,NPC ,TF ,
39 6 CONDINT,PHI1,PHI2 ,PHI3 ,PHI4 ,FHEATS,
40 7 FHEATM,EFRICT,TEMP ,H1 ,H2 ,H3 ,
45#include "implicit_f.inc"
58 INTEGER JLT, IXS(NIXS,*),IPARG(NPARG,*),IELES(*),
59 . IX1(MVSIZ),IX2(MVSIZ),IX3(MVSIZ),IX4(),
60 . IELECI(MVSIZ),NPC(*),
62 my_real,
intent(in) :: theaccfact
64 . PM(NPROPM,*),TEMP(*),TEMPI(MVSIZ),XI(MVSIZ),YI(MVSIZ),
65 . ZI(MVSIZ),X1(MVSIZ),Y1(MVSIZ),Z1(MVSIZ),X2(MVSIZ),Y2(MVSIZ)
67 . z4(mvsiz),rstif,phi(mvsiz),areas(mvsiz),gapv(mvsiz),
68 . penrad(mvsiz),fni(mvsiz),tf(*),condint(mvsiz),efrict(mvsiz),
69 . phi1(mvsiz),phi2(mvsiz),phi3(mvsiz),phi4(mvsiz),h1(mvsiz),
70 . h2(mvsiz),h3(mvsiz),h4(mvsiz),
71 . x(3,*),tint,frad,drad,dydx,xthe,fheatm,fheats
75 INTEGER I, II,L,NB3M, I3N,LS,J,IE,MAT
78 . SX1 , SY1 , SZ1 , SX2 , SY2 , SZ2,
79 . AREAM ,TS, VOLM, TSTIF, TM,TSTIFM,
80 . TSTIFT,AX,AY,AZ,DIST, NORM,COND,P,RSTIFF,
81 . AX1,AY1,AZ1,AX2,AY2,AZ2,AREA,AREAC,PHIM
100 sx1=(y1(i)-y3(i))*(z2(i)-z4(i)) - (z1(i)-z3(i))*(y2(i)-y4(i))
101 sy1=(z1(i)-z3(i))*(x2(i)-x4(i)) - (x1(i)-x3(i))*(z2(i)-z4(i))
102 sz1=(x1(i)-x3(i))*(y2(i)-y4
104 norm = sqrt(sx1**2 + sy1**2 + sz1**2)
108 IF(ix3(i)/=ix4(i))
THEN
109 sx2 = fourth*(x1(i) + x2(i) + x3(i) + x4(i)) - xi(i)
110 sy2 = fourth*(y1(i) + y2(i) + y3(i) + y4(i)) - yi(i)
111 sz2 = fourth*(z1(i) + z2(i) + z3(i) + z4(i)) - zi(i)
113 sx2 = third*(x1(i) + x2(i) + x3(i)) - xi(i)
114 sy2 = third*(y1(i) + y2(i) + y3(i)) - yi(i)
115 sz2 = third*(z1(i) + z2(i) + z3(i)) - zi(i)
122 dist = (sx2*sx1+sy2*sy1+sz2*sz1) /
max(em15,norm)
130 IF(areas(i) == zero )
THEN
137 IF(penrad(i) <= drad.AND.penrad(i)>= gapv(i))
THEN
141 phi(i) = frad * areac * (tint*tint+ts*ts)
142 . * (tint + ts) * (tint - ts) * dt1 * theaccfact
149 cond=pm(75,mat)+pm(76,mat)*ts
150 tstifm =
max(dist,zero) / cond
156 tstift = tstifm + rstif
157 condint(i) = areac * theaccfact / tstift
158 phi(i) = areac * (tint - ts) * dt1 * theaccfact / tstift
168 IF(fheats/=zero) phi(i) = phi(i) + fheats * efrict(i)
174 tm = h1(i)*temp(ix1(i)) + h2(i)*temp(ix2(i))
175 . + h3(i)*temp(ix3(i)) + h4(i)*temp(ix4(i))
178 IF(penrad(i) <= drad.AND.penrad(i)>= gapv(i))
THEN
182 phi(i) = frad * areac * (tm*tm+ts*ts)
183 . * (tm + ts) * (tm - ts) * dt1 * theaccfact
188 phi(i) = areac * (tm - ts) * dt1 * theaccfact / rstif
189 condint(i) = areac * theaccfact / rstif
191 phi1(i) = -phi(i) *h1(i)
192 phi2(i) = -phi(i) *h2(i)
193 phi3(i) = -phi(i) *h3(i)
194 phi4(i) = -phi(i) *h4(i)
198 phi(i) = phi(i) + fheats * efrict(i)
200 phim = fheatm * efrict(i)
201 phi1(i) = phi1(i) + phim*h1(i)
202 phi2(i) = phi2(i) + phim*h2(i)
203 phi3(i) = phi3(i) + phim*h3(i)
204 phi4(i) = phi4(i) + phim*h4(i)
219 sx1=(y1(i)-y3(i))*(z2(i)-z4(i)) - (z1(i)-z3(i))*(y2(i)-y4(i))
220 sy1=(z1(i)-z3(i))*(x2(i)-x4(i)) - (x1(i)-x3(i))*(z2(i)-z4(i))
221 sz1=(x1(i)-x3(i))*(y2(i)-y4(i)) - (y1(i)-y3(i))*(x2(i)-x4(i))
223 norm = sqrt(sx1**2 + sy1**2 + sz1**2)
227 IF(ix3(i)/=ix4(i))
THEN
229 sy2 = fourth*(y1(i) + y2(i) + y3(i) + y4(i)) - yi(i)
230 sz2 = fourth*(z1(i) + z2(i) + z3(i) + z4(i)) - zi(i)
232 sx2 = third*(x1(i) + x2(i) + x3(i)) - xi(i)
233 sy2 = third*(y1(i) + y2(i) + y3(i)) - yi(i)
234 sz2 = third*(z1(i) + z2(i) + z3(i)) - zi(i)
241 dist = (sx2*sx1+sy2*sy1+sz2*sz1) /
max(em15,norm)
249 IF(areas(i) == zero )
THEN
256 IF(penrad(i) <= drad.AND.penrad(i)>= gapv(i))
THEN
260 phi(i) = frad * areac * (tint*tint+ts*ts)
261 . * (tint + ts) * (tint - ts) * dt1 * theaccfact
271 p = xthe * abs(fni(i)) / areac
272 rstiff = rstif /
max(em30,finter(ifunctk,p,npc,tf,dydx))
274 cond=pm(75,mat)+pm(76,mat)*ts
275 tstifm =
max(dist,zero) / cond
281 tstift = tstifm + rstiff
282 condint(i) = areac * theaccfact / tstift
284 phi(i) = areac * (tint - ts) * dt1 * theaccfact / tstift
295 tm = h1(i)*temp(ix1(i)) + h2(i)*temp(ix2(i))
296 . + h3(i)*temp(ix3(i)) + h4(i)*temp(ix4(i))
299 IF(penrad(i) <= drad.AND.penrad(i)>= gapv(i))
THEN
303 phi(i) = frad * areac * (tm*tm+ts*ts)
304 . * (tm + ts) * (tm- ts) * dt1 * theaccfact
309 p = xthe * abs(fni(i)) / areac
310 rstiff = rstif /
max(em30,finter(ifunctk,p
312 phi(i) = areac * (tm - ts) * dt1 * theaccfact / rstiff
313 condint(i) = areac * theaccfact / rstiff
318 phi(i) = phi(i) + fheats * efrict(i)
320 phim = fheatm * efrict(i)
321 phi1(i) = phi1(i) + phim*h1(i)
322 phi2(i) = phi2(i) + phim*h2(i)
323 phi3(i) = phi3(i) + phim*h3(i)
324 phi4(i) = phi4(i) + phim*h4(i)
subroutine i7therm(jlt, iparg, pm, ixs, iform, x, xi, yi, zi, x1, y1, z1, x2, y2, z2, x3, y3, z3, x4, y4, z4, ix1, ix2, ix3, ix4, rstif, tempi, ieles, phi, tint, areas, ieleci, frad, drad, gapv, fni, ifunctk, xthe, npc, tf, condint, phi1, phi2, phi3, phi4, fheats, fheatm, efrict, temp, h1, h2, h3, h4, theaccfact)