1! This is part of the netCDF package.
2! Copyright 2006 University Corporation for Atmospheric Research/Unidata.
3! See COPYRIGHT file for conditions of use.
4
5! This is an example program which writes some 4D pressure and
6! temperatures. It is intended to illustrate the use of the netCDF
7! fortran 90 API. The companion program nc4_pres_temp_4D_rd.f shows how
8! to read the netCDF data file created by this program.
9
10! This program is part of the netCDF tutorial:
11! http://www.unidata.ucar.edu/software/netcdf/docs/tutorial_8dox.html
12
13! Full documentation of the netCDF Fortran 90 API can be found at:
14! http://www.unidata.ucar.edu/software/netcdf/docs-fortran/f90_The-NetCDF-Fortran-90-Interface-Guide.html
15
16! Ed Hartnett
17
18program nc4_pres_temp_4D_wr
19  use netcdf
20  implicit none
21
22  ! This is the name of the data file we will create.
23  character (len = *), parameter :: FILE_NAME = "nc4_pres_temp_4D.nc"
24  integer :: ncid
25
26  ! We are writing 4D data, a 12 x 6 x 2 lon-lat-lvl grid, with 2
27  ! timesteps of data.
28  integer, parameter :: NDIMS = 4, NRECS = 2
29  integer, parameter :: NLVLS = 2, NLATS = 6, NLONS = 12
30  character (len = *), parameter :: LVL_NAME = "level"
31  character (len = *), parameter :: LAT_NAME = "latitude"
32  character (len = *), parameter :: LON_NAME = "longitude"
33  character (len = *), parameter :: REC_NAME = "time"
34  integer :: lvl_dimid, lon_dimid, lat_dimid, rec_dimid
35
36  ! The start and count arrays will tell the netCDF library where to
37  ! write our data.
38  integer :: start(NDIMS), count(NDIMS)
39
40  ! These program variables hold the latitudes and longitudes.
41  real :: lats(NLATS), lons(NLONS)
42  integer :: lon_varid, lat_varid
43
44  ! We will create two netCDF variables, one each for temperature and
45  ! pressure fields.
46  character (len = *), parameter :: PRES_NAME="pressure"
47  character (len = *), parameter :: TEMP_NAME="temperature"
48  integer :: pres_varid, temp_varid
49  integer :: dimids(NDIMS)
50
51  ! We recommend that each variable carry a "units" attribute.
52  character (len = *), parameter :: UNITS = "units"
53  character (len = *), parameter :: PRES_UNITS = "hPa"
54  character (len = *), parameter :: TEMP_UNITS = "celsius"
55  character (len = *), parameter :: LAT_UNITS = "degrees_north"
56  character (len = *), parameter :: LON_UNITS = "degrees_east"
57
58  ! Program variables to hold the data we will write out. We will only
59  ! need enough space to hold one timestep of data; one record.
60  real, dimension(:,:,:), allocatable :: pres_out
61  real, dimension(:,:,:), allocatable :: temp_out
62  real, parameter :: SAMPLE_PRESSURE = 900.0
63  real, parameter :: SAMPLE_TEMP = 9.0
64
65  ! Use these to construct some latitude and longitude data for this
66  ! example.
67  real, parameter :: START_LAT = 25.0, START_LON = -125.0
68
69  ! Loop indices
70  integer :: lvl, lat, lon, rec, i
71
72  ! Allocate memory.
73  allocate(pres_out(NLONS, NLATS, NLVLS))
74  allocate(temp_out(NLONS, NLATS, NLVLS))
75
76  ! Create pretend data. If this were not an example program, we would
77  ! have some real data to write, for example, model output.
78  do lat = 1, NLATS
79     lats(lat) = START_LAT + (lat - 1) * 5.0
80  end do
81  do lon = 1, NLONS
82     lons(lon) = START_LON + (lon - 1) * 5.0
83  end do
84  i = 0
85  do lvl = 1, NLVLS
86     do lat = 1, NLATS
87        do lon = 1, NLONS
88           pres_out(lon, lat, lvl) = SAMPLE_PRESSURE + i
89           temp_out(lon, lat, lvl) = SAMPLE_TEMP + i
90           i = i + 1
91        end do
92     end do
93  end do
94
95  ! Create the file.
96  call check( nf90_create(FILE_NAME, NF90_NETCDF4, ncid) )
97
98  ! Define the dimensions. The record dimension is defined to have
99  ! unlimited length - it can grow as needed. In this example it is
100  ! the time dimension.
101  call check( nf90_def_dim(ncid, LVL_NAME, NLVLS, lvl_dimid) )
102  call check( nf90_def_dim(ncid, LAT_NAME, NLATS, lat_dimid) )
103  call check( nf90_def_dim(ncid, LON_NAME, NLONS, lon_dimid) )
104  call check( nf90_def_dim(ncid, REC_NAME, NF90_UNLIMITED, rec_dimid) )
105
106  ! Define the coordinate variables. We will only define coordinate
107  ! variables for lat and lon.  Ordinarily we would need to provide
108  ! an array of dimension IDs for each variable's dimensions, but
109  ! since coordinate variables only have one dimension, we can
110  ! simply provide the address of that dimension ID (lat_dimid) and
111  ! similarly for (lon_dimid).
112  call check( nf90_def_var(ncid, LAT_NAME, NF90_REAL, lat_dimid, lat_varid) )
113  call check( nf90_def_var(ncid, LON_NAME, NF90_REAL, lon_dimid, lon_varid) )
114
115  ! Assign units attributes to coordinate variables.
116  call check( nf90_put_att(ncid, lat_varid, UNITS, LAT_UNITS) )
117  call check( nf90_put_att(ncid, lon_varid, UNITS, LON_UNITS) )
118
119  ! The dimids array is used to pass the dimids of the dimensions of
120  ! the netCDF variables. Both of the netCDF variables we are creating
121  ! share the same four dimensions. In Fortran, the unlimited
122  ! dimension must come last on the list of dimids.
123  dimids = (/ lon_dimid, lat_dimid, lvl_dimid, rec_dimid /)
124
125  ! Define the netCDF variables for the pressure and temperature data.
126  call check( nf90_def_var(ncid, PRES_NAME, NF90_REAL, dimids, pres_varid) )
127  call check( nf90_def_var(ncid, TEMP_NAME, NF90_REAL, dimids, temp_varid) )
128
129  ! Assign units attributes to the netCDF variables.
130  call check( nf90_put_att(ncid, pres_varid, UNITS, PRES_UNITS) )
131  call check( nf90_put_att(ncid, temp_varid, UNITS, TEMP_UNITS) )
132
133  ! End define mode.
134  call check( nf90_enddef(ncid) )
135
136  ! Write the coordinate variable data. This will put the latitudes
137  ! and longitudes of our data grid into the netCDF file.
138  call check( nf90_put_var(ncid, lat_varid, lats) )
139  call check( nf90_put_var(ncid, lon_varid, lons) )
140
141  ! These settings tell netcdf to write one timestep of data. (The
142  ! setting of start(4) inside the loop below tells netCDF which
143  ! timestep to write.)
144  count = (/ NLONS, NLATS, NLVLS, 1 /)
145  start = (/ 1, 1, 1, 1 /)
146
147  ! Write the pretend data. This will write our surface pressure and
148  ! surface temperature data. The arrays only hold one timestep worth
149  ! of data. We will just rewrite the same data for each timestep. In
150  ! a real :: application, the data would change between timesteps.
151  do rec = 1, NRECS
152     start(4) = rec
153     call check( nf90_put_var(ncid, pres_varid, pres_out, start = start, &
154                              count = count) )
155     call check( nf90_put_var(ncid, temp_varid, temp_out, start = start, &
156                              count = count) )
157  end do
158
159  ! Close the file. This causes netCDF to flush all buffers and make
160  ! sure your data are really written to disk.
161  call check( nf90_close(ncid) )
162
163  print *,"*** SUCCESS writing example file ", FILE_NAME, "!"
164
165contains
166  subroutine check(status)
167    integer, intent ( in) :: status
168
169    if(status /= nf90_noerr) then
170      print *, trim(nf90_strerror(status))
171      stop 2
172    end if
173  end subroutine check
174end program nc4_pres_temp_4D_wr
175
176