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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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