source: palm/tags/release-3.6/UTIL/find_palm_config.f90 @ 4095

Last change on this file since 4095 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 10.9 KB
Line 
1 PROGRAM find_palm_config
2
3!------------------------------------------------------------------------------!
4! Description:
5! -------------
6! Find possible configurations for given processor and grid point numbers
7!------------------------------------------------------------------------------!
8
9    IMPLICIT NONE
10
11    CHARACTER (LEN=1) ::  char = ''
12    INTEGER ::  count = 0, i, ii(1), j, k, maximum_grid_level, mg_levels_x, &
13                mg_levels_y, mg_levels_z, n, numprocs, numprocs_max,        &
14                numprocs_min, nx, nxanz, nx_max, nx_min, ny, nyanz, ny_max, &
15                ny_min, nz, nz_max, nz_min, pdims(2)
16    INTEGER ::  numnx(10000), numpr(10000)
17    LOGICAL ::  cubic_domain = .FALSE., found, found_once = .FALSE., &
18                one_d_decomp = .FALSE., quadratic_domain_xy = .FALSE.
19    REAL    ::  grid_ratio, grid_ratio_new, maximum_grid_ratio, tolerance, &
20                tolerance_nx, tolerance_ny, tolerance_nz
21    REAL    ::  gridratio(10000)
22
23    TYPE configuration
24       REAL               ::  grid_ratio
25       INTEGER            ::  numprocs, pdims_1, pdims_2, nx, ny, nz, nxanz, &
26                              nyanz, grid_levels, nx_mg, ny_mg, nz_mg
27    END TYPE configuration
28
29    TYPE(configuration), DIMENSION(10000) ::  config
30
31!
32!-- Ask number of processors available
33    PRINT*, '*** number of PEs available + allowed tolerance:'
34    READ (*,*)  numprocs, tolerance
35    IF ( tolerance < 0.0 )  THEN
36       numprocs_max = numprocs
37       numprocs_min = numprocs * ( 1.0 + tolerance )
38    ELSE
39       numprocs_max = numprocs * ( 1.0 + tolerance )
40       numprocs_min = numprocs * ( 1.0 - tolerance )
41    ENDIF
42
43!
44!-- Ask for 1D-decomposition
45    PRINT*, ' '
46    PRINT*, ' '
47    PRINT*, '*** shall a 1d-decomposition along x be used (y/n)?'
48    READ (*,*)  char
49    IF ( char == 'y' )  one_d_decomp = .TRUE.
50
51!
52!-- Ask for quadratic domain
53    PRINT*, ' '
54    PRINT*, ' '
55    PRINT*, '*** shall a quadratic domain along x and y be used (y/n)?'
56    READ (*,*)  char
57    IF ( char == 'y' )  THEN
58       quadratic_domain_xy = .TRUE.
59       PRINT*, ' '
60       PRINT*, ' '
61       PRINT*, '*** shall also grid points along z be equal to x and y (y/n)?'
62       READ (*,*)  char
63       IF ( char == 'y' )  cubic_domain = .TRUE.
64    ENDIF
65
66!
67!-- Read number of gridpoints in each direction
68    PRINT*, ' '
69    PRINT*, ' '
70    PRINT*, '*** please type nx + allowed tolerance:'
71    READ (*,*)  nx, tolerance_nx
72    IF ( tolerance_nx < 0.0 )  THEN
73       nx_max = nx
74       nx_min = nx * ( 1.0 + tolerance_nx )
75    ELSE
76       nx_max = nx * ( 1.0 + tolerance_nx )
77       nx_min = nx * ( 1.0 - tolerance_nx )
78    ENDIF
79    IF ( quadratic_domain_xy )  THEN
80       ny           = nx
81       tolerance_ny = tolerance_nx
82    ELSE
83       PRINT*, '*** please type ny + allowed tolerance:'
84       READ (*,*)  ny, tolerance_ny
85    ENDIF
86    IF ( tolerance_ny < 0.0 )  THEN
87       ny_max = ny
88       ny_min = ny * ( 1.0 + tolerance_ny )
89    ELSE
90       ny_max = ny * ( 1.0 + tolerance_ny )
91       ny_min = ny * ( 1.0 - tolerance_ny )
92    ENDIF
93    IF ( cubic_domain )  THEN
94       nz           = nx
95       tolerance_nz = tolerance_nx
96    ELSE
97       PRINT*, '*** please type nz + allowed tolerance:'
98       READ (*,*)  nz, tolerance_nz
99    ENDIF
100    IF ( tolerance_nz < 0.0 )  THEN
101       nz_max = nz
102       nz_min = nz * ( 1.0 + tolerance_nz )
103    ELSE
104       nz_max = nz * ( 1.0 + tolerance_nz )
105       nz_min = nz * ( 1.0 - tolerance_nz )
106    ENDIF
107
108!
109!-- Read maximum gridpoint-ratio for which results shall be printed
110    PRINT*, ' '
111    PRINT*, '*** please type maximum subdomain gridpoint-ratio'
112    PRINT*, '    ( ABS( nx_sub / ny_sub - 1.0 ) ) for which results shall be'
113    PRINT*, '    printed'
114    READ (*,*)  maximum_grid_ratio
115
116!
117!-- Loop over allowed numbers of processors
118g:  DO  n = numprocs_max, numprocs_min, -1
119
120!
121!--    Set initial configuration
122       numprocs   = n
123       pdims(1)   = numprocs + 1
124       pdims(2)   = 1
125
126!
127!--    Looking for practicable virtual processor grids
128p:     DO  WHILE ( pdims(1) > 1 )
129
130          pdims(1) = pdims(1) - 1
131
132!
133!--       Create the virtual PE-grid topology
134          IF ( MOD( numprocs , pdims(1) ) /= 0 )  THEN
135             CYCLE p
136          ELSE
137             IF ( one_d_decomp  .AND.  pdims(1) < numprocs )  CYCLE g
138          ENDIF
139          pdims(2) = numprocs / pdims(1)
140
141      xn: DO  nx = nx_min, nx_max
142!
143!--          Proof, if grid points in x-direction can be distributed without
144!--          rest to the processors in x- and y-direction
145             IF ( MOD(nx+1, pdims(1)) /= 0 .OR. &
146                  MOD(nx+1, pdims(2)) /= 0 )  CYCLE xn
147             nxanz  = ( nx + 1 ) / pdims(1)
148
149         yn: DO  ny = ny_min, ny_max
150!
151!--             Eventually exit in case of non quadratic domains
152                IF ( quadratic_domain_xy  .AND.  ny /= nx )  CYCLE yn
153!
154!--             Proof, if grid points in y-direction can be distributed without
155!--             rest to the processors in x- and y-direction
156                IF ( MOD( ny+1 , pdims(2) ) /= 0 .OR. &
157                     MOD( ny+1, pdims(1) ) /= 0 )  CYCLE yn
158                nyanz  = ( ny + 1 ) / pdims(2)
159
160                grid_ratio = ABS( REAL( nxanz ) / REAL( nyanz ) - 1.0 )
161
162            zn: DO  nz = nz_min, nz_max
163!
164!--                Eventually exit in case of non cubic domains
165                   IF ( cubic_domain  .AND.  nz /= nx )  CYCLE zn
166!
167!--                Proof, if grid points in z-direction can be distributed
168!--                without rest to the processors in x-direction
169                   IF ( MOD( nz, pdims(1) ) /= 0  .AND.  .NOT. one_d_decomp ) &
170                   THEN
171                      CYCLE zn
172                   ENDIF
173
174!
175!--                Store configuration found
176                   IF ( grid_ratio < maximum_grid_ratio )  THEN
177                      found = .TRUE.
178                      count = count + 1
179                      config(count)%grid_ratio = grid_ratio
180                      config(count)%numprocs   = numprocs
181                      config(count)%pdims_1    = pdims(1)
182                      config(count)%pdims_2    = pdims(2)
183                      config(count)%nx         = nx
184                      config(count)%ny         = ny
185                      config(count)%nz         = nz
186                      config(count)%nxanz      = nxanz
187                      config(count)%nyanz      = nyanz
188                      IF ( count == 10000 )  THEN
189                         PRINT*, '+++ more than 10000 configurations'
190                         EXIT g
191                      ENDIF
192                   ENDIF
193
194                   IF ( one_d_decomp )  CYCLE yn
195
196                ENDDO zn
197
198             ENDDO yn
199
200          ENDDO xn
201
202       ENDDO p
203
204    ENDDO g
205
206    IF ( .NOT. found )  THEN
207       PRINT*, ' '
208       PRINT*, '+++ No valid processor grid found for the given number of'
209       PRINT*, '    processors and gridpoints'
210       STOP
211    ENDIF
212
213!
214!-- Calculate number of possible grid levels and gridpoints of the coarsest grid
215!-- used by the multigrid method
216    DO  n = 1, count
217       mg_levels_x = 1
218       mg_levels_y = 1
219       mg_levels_z = 1
220
221       i =  config(n)%nxanz
222       DO WHILE ( MOD( i, 2 ) == 0  .AND.  i /= 2 )
223          i = i / 2
224          mg_levels_x = mg_levels_x + 1
225       ENDDO
226
227       j =  config(n)%nyanz
228       DO WHILE ( MOD( j, 2 ) == 0  .AND.  j /= 2 )
229          j = j / 2
230          mg_levels_y = mg_levels_y + 1
231       ENDDO
232
233       k =  config(n)%nz
234       DO WHILE ( MOD( k, 2 ) == 0  .AND.  k /= 2 )
235          k = k / 2
236          mg_levels_z = mg_levels_z + 1
237       ENDDO
238
239       maximum_grid_level = MIN( mg_levels_x, mg_levels_y, mg_levels_z )
240       config(n)%grid_levels = maximum_grid_level
241       config(n)%nx_mg = config(n)%nxanz / 2**(maximum_grid_level-1) 
242       config(n)%ny_mg = config(n)%nyanz / 2**(maximum_grid_level-1)
243       config(n)%nz_mg = config(n)%nz    / 2**(maximum_grid_level-1)
244    ENDDO
245
246!
247!-- Print the configurations computed above
248    PRINT*, ' '
249    PRINT*, ' '
250    PRINT*, '*** print out results in ascending grid-ratio order (y/n)?'
251    READ (*,*)  char
252    IF ( char == 'y' )  THEN
253       gridratio = 10000.0
254       gridratio(1:count) = config(1:count)%grid_ratio
255       WRITE ( *, * )  ' '
256       WRITE ( *, * )  'Possible configurations found:'
257       WRITE ( *, * )  'sorted in ascending grid-ratio order'
258       WRITE ( *, 100 )
259       DO
260          ii = MINLOC( gridratio )
261          i = ii(1)
262          IF ( gridratio(i) /= 10000.0 )  THEN
263             WRITE ( *, 101 ) &
264                config(i)%grid_ratio, config(i)%numprocs, config(i)%pdims_1, &
265                config(i)%pdims_2, config(i)%nx, config(i)%ny, config(i)%nz, &
266                config(i)%nxanz, config(i)%nyanz, config(i)%grid_levels,     &
267                config(i)%nx_mg, config(i)%ny_mg, config(i)%nz_mg
268             gridratio(i) = 10000.0
269          ELSE
270             EXIT
271          ENDIF
272       ENDDO
273    ENDIF
274
275    PRINT*, ' '
276    PRINT*, ' '
277    PRINT*, '*** print out results in descending PE order (y/n)?'
278    READ (*,*)  char
279    IF ( char == 'y' )  THEN
280       numpr = 0
281       numpr(1:count) = config(1:count)%numprocs
282       WRITE ( *, * )  ' '
283       WRITE ( *, * )  'Possible configurations found:'
284       WRITE ( *, * )  'sorted after number of PEs'
285       WRITE ( *, 100 )
286       DO
287          ii = MAXLOC( numpr )
288          i = ii(1)
289          IF ( numpr(i) /= 0 )  THEN
290             WRITE ( *, 101 ) &
291                config(i)%grid_ratio, config(i)%numprocs, config(i)%pdims_1, &
292                config(i)%pdims_2, config(i)%nx, config(i)%ny, config(i)%nz, &
293                config(i)%nxanz, config(i)%nyanz, config(i)%grid_levels,     &
294                config(i)%nx_mg, config(i)%ny_mg, config(i)%nz_mg
295             numpr(i) = 0
296          ELSE
297             EXIT
298          ENDIF
299       ENDDO
300    ENDIF
301
302    PRINT*, ' '
303    PRINT*, ' '
304    PRINT*, '*** print out results in descending grid size order (y/n)?'
305    READ (*,*)  char
306    IF ( char == 'y' )  THEN
307       numnx = 0
308       DO  i = 1, count
309          numnx(i) = config(i)%nx * config(i)%ny * config(i)%nz
310       ENDDO
311       WRITE ( *, * )  ' '
312       WRITE ( *, * )  'Possible configurations found:'
313       WRITE ( *, * )  'sorted after grid size'
314       WRITE ( *, 100 )
315       DO
316          ii = MAXLOC( numnx )
317          i = ii(1)
318          IF ( numnx(i) /= 0 )  THEN
319             WRITE ( *, 101 ) &
320                config(i)%grid_ratio, config(i)%numprocs, config(i)%pdims_1, &
321                config(i)%pdims_2, config(i)%nx, config(i)%ny, config(i)%nz, &
322                config(i)%nxanz, config(i)%nyanz, config(i)%grid_levels,     &
323                config(i)%nx_mg, config(i)%ny_mg, config(i)%nz_mg
324             numnx(i) = 0
325          ELSE
326             EXIT
327          ENDIF
328       ENDDO
329    ENDIF
330
331100 FORMAT('ratio  PEs   PE-grid      nx   ny   nz   subdomain  grid_levels  ', &
332           'coarsest subd.')
333101 FORMAT(F4.2,2X,I4,' (',I4,',',I4,')',2X,I4,1X,I4,1X,I4,'  (',I4,',',I4,')', &
334           5X,I2,7X,'(',I3,',',I3,',',I3,')')
335
336 END PROGRAM find_palm_config
Note: See TracBrowser for help on using the repository browser.