46
47
48
51 USE sensor_mod
52 USE python_funct_mod
53
54
55
56#include "implicit_f.inc"
57#include "comlock.inc"
58#include "param_c.inc"
59
60
61
62#include "com04_c.inc"
63#include "com06_c.inc"
64#include "com08_c.inc"
65#include "scr14_c.inc"
66#include "scr16_c.inc"
67#include "parit_c.inc"
68
69
70
71 INTEGER GET_U_NUMSENS,GET_U_SENS_FPAR,GET_U_SENS_IPAR,
72 . ,SET_U_SENS_VALUE
73 EXTERNAL
75
76
77
78 INTEGER ,INTENT(IN) :: NSENSOR
79 INTEGER NPC(*)
80 INTEGER IB(NIBCLD,*)
81 INTEGER WEIGHT(*), IADC(4,*)
83 . fac(lfaccld,*), tf(*), a(3,*), v(3,*), ar(3,*), vr(3,*),
84 . x(3,*), skew(lskew,*), tfexc,
85 . fsky(8,lsky), fskyv(lsky,8),fext(3,*),
86 . apinch(3,*),vpinch(3,*)
87 TYPE(H3D_DATABASE) :: H3D_DATA
88 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) :: SENSOR_TAB
89 TYPE(PYTHON_) :: PYTHON
90 DOUBLE PRECISION,INTENT(INOUT) :: WFEXT
91
92
93
94 INTEGER NL, N1, ISK, N2, N3, N4, N5, K1, K2, K3, ISENS,K,LL,IERR,
95 . ICODE,IAD,N_OLD, Bric(2), Face(2), NumBric, IBRIC, IANIM,I,
96 . ISMOOTH
98 . nx, ny, nz, axi, aa, a0, vv, fx, fy, fz, ax, dydx, ts,
99 . sixth,wfextt,x_old, f1, f2,xsens,fcx,fcy
100 my_real finter, zfx,zfy,zfz, zzfx,zzfy,zzfz,ps, zx,zy,zz,finter_smooth
102 . fcypinch, fxpinch, fypinch, fzpinch, aapinch
103 EXTERNAL finter,finter_smooth
104
105
106 sixth = one_over_6
107 tfexc = zero
108 wfextt = zero
109 n_old = 0
110 x_old = zero
111 ianim = anim_v(5)+outp_v(5)+h3d_data%N_VECT_FINT+
112 . anim_v(6)+outp_v(6)+h3d_data%N_VECT_FEXT
113
123
124 isens = 0
125 xsens = one
126 DO k=1,nsensor
127 IF(ib(6,
nl)==sensor_tab(k)%SENS_ID) isens=k
128 ENDDO
129 IF(isens==0)THEN
130 ts=tt
131 ELSE
132 ts = tt-sensor_tab(isens)%TSTART
133 IF(ts < zero) GOTO 10
134 ENDIF
135
136
137
138 IF(n_old/=n5.OR.x_old/=ts) THEN
139
140 ismooth = 0
141 IF (n5 > 0) ismooth = npc(2*nfunct+n5+1)
142
143 IF (ismooth == 0) THEN
144 f1 = finter(n5,ts*fcx,npc,tf,dydx)
145 ELSE IF(ismooth > 0) THEN
146 f1 = finter_smooth(n5,ts*fcx,npc,tf,dydx)
147 ELSE
148 ismooth = -ismooth
149 CALL python_call_funct1d(python, ismooth,(ts)*fcx, f1)
150 ENDIF
151 n_old = n5
152 x_old = ts
153 ENDIF
154 aapinch = fcypinch*f1*xsens
155
156 IF(n4/=0)THEN
157 nx = (x(2,n3)-x(2,n1))*(x(3,n4)-x(3,n2)) - (x(3,n3)-x(3,n1))*(x(2,n4)-x(2,n2
158 ny = (x(3,n3)-x(3,n1))*(x(1,n4)-x(1,n2)) - (x(1,n3)-x(1,n1))*(x(3,n4)-x(3,n2))
159 nz = (x(1,n3)-x(1,n1))*(x(2,n4)-x(2,n2)) - (x(2,n3)-x(2,n1))*(x(1,n4)-x(1,n2))
160
161 fxpinch = aapinch*nx*one_over_8
162 fypinch = aapinch*ny*one_over_8
163 fzpinch = aapinch*nz*one_over_8
164
165 apinch(1,n1) = apinch(1,n1) + fxpinch
166 apinch(2,n1) = apinch(2,n1) + fypinch
167 apinch(3,n1) = apinch(3,n1) + fzpinch
168
169 apinch(1,n2) = apinch(1,n2) + fxpinch
170 apinch(2,n2) = apinch(2,n2) + fypinch
171 apinch(3,n2) = apinch(3,n2) + fzpinch
172
173 apinch(1,n3) = apinch(1,n3) + fxpinch
174 apinch(2,n3) = apinch(2,n3) + fypinch
175 apinch(3,n3) = apinch(3,n3) + fzpinch
176
177 apinch(1,n4) = apinch(1,n4) + fxpinch
178 apinch(2,n4) = apinch(2,n4) + fypinch
179 apinch(3,n4) = apinch(3,n4) + fzpinch
180
181
182 wfextt=wfextt+dt1*(fxpinch
183 1 +fypinch*(vpinch(2,n1)+vpinch(2,n2)+vpinch(2,n3)+vpinch(2,n4))
184 2 +fzpinch*(vpinch(3,n1)+vpinch(3,n2)+vpinch(3,n3)+vpinch(3,n4)))
185
186 ELSE
187
188 nx = (x(2,n3)-x(2,n1))*(x(3,n3)-x(3,n2)) - (x(3,n3)-x(3,n1))*(x(2,n3)-x(2,n2))
189 ny = (x(3,n3)-x(3,n1))*(x(1,n3)-x(1,n2)) - (x(1,n3)-x(1,n1))*(x
190 nz = (x(1,n3)-x(1,n1))*(x(2,n3)-x(2,n2)) - (x(2,n3)-x(2,n1))*(x(1,n3)-x(1,n2))
191
192 fxpinch = aapinch*nx*sixth
193 fypinch = aapinch*ny*sixth
194 fzpinch = aapinch*nz*sixth
195
196 apinch(1,n1)=apinch(1,n1)+fxpinch
197 apinch(2,n1)=apinch(2,n1)+fypinch
198 apinch(3,n1)=apinch(3,n1)+fzpinch
199
200 apinch(1,n2)=apinch(1,n2)+fxpinch
201 apinch(2,n2)=apinch(2,n2)+fypinch
202 apinch(3,n2)=apinch(3,n2)+fzpinch
203
204 apinch(1,n3)=apinch(1,n3)+fxpinch
205 apinch(2,n3)=apinch(2,n3)+fypinch
206 apinch(3,n3)=apinch(3,n3)+fzpinch
207
208 ENDIF
209 10 CONTINUE
210
211
212 wfext = wfext + wfextt
213
214 RETURN
character *2 function nl()
integer function set_u_sens_value(nsens, ivar, var)
integer function get_u_sens_ipar(nsens, ivar, var)
integer function get_u_sens_value(nsens, ivar, var)
integer function get_u_sens_fpar(nsens, ivar, var)
integer function get_u_numsens(idsens)