35 SUBROUTINE convec (IBCV ,FCONV ,NPC ,TF , X ,
36 1 TEMP ,NSENSOR ,SENSOR_TAB ,FTHE ,IAD ,
37 2 FTHESKY, PYTHON ,GLOB_THERM)
47#include "implicit_f.inc"
59 type (glob_therm_) ,
intent(inout) :: glob_therm
60 INTEGER ,
INTENT(IN) :: NSENSOR
61 INTEGER NPC(*),IAD(4,*)
62 INTEGER IBCV(GLOB_THERM%NICONV,*)
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
72 INTEGER NL,N1,N2,N3,N4,ISENS,IFUNC_OLD,IFUNC,IAD1,IAD2,IAD3,IAD4,IFLAG
73 my_real :: , NY,NZ, DYDX,TS,FLUX,TS_OLD,FCX,FCY
75 my_real :: heat_conv_l
78 INTEGER :: OMP_GET_THREAD_NUM,ITSK
79 EXTERNAL omp_get_thread_num
92 itsk = omp_get_thread_num()
98 DO nl=1,glob_therm%NUMCONV
100 IF(offg <= zero) cycle
107 ts = tt*glob_therm%THEACCFACT - startt
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)
114 IF(tt*glob_therm%THEACCFACT < startt) cycle
115 IF(tt*glob_therm%THEACCFACT > stopt ) cycle
127 IF(ifunc_old /= ifunc .OR. ts_old /= ts .OR. fcy_old /= fcy )
THEN
129 IF (ifunc > 0) ismooth = npc(2*nfunct+ifunc+1)
131 CALL python_call_funct1d(python, -ismooth,ts*fcx, t_inf)
134 t_inf = fcy*finter(ifunc, ts*fcx,npc,tf,dydx)
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))
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
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
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))
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
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
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
190 fthe(s1*itsk+n1)=fthe(s1*itsk+n1) + flux
191 fthe(s1*itsk+n2)=fthe(s1*itsk+n2) + flux
198 glob_therm%HEAT_CONV = glob_therm%HEAT_CONV + heat_conv_l
206 DO nl=1,glob_therm%NUMCONV
212 ts = tt*glob_therm%THEACCFACT - startt
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)
219 IF(tt*glob_therm%THEACCFACT < startt) iflag = 0
220 IF(tt*glob_therm%THEACCFACT > stopt ) iflag = 0
221 IF(offg <= zero) iflag = 0
234 IF(ifunc_old /= ifunc .OR. ts_old /= ts)
THEN
236 IF (ifunc > 0) ismooth = npc(2*nfunct+ifunc+1)
238 CALL python_call_funct1d(python, -ismooth,ts*fcx, t_inf)
241 t_inf = fcy*finter(ifunc,ts*fcx,npc,tf,dydx)
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))
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
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))
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
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
331 glob_therm%HEAT_CONV = glob_therm%HEAT_CONV + heat_conv_l