38
39
40
41 USE python_funct_mod
42 USE sensor_mod
43 use glob_therm_mod
44
45
46
47#include "implicit_f.inc"
48#include "comlock.inc"
49#include "param_c.inc"
50
51
52
53#include "com04_c.inc"
54#include "com08_c.inc"
55#include "parit_c.inc"
56
57
58
59 type (glob_therm_) ,intent(inout) :: glob_therm
60 INTEGER ,INTENT(IN) :: NSENSOR
61 INTEGER NPC(*),IAD(4,*)
62 INTEGER IBCV(GLOB_THERM%NICONV,*)
63
65 . fconv(glob_therm%LFACTHER,*), tf(*), x(3,*),
66 . fthesky(lsky), temp(*), fthe(*)
67 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) ,INTENT(IN) :: SENSOR_TAB
68 TYPE(PYTHON_) :: PYTHON
69
70
71
72 INTEGER NL,N1,N2,N3,N4,ISENS,IFUNC_OLD,IFUNC,IAD1,IAD2,IAD3,IAD4,IFLAG
73 my_real :: nx, ny,nz, dydx,ts,flux,ts_old,fcx
74 . startt, stopt, fcy_old, offg
75 my_real :: heat_conv_l ! thread-local
77 EXTERNAL finter
78 INTEGER :: OMP_GET_THREAD_NUM,ITSK
79 EXTERNAL omp_get_thread_num
80 INTEGER
81 INTEGER :: ISMOOTH
82
83
84 ifunc_old = 0
85 ts_old = zero
86 fcy_old= zero
87 heat_conv_l = zero
88 s1 = numnod
89 t_inf = zero
90
91 IF(iparit==0) THEN
92 itsk = omp_get_thread_num()
93
94
95
96
97
98 DO nl=1,glob_therm%NUMCONV
100 IF(offg <= zero) cycle
101
104
106 IF(isens == 0)THEN
107 ts = tt*glob_therm%THEACCFACT - startt
108 ELSE
109 startt = startt + sensor_tab(isens)%TSTART
110 stopt = stopt + sensor_tab(isens)%TSTART
111 ts = tt*glob_therm%THEACCFACT -(startt + sensor_tab(isens)%TSTART)
112 ENDIF
113
114 IF(tt*glob_therm%THEACCFACT < startt) cycle
115 IF(tt*glob_therm%THEACCFACT > stopt ) cycle
124
125
126
127 IF(ifunc_old /= ifunc .OR. ts_old /= ts .OR. fcy_old /= fcy ) THEN
128 ismooth = 0
129 IF (ifunc > 0) ismooth = npc(2*nfunct+ifunc+1)
130 IF(ismooth < 0) THEN
131 CALL python_call_funct1d(python, -ismooth,ts*fcx, t_inf)
132 t_inf = fcy*t_inf
133 ELSE
134 t_inf = fcy*finter(ifunc, ts*fcx,npc,tf,dydx)
135 ENDIF
136 ifunc_old = ifunc
137 ts_old = ts
138 fcy_old= fcy
139 ENDIF
140
141 IF(n4 > 0)THEN
142
143 nx= (x(2,n3)-x(2,n1))*(x(3,n4)-x(3,n2))
144 + -(x(3,n3)-x(3,n1))*(x(2,n4)-x(2,n2))
145 ny= (x(3,n3)-x(3,n1))*(x(1,n4)-x(1,n2))
146 + -(x(1,n3)-x(1,n1))*(x(3,n4)-x(3,n2))
147 nz= (x(1,n3)-x(1,n1))*(x(2,n4)-x(2,n2))
148 + -(x(2,n3)-x(2,n1))*(x(1,n4)-x(1,n2))
149
150 te = fourth*(temp(n1) + temp(n2) + temp(n3) + temp(n4))
151 area = half*sqrt( nx*nx + ny*ny + nz*nz)
152 flux =
area*h*(t_inf - te)*dt1*glob_therm%THEACCFACT
153 heat_conv_l = heat_conv_l + flux
154 flux = fourth*flux
155
156 fthe(s1*itsk+n1) = fthe(s1*itsk+n1) + flux
157 fthe(s1*itsk+n2) = fthe(s1*itsk+n2) + flux
158 fthe(s1*itsk+n3)= fthe(s1*itsk+n3) + flux
159 fthe(s1*itsk+n4)= fthe(s1*itsk+n4) + flux
160
161
162 ELSEIF(n3 > 0) THEN
163 nx= (x(2,n3)-x(2,n1))*(x(3,n3)-x(3,n2))
164 + -(x(3,n3)-x(3,n1))*(x(2,n3)-x(2,n2))
165 ny= (x(3,n3)-x(3,n1))*(x(1,n3)-x(1,n2))
166 + -(x(1,n3)-x(1,n1))*(x(3,n3)-x(3,n2))
167 nz= (x(1,n3)-x(1,n1))*(x(2,n3)-x(2,n2))
168 + -(x(2,n3)-x(2,n1))*(x(1,n3)-x(1,n2))
169
170 te = third*(temp(n1) + temp(n2) + temp(n3) )
171 area = half*sqrt( nx*nx + ny*ny + nz*nz)
172 flux =
area*h*(t_inf - te)*dt1*glob_therm%THEACCFACT
173 heat_conv_l = heat_conv_l + flux
174 flux = third*flux
175
176 fthe(s1*itsk+n1) = fthe(s1*itsk+n1) + flux
177 fthe(s1*itsk+n2) = fthe(s1*itsk+n2) + flux
178 fthe(s1*itsk+n3)= fthe(s1*itsk+n3) + flux
179
180 ELSE
181 ny= -x(3,n2)+x(3,n1)
182 nz= x(2,n2)-x(2,n1)
183
184 te = half*(temp(n1) + temp(n2) )
185 area = sqrt( ny*ny + nz*nz)
186 flux =
area*h*(t_inf - te)*dt1*glob_therm%THEACCFACT
187 heat_conv_l = heat_conv_l + flux
188 flux = half*flux
189
190 fthe(s1*itsk+n1)=fthe(s1*itsk+n1) + flux
191 fthe(s1*itsk+n2)=fthe(s1*itsk+n2) + flux
192
193 ENDIF
194 ENDDO
195
196
197
198 glob_therm%HEAT_CONV = glob_therm%HEAT_CONV + heat_conv_l
199
200 ELSE
201
202
203
204
205
206 DO nl=1,glob_therm%NUMCONV
211 IF(isens == 0)THEN
212 ts = tt*glob_therm%THEACCFACT - startt
213 ELSE
214 startt = startt + sensor_tab(isens)%TSTART
215 stopt = stopt + sensor_tab(isens)%TSTART
216 ts = tt*glob_therm%THEACCFACT -(startt + sensor_tab(isens)%TSTART)
217 ENDIF
218 iflag = 1
219 IF(tt*glob_therm%THEACCFACT < startt) iflag = 0
220 IF(tt*glob_therm%THEACCFACT > stopt ) iflag = 0
221 IF(offg <= zero) iflag = 0
222
223
224
225 IF(iflag==1) THEN
234 IF(ifunc_old /= ifunc .OR. ts_old /= ts) THEN
235 ismooth = 0
236 IF (ifunc > 0) ismooth = npc(2*nfunct+ifunc+1)
237 IF(ismooth < 0) THEN
238 CALL python_call_funct1d(python, -ismooth,ts*fcx, t_inf)
239 t_inf = fcy*t_inf
240 ELSE
241 t_inf = fcy*finter(ifunc,ts*fcx,npc,tf,dydx)
242 ENDIF
243 ifunc_old = ifunc
244 ts_old = ts
245 ENDIF
246
247 IF(n4 > 0)THEN
248 nx= (x(2,n3)-x(2,n1))*(x(3,n4)-x(3,n2))
249 + -(x(3,n3)-x(3,n1))*(x(2,n4)-x(2,n2))
250 ny= (x(3,n3)-x(3,n1))*(x(1,n4)-x(1,n2))
251 + -(x(1,n3)-x(1,n1))*(x(3,n4)-x(3,n2))
252 nz= (x(1,n3)-x(1,n1))*(x(2,n4)-x(2,n2))
253 + -(x(2,n3)-x(2,n1))*(x(1,n4)-x(1,n2))
254
255 te = fourth*(temp(n1) + temp(n2) + temp(n3) + temp(n4))
256 area = half*sqrt( nx*nx + ny*ny + nz*nz)
257 flux =
area*h*(t_inf - te)*dt1*glob_therm%THEACCFACT
258 heat_conv_l = heat_conv_l + flux
259 flux = fourth*flux
260
262 fthesky(iad1) = flux
264 fthesky(iad2) = flux
266 fthesky(iad3) = flux
268 fthesky(iad4) = flux
269
270 ELSEIF( n3 > 0) THEN
271 nx= (x(2,n3)-x(2,n1))*(x(3,n3)-x(3,n2))
272 + -(x(3,n3)-x(3,n1))*(x(2,n3)-x(2,n2))
273 ny= (x(3,n3)-x(3,n1))*(x(1,n3)-x(1,n2))
274 + -(x(1,n3)-x(1,n1))*(x(3,n3)-x(3,n2))
275 nz= (x(1,n3)-x(1,n1))*(x(2,n3)-x(2,n2))
276 + -(x(2,n3)-x(2,n1))*(x(1,n3)-x(1,n2))
277
278 te = third*(temp(n1) + temp(n2) + temp(n3) )
279 area = half*sqrt( nx*nx + ny*ny + nz*nz)
280 flux =
area*h*(t_inf - te)*dt1*glob_therm%THEACCFACT
281 heat_conv_l = heat_conv_l + flux
282 flux = third*flux
283
285 fthesky(iad1) = flux
286
288 fthesky(iad2) = flux
289
291 fthesky(iad3) = flux
292
293 ELSE
294 ny= -x(3,n2)+x(3,n1)
295 nz= x(2,n2)-x(2,n1)
296
297 te = half*(temp(n1) + temp(n2) )
298 area = sqrt( ny*ny + nz*nz)
299 flux =
area*h*(t_inf - te)*dt1*glob_therm%THEACCFACT
300 heat_conv_l = heat_conv_l + flux
301 flux = half*flux
302
304 fthesky(iad1) = flux
305
307 fthesky(iad2) = flux
308
309 ENDIF
310 ELSE
312 fthesky(iad1) = zero
314 fthesky(iad2) = zero
317 IF(n4 > 0)THEN
319 fthesky(iad3) = zero
321 fthesky(iad4) = zero
322 ELSEIF(n3 > 0)THEN
324 fthesky(iad3) = zero
325 ENDIF
326 ENDIF
327 ENDDO
328
329
330
331 glob_therm%HEAT_CONV = glob_therm%HEAT_CONV + heat_conv_l
332
333
334 ENDIF
335
336 RETURN
subroutine area(d1, x, x2, y, y2, eint, stif0)
character *2 function nl()