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

Go to the source code of this file.

Functions/Subroutines

subroutine get_size_tag (flag_fvm, flag_tag, i24maxnsne, size_tag, ipari)
subroutine get_size_inter24 (i24maxnsne, ninter, npari, ipari, flag_24_25)
subroutine get_size_numnod_local (numnod, numnod_l)

Function/Subroutine Documentation

◆ get_size_inter24()

subroutine get_size_inter24 ( integer, intent(inout) i24maxnsne,
integer, intent(in) ninter,
integer, intent(in) npari,
integer, dimension(npari,*), intent(in) ipari,
logical, intent(inout) flag_24_25 )

Definition at line 86 of file get_size_tag.F.

87! ----------------------------------------------------------------
88! Description : GET_SIZE_INTER24 checks if NODLOCAL24 array is used and computes
89! the size of NODLOCAL24
90! NODLOCAL24 is used for the following interfaces:
91! 24 and 25
92! size of NODLOCAL24: NUMNOD + I24MAXNSNE
93! |
94! max NSNE for TYP24 ____|
95!
96! ----------------------------------------------------------------
97C-----------------------------------------------
98C I m p l i c i t T y p e s
99C-----------------------------------------------
100#include "implicit_f.inc"
101C-----------------------------------------------
102C D u m m y A r g u m e n t s
103C-----------------------------------------------
104! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
105! NINTER : integer, number of interface
106! NPARI : integer, size of IPARI
107! I24MAXNSNE : integer, size of TAG_SCRATCH for interface 24
108! FLAG_24_25 : logical, flag for interface 24 or 25
109! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
110 INTEGER, INTENT(IN) :: NINTER,NPARI
111 INTEGER, INTENT(INOUT) :: I24MAXNSNE
112 LOGICAL, INTENT(INOUT) :: FLAG_24_25
113 INTEGER, DIMENSION(NPARI,*), INTENT(IN) :: IPARI
114C-----------------------------------------------
115C L o c a l V a r i a b l e s
116C-----------------------------------------------
117 INTEGER :: NI,ITYP,NSNE
118C ----------------------------------------
119C Care TYPE24 + E2E
120C Edge to Edge Nodes fictive Nodes are numbered over NUMNOD
121C Tag Arrays must be increased accordingly
122 i24maxnsne = 0
123 flag_24_25 = .false.
124 DO ni= 1, ninter
125 ityp = ipari(7,ni)
126 IF(ityp==24)THEN
127 nsne = ipari(55,ni)
128 i24maxnsne = max(i24maxnsne,nsne)
129 ENDIF
130 IF( (ityp==24).OR.(ityp==25) ) flag_24_25 = .true.
131 ENDDO
132
#define max(a, b)
Definition macros.h:21

◆ get_size_numnod_local()

subroutine get_size_numnod_local ( integer, intent(in) numnod,
integer, dimension(nspmd), intent(inout) numnod_l )

Definition at line 142 of file get_size_tag.F.

143! ----------------------------------------------------------------
144! Description : GET_SIZE_NUMNOD_LOCAL computes the local number of
145! element on each domain
146! ----------------------------------------------------------------
147C-----------------------------------------------
148C I m p l i c i t T y p e s
149C-----------------------------------------------
150#include "implicit_f.inc"
151C-----------------------------------------------
152C C o m m o n B l o c k s
153C-----------------------------------------------
154#include "com01_c.inc"
155C-----------------------------------------------
156C D u m m y A r g u m e n t s
157C-----------------------------------------------
158 INTEGER, INTENT(IN) :: NUMNOD
159 INTEGER, DIMENSION(NSPMD), INTENT(INOUT) :: NUMNOD_L
160! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
161! NUMNOD : integer,
162! total number of element
163! NSPMD : integer,
164! number of domain
165! NUMNOD_L : integer, dimension=NSPMD
166! number of element on each domain
167! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*
168C-----------------------------------------------
169C L o c a l V a r i a b l e s
170C-----------------------------------------------
171 INTEGER I, J, ISPMD, NBR_PROC
172 INTEGER, DIMENSION(NSPMD) :: ID_SPMD
173C ----------------------------------------
174 numnod_l(1:nspmd) = 0
175 DO i=1,numnod
176 CALL plist_ifront(id_spmd,i,nbr_proc)
177#include "vectorize.inc"
178 DO j=1,nbr_proc
179 ispmd = id_spmd(j)
180 numnod_l(ispmd) = numnod_l(ispmd) + 1
181 ENDDO
182 ENDDO
183C
184 RETURN
subroutine plist_ifront(tab, n, cpt)
Definition ddtools.F:153

◆ get_size_tag()

subroutine get_size_tag ( logical, intent(in) flag_fvm,
logical, intent(inout) flag_tag,
integer, intent(in) i24maxnsne,
integer, intent(inout) size_tag,
integer, dimension(npari,*), intent(in) ipari )

Definition at line 26 of file get_size_tag.F.

27! ----------------------------------------------------------------
28! Description : GET_SIZE_TAG checks if TAG array is used and computes
29! the size of TAG
30! TAG is used for the following interfaces:
31! 7, 20, 22, 23, 24 and 25
32! size of TAG: NUMNOD + I24MAXNSNE + SIZE_FVM
33! | |
34! max NSNE for TYP24 ____| |
35! SIZE_FVM=NUMELS for INACTI=7 and FVM, otherwise 0 ___|
36! ----------------------------------------------------------------
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com04_c.inc"
45#include "param_c.inc"
46C-----------------------------------------------
47
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 LOGICAL, INTENT(INOUT) :: FLAG_TAG
52 LOGICAL, INTENT(IN) :: FLAG_FVM
53 INTEGER, INTENT(IN) :: I24MAXNSNE
54 INTEGER, INTENT(INOUT) :: SIZE_TAG
55 INTEGER, DIMENSION(NPARI,*), INTENT(IN) :: IPARI
56C-----------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59 INTEGER :: NI,ITYP,INACTI,SIZE_FVM
60C-----------------------------------------------
61C
62 flag_tag=.false.
63 size_fvm=0
64 size_tag=0
65 DO ni =1, ninter
66 ityp = ipari(7,ni)
67 inacti = ipari(22,ni)
68 IF( ityp==7.OR.ityp==20.OR.ityp==22.OR.ityp==23.OR.
69 . ityp==24.OR.ityp==25 ) THEN
70 flag_tag=.true.
71 size_tag = numnod+i24maxnsne
72 IF (flag_fvm .AND. inacti == 7) size_fvm = numels
73 ENDIF
74 ENDDO
75 IF(flag_tag) size_tag = numnod+i24maxnsne+size_fvm
76
77
78 RETURN