32 SUBROUTINE i2_dtn_27(X,INTBUF_TAB,IPARI,STIFN,MS,IN,N,NSN)
40#include "implicit_f.inc"
49 INTEGER IPARI(NPARI,*),NSN,N
52 . x(3,*),stifn(*),ms(*),in(*)
54 TYPE(intbuf_struct_) INTBUF_TAB(*)
58 INTEGER I,NI,NINDXC,NINDXP
64 IF (intbuf_tab(n)%IRUPT(i) == 0)
THEN
72 CALL i2_dtn_27_cin(x,intbuf_tab(n)%IRECTM,intbuf_tab(n)%CSTS,intbuf_tab(n)%CSTS_BIS,intbuf_tab(n)%NSV,
73 . intbuf_tab(n)%IRTLM ,ipari(1,n),intbuf_tab(n)%MSEGTYP2, stifn, stifn(numnod+1),
74 . ms,in,intbuf_tab(n)%IRUPT)
78 CALL i2_dtn_27_pen(x,intbuf_tab(n)%IRECTM,intbuf_tab(n)%CSTS,intbuf_tab
79 . ipari(1,n),intbuf_tab(n)%MSEGTYP2,stifn,stifn(numnod+1),intbuf_tab(n
80 . intbuf_tab(n)%STFR_PENALTY,intbuf_tab(n)%VARIABLES(14),in,intbuf_tab(n)%IRUPT)
93 2 IRTL ,IPARI, MSEGTYP2, STIFN, STIFR,
98#include "implicit_f.inc"
103 INTEGER IRECT(4,*), NSV(*),IRTL(*),
104 . IPARI(*),MSEGTYP2(*),IRUPT(
106 . x(3,*),crst(2,*),stifn(*),stifr(*), ms(*),csts_bis(2,*),in(*)
110 INTEGER II,I,J,JJ,L,IX1,IX2,IX3,IX4,NIR,NRTM,NSN,NMN,K
112 . bid,bid4(4),bid9(9),x1,x2,x3,x4,y1,y2,y3,y4,z1,z2,z3,z4,xs(3),xm(3),x0,y0,z0,betax,betay,betaz,
113 . e1x,e1y,e1z,e2x,e2y,e2z,e3x,e3y,e3z,h(4),h2(4),ss,st,sp,sm,tp
114 . fac_triang,stbrk,dwdu,stifmr,stifm,ins,stf,aa
125 IF (irupt(ii) /= 0) cycle
139 h(3) = one-crst(1,ii)-crst(2,ii)
141 h2(1) = csts_bis(1,ii)
142 h2(2) = csts_bis(2,ii)
143 h2(3) = one-csts_bis(1,ii)-csts_bis(2,ii)
172 IF (msegtyp2(l)==0)
THEN
196 . e3x ,e3y ,e3z ,nir)
201 x0 = fourth*(x1 + x2 + x3 + x4)
202 y0 = fourth*(y1 + y2 + y3 + y4)
203 z0 = fourth*(z1 + z2 + z3 + z4)
206 x0 = third*(x1 + x2 + x3)
207 y0 = third*(y1 + y2 + y3)
208 z0 = third*(z1 + z2 + z3)
234 xm(1) = x1*h(1) + x2*h(2) + x3*h(3) + x4*h(4)
235 xm(2) = y1*h(1) + y2*h(2) + y3*h(3) + y4*h(4)
236 xm(3) = z1*h(1) + z2*h(2) + z3*h(3) + z4*h(4)
240 rs(1) = xs(1)*e1x + xs(2)*e1y + xs(3)*e1z
241 rs(2) = xs(1)*e2x + xs(2)*e2y + xs(3)*e2z
242 rs(3) = xs(1)*e3x + xs(2)*e3y + xs(3)*e3z
244 rm(1) = xm(1)*e1x + xm(2)*e1y + xm(3)*e1z
245 rm(2) = xm(1)*e2x + xm(2)*e2y + xm(3)*e2z
246 rm(3) = xm(1)*e3x + xm(2)*e3y + xm(3)*e3z
248 rx(1) = e1x*x1 + e1y*y1 + e1z*z1
249 ry(1) = e2x*x1 + e2y*y1 + e2z*z1
250 rz(1) = e3x*x1 + e3y*y1 + e3z*z1
251 rx(2) = e1x*x2 + e1y*y2 + e1z*z2
252 ry(2) = e2x*x2 + e2y*y2 + e2z*z2
253 rz(2) = e3x*x2 + e3y*y2 + e3z*z2
254 rx(3) = e1x*x3 + e1y*y3 + e1z*z3
255 ry(3) = e2x*x3 + e2y*y3 + e2z*z3
256 rz(3) = e3x*x3 + e3y*y3 + e3z*z3
257 rx(4) = e1x*x4 + e1y*y4 + e1z*z4
258 ry(4) = e2x*x4 + e2y*y4 + e2z*z4
259 rz(4) = e3x*x4 + e3y*y4 + e3z*z4
262 CALL i2cin_rot27(stbrk,rs,rm,rx(1),ry(1),rz(1),rx(2),ry(2),rz(2),rx(3),ry(3),rz(3),
263 . rx(4),ry(4),rz(4),bid9,dwdu,e1x,e1y,e1z,e2x,e2y,e2z,e3x,e3y,e3z,
270 . bid4 ,bid4 ,bid4 ,h ,stifm ,
271 . bid4 ,bid4 ,bid4 ,stifmr ,betax ,
276 . bid4 ,bid4 ,bid4 ,h ,stifm ,
277 . bid4 ,bid4 ,bid4 ,stifmr ,betax ,
289 IF ((iroddl/=0).AND.(msegtyp2(l)==0))
THEN
291 aa =(xm(1)-xs(1))*(xm(1)-xs(1))+(xm(2)-xs(2))*(xm(2)-xs(2))+(xm(3)-xs(3))*(xm(3)-xs(3))
292 ins = in(i) + aa * ms(i)
293 stf = stifr(i) + aa * stifn(i)
297 ms(j)=ms(j)+ms(i)*h2(jj)
298 stifn(j)=stifn(j)+stifn(i)*(one+stbrk)*(abs(h(jj))+stifm)+stifr(i)*stifmr*dwdu
299 in(j)=in(j)+ins*h2(jj)
300 stifr(j)=stifr(j)+abs(stf*h(jj))
311 ms(j)=ms(j)+ms(i)*h2(jj)
312 stifn(j)=stifn(j)+stifn(i)*(one+stbrk)*(abs(h(jj))+stifm)
333 2 IPARI,MSEGTYP2,STIFN, STIFR,STFN,
334 3 STFR,VISC,IN,IRUPT)
338#include "implicit_f.inc"
342 INTEGER IRECT(4,*),NSV(*),IRTL(*),MSEGTYP2(*),IPARI(*),IRUPT(*)
345 . X(3,*),IN(*),STIFN(*),STIFR(*),STFN(*),STFR(*),CRST(2,*),VISC
349#include "com01_c.inc"
353 INTEGER NIR,I,J,II,JJ,L,W,NN,KK,LLT,
354 . IX1, IX2, IX3, IX4,NSVG,NSN
357 . s,t,sp,sm,tp,tm,e1x,e1y,e1z,e2x,e2y,e2z,e3x,e3y,e3z,
358 . xsm,ysm,zsm,xm,ym,zm,x1,x2,x3,x4,y1,y2,y3,y4,z1,z2,z3,z4,x0,y0,z0,xs,ys,zs,stifm,
359 . stf,str,stbrk,b1,b2,b3,c1,c2,c3,det
361 . h(4),rx(4),ry(4),rz(4),rm(3),rs(3),stif, vis
363 . len2,fac_triang,irot,skew(9),tt,bid,bid3(4)
372 IF (irupt(ii) == 0) cycle
393 IF ((msegtyp2(l)==1).AND.(in(i)>em20))
THEN
439 CALL i2rep(x1 ,x2 ,x3 ,x4 ,
444 . e3x ,e3y ,e3z ,nir )
449 xm = x1*h(1) + x2*h(2) + x3*h(3) + x4*h(4)
450 ym = y1*h(1) + y2*h(2) + y3*h(3) + y4*h(4)
451 zm = z1*h(1) + z2*h(2) + z3*h(3) + z4*h(4)
453 y0 = (y1 + y2 + y3 + y4)/nir
454 z0 = (z1 + z2 + z3 + z4)/nir
469 x0 = (x1 + x2 + x3)/nir
470 y0 = (y1 + y2 + y3)/nir
471 z0 = (z1 + z2 + z3)/nir
473 xm = x1*h(1) + x2*h(2) + x3*h(3)
474 ym = y1*h(1) + y2*h(2) + y3*h(3)
475 zm = z1*h(1) + z2*h(2) + z3*h(3)
503 rs(1) = xs*e1x + ys*e1y + zs*e1z
504 rs(2) = xs*e2x + ys*e2y + zs*e2z
505 rs(3) = xs*e3x + ys*e3y + zs*e3z
506 rm(1) = xm*e1x + ym*e1y + zm*e1z
507 rm(2) = xm*e2x + ym*e2y + zm*e2z
508 rm(3) = xm*e3x + ym*e3y + zm*e3z
510 rx(1) = e1x*x1 + e1y*y1 + e1z*z1
511 ry(1) = e2x*x1 + e2y*y1 + e2z*z1
512 rz(1) = e3x*x1 + e3y*y1 + e3z*z1
513 rx(2) = e1x*x2 + e1y*y2 + e1z*z2
514 ry(2) = e2x*x2 + e2y*y2 + e2z*z2
515 rz(2) = e3x*x2 + e3y*y2 + e3z*z2
516 rx(3) = e1x*x3 + e1y*y3 + e1z*z3
517 ry(3) = e2x*x3 + e2y*y3 + e2z*z3
518 rz(3) = e3x*x3 + e3y*y3 + e3z*z3
519 rx(4) = e1x*x4 + e1y*y4 + e1z*z4
520 ry(4) = e2x*x4 + e2y*y4 + e2z*z4
521 rz(4) = e3x*x4 + e3y*y4 + e3z*z4
531 . skew ,tt ,bid ,stbrk,
532 . rs ,rm ,bid3 ,bid3 ,bid3 ,
533 . rx ,ry ,rz ,bid3 ,bid3 ,
534 . bid3 ,bid3 ,bid3 ,bid3 ,det ,
535 . b1 ,b2 ,b3 ,c1 ,c2 ,
540 stf = stfn(ii)*(visc + sqrt(visc**2 + (one+stbrk)))**2
545 IF (irot > zero)
THEN
549 len2 = xsm**2+ysm**2+zsm**2
550 str = (stfr(ii)+stfn(ii)*len2)*(visc + sqrt(visc**2 + one))**2
558 CALL i2loceq( nir ,rs ,rx ,ry ,rz ,
559 . bid3 ,bid3 ,bid3 ,h(1) ,stifm)
565 stifn(ix1) = stifn(ix1)+abs(stf*h(1))+stifm*stf
566 stifn(ix2) = stifn(ix2)+abs(stf*h(2))+stifm*stf
567 stifn(ix3) = stifn(ix3)+abs(stf*h(3))+stifm*stf
568 stifn(ix4) = stifn(ix4)+abs(stf*h(4))+stifm*stf*fac_triang
570 IF (iroddl == 1)
THEN
573 stifr(ix1) = stifr(ix1)+abs(str*h(1))
574 stifr(ix2) = stifr(ix2)+abs(str*h(2))
575 stifr(ix3) = stifr(ix3)+abs(str*h(3))
576 stifr(ix4) = stifr(ix4)+abs(str*h(4))
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)
subroutine i2pen_rot27(skew, tt, dt1, stif, rs, rm, vx, vy, vz, rx, ry, rz, va, vb, vc, vd, vrm, vrs, det, b1, b2, b3, c1, c2, c3, in_secnd)