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