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

Last change on this file since 1673 was 1673, checked in by raasch, 9 years ago

informative message about definition of tolerance added

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