38 3 CPTREAC,NODREAC,NODNX_SMS,NSENSOR,
44 use python_call_funct_cload_mod
50#include "implicit_f.inc"
64 TYPE(python_),
INTENT(IN) :: PYTHON
65 TYPE(nodal_arrays_) :: NODES
66 INTEGER ,
INTENT(IN) :: NSENSOR
67 INTEGER NPC(*),CPTREAC,NODREAC(*)
68 INTEGER IBFV(NIFV,*), NODNX_SMS(*)
69 my_real :: tf(*), vel(lfxvelr,*), fthreac(6,*)
73 INTEGER N, I, J, K, L, I1, N1, N2, ISENS,
74 . ILENC, IPOSC, IADC, ICOOR, ISMOOTH
75 AX, AXI, VV, A0, AA, FAC, FACX, STARTT, STOPT, TS,
77 . yc, tsc, dydxc, rw_sms,
78 . skew1, skew2, skew3,
79 . xi, yi, zi, xf, yf, zf, xa, ya, za,
81 . vx1, vy1, vz1, vx2, vy2, vz2
82 my_real,
DIMENSION(:),
ALLOCATABLE ::
83 TYPE (SENSOR_STR_) ,
DIMENSION(NSENSOR) ,
INTENT(IN) :: SENSOR_TAB
84 DOUBLE PRECISION,
INTENT(INOUT) :: WFEXT
89 EXTERNAL finter2,finter2_smooth
99 ALLOCATE(mass(numnod),vx(numnod),vy(numnod),vz(numnod))
105 IF (ibfv(13,n) /= 2) cycle
111 vx1= nodes%V(1,n1)+nodes%A(1,n1)*dt12
112 vy1= nodes%V(2,n1)+nodes%A(2,n1)*dt12
113 vz1= nodes%V(3,n1)+nodes%A(3,n1)*dt12
114 vx2= nodes%V(1,n2)+nodes%A(1,n2)*dt12
115 vy2= nodes%V(2,n2)+nodes%A(2,n2)*dt12
116 vz2= nodes%V(3,n2)+nodes%A(3,n2)*dt12
118 vx(n2) = vx(n2) + nodes%MS(n1)*vx1+ nodes%MS(n2)*vx2
119 vy(n2) = vy(n2) + nodes%MS(n1)*vy1+ nodes%MS(n2)*vy2/ibfv(16,n)
120 vz(n2) = vz(n2) + nodes%MS(n1)*vz1+ nodes%MS(n2)*vz2/ibfv(16,n)
121 mass(n2) = mass(n2) + nodes%MS(n1) + nodes%MS(n2)/ibfv(16,n)
125 IF(mass(n) == zero) cycle
132 IF (ibfv(13,n) /= 2) cycle
137 nodes%A(1,n1)=(vx(n2)-nodes%V(1
138 nodes%A(2,n1)=(vy(n2)-nodes%V(2,n1))/dt12
139 nodes%A(3,n1)=(vz(n2)-nodes%V(3,n1))/dt12
140 nodes%A(1,n2)=(vx(n2)-nodes%V(1,n2))/dt12
141 nodes%A(2,n2)=(vy(n2)-nodes%V(2,n2))/dt12
142 nodes%A(3,n2)=(vz(n2)-nodes%V(3,n2))/dt12
145 DEALLOCATE(mass, vx, vy, vz)
150 IF (ibfv(13,n) == 0) cycle
162 ts = tt - sensor_tab(isens)%TSTART
169 IF(idtmins==0.AND.idtmins_int==0)
THEN
172 IF(nodnx_sms(i)==0)
THEN
180 aold0(1)=nodes%A(1,i)
181 aold0(2)=nodes%A(2,i)
182 aold0(3)=nodes%A(3,i)
191 iadc = npc(l) / 2 + 1
192 ilenc = npc(l+1) / 2 - iadc - iposc
195 IF (l > 0) ismooth = npc(2*nfunct+l+1)
196 IF (ismooth == 0)
THEN
198 ELSE IF(ismooth > 0)
THEN
199 yc = finter2_smooth(tf,iadc,iposc,ilenc,tsc,dydxc)
203 CALL python_call_funct_cload(python, ismooth,tsc, yc,i,nodes)
207 IF(ibfv(13,n) == 1)
THEN
213 ELSEIF(ibfv(13,n) == 2)
THEN
223 IF(fac < vel(7,n))
THEN
226 WRITE(iout,
'(A,I10,1X,I10,A,1PE12.5)')
227 .
' RIGID LINK ON NODES',nodes%ITAB(ibfv(1,n)),ibfv(14,n),
228 .
' ACTIVATED AT TIME',tt
240 wfext = wfext + rw_sms*dw
241 vel(4,n)= (one-rw_sms)*vel(4,n)
244 axi=one-ax+ax*nodes%X(2,i)
246 dd = skew1*nodes%D(1,i) + skew2*nodes%D(2,i) + skew3*nodes%D(3,i)
247 vv = skew1*nodes%V(1,i) + skew2*nodes%V(2,i) + skew3*nodes%V(3,i)
248 a0 = skew1*nodes%A(1,i) + skew2*nodes%A(2,i) + skew3*nodes%A(3,i)
250 IF(ibfv(13,n) == 1) yc =(yc-dd)/dt2
254 nodes%A(1,i)=skew1*yc
255 nodes%A(2,i)=skew2*yc
256 nodes%A(3,i)=skew3*yc
258 dw = fourth*nodes%MS(i)*(yc*dt12+two*vv)*aa*axi*nodes%WEIGHT(i)
259 wfext = wfext + dt1*dw
263 vel(4,n) = vel(4,n)+dt2*dw
267 IF (nodreac(i)/=0)
THEN
268 fthreac(1,nodreac(i)) = fthreac(1,nodreac(i)) + (nodes%A(1,i) -
269 & aold0(1))*nodes%MS(i)*dt12
270 fthreac(2,nodreac(i)) = fthreac(2,nodreac(i)) + (nodes%A(2,i) -
271 & aold0(2))*nodes%MS(i)*dt12
272 fthreac(3,nodreac(i)) = fthreac(3,nodreac(i)) + (nodes%A(3,i) -
273 & aold0(3))*nodes%MS(i)*dt12