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

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

last commit documented

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