38 SUBROUTINE fixtemp(PYTHON,IBFT ,VAL , TEMP ,NPC ,TF ,
39 . NSENSOR,SENSOR_TAB,GLOB_THERM,snpc)
43 USE redef3_mod,
only: get_python_funct_id
51#include "implicit_f.inc"
68 type (glob_therm_) ,
intent(inout) :: glob_therm
69 INTEGER ,
INTENT(IN) :: NSENSOR
71 INTEGER IBFT(GLOB_THERM%NIFT,*)
73 my_real :: val(glob_therm%LFACTHER,*)
74 integer,
intent(in) :: SNPC
75 TYPE (SENSOR_STR_) ,
DIMENSION(NSENSOR) ,
INTENT(IN) :: SENSOR_TAB
79 INTEGER I,N,L,II, NN,,IC, IDEB, ISMOOTH
80 INTEGER ILENC(MVSIZ), IPOSC(MVSIZ), IADC(MVSIZ)
82 my_real fac, facx, startt, stopt, ts
83 my_real yc(mvsiz), tsc(mvsiz), dydxc(mvsiz)
85 logical :: any_python_func
90 DO nn=1,glob_therm%NFXTEMP,nvsiz
93 DO ii = 1,
min(glob_therm%NFXTEMP - ideb,nvsiz)
100 ts = tt*glob_therm%THEACCFACT - startt
102 startt = startt + sensor_tab(isens)%TSTART
103 stopt = stopt + sensor_tab(isens)%TSTART
104 ts = tt*glob_therm%THEACCFACT -(startt + sensor_tab(isens)%TSTART)
107 IF(tt*glob_therm%THEACCFACT < startt) cycle
108 IF(tt*glob_therm%THEACCFACT > stopt) cycle
118 DO ii = 1,
min(glob_therm%NFXTEMP-ideb,nvsiz)
122 IF (tt*glob_therm%THEACCFACT < startt) cycle
123 IF (tt*glob_therm%THEACCFACT > stopt) cycle
128 ts = tt*glob_therm%THEACCFACT - startt
133 ideb = ideb +
min(glob_therm%NFXTEMP-ideb,nvsiz)
135 any_python_func = .false.
140 IF (l > 0) ismooth = npc(2*nfunct+l+1)
142 pyid = get_python_funct_id(nfunct,l,npc,snpc)
146 any_python_func = .true.
148 iadc(ii) = npc(l) / 2 + 1
149 ilenc(ii) = npc(l+1) / 2 - iadc(ii) - iposc(ii)
156 IF (l > 0) ismooth = npc(2*nfunct+l+1)
157 iposc(ii) = ibft(4,n)
158 pyid = get_python_funct_id(nfunct,l,npc,snpc)
162 any_python_func = .true.
164 iadc(ii) = npc(l) / 2 + 1
165 ilenc(ii) = npc(l+1) / 2 - iadc(ii) - iposc(ii)
170 if(any_python_func)
then
171 call vinter_mixed(python,tf,iadc,iposc,ilenc,ic,tsc,dydxc,yc)
173 IF (ismooth == 0)
THEN
174 CALL vinter(tf,iadc,iposc,ilenc,ic,tsc,dydxc,yc)
180 IF(ivector == 0)
THEN
183 ibft(4,n) = iposc(ii)
185 yc(ii) = yc(ii) * fac
191#include "vectorize.inc"
194 ibft(4,n) = iposc(ii)
196 yc(ii) = yc(ii) * fac
subroutine fixtemp(python, ibft, val, temp, npc, tf, nsensor, sensor_tab, glob_therm, snpc)