source: palm/tags/release-3.10/UTIL/check_pegrid.f90 @ 4901

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

last commit documented / added nc2vdf

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