source: palm/trunk/UTIL/check_pegrid.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: 5.5 KB
Line 
1 PROGRAM check_pegrid
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: check_pegrid.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! 1310 2014-03-14 08:01:56Z raasch
34! update of GPL copyright
35!
36! 1046 2012-11-09 14:38:45Z maronga
37! code put under GPL (PALM 3.9)
38!
39! Description:
40! -------------
41! Ueberpruefung der Konsistenz von Prozessortopologie und gewaehlten Feldgrenzen
42!------------------------------------------------------------------------------!
43
44    IMPLICIT NONE
45
46    CHARACTER (LEN=1) ::  char = ''
47    INTEGER ::  i, j, k, maximum_grid_level, mg_levels_x, mg_levels_y,        &
48                mg_levels_z, numprocs, numproc_sqr, nx, nxanz, ny, nyanz, nz, &
49                pdims(2)
50
51!
52!-- Prozessoranzahl abfragen
53    PRINT*, '*** Anzahl der verfuegbaren PE''s:'
54    READ (*,*)  numprocs
55
56!
57!-- Prozessortopologie bestimmen
58    numproc_sqr = SQRT( REAL( numprocs ) )
59    pdims(1)    = MAX( numproc_sqr , 1 )
60    DO  WHILE ( MOD( numprocs , pdims(1) ) /= 0 )
61       pdims(1) = pdims(1) - 1
62    ENDDO
63    pdims(2) = numprocs / pdims(1)
64
65!
66!-- Prozessortopologie ausgeben
67    PRINT*, ' '
68    PRINT*, '*** berechnetes Prozessorgitter: (',pdims(1),',',pdims(2),')'
69
70!
71!-- Evtl. Uebersteuerung der Prozessortopologie durch den Benutzer
72    PRINT*, ' '
73    PRINT*, '*** soll dieses Prozessorgitter benutzt werden? (y/n/<return>=y)'
74    READ (*,'(A1)')  char
75    IF ( char /= 'y'  .AND.  char /= 'Y'  .AND.  char /= '' )  THEN
76       DO
77          PRINT*, ' '
78          PRINT*, '*** Bitte Prozessoranzahl in x- und y-Richtung angeben:'
79          READ (*,*)  pdims(1), pdims(2)
80          IF ( pdims(1)*pdims(2) == numprocs )  EXIT
81          PRINT*, '+++ berechnete Prozessoranzahl (', pdims(1)*pdims(2), &
82                  ') stimmt nicht mit vorgegebener Anzahl'
83          PRINT*, '    (', numprocs, ') ueberein!'
84       ENDDO
85    ENDIF
86
87!
88!-- Gitterpunktanzahl abfragen
89    PRINT*, ' '
90    PRINT*, ' '
91    PRINT*, '*** bitte nx, ny und nz angeben:'
92    READ (*,*)  nx, ny, nz
93
94!
95!-- Pruefung, ob sich Gitterpunkte in x-Richtung glatt aufteilen lassen
96    IF ( MOD( nx+1 , pdims(1) ) /= 0 )  THEN
97       PRINT*,'+++ x-Richtung:  Gitterpunktanzahl (',nx+1,') ist kein ganz-'
98       PRINT*,'                 zahliges Vielfaches der Prozessoranzahl (',&
99                                &pdims(1),')'
100       STOP
101    ELSE
102       nxanz  = ( nx + 1 ) / pdims(1)
103    ENDIF
104
105!
106!-- Pruefung, ob sich Gitterpunkte in y-Richtung glatt aufteilen lassen
107    IF ( MOD( ny+1 , pdims(2) ) /= 0 )  THEN
108       PRINT*,'+++ y-Richtung:  Gitterpunktanzahl (',ny+1,') ist kein ganz-'
109       PRINT*,'                 zahliges Vielfaches der Prozessoranzahl (',&
110                                &pdims(2),')'
111       STOP
112    ELSE
113       nyanz  = ( ny + 1 ) / pdims(2)
114    ENDIF
115
116    PRINT*, ''
117    PRINT*, '*** Anzahl der Gitterpunkte in x- und y-Richtung je PE: (', &
118            nxanz,',',nyanz,')'
119
120!
121!-- Pruefen der Gitterpunktanzahl bzgl. Transposition
122    IF ( MOD( nz , pdims(1) ) /= 0 )  THEN
123       PRINT*,'+++ Transposition z --> x:'
124       PRINT*,'    nz=',nz,' ist kein ganzzahliges Vielfaches von pdims(1)=', &
125              &pdims(1)
126       PRINT*, ''
127       STOP
128    ENDIF
129    IF ( MOD( nx+1 , pdims(2) ) /= 0 )  THEN
130       PRINT*,'+++ Transposition x --> y:'
131       PRINT*,'    nx+1=',nx+1,' ist kein ganzzahliges Vielfaches von ',&
132              &'pdims(2)=',pdims(2)
133       PRINT*, ''
134       STOP
135    ENDIF
136    IF ( MOD( ny+1 , pdims(1) ) /= 0 )  THEN
137       PRINT*,'+++ Transposition y --> z:'
138       PRINT*,'    ny+1=',ny+1,' ist kein ganzzahliges Vielfaches von ',&
139              &'pdims(1)=',pdims(1)
140       PRINT*, ''
141       STOP
142    ENDIF
143
144!
145!-- Moegliche Anzahl von Gitterniveaus im Falle der Benutzung des
146!-- Mehrgitterverfahrens berechnen und die Gitterpunktanzahl des groebsten
147!-- Gitters ausgeben
148    mg_levels_x = 1
149    mg_levels_y = 1
150    mg_levels_z = 1
151
152    i = nxanz
153    DO WHILE ( MOD( i, 2 ) == 0  .AND.  i /= 2 )
154       i = i / 2
155       mg_levels_x = mg_levels_x + 1
156    ENDDO
157
158    j = nyanz
159    DO WHILE ( MOD( j, 2 ) == 0  .AND.  j /= 2 )
160       j = j / 2
161       mg_levels_y = mg_levels_y + 1
162    ENDDO
163
164    k = nz
165    DO WHILE ( MOD( k, 2 ) == 0  .AND.  k /= 2 )
166       k = k / 2
167       mg_levels_z = mg_levels_z + 1
168    ENDDO
169
170    maximum_grid_level = MIN( mg_levels_x, mg_levels_y, mg_levels_z )
171    i = nxanz / 2**(maximum_grid_level-1) 
172    j = nyanz / 2**(maximum_grid_level-1)
173    k = nz    / 2**(maximum_grid_level-1)
174
175    PRINT*, '    Anzahl der moeglichen Gitterniveaus: ', maximum_grid_level
176    PRINT*, '    Anz. Gitterpunkte auf groebstem Gitter (x,y,z): (', i, ',', &
177                 j,',',k,')'
178    PRINT*, ''
179
180 END PROGRAM check_pegrid
Note: See TracBrowser for help on using the repository browser.