source: palm/trunk/UTIL/analyze_particle_netcdf_data.f90 @ 1046

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

put scripts and utilities under GPL

  • Property svn:keywords set to Id
File size: 8.8 KB
Line 
1 PROGRAM analyze_particle_netcdf_data
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! code put under GPL (PALM 3.9)
23!
24! Former revisions:
25! -----------------
26! $Id: analyze_particle_netcdf_data.f90 1046 2012-11-09 14:38:45Z maronga $
27!
28! Initial revision 12/07/05
29!
30!
31! Description:
32! ------------
33! This is an EXAMPLE routine how to read NetCDF particle data output by PALM.
34! As an example, the mean heigth and radius of all particles are calculated
35! and output for each output time available on the file
36!
37!
38! Any additonal analyzation requested has to be added by the user by following
39! the steps given in this example!
40!
41!
42!
43! This routine must be compiled with:
44! decalpha:
45!    f95 -fast -r8 -I/usr/local/netcdf-3.5.1/include
46!    -L/usr/local/netcdf-3.5.1/lib -lnetcdf
47! IBM-Regatta:
48!    xlf95 -qsuffix=cpp=f90 -qrealsize=8 -q64 -qmaxmem=-1 -Q
49!    -I /aws/dataformats/netcdf-3.5.0/netcdf-64-32-3.5.0/include_F90_64
50!    -L/aws/dataformats/netcdf-3.5.0/netcdf-64-32-3.5.0/lib -lnetcdf -O3
51! IBM-Regatta KISTI:
52!    xlf95 -qsuffix=cpp=f90 -qrealsize=8 -q64 -qmaxmem=-1 -Q
53!    -I /applic/netcdf64/src/f90
54!    -L/applic/lib/NETCDF64 -lnetcdf -O3
55! IMUK:
56!    ifort analyze_particle_netcdf_data
57!    -I /muksoft/packages/netcdf/linux/include -axW -r8 -nbs -Vaxlib
58!    -L /muksoft/packages/netcdf/linux/lib -lnetcdf
59! NEC-SX6:
60!    sxf90 analyze_particle_netcdf_data.f90
61!    -I /pool/SX-6/netcdf/netcdf-3.6.0-p1/include  -C hopt -Wf '-A idbl4'
62!    -D__netcdf -L/pool/SX-6/netcdf/netcdf-3.6.0-p1/lib -lnetcdf
63!------------------------------------------------------------------------------!
64
65    USE netcdf
66
67    IMPLICIT NONE
68
69!
70!-- Local variables
71    CHARACTER (LEN=7)    ::  id_char
72    CHARACTER (LEN=2000) ::  string
73
74
75    INTEGER ::  f, fn, i, id_dim_time, id_var_rnop, id_var_r, id_var_time, &
76                id_var_x, id_var_y, id_var_z, n, nc_stat, ntl, start
77
78    INTEGER, DIMENSION(1000) ::  id_set
79    INTEGER, DIMENSION(1)    ::  id_dim_time_old
80
81    INTEGER, DIMENSION(:), ALLOCATABLE   ::  total_nop
82    INTEGER, DIMENSION(:,:), ALLOCATABLE ::  nop
83
84    LOGICAL ::  found
85
86    REAL ::  mean_r, mean_z
87    REAL, DIMENSION(:), ALLOCATABLE ::  prt_r, prt_x, prt_y, prt_z, tl
88
89!
90!-- Check, if file from PE0 exists. If it does not exist, PALM did not
91!-- create any output for this cross-section.
92    fn = 0
93    WRITE (id_char,'(''_'',I4.4)')  fn
94    INQUIRE ( FILE=id_char, EXIST=found )
95
96!
97!-- Find out the number of files (equal to the number of PEs which
98!-- have been used in PALM) and open them
99    IF ( .NOT. found )  THEN
100       PRINT*, '+++ no file _0000 found in current working directory'
101       STOP
102    ENDIF
103
104    DO  WHILE ( found )
105
106!
107!--    Open NetCDF dataset
108       nc_stat = NF90_OPEN( id_char, NF90_NOWRITE, id_set(fn) )
109       IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 1 )
110       fn = fn + 1
111       WRITE (id_char,'(''_'',I4.4)')  fn
112       INQUIRE ( FILE=id_char, EXIST=found )
113
114    ENDDO
115    fn = fn - 1
116
117    PRINT*, '*** ', fn+1, ' files found'
118
119!
120!-- Get the run description header and print it out
121    string = ' '
122    nc_stat = NF90_GET_ATT( id_set(0), NF90_GLOBAL, 'title', string )
123    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 2 )
124    PRINT*, '*** run: ', TRIM( string )
125
126!
127!-- Get the available time levels
128    nc_stat = NF90_INQ_VARID( id_set(0), 'time', id_var_time )
129    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 3 )
130
131    nc_stat = NF90_INQUIRE_VARIABLE( id_set(0), id_var_time, &
132                                     dimids = id_dim_time_old )
133    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 4 )
134    id_dim_time = id_dim_time_old(1)
135
136    nc_stat = NF90_INQUIRE_DIMENSION( id_set(0), id_dim_time, len = ntl )
137    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 5 )
138    ALLOCATE( tl(1:ntl) )
139    print*, 'ntl=',ntl
140
141    nc_stat = NF90_GET_VAR( id_set(0), id_var_time, tl )
142    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 6 )
143
144    DO  n = 1, ntl
145       print*, '*** time_level(', n, ') =', tl(n)
146    ENDDO
147
148!
149!-- Get the number of particles used
150    nc_stat = NF90_INQ_VARID( id_set(0), 'real_num_of_prt', id_var_rnop )
151    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 7 )
152
153    ALLOCATE( nop(1:ntl,0:fn), total_nop(1:ntl) )
154
155    DO  f = 0, fn
156
157       nc_stat = NF90_GET_VAR( id_set(f), id_var_rnop, nop(1:ntl,f) )
158       IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 8 )
159
160    ENDDO
161
162    total_nop = 0
163    DO  n = 1, ntl
164
165       DO  f = 0, fn
166          total_nop(n) = total_nop(n) + nop(n,f)
167       ENDDO
168
169       PRINT*, '*** time = ', tl(n), ' total # of particles: ', total_nop(n)
170
171    ENDDO
172
173!
174!-- Get the particle x and y coordinates
175    nc_stat = NF90_INQ_VARID( id_set(0), 'pt_x', id_var_x )
176    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 9 )
177
178    nc_stat = NF90_INQ_VARID( id_set(0), 'pt_y', id_var_y )
179    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 10 )
180
181    nc_stat = NF90_INQ_VARID( id_set(0), 'pt_z', id_var_z )
182    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 11 )
183
184    nc_stat = NF90_INQ_VARID( id_set(0), 'pt_radius', id_var_r )
185    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 12 )
186
187    PRINT*, ' '
188!
189!-- Loop over all timelevels
190    DO  n = 1, ntl
191
192       ALLOCATE( prt_x(total_nop(n)), prt_y(total_nop(n)), &
193                 prt_z(total_nop(n)), prt_r(total_nop(n)) )
194
195       start = 1
196
197!
198!--    Read the data from the files (one file per processor)
199       DO  f = 0, fn
200
201          nc_stat = NF90_GET_VAR( id_set(f), id_var_x,           &
202                                  prt_x(start:start+nop(n,f)-1), &
203                                  start = (/ 1, n /),            &
204                                  count = (/ nop(n,f), 1 /) )
205          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 13 )
206
207          nc_stat = NF90_GET_VAR( id_set(f), id_var_y,           &
208                                  prt_y(start:start+nop(n,f)-1), &
209                                  start = (/ 1, n /),            &
210                                  count = (/ nop(n,f), 1 /) )
211          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 14 )
212
213          nc_stat = NF90_GET_VAR( id_set(f), id_var_z,           &
214                                  prt_z(start:start+nop(n,f)-1), &
215                                  start = (/ 1, n /),            &
216                                  count = (/ nop(n,f), 1 /) )
217          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 15 )
218
219          nc_stat = NF90_GET_VAR( id_set(f), id_var_r,           &
220                                  prt_r(start:start+nop(n,f)-1), &
221                                  start = (/ 1, n /),            &
222                                  count = (/ nop(n,f), 1 /) )
223          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( nc_stat, 16 )
224
225          start = start + nop(n,f)
226
227       ENDDO
228
229       mean_z = 0.0
230       mean_r = 0.0
231       DO  i = 1, total_nop(n)
232          mean_z = mean_z + prt_z(i)
233          mean_r = mean_r + prt_r(i)
234       ENDDO
235       mean_z = mean_z / total_nop(n)
236       mean_r = mean_r / total_nop(n)
237
238       PRINT*, '*** time = ', tl(n), ' mean height = ', mean_z, &
239                                     ' mean radius = ', mean_r
240
241!
242!--    prt_x, prt_y, prt_z, and prt_r contain the particle coordinates and
243!--    radii, respectively. Please output these data or carry out the
244!--    requested analyzing in this program before you deallocate the arrays.
245
246       DEALLOCATE( prt_x, prt_y, prt_z, prt_r )
247
248    ENDDO
249
250
251 END PROGRAM analyze_particle_netcdf_data
252
253
254
255 SUBROUTINE handle_netcdf_error( nc_stat, position )
256!
257!-- Prints out a text message corresponding to the current NetCDF status
258
259    USE netcdf
260
261    IMPLICIT NONE
262
263    INTEGER, INTENT(IN) ::  nc_stat, position
264
265    IF ( nc_stat /= NF90_NOERR )  THEN
266       PRINT*, '+++ analyze_particle_netcdf_data'
267       PRINT*, '    netcdf error: ', TRIM( nf90_strerror( nc_stat ) )
268       PRINT*, '    position = ', position
269       STOP
270    ENDIF
271
272 END SUBROUTINE handle_netcdf_error
Note: See TracBrowser for help on using the repository browser.