OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
lag_ntag.F File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine init_int (i, j)
subroutine init_intv (intv, len)
subroutine ltag_bcs (comntag, ngrnod, igrnod, ibcslag)
subroutine ltag_i2main (comntag, ipari, intbuf_tab)
subroutine ltag_i2 (irect, nsv, irtl, comntag, nsn)
subroutine ltag_fxv (comntag, ibfv)
subroutine ltag_gjnt (comntag, gjbufi)
subroutine ltag_mpc (comntag, impcnc, impcnn)
subroutine ltag_rby (comntag, npbyl, lpbyl)

Function/Subroutine Documentation

◆ init_int()

subroutine init_int ( integer i,
integer j )

Definition at line 30 of file lag_ntag.F.

31C !!!! I est reel a l'appel
32 INTEGER I,J
33 i = j
34 RETURN

◆ init_intv()

subroutine init_intv ( integer, dimension(*) intv,
integer len )

Definition at line 43 of file lag_ntag.F.

44#include "implicit_f.inc"
45 INTEGER LEN, INTV(*)
46 INTEGER I
47 DO i = 1,len
48 intv(i) = 0
49 ENDDO
50 RETURN

◆ ltag_bcs()

subroutine ltag_bcs ( integer, dimension(*) comntag,
integer ngrnod,
type (group_), dimension(ngrnod) igrnod,
integer, dimension(5,*) ibcslag )

Definition at line 61 of file lag_ntag.F.

62C-----------------------------------------------
63C M o d u l e s
64C-----------------------------------------------
65 USE groupdef_mod
66C-----------------------------------------------
67C I m p l i c i t T y p e s
68C-----------------------------------------------
69#include "implicit_f.inc"
70C-----------------------------------------------
71C C o m m o n B l o c k s
72C-----------------------------------------------
73#include "lagmult.inc"
74C-----------------------------------------------
75C D u m m y A r g u m e n t s
76C-----------------------------------------------
77 INTEGER IBCSLAG(5,*),COMNTAG(*),NGRNOD
78C-----------------------------------------------
79 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
80C-----------------------------------------------
81C L o c a l V a r i a b l e s
82C-----------------------------------------------
83 INTEGER I,N,IGR,NN
84C======================================================================|
85 DO i=1,nbcslag
86 igr = ibcslag(1,i)
87 DO n=1,igrnod(igr)%NENTITY
88 nn=igrnod(igr)%ENTITY(n)
89 comntag(nn) = comntag(nn) + 1
90 ENDDO
91 ENDDO
92C---
93 RETURN

◆ ltag_fxv()

subroutine ltag_fxv ( integer, dimension(*) comntag,
integer, dimension(nifv,*) ibfv )

Definition at line 181 of file lag_ntag.F.

182C-----------------------------------------------
183C I m p l i c i t T y p e s
184C-----------------------------------------------
185#include "implicit_f.inc"
186C-----------------------------------------------
187C C o m m o n B l o c k s
188C-----------------------------------------------
189#include "param_c.inc"
190#include "com04_c.inc"
191C-----------------------------------------------
192C D u m m y A r g u m e n t s
193C-----------------------------------------------
194 INTEGER IBFV(NIFV,*), COMNTAG(*)
195C-----------------------------------------------
196C L o c a l V a r i a b l e s
197C-----------------------------------------------
198 INTEGER N, NN
199C======================================================================|
200 DO n=1,nfxvel
201 IF (ibfv(8,n)/=0) THEN
202 nn = iabs(ibfv(1,n))
203 comntag(nn) = comntag(nn) + 1
204 ENDIF
205 ENDDO
206C---
207 RETURN

◆ ltag_gjnt()

subroutine ltag_gjnt ( integer, dimension(*) comntag,
integer, dimension(lkjni,*) gjbufi )

Definition at line 214 of file lag_ntag.F.

215C-----------------------------------------------
216C I m p l i c i t T y p e s
217C-----------------------------------------------
218#include "implicit_f.inc"
219C-----------------------------------------------
220C C o m m o n B l o c k s
221C-----------------------------------------------
222#include "param_c.inc"
223C-----------------------------------------------
224C D u m m y A r g u m e n t s
225C-----------------------------------------------
226 INTEGER GJBUFI(LKJNI,*), COMNTAG(*)
227C-----------------------------------------------
228C L o c a l V a r i a b l e s
229C-----------------------------------------------
230 INTEGER I,JTYP,N0,N1,N2,N3
231C======================================================================|
232 DO i=1,ngjoint
233 jtyp= gjbufi(2,i)
234 n0 = gjbufi(3,i)
235 n1 = gjbufi(4,i)
236 n2 = gjbufi(5,i)
237 n3 = gjbufi(6,i)
238 comntag(n0) = comntag(n0) + 1
239 comntag(n1) = comntag(n1) + 1
240 comntag(n2) = comntag(n2) + 1
241 IF (jtyp==2) comntag(n3) = comntag(n3) + 1
242 ENDDO
243C---
244 RETURN

◆ ltag_i2()

subroutine ltag_i2 ( integer, dimension(4,*) irect,
integer, dimension(*) nsv,
integer, dimension(*) irtl,
integer, dimension(*) comntag,
integer nsn )

