OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i2for27_cin.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| i2for27_cin ../engine/source/interfaces/interf/i2for27_cin.F
25!||--- called by ------------------------------------------------------
26!|| i2for27 ../engine/source/interfaces/interf/i2for27.F
27!||--- calls -----------------------------------------------------
28!|| i2cin_rot27 ../common_source/interf/i2cin_rot27.f
29!|| i2forces ../engine/source/interfaces/interf/i2forces.F
30!|| i2loceq_27 ../common_source/interf/i2loceq.F
31!|| i2rep ../common_source/interf/i2rep.F
32!||--- uses -----------------------------------------------------
33!|| h3d_mod ../engine/share/modules/h3d_mod.F
34!||====================================================================
35 SUBROUTINE i2for27_cin(NSN ,NMN ,A ,IRECT ,CRST ,
36 2 MSR ,NSV ,IRTL ,MS ,WEIGHT ,
37 3 STIFN ,MMASS ,IDEL2 ,SMASS ,X ,
38 4 V ,FSAV ,FNCONT ,INDXC ,H3D_DATA,
39 5 IN ,SINER ,DPARA ,MSEGTYP2,AR ,
40 6 STIFR ,CSTS_BIS,T2FAC_SMS,FNCONTP,FTCONTP)
41C-----------------------------------------------
42C M o d u l e s
43C-----------------------------------------------
44 USE h3d_mod
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 INTEGER NSN, NMN, IDEL2,
53 . IRECT(4,*), MSR(*), NSV(*), IRTL(*), WEIGHT(*),INDXC(NSN),MSEGTYP2(*)
54C REAL
55 my_real
56 . X(3,*),V(3,*),A(3,*),MS(*),CRST(2,*),STIFN(*),MMASS(*),SMASS(*),
57 . fsav(*),fncont(3,*),in(*),siner(*),dpara(7,*),ar(3,*),stifr(*),csts_bis(2,*),
58 . t2fac_sms(*),fncontp(3,*) ,ftcontp(3,*)
59 TYPE (H3D_DATABASE) :: H3D_DATA
60C-----------------------------------------------
61C C o m m o n B l o c k s
62C-----------------------------------------------
63#include "com01_c.inc"
64#include "impl1_c.inc"
65#include "sms_c.inc"
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER NIR, I, J, K, II, L, JJ,
70 . IX1,IX2,IX3,IX4
71C REAL
72 my_real
73 . H(4),XMSJ, SS, ST, XMSI,FS(3),SP,SM,TP,TM,
74 . e1x,e1y,e1z,e2x,e2y,e2z,e3x,e3y,e3z,
75 . x1,x2,x3,x4,y1,y2,y3,y4,z1,z2,z3,z4,x0,y0,z0,xs(3),xm(3),
76 . stifm,fmx(4),fmy(4),fmz(4),fx(4),fy(4),fz(4),
77 . rx(4),ry(4),rz(4),rs(3),flx,fly,flz,fac_triang,stbrk,
78 . mxs,mys,mzs,stifmr,dwdu,rm(3),betax,betay,h2(4),mxi,myi,mzi
79C=======================================================================
80 nir=2
81 IF(n2d==0)nir=4
82C
83 IF(impl_s>0) THEN
84 DO ii=1,nsn
85 k = indxc(ii)
86 IF (k == 0) cycle
87 i = nsv(k)
88 IF(i>0)THEN
89 l=irtl(ii)
90C
91 xmsi=ms(i)*weight(i)
92 fs(1)=a(1,i)*weight(i)
93 fs(2)=a(2,i)*weight(i)
94 fs(3)=a(3,i)*weight(i)
95C
96 IF (iroddl == 1) THEN
97 mxi=ar(1,i)*weight(i)
98 myi=ar(2,i)*weight(i)
99 mzi=ar(3,i)*weight(i)
100 ENDIF
101C
102 ix1 = irect(1,l)
103 ix2 = irect(2,l)
104 ix3 = irect(3,l)
105 ix4 = irect(4,l)
106C
107 IF (ix3 == ix4) THEN
108C-- Shape functions of triangles
109 nir = 3
110 h(1) = crst(1,ii)
111 h(2) = crst(2,ii)
112 h(3) = one-crst(1,ii)-crst(2,ii)
113 h(4) = zero
114 h2(1) = csts_bis(1,ii)
115 h2(2) = csts_bis(2,ii)
116 h2(3) = one-csts_bis(1,ii)-csts_bis(2,ii)
117 h2(4) = zero
118 ELSE
119C-- Shape functions of quadrangles
120 nir = 4
121 ss=crst(1,ii)
122 st=crst(2,ii)
123 sp=one + ss
124 sm=one - ss
125 tp=fourth*(one + st)
126 tm=fourth*(one - st)
127 h(1)=tm*sm
128 h(2)=tm*sp
129 h(3)=tp*sp
130 h(4)=tp*sm
131
132C Additional form functions for distribution of mass / inertia - to avoid negative masses for projection outside of the element
133 ss=csts_bis(1,ii)
134 st=csts_bis(2,ii)
135 sp=one + ss
136 sm=one - ss
137 tp=fourth*(one + st)
138 tm=fourth*(one - st)
139 h2(1)=tm*sm
140 h2(2)=tm*sp
141 h2(3)=tp*sp
142 h2(4)=tp*sm
143 ENDIF
144C
145 IF (msegtyp2(l)==0) THEN
146C
147C--------------------------------------------------------------C
148C--- solid main segment -- moment equilibrium----------------C
149C--------------------------------------------------------------C
150C
151C---- rep local facette main
152C
153 x1 = x(1,ix1)
154 y1 = x(2,ix1)
155 z1 = x(3,ix1)
156 x2 = x(1,ix2)
157 y2 = x(2,ix2)
158 z2 = x(3,ix2)
159 x3 = x(1,ix3)
160 y3 = x(2,ix3)
161 z3 = x(3,ix3)
162 x4 = x(1,ix4)
163 y4 = x(2,ix4)
164 z4 = x(3,ix4)
165 xs(1) = x(1,i)
166 xs(2) = x(2,i)
167 xs(3) = x(3,i)
168C
169 CALL i2rep(x1 ,x2 ,x3 ,x4 ,
170 . y1 ,y2 ,y3 ,y4 ,
171 . z1 ,z2 ,z3 ,z4 ,
172 . e1x ,e1y ,e1z ,
173 . e2x ,e2y ,e2z ,
174 . e3x ,e3y ,e3z ,nir)
175
176C
177 IF (nir == 4) THEN
178 fac_triang = one
179 x0 = fourth*(x1 + x2 + x3 + x4)
180 y0 = fourth*(y1 + y2 + y3 + y4)
181 z0 = fourth*(z1 + z2 + z3 + z4)
182 ELSE
183 fac_triang = zero
184 x0 = third*(x1 + x2 + x3)
185 y0 = third*(y1 + y2 + y3)
186 z0 = third*(z1 + z2 + z3)
187 ENDIF
188C
189 xs(1) = xs(1) - x0
190 xs(2) = xs(2) - y0
191 xs(3) = xs(3) - z0
192C
193 x1 = x1 - x0
194 y1 = y1 - y0
195 z1 = z1 - z0
196 x2 = x2 - x0
197 y2 = y2 - y0
198 z2 = z2 - z0
199 x3 = x3 - x0
200 y3 = y3 - y0
201 z3 = z3 - z0
202 x4 = x4 - x0
203 y4 = y4 - y0
204 z4 = z4 - z0
205 IF (nir==3) THEN
206 x4 = zero
207 y4 = zero
208 z4 = zero
209 END IF
210C
211 xm(1) = x1*h(1) + x2*h(2) + x3*h(3) + x4*h(4)
212 xm(2) = y1*h(1) + y2*h(2) + y3*h(3) + y4*h(4)
213 xm(3) = z1*h(1) + z2*h(2) + z3*h(3) + z4*h(4)
214
215C---- computation of local coordinates
216C
217 rs(1) = xs(1)*e1x + xs(2)*e1y + xs(3)*e1z
218 rs(2) = xs(1)*e2x + xs(2)*e2y + xs(3)*e2z
219 rs(3) = xs(1)*e3x + xs(2)*e3y + xs(3)*e3z
220C
221 rm(1) = xm(1)*e1x + xm(2)*e1y + xm(3)*e1z
222 rm(2) = xm(1)*e2x + xm(2)*e2y + xm(3)*e2z
223 rm(3) = xm(1)*e3x + xm(2)*e3y + xm(3)*e3z
224c
225 rx(1) = e1x*x1 + e1y*y1 + e1z*z1
226 ry(1) = e2x*x1 + e2y*y1 + e2z*z1
227 rz(1) = e3x*x1 + e3y*y1 + e3z*z1
228 rx(2) = e1x*x2 + e1y*y2 + e1z*z2
229 ry(2) = e2x*x2 + e2y*y2 + e2z*z2
230 rz(2) = e3x*x2 + e3y*y2 + e3z*z2
231 rx(3) = e1x*x3 + e1y*y3 + e1z*z3
232 ry(3) = e2x*x3 + e2y*y3 + e2z*z3
233 rz(3) = e3x*x3 + e3y*y3 + e3z*z3
234 rx(4) = e1x*x4 + e1y*y4 + e1z*z4
235 ry(4) = e2x*x4 + e2y*y4 + e2z*z4
236 rz(4) = e3x*x4 + e3y*y4 + e3z*z4
237C
238C---- computation of kinematic parameters and stbrk - local coordinates
239 CALL i2cin_rot27(stbrk,rs,rm,rx(1),ry(1),rz(1),rx(2),ry(2),rz(2),rx(3),ry(3),rz(3),
240 . rx(4),ry(4),rz(4),dpara(1,ii),dwdu,e1x,e1y,e1z,e2x,e2y,e2z,e3x,e3y,e3z,
241 . nir,betax,betay)
242C
243C---- computation of force in local skew
244C
245 flx = fs(1)*e1x + fs(2)*e1y + fs(3)*e1z
246 fly = fs(1)*e2x + fs(2)*e2y + fs(3)*e2z
247 flz = fs(1)*e3x + fs(2)*e3y + fs(3)*e3z
248C
249 DO j=1,4
250 fmx(j) = h(j)*flx
251 fmy(j) = h(j)*fly
252 fmz(j) = h(j)*flz
253 ENDDO
254C
255C---- update main forces (moment balance) - local coordinates RX
256 IF (iroddl==1) THEN
257 mxs = mxi*e1x + myi*e1y + mzi*e1z
258 mys = mxi*e2x + myi*e2y + mzi*e2z
259 mzs = mxi*e3x + myi*e3y + mzi*e3z
260
261C-- moment balance + moment transfer
262 CALL i2loceq_27(nir ,rs ,rx ,ry ,rz ,
263 . fmx ,fmy ,fmz ,h ,stifm ,
264 . mxs ,mys ,mzs ,stifmr ,betax ,
265 . betay)
266 ELSE
267 mxs = zero
268 mys = zero
269 mzs = zero
270
271C-- moment balance
272 CALL i2loceq_27(nir ,rs ,rx ,ry ,rz ,
273 . fmx ,fmy ,fmz ,h ,stifm ,
274 . mxs ,mys ,mzs ,stifmr ,betax ,
275 . betay)
276 stifmr = zero
277 ENDIF
278C
279C---- computation of force in global skew
280C
281 DO j=1,4
282 fx(j) = e1x*fmx(j) + e2x*fmy(j) + e3x*fmz(j)
283 fy(j) = e1y*fmx(j) + e2y*fmy(j) + e3y*fmz(j)
284 fz(j) = e1z*fmx(j) + e2z*fmy(j) + e3z*fmz(j)
285 ENDDO
286C
287 ELSE
288C----------------------------------------------------C
289C--- shell / shell or shell / solide connection ----C
290C----------------------------------------------------C
291C
292 stifm=zero
293 stbrk=zero
294 stifmr=zero
295 dwdu=zero
296C
297 DO j=1,4
298 fx(j) = fs(1)*h(j)
299 fy(j) = fs(2)*h(j)
300 fz(j) = fs(3)*h(j)
301 ENDDO
302C
303 ENDIF
304C
305 IF(iroddl/=0)THEN
306 DO jj=1,nir
307 j=irect(jj,l)
308 a(1,j)=a(1,j)+fx(jj)
309 a(2,j)=a(2,j)+fy(jj)
310 a(3,j)=a(3,j)+fz(jj)
311 ms(j)=ms(j)+xmsi*h2(jj)
312 stifn(j)=stifn(j)+weight(i)*(stifn(i)*(one+stbrk)*(abs(h(jj))+stifm)+stifr(i)*stifmr*dwdu)
313 ENDDO
314 ELSE
315 DO jj=1,nir
316 j=irect(jj,l)
317 a(1,j)=a(1,j)+fx(jj)
318 a(2,j)=a(2,j)+fy(jj)
319 a(3,j)=a(3,j)+fz(jj)
320 ms(j)=ms(j)+xmsi*h2(jj)
321 stifn(j)=stifn(j)+weight(i)*(stifn(i)*(one+stbrk)*(abs(h(jj))+stifm))
322 ENDDO
323 END IF
324C
325C--- output of tied contact forces
326 CALL i2forces(x ,fs ,fx ,fy ,fz ,
327 . irect(1,l),nir ,fsav ,fncont ,fncontp,
328 . ftcontp ,weight ,h3d_data,i ,h)
329C
330 IF(iroddl==0)THEN
331 IF(idel2/=0.AND.ms(i)/=0.)smass(ii)=ms(i)
332 ms(i)=zero
333 stifn(i)=em20
334 a(1,i)=zero
335 a(2,i)=zero
336 a(3,i)=zero
337 ENDIF
338C
339 ENDIF
340C----
341 ENDDO
342c
343c
344 ELSE
345c
346 DO ii=1,nsn
347 k = indxc(ii)
348 IF (k == 0) cycle
349 i = nsv(k)
350 IF(i>0)THEN
351 l=irtl(ii)
352C
353 xmsi=ms(i)*weight(i)
354 fs(1)=a(1,i)*weight(i)
355 fs(2)=a(2,i)*weight(i)
356 fs(3)=a(3,i)*weight(i)
357C
358 IF (iroddl == 1) THEN
359 mxi=ar(1,i)*weight(i)
360 myi=ar(2,i)*weight(i)
361 mzi=ar(3,i)*weight(i)
362 ENDIF
363C
364 ix1 = irect(1,l)
365 ix2 = irect(2,l)
366 ix3 = irect(3,l)
367 ix4 = irect(4,l)
368C
369 IF (ix3 == ix4) THEN
370C-- Shape functions of triangles
371 nir = 3
372 h(1) = crst(1,ii)
373 h(2) = crst(2,ii)
374 h(3) = one-crst(1,ii)-crst(2,ii)
375 h(4) = zero
376 h2(1) = csts_bis(1,ii)
377 h2(2) = csts_bis(2,ii)
378 h2(3) = one-csts_bis(1,ii)-csts_bis(2,ii)
379 h2(4) = zero
380 ELSE
381C-- Shape functions of quadrangles
382 nir = 4
383 ss=crst(1,ii)
384 st=crst(2,ii)
385 sp=one + ss
386 sm=one - ss
387 tp=fourth*(one + st)
388 tm=fourth*(one - st)
389 h(1)=tm*sm
390 h(2)=tm*sp
391 h(3)=tp*sp
392 h(4)=tp*sm
393
394C Additional form functions for distribution of mass / inertia - to avoid negative masses for projection outside of the element
395 ss=csts_bis(1,ii)
396 st=csts_bis(2,ii)
397 sp=one + ss
398 sm=one - ss
399 tp=fourth*(one + st)
400 tm=fourth*(one - st)
401 h2(1)=tm*sm
402 h2(2)=tm*sp
403 h2(3)=tp*sp
404 h2(4)=tp*sm
405 ENDIF
406C
407 IF (msegtyp2(l)==0) THEN
408C
409C--------------------------------------------------------------C
410C--- solid main segment -- moment equilibrium----------------C
411C--------------------------------------------------------------C
412C
413C---- rep local facette main
414C
415 x1 = x(1,ix1)
416 y1 = x(2,ix1)
417 z1 = x(3,ix1)
418 x2 = x(1,ix2)
419 y2 = x(2,ix2)
420 z2 = x(3,ix2)
421 x3 = x(1,ix3)
422 y3 = x(2,ix3)
423 z3 = x(3,ix3)
424 x4 = x(1,ix4)
425 y4 = x(2,ix4)
426 z4 = x(3,ix4)
427 xs(1) = x(1,i)
428 xs(2) = x(2,i)
429 xs(3) = x(3,i)
430C
431 CALL i2rep(x1 ,x2 ,x3 ,x4 ,
432 . y1 ,y2 ,y3 ,y4 ,
433 . z1 ,z2 ,z3 ,z4 ,
434 . e1x ,e1y ,e1z ,
435 . e2x ,e2y ,e2z ,
436 . e3x ,e3y ,e3z ,nir)
437
438C
439 IF (nir == 4) THEN
440 fac_triang = one
441 x0 = fourth*(x1 + x2 + x3 + x4)
442 y0 = fourth*(y1 + y2 + y3 + y4)
443 z0 = fourth*(z1 + z2 + z3 + z4)
444 ELSE
445 fac_triang = zero
446 x0 = third*(x1 + x2 + x3)
447 y0 = third*(y1 + y2 + y3)
448 z0 = third*(z1 + z2 + z3)
449 ENDIF
450C
451 xs(1) = xs(1) - x0
452 xs(2) = xs(2) - y0
453 xs(3) = xs(3) - z0
454C
455 x1 = x1 - x0
456 y1 = y1 - y0
457 z1 = z1 - z0
458 x2 = x2 - x0
459 y2 = y2 - y0
460 z2 = z2 - z0
461 x3 = x3 - x0
462 y3 = y3 - y0
463 z3 = z3 - z0
464 x4 = x4 - x0
465 y4 = y4 - y0
466 z4 = z4 - z0
467 IF (nir==3) THEN
468 x4 = zero
469 y4 = zero
470 z4 = zero
471 END IF
472c
473 xm(1) = x1*h(1) + x2*h(2) + x3*h(3) + x4*h(4)
474 xm(2) = y1*h(1) + y2*h(2) + y3*h(3) + y4*h(4)
475 xm(3) = z1*h(1) + z2*h(2) + z3*h(3) + z4*h(4)
476
477C---- computation of local coordinates
478C
479 rs(1) = xs(1)*e1x + xs(2)*e1y + xs(3)*e1z
480 rs(2) = xs(1)*e2x + xs(2)*e2y + xs(3)*e2z
481 rs(3) = xs(1)*e3x + xs(2)*e3y + xs(3)*e3z
482C
483 rm(1) = xm(1)*e1x + xm(2)*e1y + xm(3)*e1z
484 rm(2) = xm(1)*e2x + xm(2)*e2y + xm(3)*e2z
485 rm(3) = xm(1)*e3x + xm(2)*e3y + xm(3)*e3z
486c
487 rx(1) = e1x*x1 + e1y*y1 + e1z*z1
488 ry(1) = e2x*x1 + e2y*y1 + e2z*z1
489 rz(1) = e3x*x1 + e3y*y1 + e3z*z1
490 rx(2) = e1x*x2 + e1y*y2 + e1z*z2
491 ry(2) = e2x*x2 + e2y*y2 + e2z*z2
492 rz(2) = e3x*x2 + e3y*y2 + e3z*z2
493 rx(3) = e1x*x3 + e1y*y3 + e1z*z3
494 ry(3) = e2x*x3 + e2y*y3 + e2z*z3
495 rz(3) = e3x*x3 + e3y*y3 + e3z*z3
496 rx(4) = e1x*x4 + e1y*y4 + e1z*z4
497 ry(4) = e2x*x4 + e2y*y4 + e2z*z4
498 rz(4) = e3x*x4 + e3y*y4 + e3z*z4
499C
500C---- computation of kinematic parameters and stbrk - local coordinates
501 CALL i2cin_rot27(stbrk,rs,rm,rx(1),ry(1),rz(1),rx(2),ry(2),rz(2),rx(3),ry(3),rz(3),
502 . rx(4),ry(4),rz(4),dpara(1,ii),dwdu,e1x,e1y,e1z,e2x,e2y,e2z,e3x,e3y,e3z,
503 . nir,betax,betay)
504C
505C---- computation of force in local skew
506C
507 flx = fs(1)*e1x + fs(2)*e1y + fs(3)*e1z
508 fly = fs(1)*e2x + fs(2)*e2y + fs(3)*e2z
509 flz = fs(1)*e3x + fs(2)*e3y + fs(3)*e3z
510C
511 DO j=1,4
512 fmx(j) = h(j)*flx
513 fmy(j) = h(j)*fly
514 fmz(j) = h(j)*flz
515 ENDDO
516C
517C---- update main forces (moment balance)
518 IF (iroddl==1) THEN
519 mxs = mxi*e1x + myi*e1y + mzi*e1z
520 mys = mxi*e2x + myi*e2y + mzi*e2z
521 mzs = mxi*e3x + myi*e3y + mzi*e3z
522
523C-- moment balance + moment transfer
524 CALL i2loceq_27(nir ,rs ,rx ,ry ,rz ,
525 . fmx ,fmy ,fmz ,h ,stifm ,
526 . mxs ,mys ,mzs ,stifmr ,betax ,
527 . betay)
528 ELSE
529 mxs = zero
530 mys = zero
531 mzs = zero
532
533C-- moment balance
534 CALL i2loceq_27(nir ,rs ,rx ,ry ,rz ,
535 . fmx ,fmy ,fmz ,h ,stifm ,
536 . mxs ,mys ,mzs ,stifmr ,betax ,
537 . betay)
538 stifmr = zero
539 ENDIF
540C
541C---- computation of force in global skew
542C
543 DO j=1,4
544 fx(j) = e1x*fmx(j) + e2x*fmy(j) + e3x*fmz(j)
545 fy(j) = e1y*fmx(j) + e2y*fmy(j) + e3y*fmz(j)
546 fz(j) = e1z*fmx(j) + e2z*fmy(j) + e3z*fmz(j)
547 ENDDO
548C
549 ELSE
550C----------------------------------------------------C
551C--- shell / shell or shell / solide connection ----C
552C----------------------------------------------------C
553C
554 stifm=zero
555 stbrk=zero
556 stifmr=zero
557 dwdu=zero
558C
559 DO j=1,4
560 fx(j) = fs(1)*h(j)
561 fy(j) = fs(2)*h(j)
562 fz(j) = fs(3)*h(j)
563 ENDDO
564C
565 ENDIF
566C
567 IF(iroddl/=0)THEN
568 DO jj=1,nir
569 j=irect(jj,l)
570 a(1,j)=a(1,j)+fx(jj)
571 a(2,j)=a(2,j)+fy(jj)
572 a(3,j)=a(3,j)+fz(jj)
573 ms(j)=ms(j)+xmsi*h2(jj)
574 stifn(j)=stifn(j)+weight(i)*(stifn(i)*(one+stbrk)*(abs(h(jj))+stifm)+stifr(i)*stifmr*dwdu)
575 ENDDO
576 ELSE
577 DO jj=1,nir
578 j=irect(jj,l)
579 a(1,j)=a(1,j)+fx(jj)
580 a(2,j)=a(2,j)+fy(jj)
581 a(3,j)=a(3,j)+fz(jj)
582 ms(j)=ms(j)+xmsi*h2(jj)
583 stifn(j)=stifn(j)+weight(i)*(stifn(i)*(one+stbrk)*(abs(h(jj))+stifm))
584 ENDDO
585 END IF
586C
587 IF(idtmins==2.OR.idtmins_int/=0) THEN
588C---- For AMS scaling factor on stiffness is stored - only used for solid main surface
589 t2fac_sms(i) = (one+stbrk)*(one+stifm)
590 ENDIF
591C
592C--- output of tied contact forces
593 CALL i2forces(x ,fs ,fx ,fy ,fz ,
594 . irect(1,l),nir ,fsav ,fncont ,fncontp,
595 . ftcontp ,weight ,h3d_data,i ,h)
596C
597 IF(iroddl==0)THEN
598 IF(idel2/=0.AND.ms(i)/=0.) smass(ii)=ms(i)
599 ms(i)=zero
600 stifn(i)=em20
601 a(1,i)=zero
602 a(2,i)=zero
603 a(3,i)=zero
604 ENDIF
605C----
606 ENDIF
607C
608 ENDDO
609 ENDIF
610C
611 RETURN
612 END
subroutine i2cin_rot27(stbrk, rs, rm, x1, y1, z1, x2, y2, z2, x3, y3, z3, x4, y4, z4, dpara, dwdu, e1x, e1y, e1z, e2x, e2y, e2z, e3x, e3y, e3z, nir, betax, betay)
Definition i2cin_rot27.F:33
subroutine i2for27_cin(nsn, nmn, a, irect, crst, msr, nsv, irtl, ms, weight, stifn, mmass, idel2, smass, x, v, fsav, fncont, indxc, h3d_data, in, siner, dpara, msegtyp2, ar, stifr, csts_bis, t2fac_sms, fncontp, ftcontp)
Definition i2for27_cin.F:41
subroutine i2forces(x, fs, fx, fy, fz, irect, nir, fsav, fncont, fncontp, ftcontp, weight, h3d_data, nsl, h)
Definition i2forces.F:52
subroutine i2loceq_27(nir, rs, rx, ry, rz, fmx, fmy, fmz, h, stifm, mxs, mys, mzs, stifmr, betax, betay)
Definition i2loceq.F:224
subroutine i2rep(x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4, e1x, e1y, e1z, e2x, e2y, e2z, e3x, e3y, e3z, nir)
Definition i2rep.F:48