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

Go to the source code of this file.

Functions/Subroutines

subroutine fvventholeint (ibuf, elem, ibaghol, nvent, igrsurf, itagel, nn, nel, nb_node)

Function/Subroutine Documentation

◆ fvventholeint()

subroutine fvventholeint ( integer, dimension(*) ibuf,
integer, dimension(3,*) elem,
integer, dimension(nibhol,*) ibaghol,
integer nvent,
type (surf_), dimension(nsurf) igrsurf,
integer, dimension(*) itagel,
integer nn,
integer nel,
integer nb_node )

Definition at line 29 of file fvventholeint.F.

32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE groupdef_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "param_c.inc"
44#include "com04_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER IBUF(*), ELEM(3,*), IBAGHOL(NIBHOL,*),
49 . NVENT,
50 . ITAGEL(*), NN, NEL, NB_NODE
51 TYPE (SURF_) , DIMENSION(NSURF) :: IGRSURF
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER I, II, ITABINV(NB_NODE), ITAGVENT(NN),
56 . ISU, NELSU, IEL, NG1, NG2, NG3, NG4, N1, N2, N3, N4,
57 . IVENT, NALL, NN1, NN2, IVENTYP
58C----------------------------------------------------
59 DO i=1,nb_node
60 itabinv(i)=0
61 ENDDO
62C
63 DO i=1,nn
64 ii=ibuf(i)
65 itabinv(ii)=i
66 itagvent(i)=0
67 ENDDO
68C
69 DO ivent=1,nvent
70 isu=ibaghol(2,ivent)
71 IF(isu == 0) cycle
72 iventyp=ibaghol(13,ivent)
73 IF(iventyp == 0) cycle
74 nelsu=igrsurf(isu)%NSEG
75 DO i=1,nelsu
76 ng1 = igrsurf(isu)%NODES(i,1)
77 ng2 = igrsurf(isu)%NODES(i,2)
78 ng3 = igrsurf(isu)%NODES(i,3)
79 ng4 = igrsurf(isu)%NODES(i,4)
80 n1=itabinv(ng1)
81 n2=itabinv(ng2)
82 n3=itabinv(ng3)
83 n4=itabinv(ng4)
84 itagvent(n1)=ivent
85 itagvent(n2)=ivent
86 itagvent(n3)=ivent
87 itagvent(n4)=ivent
88 ENDDO
89 ENDDO
90C
91 DO iel=1,nel
92 IF(itagel(iel) > 0) cycle ! injecteur
93 n1=elem(1,iel)
94 n2=elem(2,iel)
95 n3=elem(3,iel)
96 nall=itagvent(n1)*itagvent(n2)*itagvent(n3)
97 IF(nall/=0) THEN
98 nn1=itagvent(n2)-itagvent(n1)
99 nn2=itagvent(n3)-itagvent(n1)
100 IF (nn1 == 0 .AND. nn2 == 0) itagel(iel)=-itagvent(n1)
101 ENDIF
102 ENDDO
103C
104 RETURN