Definition at line 146 of file lag_ntag.F.

147C-----------------------------------------------
148C I m p l i c i t T y p e s
149C-----------------------------------------------
150#include "implicit_f.inc"
151C-----------------------------------------------
152C D u m m y A r g u m e n t s
153C-----------------------------------------------
154 INTEGER NSN, IRECT(4,*), NSV(*), IRTL(*), COMNTAG(*)
155C-----------------------------------------------
156C L o c a l V a r i a b l e s
157C-----------------------------------------------
158 INTEGER II, JJ, L, NN, NIR, N4
159C-----------------------------------------------
160 DO ii=1,nsn
161 l = irtl(ii)
162 nn = nsv(ii)
163 comntag(nn) = comntag(nn) + 1
164 nir = 3
165 DO jj=1,3
166 nn = irect(jj,l)
167 comntag(nn) = comntag(nn) + 1
168 ENDDO
169 n4 = irect(4,l)
170 IF (n4/=irect(3,l)) comntag(n4) = comntag(n4) + 1
171 ENDDO
172C---
173 RETURN

◆ ltag_i2main()

subroutine ltag_i2main ( integer, dimension(*) comntag,
integer, dimension(npari,ninter) ipari,
type(intbuf_struct_), dimension(*) intbuf_tab )

Definition at line 105 of file lag_ntag.F.

106C-----------------------------------------------
107C M o d u l e s
108C-----------------------------------------------
109 USE intbufdef_mod
110C-----------------------------------------------
111C I m p l i c i t T y p e s
112C-----------------------------------------------
113#include "implicit_f.inc"
114C-----------------------------------------------
115C C o m m o n B l o c k s
116C-----------------------------------------------
117#include "param_c.inc"
118#include "com04_c.inc"
119C-----------------------------------------------
120C D u m m y A r g u m e n t s
121C-----------------------------------------------
122 INTEGER IPARI(NPARI,NINTER), COMNTAG(*)
123C-----------------------------------------------
124C L o c a l V a r i a b l e s
125C-----------------------------------------------
126 INTEGER NTY,ILAGM,NSN,NMN,NRTS,NRTM,NIN
127
128 TYPE(INTBUF_STRUCT_) INTBUF_TAB(*)
129C======================================================================|
130 DO nin=1,ninter
131 IF (ipari(33,nin)==1.AND.ipari(7,nin)==2) THEN
132 nrts = ipari(3,nin)
133 nrtm = ipari(4,nin)
134 nsn = ipari(5,nin)
135 nmn = ipari(6,nin)
136 CALL ltag_i2(intbuf_tab(nin)%IRECTM,intbuf_tab(nin)%NSV,intbuf_tab(nin)%IRTLM,comntag,nsn )
137 ENDIF
138 ENDDO
139 RETURN
subroutine ltag_i2(irect, nsv, irtl, comntag, nsn)
Definition lag_ntag.F:147

◆ ltag_mpc()

subroutine ltag_mpc ( integer, dimension(*) comntag,
integer, dimension(*) impcnc,
integer, dimension(*) impcnn )

Definition at line 252 of file lag_ntag.F.

253C-----------------------------------------------
254C I m p l i c i t T y p e s
255C-----------------------------------------------
256#include "implicit_f.inc"
257C-----------------------------------------------
258C C o m m o n B l o c k s
259C-----------------------------------------------
260#include "param_c.inc"
261C-----------------------------------------------
262C D u m m y A r g u m e n t s
263C-----------------------------------------------
264 INTEGER IMPCNC(*), IMPCNN(*), COMNTAG(*)
265C-----------------------------------------------
266C L o c a l V a r i a b l e s
267C-----------------------------------------------
268 INTEGER I, J, KF, NN
269C======================================================================|
270 kf = 0
271 DO i=1,nummpc
272 DO j=1,impcnc(i)
273 kf = kf+1
274 nn = impcnn(kf)
275 comntag(nn) = comntag(nn) + 1
276 ENDDO
277 ENDDO
278C---
279 RETURN

◆ ltag_rby()

subroutine ltag_rby ( integer, dimension(*) comntag,
integer, dimension(nnpby,*) npbyl,
integer, dimension(*) lpbyl )

Definition at line 287 of file lag_ntag.F.

288C-----------------------------------------------
289C I m p l i c i t T y p e s
290C-----------------------------------------------
291#include "implicit_f.inc"
292C-----------------------------------------------
293C C o m m o n B l o c k s
294C-----------------------------------------------
295#include "lagmult.inc"
296#include "param_c.inc"
297C-----------------------------------------------
298C D u m m y A r g u m e n t s
299C-----------------------------------------------
300 INTEGER COMNTAG(*), NPBYL(NNPBY,*), LPBYL(*)
301C-----------------------------------------------
302C L o c a l V a r i a b l e s
303C-----------------------------------------------
304 INTEGER I,N,NN,MSL,TNSL
305C======================================================================|
306 tnsl = 0
307 DO n = 1,nrbylag
308 msl = npbyl(2,n)
309 DO i=1,msl
310 nn = lpbyl(tnsl+i)
311 comntag(nn) = comntag(nn) + 1
312 ENDDO
313 tnsl = tnsl + msl*3
314 ENDDO
315C---
316 RETURN