30 SUBROUTINE i25therm(JLT ,KTHE ,TEMPI ,AREAS ,IELESI ,
31 2 IELEMI ,GAPV ,IFUNCTK,XTHE ,FNI ,
32 3 NPC ,TF ,FRAD ,DRAD ,EFRICT ,
33 4 FHEATS ,FHEATM,CONDINT,IFORM ,TEMP ,
34 5 H1 ,H2 ,H3 ,H4 ,FCOND ,
35 6 DCOND ,TINT ,XI ,YI ,ZI ,
36 7 X1 ,Y1 ,Z1 ,X2 ,Y2 ,
37 8 Z2 ,X3 ,Y3 ,Z3 ,X4 ,
38 9 Y4 ,Z4 ,IX1 ,IX2 ,IX3 ,
39 A IX4 ,PHI ,PHI1 ,PHI2 ,PHI3 ,
40 B PHI4 ,PM ,NSV ,ITAB ,THEACCFACT)
44#include "implicit_f.inc"
57 INTEGER JLT, IFUNCTK, FCOND,ITAB(*) ,NSV(*),
58 . NPC(*),IFORM,IELESI(MVSIZ) ,IELEMI(MVSIZ),
59 . IX1(MVSIZ), IX2(MVSIZ), IX3(MVSIZ), IX4(MVSIZ)
60 my_real,
intent(in) :: theaccfact
64 . KTHE, XTHE, FRAD, DRAD, FHEATS, FHEATM,
65 . TEMPI(MVSIZ), XI(MVSIZ), YI(),TEMP(*),
66 . ZI(MVSIZ), PHI(MVSIZ), AREAS(MVSIZ), ASI(MVSIZ),
67 . bsi(mvsiz), gapv(mvsiz), condint(mvsiz),
68 . fni(mvsiz), tf(*), efrict(mvsiz),
69 . h1(mvsiz), h2(mvsiz), h3(mvsiz), h4(mvsiz),
70 . phi1(mvsiz),phi2(mvsiz),phi3(mvsiz),phi4(mvsiz),
71 . x1(mvsiz), x2(mvsiz), x3(mvsiz), x4(mvsiz),
72 . y1(mvsiz), y2(mvsiz), y3(mvsiz), y4(mvsiz),
73 . z1(mvsiz), z2(mvsiz), z3(mvsiz), z4(mvsiz)
80 INTEGER I, MATS , MATM
83 . SX1 , SY1 , SZ1 , SX2 , SY2 , SZ2,
84 . ts, rstif, tstifm, tstift, cond, p, dydx,
85 . tm, ddcond, dd, hcond, dist, penrad,
norm, areac,
86 . phim,
area,conds,condm
90 rstif = one/
max(em30,kthe)
96 tm = h1(i)*temp(ix1(i)) + h2(i)*temp(ix2(i))
97 . + h3(i)*temp(ix3(i)) + h4(i)*temp(ix4(i))
100 ddcond =
max(dcond-gapv(i),em20)
105 sx1=(y1(i)-y3(i))*(z2(i)-z4(i)) - (z1(i)-z3(i))*(y2(i)-y4(i))
106 sy1=(z1(i)-z3(i))*(x2(i)-x4(i)) - (x1(i)-x3(i))*(z2(i)-z4(i))
107 sz1=(x1(i)-x3(i))*(y2(i)-y4(i)) - (y1(i)-y3(i))*(x2(i)-x4(i))
109 norm = sqrt(sx1**2 + sy1**2 + sz1**2)
113 IF(ix3(i)/=ix4(i))
THEN
114 sx2 = fourth*(x1(i) + x2(i) + x3(i) + x4(i)) - xi(i)
115 sy2 = fourth*(y1(i) + y2(i) + y3(i) + y4(i)) - yi(i)
116 sz2 = fourth*(z1(i) + z2(i) + z3(i) + z4(i)) - zi(i)
118 sx2 = third*(x1(i) + x2(i) + x3(i)) - xi(i)
119 sy2 = third*(y1(i) + y2(i) + y3(i)) - yi(i)
120 sz2 = third*(z1(i) + z2(i) + z3(i)) - zi(i)
127 dist = -(sx2*sx1+sy2*sy1+sz2*sz1) /
max(em15,
norm)
129 penrad = dist - gapv(i)
131 IF(areas(i) == zero )
THEN
150 IF(penrad <= zero)
THEN
164 condm=pm(75,matm)+pm(76,matm)*tm
168 IF(condm == zero)
THEN
170 ELSEIF(conds == zero)
THEN
173 cond = two*conds*condm/(condm + conds)
178 IF(cond /= zero) tstifm = abs(dist) / cond
179 tstift = tstifm + rstif
180 condint(i) = areac * theaccfact /tstift
182 phi(i) = areac*(tm - ts)*dt1*theaccfact / tstift
186 ELSEIF(penrad <= ddcond)
THEN
192 conds=pm(75,mats)+pm(76,mats)*ts
200 condm=pm(75,matm)+pm(76,matm)*tm
204 IF(condm == zero)
THEN
206 ELSEIF(conds == zero)
THEN
209 cond = two*conds*condm/(condm + conds)
215 IF(cond /= zero) tstifm =
max(dist,zero) / cond
216 tstift = tstifm + rstif
218 hcond = finter(fcond,dd,npc,tf,dydx) / tstift
219 condint(i) = areac*hcond*theaccfact
221 phi(i) = areac * (tm - ts)*dt1* hcond*theaccfact
223 phi(i) = phi(i) + frad * areac * (tm*tm+ts*ts)
224 . * (tm + ts) * (tm - ts) * dt1
228 ELSEIF(penrad <= drad)
THEN
230 phi(i) = frad * areac * (tm*tm+ts*ts)
231 . * (tm + ts) * (tm - ts) * dt1 * theaccfact
236 phi1(i) = -phi(i) *h1(i)
237 phi2(i) = -phi(i) *h2(i)
238 phi3(i) = -phi(i) *h3(i)
239 phi4(i) = -phi(i) *h4(i)
243 phim = fheatm * efrict(i)
244 phi1(i) = phi1(i) + phim*h1(i)
245 phi2(i) = phi2(i) + phim*h2(i)
246 phi3(i) = phi3(i) + phim*h3(i)
247 phi4(i) = phi4(i) + phim*h4(i)
253 phi(i) = phi(i) + fheats * efrict(i) * theaccfact
262 tm = h1(i)*temp(ix1(i)) + h2
263 . + h3(i)*temp(ix3(i)) + h4(i)*temp(ix4(i))
266 ddcond =
max(dcond-gapv(i),em20)
271 sx1=(y1(i)-y3(i))*(z2(i)-z4(i)) - (z1(i)-z3(i))*(y2(i)-y4(i))
272 sy1=(z1(i)-z3(i))*(x2(i)-x4(i)) - (x1(i)-x3(i))*(z2(i)-z4(i))
273 sz1=(x1(i)-x3(i))*(y2(i)-y4(i)) - (y1(i)-y3(i))*(x2(i)-x4(i))
275 norm = sqrt(sx1**2 + sy1**2 + sz1**2)
279 IF(ix3(i)/=ix4(i))
THEN
280 sx2 = fourth*(x1(i) + x2(i) + x3(i) + x4(i)) - xi(i)
281 sy2 = fourth*(y1(i) + y2(i) + y3(i) + y4(i)) - yi(i)
282 sz2 = fourth*(z1(i) + z2(i) + z3(i) + z4(i)) - zi(i)
284 sx2 = third*(x1(i) + x2(i) + x3(i)) - xi(i)
285 sy2 = third*(y1(i) + y2(i) + y3(i)) - yi(i)
286 sz2 = third*(z1(i) + z2(i) + z3(i)) - zi(i)
293 dist = -(sx2*sx1+sy2*sy1+sz2*sz1) /
max(em15,
norm)
295 penrad = dist - gapv(i)
297 IF(areas(i) == zero )
THEN
311 IF(penrad <= zero)
THEN
315 p = xthe * abs(fni(i)) / areas(i)
316 rstif = one /
max(em30,kthe * finter(ifunctk,p,npc,tf,dydx))
319 conds=pm(75,mats)+pm(76,mats)*ts
327 condm=pm(75,matm)+pm(76,matm)*tm
331 IF(condm == zero)
THEN
333 ELSEIF(conds == zero)
THEN
336 cond = two*conds*condm/(condm + conds)
342 IF(cond /= zero) tstifm = abs(dist) / cond
343 tstift = tstifm + rstif
344 condint(i) = areac*theaccfact /tstift
346 phi(i) = areac * (tm- ts)*dt1 * theaccfact / tstift
351 ELSEIF(penrad <= ddcond)
THEN
356 conds=pm(75,mats)+pm(76,mats)*ts
364 condm=pm(75,matm)+pm(76,matm)*tm
368 IF(condm == zero)
THEN
370 ELSEIF(conds == zero)
THEN
373 cond = two*conds*condm/(condm + conds)
379 rstif = one /
max(em30,kthe * finter(ifunctk,p,npc,tf,dydx))
381 IF(cond /= zero)tstifm =
max(dist,zero) / cond
382 tstift = tstifm + rstif
385 hcond = finter(fcond,dd,npc,tf,dydx) / tstift
386 condint(i) = areac*hcond*theaccfact
388 phi(i) = areac * (tm - ts)*dt1 * hcond * theaccfact
390 phi(i) = phi(i) + frad * areac * (tm*tm+ts*ts)
391 . * (tm + ts) * (tm - ts) * dt1 * theaccfact
396 ELSEIF(penrad <= drad)
THEN
398 phi(i) = frad * areac * (tm*tm+ts*ts)
399 . * (tm + ts) * (tm - ts) * dt1 * theaccfact
404 phi1(i) = -phi(i) *h1(i)
405 phi2(i) = -phi(i) *h2(i)
406 phi3(i) = -phi(i) *h3(i)
407 phi4(i) = -phi(i) *h4(i)
411 phim = fheatm * efrict(i)
412 phi1(i) = phi1(i) + phim*h1(i)
413 phi2(i) = phi2(i) + phim*h2(i)
414 phi3(i) = phi3(i) + phim*h3(i)
415 phi4(i) = phi4(i) + phim*h4(i)
420 phi(i) = phi(i) + fheats * efrict(i) * theaccfact
subroutine i25therm(jlt, kthe, tempi, areas, ielesi, ielemi, gapv, ifunctk, xthe, fni, npc, tf, frad, drad, efrict, fheats, fheatm, condint, iform, temp, h1, h2, h3, h4, fcond, dcond, tint, xi, yi, zi, x1, y1, z1, x2, y2, z2, x3, y3, z3, x4, y4, z4, ix1, ix2, ix3, ix4, phi, phi1, phi2, phi3, phi4, pm, nsv, itab, theaccfact)