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

Go to the source code of this file.

Functions/Subroutines

subroutine w_group_str (len_ia, igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart, cep, cel, nodlocal, proc, frontb_r2r, numnod_l)

Function/Subroutine Documentation

◆ w_group_str()

subroutine w_group_str ( integer len_ia,
type (group_), dimension(ngrnod) igrnod,
type (group_), dimension(ngrbric) igrbric,
type (group_), dimension(ngrquad) igrquad,
type (group_), dimension(ngrshel) igrsh4n,
type (group_), dimension(ngrsh3n) igrsh3n,
type (group_), dimension(ngrtrus) igrtruss,
type (group_), dimension(ngrbeam) igrbeam,
type (group_), dimension(ngrspri) igrspring,
type (group_), dimension(ngrpart) igrpart,
integer, dimension(*) cep,
integer, dimension(*) cel,
integer, dimension(*) nodlocal,
integer proc,
integer, dimension(*) frontb_r2r,
integer numnod_l )

Definition at line 33 of file w_group_str.F.

37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE groupdef_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com04_c.inc"
49#include "tabsiz_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER LEN_IA,CEP(*),CEL(*),NODLOCAL(*),PROC,FRONTB_R2R(*),NUMNOD_L
54!
55 TYPE (GROUP_) , DIMENSION(NGRNOD) :: IGRNOD
56 TYPE (GROUP_) , DIMENSION(NGRBRIC) :: IGRBRIC
57 TYPE (GROUP_) , DIMENSION(NGRQUAD) :: IGRQUAD
58 TYPE (GROUP_) , DIMENSION(NGRSHEL) :: IGRSH4N
59 TYPE (GROUP_) , DIMENSION(NGRSH3N) :: IGRSH3N
60 TYPE (GROUP_) , DIMENSION(NGRTRUS) :: IGRTRUSS
61 TYPE (GROUP_) , DIMENSION(NGRBEAM) :: IGRBEAM
62 TYPE (GROUP_) , DIMENSION(NGRSPRI) :: IGRSPRING
63 TYPE (GROUP_) , DIMENSION(NGRPART) :: IGRPART
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67 INTEGER ESHIFT
68C-----------------------------------------------
69! --- WRITE IGRNOD ---
70 IF (ngrnod > 0) CALL w_gr_entity_n(igrnod ,ngrnod ,len_ia,lenigrnod,nodlocal,
71 . proc ,frontb_r2r,numnod_l)
72! --- WRITE IGRBRIC ---
73 eshift = 0
74 IF (ngrbric > 0) CALL w_gr_entity_e(igrbric,ngrbric,len_ia,lenigrbric,cep,
75 . cel ,proc ,eshift)
76! --- WRITE IGRQUAD ---
77 eshift = eshift + numels
78 IF (ngrquad > 0) CALL w_gr_entity_e(igrquad,ngrquad,len_ia,lenigrquad,cep,
79 . cel ,proc ,eshift)
80! --- WRITE IGRSH4N ---
81 eshift = eshift + numelq
82 IF (ngrshel > 0) CALL w_gr_entity_e(igrsh4n,ngrshel,len_ia,lenigrsh4n,cep,
83 . cel ,proc ,eshift)
84! --- WRITE IGRTRUSS ---
85 eshift = eshift + numelc
86 IF (ngrtrus > 0) CALL w_gr_entity_e(igrtruss,ngrtrus,len_ia,lenigrtrus,cep,
87 . cel ,proc ,eshift)
88! --- WRITE IGRBEAM ---
89 eshift = eshift + numelt
90 IF (ngrbeam > 0) CALL w_gr_entity_e(igrbeam,ngrbeam,len_ia,lenigrbeam,cep,
91 . cel ,proc ,eshift)
92! --- WRITE IGRSPRING ---
93 eshift = eshift + numelp
94 IF (ngrspri > 0) CALL w_gr_entity_e(igrspring,ngrspri,len_ia,lenigrspri,cep,
95 . cel ,proc ,eshift)
96! --- WRITE IGRSH3N ---
97 eshift = eshift + numelr
98 IF (ngrsh3n > 0) CALL w_gr_entity_e(igrsh3n,ngrsh3n,len_ia,lenigrsh3n,cep,
99 . cel ,proc ,eshift)
100!! ESHIFT = ESHIFT + NUMELTG
101! --- WRITE IGRPART ---
102 IF (ngrpart > 0) CALL w_gr_entity_p(igrpart,ngrpart,len_ia,lenigrpart,cep,
103 . cel ,proc )
104!---------
105 RETURN
subroutine w_gr_entity_e(igr, ngr, len_ia, lenigr, cep, cel, proc, eshift)
Definition w_gr_entity.F:33
subroutine w_gr_entity_p(igr, ngr, len_ia, lenigr, cep, cel, proc)
subroutine w_gr_entity_n(igr, ngr, len_ia, lenigr, nodlocal, proc, frontb_r2r, numnod_l)