source: palm/trunk/UTIL/read_palm_netcdf_data.f90 @ 2114

Last change on this file since 2114 was 1310, checked in by raasch, 10 years ago

update of GPL copyright

  • Property svn:keywords set to Id
File size: 7.2 KB
Line 
1 PROGRAM read_palm_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-2014  Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23! Former revisions:
24! -----------------
25! $Id: read_palm_netcdf_data.f90 1310 2014-03-14 08:01:56Z kanani $
26!
27! 1046 2012-11-09 14:38:45Z maronga
28! code put under GPL (PALM 3.9)
29!
30! Description:
31! ------------                     
32! This is an example program for reading PALM 2d/3d NetCDF datasets
33!
34! The user has to add his own code for further storing and analyzing of
35! these data!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
36!
37! The NetCDF include file and library has to be given with the respective
38! compiler options. Please find out the respective paths on your system and
39! set them appropriately.
40!
41! Here are some examples how this routine should be compiled:
42!
43! decalpha:
44!    f95 -fast -r8 -I/usr/local/netcdf-3.5.1/include
45!    -L/usr/local/netcdf-3.5.1/lib -lnetcdf
46! IBM-Regatta:
47!    xlf95 -qrealsize=8 -q64 -qmaxmem=-1 -Q
48!    -I /aws/dataformats/netcdf-3.6.0-p1/64-32/include
49!    -L/aws/dataformats/netcdf-3.6.0-p1/64-32/lib -lnetcdf -O3
50! IBM-Regatta KISTI:
51!    xlf95 -qrealsize=8 -q64 -qmaxmem=-1 -Q
52!    -I /applic/netcdf64/src/f90
53!    -L/applic/lib/NETCDF64 -lnetcdf -O3
54! IBM-Regatta Yonsei (gfdl5):
55!    xlf95 -qrealsize=8 -q64 -qmaxmem=-1 -Q
56!    -I /usr1/users/raasch/pub/netcdf-3.6.0-p1/include
57!    -L/usr1/users/raasch/pub/netcdf-3.6.0-p1/lib -lnetcdf -O3
58! IMUK:
59!    ifort read_palm...f90 -o read_palm...x
60!    -I /muksoft/packages/netcdf/linux/include -axW -r8 -nbs
61!    -Vaxlib -L /muksoft/packages/netcdf/linux/lib -lnetcdf
62! NEC-SX6:
63!    sxf90 read_palm...f90 -o read_palm...x
64!    -I /pool/SX-6/netcdf/netcdf-3.6.0-p1/include  -C hopt -Wf '-A idbl4'
65!    -L/pool/SX-6/netcdf/netcdf-3.6.0-p1/lib -lnetcdf
66!------------------------------------------------------------------------------!
67
68    USE netcdf
69
70    IMPLICIT NONE
71
72!
73!-- Local variables
74    CHARACTER (LEN=10)   ::  dimname(4), var_name
75    CHARACTER (LEN=40)   ::  filename
76
77    CHARACTER (LEN=2000) ::  title, var_list
78
79    INTEGER ::  i, j, k, nc_stat, pos, time_step
80
81    INTEGER ::  current_level, current_var, id_set, id_var_time, num_var
82
83    INTEGER, DIMENSION(4) ::  id_dims, id_dims_loc, levels
84
85    INTEGER, DIMENSION(1000) ::  id_var
86
87    REAL ::  time(1)
88
89    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  data_array
90
91
92    PRINT*, '*** Please type NetCDF filename to be read:'
93    READ*, filename
94
95    nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set )
96    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 1 )
97
98!
99!-- Get the run description header and output
100    title = ' '
101    nc_stat = NF90_GET_ATT( id_set, NF90_GLOBAL, 'title', title )
102    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 2 )
103    WRITE (*,'(/A/A)')  '*** file created by:', TRIM( title )
104
105!
106!-- Get the list of variables (order of variables corresponds with the
107!-- order of data on the binary file)
108    var_list = ' '    ! GET_ATT does not assign trailing blanks
109    nc_stat = NF90_GET_ATT( id_set, NF90_GLOBAL, 'VAR_LIST', var_list )
110    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 3 )
111
112!
113!-- Inquire id of the time coordinate variable
114    nc_stat = NF90_INQ_VARID( id_set, 'time', id_var_time )
115    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 4 )
116
117!
118!-- Count number of variables; there is one more semicolon in the
119!-- string than variable names
120    num_var = -1
121    DO  i = 1, LEN( var_list )
122       IF ( var_list(i:i) == ';' )  num_var = num_var + 1
123    ENDDO
124    WRITE (*,'(/A,I3,A/)')  '*** file contains ', num_var, ' variable(s)'
125
126
127    pos = INDEX( var_list, ';' )
128!
129!-- Loop over all variables
130    DO  i = 1, num_var
131
132!
133!--    Extract variable name from list
134       var_list = var_list(pos+1:)
135       pos = INDEX( var_list, ';' )
136       var_name = var_list(1:pos-1)
137
138!
139!--    Get variable ID from name
140       nc_stat = NF90_INQ_VARID( id_set, TRIM( var_name ), id_var(i) )
141       IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 5 )
142
143!
144!--    Inquire the dimension IDs
145       nc_stat = NF90_INQUIRE_VARIABLE( id_set, id_var(i), &
146                                        dimids = id_dims_loc )
147       IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 6 )
148       id_dims = id_dims_loc
149
150!
151!--    Get number of x/y/z/time levels(gridpoints) for that variable
152       DO  j = 1, 4
153          nc_stat = NF90_INQUIRE_DIMENSION( id_set, id_dims(j),&
154                                            dimname(j), levels(j) )
155          IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 7 )
156       ENDDO
157
158       WRITE (*,100)  '*** reading variable "', TRIM(var_name),         &
159                      '", dimensioned as', TRIM(var_name), levels(1)-1, &
160                      levels(2)-1, levels(3)-1
161100    FORMAT (A,A,A/4X,A,'(0:',I4,',0:',I4,',0:',I4,')   (x/y/z)'/)
162
163!
164!--    Allocate the data array to be read
165       ALLOCATE( data_array(0:levels(1)-1,0:levels(2)-1,0:levels(3)-1) )
166
167!
168!--    Read the data from file for each timestep
169       DO  j = 1, levels(4)
170
171!
172!--        Get the time of the current timelevel and output
173           nc_stat = NF90_GET_VAR( id_set, id_var_time, time, start = (/ j /), &
174                                   count = (/ 1 /) )
175
176           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 7+i )
177
178           WRITE (*,'(A,I3,A,F8.1,A)')  '    reading timelevel ', i, &
179                                        '    time = ', time(1), ' s'     
180
181           nc_stat = NF90_GET_VAR( id_set, id_var(i),                    &
182                                   data_array, start = (/ 1, 1, 1, j /), &
183                             count = (/ levels(1), levels(2), levels(3), 1 /) )
184
185           IF ( nc_stat /= NF90_NOERR )  &
186                                       CALL handle_netcdf_error( 7+levels(4)+i )
187!
188!--        ADD YOUR OWN CODE FOR FURTHER STORING OF THESE DATA HERE
189!--        --------------------------------------------------------
190
191
192       ENDDO
193
194       WRITE (*,'(/)')
195
196       DEALLOCATE( data_array )
197
198    ENDDO
199
200
201
202 CONTAINS
203
204
205    SUBROUTINE handle_netcdf_error( errno )
206!
207!--    Prints out a text message corresponding to the current NetCDF status
208
209       IMPLICIT NONE
210
211       INTEGER, INTENT(IN) ::  errno
212
213       IF ( nc_stat /= NF90_NOERR )  THEN
214          WRITE (*,'(A,1X,I3/4X,A)')                                           &
215                                   '+++ read_palm_netcdf_data  error handle:', &
216                                   errno, TRIM( nf90_strerror( nc_stat ) )
217          STOP
218       ENDIF
219
220    END SUBROUTINE handle_netcdf_error
221
222
223 END PROGRAM read_palm_netcdf_data
224
225
226
Note: See TracBrowser for help on using the repository browser.