OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c_irbe2.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 c_irbe2 (irbe2, lrbe2, proc, nrbe2_l, slmn_l, nbddrbe2)

Function/Subroutine Documentation

◆ c_irbe2()

subroutine c_irbe2 ( integer, dimension(nrbe2l,*) irbe2,
integer, dimension(*) lrbe2,
integer proc,
integer nrbe2_l,
integer slmn_l,
integer nbddrbe2 )

Definition at line 32 of file c_irbe2.F.

34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
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 "com01_c.inc"
45#include "com04_c.inc"
46#include "param_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER PROC, NRBE2_L,SLMN_L,NBDDRBE2,
51 . IRBE2(NRBE2L,*), LRBE2(*)
52C-----------------------------------------------
53C F u n c t i o n
54C-----------------------------------------------
55 INTEGER NLOCAL
56 EXTERNAL nlocal
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I, J, K, NSN, ILP, N,P,M,NS,PROC1,SPLIST,SLMN_L0
61 INTEGER,DIMENSION(:), ALLOCATABLE :: MAIN_NODES,TAG,PLIST
62
63C-----------------------------------------------
64 ALLOCATE(main_nodes(nrbe2))
65 ALLOCATE(tag(numnod))
66 ALLOCATE(plist(nspmd))
67! ------------------------
68C
69C
70C NRBE2_L : Same initialization done in ddsplit
71C but cleaner to have it here once again.
72C
73 nrbe2_l = 0
74C
75 proc1 = proc + 1
76 slmn_l = 0
77 nbddrbe2 = 0
78 DO i = 1, nrbe2
79 nsn = irbe2(5,i)
80 k = irbe2(1,i)
81 m = irbe2(3,i)
82C----- only remove zero NSN (global) one to work the output(H3d)
83 IF (nsn==0) cycle
84 DO j = 1, nsn
85 ns = lrbe2(k+j)
86 IF(nlocal(ns,proc1)==1) slmn_l = slmn_l + 1
87 ENDDO
88C-----remove local nsn_l=0 will get spmd issue in engine (M in front)
89 IF (nlocal(m,proc1)==1)THEN
90 nrbe2_l = nrbe2_l+1
91C Stacking Main nodes.
92 main_nodes(nrbe2_l)=m
93 END IF
94 ENDDO
95C
96C Memory optimization - avoid NSPMD*NUMNOD array.
97C Fill a list with all RBE2 Main present on one domain
98C The issue, Main Nodes can appear twice, but one wants to
99C have it only one time.
100C One NUMNOD array is acceptable, other treatments in DDSPLIT take more.
101C
102 tag(1:numnod)=0
103C
104 DO i=1,nrbe2_l
105 m=main_nodes(i)
106
107 IF(tag(m)==0)THEN
108 tag(m)=1
109
110C List of All domains where M is sticked
111 CALL plist_ifront(plist,m,splist)
112 DO p=1,splist
113 IF( plist(p) /= proc1)THEN
114 nbddrbe2 = nbddrbe2 + 1
115 ENDIF
116 ENDDO
117 ENDIF
118 ENDDO
119C --------------------------------
120 DEALLOCATE(main_nodes)
121 DEALLOCATE(tag)
122C --------------------------------
123 RETURN
subroutine plist_ifront(tab, n, cpt)
Definition ddtools.F:153
integer function nlocal(n, p)
Definition ddtools.F:349