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

Last change on this file since 3183 was 2718, checked in by maronga, 6 years ago

deleting of deprecated files; headers updated where needed

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