OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i3sti2.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine i3sti2 (x, irect, stf, ixq, pm, nrt, stfn, nseg, lnsv, nint, nsn, nsv, slsfac, noint, ipm, id, titr, areas, knod2elq, nod2elq, nty, nsns, nsvs, segquadfr)

Function/Subroutine Documentation

◆ i3sti2()

subroutine i3sti2 ( x,
integer, dimension(4,*) irect,
stf,
integer, dimension(7,*) ixq,
pm,
integer nrt,
stfn,
integer, dimension(*) nseg,
integer, dimension(*) lnsv,
integer nint,
integer nsn,
integer, dimension(*) nsv,
slsfac,
integer noint,
integer, dimension(npropmi,*) ipm,
integer id,
character(len=nchartitle) titr,
areas,
integer, dimension(*) knod2elq,
integer, dimension(*) nod2elq,
integer nty,
integer nsns,
integer, dimension(*) nsvs,
integer, dimension(2,*) segquadfr )

Definition at line 37 of file i3sti2.F.

43C-----------------------------------------------
44C M o d u l e s
45C-----------------------------------------------
46 USE message_mod
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 "com01_c.inc"
56#include "com04_c.inc"
57#include "param_c.inc"
58C-----------------------------------------------
59C D u m m y A r g u m e n t s
60C-----------------------------------------------
61 INTEGER NRT, NINT, NSN, NOINT, NTY, NSNS, IPM(NPROPMI,*)
63 . slsfac
64 INTEGER IRECT(4,*), IXQ(7,*), NSEG(*), LNSV(*), NSV(*),
65 . KNOD2ELQ(*),NOD2ELQ(*), NSVS(*), SEGQUADFR(2,*)
67 . x(3,*), stf(*), pm(npropm,*), stfn(*),areas(*)
68 INTEGER ID
69 CHARACTER(LEN=NCHARTITLE) :: TITR
70C-----------------------------------------------
71C L o c a l V a r i a b l e s
72C-----------------------------------------------
73 INTEGER I, II, NEL, MT, J, NUM, NPT, JJ, LL, IG, IL, IE, INRT,
74 . N1 ,N2 ,STAT, ILINE, LIN, L, N, K
75 INTEGER LINES(2,4)
76 INTEGER, DIMENSION(:),ALLOCATABLE ::INRTIE
77C REAL
79 . area, xl2, ym1, ym2, zm1, zm2,ye(4) ,ze(4),
80 . y1 ,y2 ,z1 ,z2
81 DATA lines/1,2,
82 . 2,3,
83 . 3,4,
84 . 4,1/
85C-----------------------------------------------
86C E x t e r n a l F u n c t i o n s
87C-----------------------------------------------
88C
89 ALLOCATE(inrtie(numelq),stat=stat)
90 IF (stat /= 0) CALL ancmsg(msgid=268,anmode=aninfo,
91 . msgtype=msgerror,
92 . c1='INRTIE')
93 inrtie(1:numelq)=0
94C
95 DO i=1,nrt
96 ii=i
97 CALL inrch2(x , irect,ixq, ii , nel,
98 . nint, ym1 ,ym2, zm1,
99 . zm2 , ye ,ze , id , titr)
100 IF(nel/=0) THEN
101 inrtie(nel) = ii
102 CALL inare2(area,ye ,ze)
103 xl2=(ym2-ym1)**2+(zm2-zm1)**2
104 mt=ixq(1,nel)
105 IF(mt>0)THEN
106 stf(i)=slsfac*xl2*pm(32,mt)/area
107 ELSE
108 stf(i)=zero
109 CALL ancmsg(msgid=347,
110 . msgtype=msgwarning,
111 . anmode=aninfo_blind_2,
112 . i1=id,
113 . c1=titr,
114 . i2=ipm(1,mt),
115 . i3=nel,
116 . i4=i)
117C
118 ENDIF
119 ELSE
120 stf(i)=zero
121 ENDIF
122C
123 CALL inori2(irect,ii,nel,nint,
124 . noint, ym1, ym2, zm1,zm2 ,
125 . ye ,ze)
126 ENDDO
127C---------------------------------------------
128C CALCUL DES RIGIDITES NODALES
129C---------------------------------------------
130 DO j=1,nsn
131 num=nseg(j+1)-nseg(j)
132 npt=nseg(j)-1
133 DO jj=1,num
134 ll=lnsv(npt+jj)
135 stfn(j)=stfn(j) + half*stf(ll)
136 ENDDO
137 ENDDO
138
139C---------------------------------------------
140C SECND NODAL SURFACE COMPUTATION
141C---------------------------------------------
142C
143 IF(nty == 3) THEN
144 DO i = 1,nsn
145 areas(i) = zero
146 DO j= knod2elq(nsv(i))+1,knod2elq(nsv(i)+1)
147 ie = nod2elq(j)
148 inrt = inrtie(ie)
149 IF(inrt/=0)THEN
150 n1=irect(1,inrt)
151 n2=irect(2,inrt)
152 y1=x(2,n1)
153 z1=x(3,n1)
154 y2=x(2,n2)
155 z2=x(3,n2)
156c
157 area = sqrt((y2-y1)*(y2-y1)+(z2-z1)*(z2-z1))
158 area = area*half
159c
160 areas(i) = areas(i) + area
161 ENDIF
162 ENDDO
163 ENDDO
164 ELSEIF(nty == 5) THEN
165 DO i = 1,nsns
166 areas(i) = zero
167 DO j= knod2elq(nsvs(i))+1,knod2elq(nsvs(i)+1)
168 ie = nod2elq(j)
169 lin = -huge(lin)
170 DO l=1,4
171 IF(ixq(lines(1,l)+1,ie) ==nsvs(i)) THEN
172 lin = l
173 EXIT
174 ENDIF
175 ENDDO
176
177 DO k=1,nsegquadfr
178 n =segquadfr(1,k)
179 iline=segquadfr(2,k)
180
181 IF(n==ie.AND.iline==lin) THEN
182
183 n1=ixq(lines(1,iline)+1,n)
184 n2=ixq(lines(2,iline)+1,n)
185
186 y1=x(2,n1)
187 z1=x(3,n1)
188 y2=x(2,n2)
189 z2=x(3,n2)
190
191 area = sqrt((y2-y1)*(y2-y1)+(z2-z1)*(z2-z1))
192 area = area*half
193
194 areas(i) = areas(i) + area
195 ENDIF
196 ENDDO
197 ENDDO
198 ENDDO
199 ENDIF
200 DEALLOCATE(inrtie)
201
202C-----------------------------------------------------
203C MISE DANS IRECT DU NUMERO LOCAL DU NOEUD
204C-----------------------------------------------------
205 DO i=1,nrt
206 ig=irect(1,i)
207 CALL local_index(il,ig,nsv,nsn)
208 irect(1,i)=il
209 ig=irect(2,i)
210 CALL local_index(il,ig,nsv,nsn)
211 irect(2,i)=il
212 ENDDO
213C
214 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine area(d1, x, x2, y, y2, eint, stif0)
subroutine inare2(area, ye, ze)
Definition inare2.F:31
subroutine inori2(irect, isg, nel, nint, noint, ym1, ym2, zm1, zm2, ye, ze)
Definition inori2.F:34
subroutine inrch2(x, irect, ico, isg, nel, nint, ym1, ym2, zm1, zm2, ye, ze, id, titr)
Definition inrch2.F:37
subroutine local_index(il, ig, nodes, n)
Definition local_index.F:37
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