OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i1tid3.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "scr03_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine i1tid3 (x, irect, crst, msr, nsv, iloc, irtl, nsn, itab, ikine, ikine1, id, titr, ilev, nty, csts_bis)

Function/Subroutine Documentation

◆ i1tid3()

subroutine i1tid3 ( x,
integer, dimension(4,*) irect,
crst,
integer, dimension(*) msr,
integer, dimension(*) nsv,
integer, dimension(*) iloc,
integer, dimension(*) irtl,
integer nsn,
integer, dimension(*) itab,
integer, dimension(*) ikine,
integer, dimension(*) ikine1,
integer id,
character(len=nchartitle) titr,
integer ilev,
integer nty,
csts_bis )

Definition at line 35 of file i1tid3.F.

38C-----------------------------------------------
39C D e s c r i p t i o n
40C-----------------------------------------------
41C INTERFACE TIED CALCUL DE S,T
42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
45 USE message_mod
46 USE format_mod , ONLY : fmw_7i_2f
48C-----------------------------------------------
49C I m p l i c i t T y p e s
50C-----------------------------------------------
51#include "implicit_f.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "units_c.inc"
56#include "scr03_c.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 INTEGER NSN
61 INTEGER IRECT(4,*), MSR(*), NSV(*), ILOC(*), IRTL(*), ITAB(*),IKINE(*),IKINE1(*),ILEV,NTY
62 my_real x(3,*), crst(2,*), csts_bis(2,*)
63 INTEGER ID
64 CHARACTER(LEN=NCHARTITLE) :: TITR
65C-----------------------------------------------
66C L o c a l V a r i a b l e s
67C-----------------------------------------------
68 INTEGER II, I, J, K, L, JJ, NN, IER
70 . n1, n2, n3, ss, tt, alp
71 my_real :: xx1(4),xx2(4),xx3(4),xs1,ys1,zs1,xc,yc,zc
72C-----------------------------------------------
73C S o u r c e L i n e s
74C-----------------------------------------------
75 alp = twoem2
76 DO ii=1,nsn
77 i=nsv(ii)
78 IF ((nty==1).OR.((nty==2).AND.(ilev /= 25 .and. ilev /= 26 .and. ilev /= 27 .and. ilev /= 28))) THEN
79 CALL kinset(2,itab(i),ikine(i),1,0,ikine1(i))
80 CALL kinset(2,itab(i),ikine(i),2,0,ikine1(i))
81 CALL kinset(2,itab(i),ikine(i),3,0,ikine1(i))
82 CALL kinset(2,itab(i),ikine(i),4,0,ikine1(i))
83 CALL kinset(2,itab(i),ikine(i),5,0,ikine1(i))
84 CALL kinset(2,itab(i),ikine(i),6,0,ikine1(i))
85 ENDIF
86 j=iloc(ii)
87 k=msr(j)
88 l=irtl(ii)
89 DO jj=1,4
90 nn=msr(irect(jj,l))
91 xx1(jj)=x(1,nn)
92 xx2(jj)=x(2,nn)
93 xx3(jj)=x(3,nn)
94 ENDDO
95 xs1=x(1,i)
96 ys1=x(2,i)
97 zs1=x(3,i)
98 CALL inist3(n1,n2,n3,ss,tt,ier,alp,xx1,xx2,xx3,xs1,ys1,zs1,xc,yc,zc)
99 IF(ipri>=1)WRITE(iout,fmt=fmw_7i_2f)
100 . itab(i),itab(k),
101 . l,(itab(msr(irect(jj,l))),jj=1,4),ss,tt
102 IF(ier==-1)THEN
103 CALL ancmsg(msgid=85,
104 . msgtype=msgerror,
105 . anmode=aninfo,
106 . i1=id,
107 . c1=titr,
108 . i2=itab(i),
109 . i3=itab(k),
110 . i4=l,
111 . i5=itab(nsv(irect(1,l))),
112 . i6=itab(nsv(irect(2,l))),
113 . i7=itab(nsv(irect(3,l))),
114 . i8=itab(nsv(irect(4,l))))
115 ELSE IF(ier==1)THEN
116 CALL ancmsg(msgid=86,
117 . msgtype=msgwarning,
118 . anmode=aninfo_blind_2,
119 . i1=id,
120 . c1=titr,
121 . i2=itab(i),
122 . i3=itab(k),
123 . i4=l,
124 . i5=itab(msr(irect(1,l))),
125 . i6=itab(msr(irect(2,l))),
126 . i7=itab(msr(irect(3,l))),
127 . i8=itab(msr(irect(4,l))),
128 . r1=ss,
129 . r2=tt)
130 ENDIF
131 crst(1,ii)=ss
132 crst(2,ii)=tt
133 IF (nty == 2) THEN
134 csts_bis(1,ii)=ss
135 csts_bis(2,ii)=tt
136 ENDIF
137 enddo!next II
138C-----------------------------------------------
139 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine inist3(n1, n2, n3, ssc, ttc, ier, alp, xx1, xx2, xx3, xs1, ys1, zs1, xc, yc, zc)
Definition inist3.F:33
subroutine kinset(ik, node, ikine, idir, isk, ikine1)
Definition kinset.F:57
initmumps id
integer, parameter nchartitle
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889