source: palm/trunk/UTIL/find_palm_config.f90 @ 1046

Last change on this file since 1046 was 1046, checked in by maronga, 11 years ago

put scripts and utilities under GPL

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