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

Go to the source code of this file.

Functions/Subroutines

subroutine split_asspar4 (addcne, numnod, nthreads, first, last, sadsky)

Function/Subroutine Documentation

◆ split_asspar4()

subroutine split_asspar4 ( integer, dimension(*), intent(in) addcne,
integer, intent(in) numnod,
integer, intent(in) nthreads,
integer, dimension(nthreads) first,
integer, dimension(nthreads) last,
integer, intent(in) sadsky )

Definition at line 28 of file split_asspar4.F.

29C-----------------------------------------------
30C I m p l i c i t T y p e s
31C-----------------------------------------------
32#include "implicit_f.inc"
33C-----------------------------------------------
34C C o m m o n B l o c k s
35C-----------------------------------------------
36
37! -----------------------------------------------
38! Global arguments
39 INTEGER, INTENT(IN) :: SADSKY,NUMNOD,NTHREADS
40 INTEGER, DIMENSION(*), INTENT(IN) :: ADDCNE
41 INTEGER, DIMENSION(NTHREADS) :: FIRST,LAST
42
43! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
44! SADSKY : integer ; dimension of ADDCNE
45! NUMNOD : integer ; Number of node
46! NTHREADS : integer ; number of OpenMP threads
47! ADDCNE : integer ; dimension=NUMNOD+2 (0:NUMNOD+1)
48! address for assembling
49! FIRST : integer ; dimension=NTHREADS
50! address of the first node for each thread
51! LAST : integer ; dimension=NTHREADS
52! address of the last node for each thread
53! -*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-**-*-*-*-*-*-*-*-*-*-*-*-*
54! -----------------------------------------------
55 INTEGER :: NC,SUM_NC,ITHREAD,N
56 INTEGER, DIMENSION(NTHREADS) :: SUM_NC_THREAD
57 my_real :: mean_nc
58! -----------------------------------------------
59
60C-----------------------------------------------
61C S o u r c e L i n e s
62C-----------------------------------------------
63!$COMMENT
64! SPLIT_ASSPAR4 description
65! initialization of the bounds for each thread
66! a fixed split(ie. use numnod/nthreads bounds
67! does not guarantee a optimized split in asspar4)
68!
69! SPLIT_ASSPAR4 organization :
70! - compute the total number of contribution
71! - compute FIRST and LAST bounds according to
72! the number of contribution
73!$ENDCOMMENT
74
75 ! FIRST and LAST initializations
76 DO ithread=1,nthreads
77 first(ithread)= 1+(ithread-1)*numnod/nthreads
78 last(ithread)= ithread*numnod/nthreads
79 ENDDO
80
81 IF(sadsky>0) THEN
82
83 ! compute the total number of contribution + mean
84 sum_nc = 0
85 DO n = 1,numnod
86 nc = addcne(n+1)-addcne(n)
87 sum_nc = sum_nc + nc
88 ENDDO
89
90 mean_nc = sum_nc / nthreads
91
92 sum_nc = 0
93 IF(numnod>0) THEN
94 ! first case : NUMNOD>NTHREADS --> try to split according to the number of contribution
95 IF(numnod>nthreads) THEN
96 ithread = 1
97 first(ithread) = 1
98 ! ------------------------
99 DO n = 1,numnod
100 nc = addcne(n+1)-addcne(n)
101 sum_nc = sum_nc + nc
102 IF(sum_nc> 0.95*mean_nc.AND.(ithread<nthreads+1) ) THEN
103 sum_nc_thread(ithread) = sum_nc
104 sum_nc = 0
105 last(ithread) = n
106 ithread = ithread + 1
107 IF(ithread<nthreads+1) first(ithread) = n+1
108 ENDIF
109 ENDDO
110 ! ------------------------
111 IF(ithread<nthreads) THEN
112 ! fail to split according to the nbr of contribution
113 ! --> back to a classical splitting (static splitting)
114 DO ithread=1,nthreads
115 first(ithread)= 1+(ithread-1)*numnod/nthreads
116 last(ithread)= ithread*numnod/nthreads
117 ENDDO
118 ELSE
119 ! splitting success : force the last bound
120 ithread = nthreads
121 last(ithread) = numnod
122 sum_nc_thread(ithread) = sum_nc
123 ENDIF
124 ! ------------------------
125 ELSE
126 ! ------------------------
127 ! second case : NUMNOD<NTHREADS --> classical splitting (static splitting)
128 DO ithread=1,nthreads
129 first(ithread)= 1+(ithread-1)*numnod/nthreads
130 last(ithread)= ithread*numnod/nthreads
131 ENDDO
132 ! ------------------------
133
134 ENDIF
135 ENDIF
136 ENDIF
137
138 RETURN
#define my_real
Definition cppsort.cpp:32
void split(mapping_t *, PORD_INT, PORD_INT, PORD_INT, PORD_INT *, PORD_INT *, FLOAT *, PORD_INT)