OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
split_joint.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| split_joint ../starter/source/constraints/general/cyl_joint/split_joint.F
25!||--- called by ------------------------------------------------------
26!|| domdec2 ../starter/source/spmd/domdec2.F
27!||--- calls -----------------------------------------------------
28!|| ifrontplus ../starter/source/spmd/node/frontplus.F
29!|| nlocal ../starter/source/spmd/node/ddtools.F
30!|| plist_ifront ../starter/source/spmd/node/ddtools.F
31!||--- uses -----------------------------------------------------
32!|| joint_mod ../starter/share/modules1/joint_mod.F
33!||====================================================================
34 SUBROUTINE split_joint( )
35!$COMMENT
36! SPLIT_JOINT description
37! split the node(secondary & main node) on the different processor
38!
39! SPLIT_JOINT organization :
40! loop over the joint :
41! - for each joint, loop over the node to find where is the node
42! - for each node, add the ID node to the CYL_JOIN(I)%PROC(P)%NODE
43! - count the max number of secondary node in order to find the main proc
44! - if 1 secondary node is on a given proc --> need to add the 2 main nodes to the proc
45! - if 1 main node is on a given proc --> need to add the other main to the proc
46!$ENDCOMMENT
47C-----------------------------------------------
48C M o d u l e s
49C-----------------------------------------------
50 USE joint_mod
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "com01_c.inc"
59#include "com04_c.inc"
60C-----------------------------------------------
61C L o c a l V a r i a b l e s
62C-----------------------------------------------
63 INTEGER :: I,II,NS,LJ,K
64 INTEGER :: J,N,NN,IJK
65 INTEGER :: WEIGHT,M1
66 INTEGER :: P,PROC_NUMBER,NB_NODE
67 INTEGER, DIMENSION(NSPMD) :: PROC_LIST
68 INTEGER, EXTERNAL :: NLOCAL
69 LOGICAL, DIMENSION(:), ALLOCATABLE :: CHECK_MAIN
70 TYPE(joint_main_node), DIMENSION(:), ALLOCATABLE :: MAIN_AND_SECONDARY
71C-----------------------------------------------
72C E x t e r n a l F u n c t i o n s
73C-----------------------------------------------
74
75C=======================================================================
76 k = 0
77 ALLOCATE( check_main(numnod) )
78 check_main(1:numnod) = .false.
79 DO i=1,njoint
80 DO j=1,2
81 n = cyl_join(i)%MAIN_NODE(j)
82 check_main(n) = .true.
83 ENDDO
84 ENDDO
85 ALLOCATE( main_and_secondary(numnod) )
86
87 main_and_secondary(1:numnod)%ID_JOINT = 0
88 main_and_secondary(1:numnod)%NB_PROC = 0
89
90 DO i=1,njoint
91 proc_list(1:nspmd) = -1
92 proc_number = 0
93 ALLOCATE( cyl_join(i)%PROC(nspmd) )
94 cyl_join(i)%NB_NODE(1:nspmd) = 0
95 cyl_join(i)%PROC(1:nspmd)%NB_NODE_WEIGHT = 0
96 ns = cyl_join(i)%NB_SECONDARY_NODE
97 DO lj=1,ns
98 ! ----------------------
99 ! check where is the secondary node
100 proc_list(1:nspmd) = -1
101 proc_number = 0
102 nn = cyl_join(i)%SECONDARY_NODE(lj)
103 CALL plist_ifront(proc_list,nn,proc_number)
104 !returns in "PROC_LIST" array list of SPMD domains on which node I is sticked
105 !PROC_NUMBER is the number of SPMD domains on which node I is sticked
106
107! IF( CHECK_MAIN(NN) ) THEN
108! MAIN_AND_SECONDARY(NN)%ID_JOINT = I
109! MAIN_AND_SECONDARY(NN)%NB_PROC = PROC_NUMBER
110! ALLOCATE( MAIN_AND_SECONDARY(NN)%PROC_LIST(PROC_NUMBER) )
111! MAIN_AND_SECONDARY(NN)%PROC_LIST(1:PROC_NUMBER) = PROC_LIST(1:PROC_NUMBER)
112! ENDIF
113
114 ! add the secondary node to the CYL_JOINT structure for proc P
115 ! for the restart writing
116 DO ii=1,proc_number
117 p = proc_list(ii)
118 cyl_join(i)%NB_NODE(p) = cyl_join(i)%NB_NODE(p) + 1
119 IF(.NOT.ALLOCATED(cyl_join(i)%PROC(p)%NODE)) ALLOCATE( cyl_join(i)%PROC(p)%NODE(ns) )
120 cyl_join(i)%PROC(p)%NODE( cyl_join(i)%NB_NODE(p) ) = cyl_join(i)%SECONDARY_NODE(lj)
121 weight = 0
122 IF(ii==1) weight = 1
123 IF(.NOT.ALLOCATED(cyl_join(i)%PROC(p)%WEIGHT)) ALLOCATE( cyl_join(i)%PROC(p)%WEIGHT(ns) )
124 cyl_join(i)%PROC(p)%WEIGHT( cyl_join(i)%NB_NODE(p) ) = weight
125 IF(weight==1) cyl_join(i)%PROC(p)%NB_NODE_WEIGHT = cyl_join(i)%PROC(p)%NB_NODE_WEIGHT + 1
126 ENDDO
127 ! ----------------------
128 ENDDO
129 k=k+ns+1
130 ENDDO
131
132 ! ----------------------
133 ! loop over the CYL_JOINT in order to find the proc main
134 ! and add the main nodes to the processor where at least 1
135 ! secondary node is present
136 k = 0
137 DO i=1,njoint
138 proc_list(1:nspmd) = -1
139 proc_number = 0
140 ns = cyl_join(i)%NB_SECONDARY_NODE
141 nb_node = 0
142 proc_number = 0
143 cyl_join(i)%PROC_MAIN = -1
144 proc_list(1:nspmd) = 0
145 DO p=1,nspmd
146 IF(cyl_join(i)%NB_NODE(p)>0) THEN
147 proc_number = proc_number + 1
148 proc_list(proc_number) = p
149 nb_node = cyl_join(i)%NB_NODE(p)
150 ! add the 2 main nodes on each proc
151 DO ijk = 1,2
152 m1 = cyl_join(i)%MAIN_NODE(ijk)
153 IF(nlocal(m1,p)==0) THEN
154 CALL ifrontplus(m1,p)
155 cyl_join(i)%NB_NODE(p) = cyl_join(i)%NB_NODE(p) + 1
156 cyl_join(i)%PROC(p)%WEIGHT( cyl_join(i)%NB_NODE(p) ) = 0
157 cyl_join(i)%PROC(p)%NODE( cyl_join(i)%NB_NODE(p) ) = cyl_join(i)%SECONDARY_NODE(ijk)
158 ENDIF
159 ENDDO
160 IF(cyl_join(i)%NB_NODE(p)>=nb_node) cyl_join(i)%PROC_MAIN = p
161 ENDIF
162! M1 = CYL_JOIN(I)%MAIN_NODE(1)
163! M2 = CYL_JOIN(I)%MAIN_NODE(2)
164! IF(nlocal(m1,p)==1) CALL ifrontplus(m2,p)
165! IF(NLOCAL(M2,P)==1) CALL IFRONTPLUS(M1,P)
166 ENDDO
167 cyl_join(i)%NUMBER_PROC = proc_number
168 ALLOCATE( cyl_join(i)%LIST_PROC( proc_number ) )
169 cyl_join(i)%LIST_PROC(1:proc_number) = proc_list(1:proc_number)
170 k=k+ns+1
171 ENDDO
172
173
174
175 DO i=njoint,1,-1
176 proc_list(1:nspmd) = -1
177 proc_number = 0
178 ns = cyl_join(i)%NB_SECONDARY_NODE
179 nb_node = 0
180 proc_number = 0
181 cyl_join(i)%PROC_MAIN = -1
182 proc_list(1:nspmd) = 0
183 DO p=1,nspmd
184 IF(cyl_join(i)%NB_NODE(p)>0) THEN
185 proc_number = proc_number + 1
186 proc_list(proc_number) = p
187 nb_node = cyl_join(i)%NB_NODE(p)
188 ! add the 2 main nodes on each proc
189 DO ijk = 1,2
190 m1 = cyl_join(i)%MAIN_NODE(ijk)
191 IF(nlocal(m1,p)==0) THEN
192 CALL ifrontplus(m1,p)
193 cyl_join(i)%NB_NODE(p) = cyl_join(i)%NB_NODE(p) + 1
194 cyl_join(i)%PROC(p)%WEIGHT( cyl_join(i)%NB_NODE(p) ) = 0
195 cyl_join(i)%PROC(p)%NODE( cyl_join(i)%NB_NODE(p) ) = cyl_join(i)%SECONDARY_NODE(ijk)
196 ENDIF
197 ENDDO
198 IF(cyl_join(i)%NB_NODE(p)>=nb_node) cyl_join(i)%PROC_MAIN = p
199 ENDIF
200! M1 = CYL_JOIN(I)%MAIN_NODE(1)
201! M2 = CYL_JOIN(I)%MAIN_NODE(2)
202! IF(NLOCAL(M1,P)==1) CALL IFRONTPLUS(M2,P)
203! IF(NLOCAL(M2,P)==1) CALL IFRONTPLUS(M1,P)
204 ENDDO
205 k=k+ns+1
206 ENDDO
207
208
209 ! ----------------------
210 ! check : if a main node is on a processor, need to add the other main node
211! K = 0
212! DO I=1,NJOINT
213! PROC_LIST(1:NSPMD) = -1
214! PROC_NUMBER = 0
215! NS = CYL_JOIN(I)%NB_SECONDARY_NODE
216! NB_NODE = 0
217! PROC_NUMBER = 0
218! proc_list_1(1:nspmd) = 0
219! CALL PLIST_IFRONT(PROC_LIST_1,CYL_JOIN(I)%MAIN_NODE(1),PROC_NUMBER_1)
220! PROC_NUMBER_2 = 0
221! PROC_LIST_2(1:NSPMD) = 0
222! CALL PLIST_IFRONT(PROC_LIST_2,CYL_JOIN(I)%MAIN_NODE(2),PROC_NUMBER_2)!
223!
224! DO P=1,PROC_NUMBER_1
225! PROC = PROC_LIST_1(P)
226! CALL IFRONTPLUS(CYL_JOIN(I)%MAIN_NODE(2),PROC)
227! ENDDO
228! DO P=1,PROC_NUMBER_2
229! PROC = PROC_LIST_2(P)
230! CALL IFRONTPLUS(CYL_JOIN(I)%MAIN_NODE(1),PROC)
231! ENDDO
232! K=K+NS+1
233! ENDDO
234 ! ----------------------
235
236 DEALLOCATE( main_and_secondary )
237
238 RETURN
239 END SUBROUTINE split_joint
240
241
242
243
244!||====================================================================
245!|| print_joint ../starter/source/constraints/general/cyl_joint/split_joint.F
246!||--- calls -----------------------------------------------------
247!|| nlocal ../starter/source/spmd/node/ddtools.F
248!|| plist_ifront ../starter/source/spmd/node/ddtools.F
249!||--- uses -----------------------------------------------------
250!|| joint_mod ../starter/share/modules1/joint_mod.F
251!||====================================================================
252 SUBROUTINE print_joint(a)
253C-----------------------------------------------
254C M o d u l e s
255C-----------------------------------------------
256 USE joint_mod
257C-----------------------------------------------
258C I m p l i c i t T y p e s
259C-----------------------------------------------
260#include "implicit_f.inc"
261C-----------------------------------------------
262C C o m m o n B l o c k s
263C-----------------------------------------------
264#include "com01_c.inc"
265#include "com04_c.inc"
266C-----------------------------------------------
267C L o c a l V a r i a b l e s
268C-----------------------------------------------
269 character(len=*) :: a
270 INTEGER :: I,NS,K
271 INTEGER :: M1,M2
272 INTEGER :: P,PROC_NUMBER,NB_NODE
273 INTEGER, DIMENSION(NSPMD) :: PROC_LIST
274 INTEGER, EXTERNAL :: NLOCAL
275C-----------------------------------------------
276C E x t e r n a l F u n c t i o n s
277C-----------------------------------------------
278
279C=======================================================================
280 k = 0
281 DO i=1,njoint
282 proc_list(1:nspmd) = -1
283 proc_number = 0
284 ns = cyl_join(i)%NB_SECONDARY_NODE
285
286 nb_node = 0
287 proc_number = 0
288 cyl_join(i)%PROC_MAIN = -1
289 proc_list(1:nspmd) = 0
290 DO p=1,nspmd
291 m1 = cyl_join(i)%MAIN_NODE(1)
292 m2 = cyl_join(i)%MAIN_NODE(2)
293! IF(nlocal(m1,p)==1) CALL ifrontplus(m2,p)
294! IF(NLOCAL(M2,P)==1) CALL IFRONTPLUS(M1,P)
295! print*,' split_joint :',p,NLOCAL(M1,P),NLOCAL(M2,P)
296 ENDDO
297! CYL_JOIN(I)%NUMBER_PROC = PROC_NUMBER
298! ALLOCATE( CYL_JOIN(I)%LIST_PROC( PROC_NUMBER ) )
299! CYL_JOIN(I)%LIST_PROC(1:PROC_NUMBER) = PROC_LIST(1:PROC_NUMBER)
300 k=k+ns+1
301
302 proc_number = 0
303 CALL plist_ifront(proc_list,cyl_join(i)%MAIN_NODE(1),proc_number)
304 print*,' ------- '
305 print*,i,' M1:',a,proc_list(1:proc_number)
306 proc_number = 0
307 CALL plist_ifront(proc_list,cyl_join(i)%MAIN_NODE(2),proc_number)
308 print*,i,' M2:',a,proc_list(1:proc_number)
309 print*,' ------- '
310 print*,' '
311
312 ENDDO
313
314
315 RETURN
316 END SUBROUTINE print_joint
subroutine plist_ifront(tab, n, cpt)
Definition ddtools.F:153
end diagonal values have been computed in the(sparse) matrix id.SOL
subroutine ifrontplus(n, p)
Definition frontplus.F:100
#define max(a, b)
Definition macros.h:21
type(joint_type), dimension(:), allocatable cyl_join
Definition joint_mod.F:61
void split(mapping_t *, PORD_INT, PORD_INT, PORD_INT, PORD_INT *, PORD_INT *, FLOAT *, PORD_INT)
subroutine print_joint(a)
subroutine split_joint()
Definition split_joint.F:35
int main(int argc, char *argv[])