/[lmdze]/trunk/libf/phylmd/Mobidic/regr_lat_time_coefoz.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/Mobidic/regr_lat_time_coefoz.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 23 - (show annotations)
Mon Dec 14 15:25:16 2009 UTC (14 years, 5 months ago) by guez
File size: 12001 byte(s)
Split "orografi.f": one file for each procedure. Put the created files
in new directory "Orography".

Removed argument "vcov" of procedure "sortvarc". Removed arguments
"itau" and "time" of procedure "caldyn0". Removed arguments "itau",
"time" and "vcov" of procedure "sortvarc0".

Removed argument "time" of procedure "dynredem1". Removed NetCDF
variable "temps" in files "start.nc" and "restart.nc", because its
value is always 0.

Removed argument "nq" of procedures "iniadvtrac" and "leapfrog". The
number of "tracers read in "traceur.def" must now be equal to "nqmx",
or "nqmx" must equal 4 if there is no file "traceur.def". Replaced
variable "nq" by constant "nqmx" in "leapfrog".

NetCDF variable for ozone field in "coefoz.nc" must now be called
"tro3" instead of "r".

Fixed bug in "zenang".

1 module regr_lat_time_coefoz_m
2
3 ! This module is clean: no C preprocessor directive, no include line.
4 ! Author: Lionel GUEZ
5
6 implicit none
7
8 private
9 public regr_lat_time_coefoz
10
11 contains
12
13 subroutine regr_lat_time_coefoz
14
15 ! "regr_lat_time_coefoz" stands for "regrid latitude time
16 ! coefficients ozone".
17
18 ! This procedure reads from a NetCDF file parameters for ozone
19 ! chemistry, regrids them in latitude and time, and writes the
20 ! regridded fields to a new NetCDF file.
21
22 ! The input fields depend on time, pressure level and
23 ! latitude.
24 ! We assume that the input fields are step functions
25 ! of latitude.
26 ! Regridding in latitude is made by averaging, with a cosine of
27 ! latitude factor.
28 ! The target LMDZ latitude grid is the "scalar" grid: "rlatu".
29 ! The values of "rlatu" are taken to be the centers of intervals.
30 ! Regridding in time is by linear interpolation.
31 ! Monthly values are processed to get daily values, on the basis
32 ! of a 360-day calendar.
33
34 ! We assume that in the input file:
35 ! -- the latitude is in degrees and strictly monotonic (as all
36 ! NetCDF coordinate variables should be);
37 ! -- time increases from January to December (even though we do
38 ! not use values of the input time coordinate).
39
40 use dimens_m, only: jjm
41 use comgeom, only: rlatv
42 use comconst, only: pi
43 use regr1_step_av_m, only: regr1_step_av
44 use regr3_lint_m, only: regr3_lint
45 use netcdf95, only: nf95_open, nf95_gw_var, nf95_close, &
46 nf95_inq_varid, handle_err, nf95_put_var
47 use netcdf, only: nf90_nowrite, nf90_get_var
48
49 ! Variables local to the procedure:
50
51 integer ncid_in, ncid_out ! NetCDF IDs for input and output files
52 integer n_plev ! number of pressure levels in the input data
53 integer n_lat! number of latitudes in the input data
54
55 real, pointer:: latitude(:)
56 ! (of input data, converted to rad, sorted in strictly increasing order)
57
58 real, allocatable:: lat_in_edg(:)
59 ! (edges of latitude intervals for input data, in rad, in strictly
60 ! increasing order)
61
62 real, pointer:: plev(:) ! pressure level of input data
63 logical decr_lat ! decreasing latitude in the input file
64
65 real, allocatable:: o3_par_in(:, :, :) ! (n_lat, n_plev, 12)
66 ! (ozone parameter from the input file)
67 ! ("o3_par_in(j, l, month)" is at latitude "latitude(j)" and pressure
68 ! level "plev(l)". "month" is between 1 and 12.)
69
70 real, allocatable:: v_regr_lat(:, :, :) ! (jjm + 1, n_plev, 0:13)
71 ! (mean of a variable "v" over a latitude interval)
72 ! (First dimension is latitude interval.
73 ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)".
74 ! If "j" is between 2 and "jjm" then the interval is:
75 ! [rlatv(j), rlatv(j-1)]
76 ! If "j" is 1 or "jjm + 1" then the interval is:
77 ! [rlatv(1), pi / 2]
78 ! or:
79 ! [- pi / 2, rlatv(jjm)]
80 ! respectively.
81 ! "v_regr_lat(:, l, :)" is for pressure level "plev(l)".
82 ! Last dimension is month number.)
83
84 real, allocatable:: o3_par_out(:, :, :) ! (jjm + 1, n_plev, 360)
85 ! (regridded ozone parameter)
86 ! ("o3_par_out(j, l, day)" is at latitude "rlatu(j)", pressure
87 ! level "plev(l)" and date "January 1st 0h" + "tmidday(day)", in a
88 ! 360-day calendar.)
89
90 integer j
91 integer i_v ! index of ozone parameter
92 integer, parameter:: n_o3_param = 8 ! number of ozone parameters
93
94 character(len=11) name_in(n_o3_param)
95 ! (name of NetCDF primary variable in the input file)
96
97 character(len=9) name_out(n_o3_param)
98 ! (name of NetCDF primary variable in the output file)
99
100 integer varid_in(n_o3_param), varid_out(n_o3_param), varid_plev, varid_time
101 integer ncerr, varid
102 ! (for NetCDF)
103
104 real, parameter:: tmidmonth(0:13) = (/(-15. + 30. * j, j = 0, 13)/)
105 ! (time to middle of month, in days since January 1st 0h, in a
106 ! 360-day calendar)
107 ! (We add values -15 and 375 so that, for example, day 3 of the year is
108 ! interpolated between the December and the January value.)
109
110 real, parameter:: tmidday(360) = (/(j + 0.5, j = 0, 359)/)
111 ! (time to middle of day, in days since January 1st 0h, in a
112 ! 360-day calendar)
113
114 !---------------------------------
115
116 print *, "Call sequence information: regr_lat_time_coefoz"
117
118 ! Names of ozone parameters:
119 i_v = 0
120
121 i_v = i_v + 1
122 name_in(i_v) = "P_net"
123 name_out(i_v) = "P_net_Mob"
124
125 i_v = i_v + 1
126 name_in(i_v) = "a2"
127 name_out(i_v) = "a2"
128
129 i_v = i_v + 1
130 name_in(i_v) = "tro3"
131 name_out(i_v) = "r_Mob"
132
133 i_v = i_v + 1
134 name_in(i_v) = "a4"
135 name_out(i_v) = "a4"
136
137 i_v = i_v + 1
138 name_in(i_v) = "temperature"
139 name_out(i_v) = "temp_Mob"
140
141 i_v = i_v + 1
142 name_in(i_v) = "a6"
143 name_out(i_v) = "a6"
144
145 i_v = i_v + 1
146 name_in(i_v) = "Sigma"
147 name_out(i_v) = "Sigma_Mob"
148
149 i_v = i_v + 1
150 name_in(i_v) = "R_Het"
151 name_out(i_v) = "R_Het"
152
153 call nf95_open("coefoz.nc", nf90_nowrite, ncid_in)
154
155 ! Get coordinates from the input file:
156
157 call nf95_inq_varid(ncid_in, "latitude", varid)
158 call nf95_gw_var(ncid_in, varid, latitude)
159 ! Convert from degrees to rad, because "rlatv" is in rad:
160 latitude = latitude / 180. * pi
161 n_lat = size(latitude)
162 ! We need to supply the latitudes to "regr1_step_av" in
163 ! increasing order, so invert order if necessary:
164 decr_lat = latitude(1) > latitude(n_lat)
165 if (decr_lat) latitude = latitude(n_lat:1:-1)
166
167 ! Compute edges of latitude intervals:
168 allocate(lat_in_edg(n_lat + 1))
169 lat_in_edg(1) = - pi / 2
170 forall (j = 2:n_lat) lat_in_edg(j) = (latitude(j - 1) + latitude(j)) / 2
171 lat_in_edg(n_lat + 1) = pi / 2
172 deallocate(latitude) ! pointer
173
174 call nf95_inq_varid(ncid_in, "plev", varid)
175 call nf95_gw_var(ncid_in, varid, plev)
176 n_plev = size(plev)
177 ! (We only need the pressure coordinate to copy it to the output file.)
178
179 ! Get the IDs of ozone parameters in the input file:
180 do i_v = 1, n_o3_param
181 call nf95_inq_varid(ncid_in, trim(name_in(i_v)), varid_in(i_v))
182 end do
183
184 ! Create the output file and get the variable IDs:
185 call prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
186 varid_out, varid_plev, varid_time)
187
188 ! Write remaining coordinate variables:
189 call nf95_put_var(ncid_out, varid_time, tmidday)
190 call nf95_put_var(ncid_out, varid_plev, plev)
191
192 deallocate(plev) ! pointer
193
194 allocate(o3_par_in(n_lat, n_plev, 12))
195 allocate(v_regr_lat(jjm + 1, n_plev, 0:13))
196 allocate(o3_par_out(jjm + 1, n_plev, 360))
197
198 do i_v = 1, n_o3_param
199 ! Process ozone parameter "name_in(i_v)"
200
201 ncerr = nf90_get_var(ncid_in, varid_in(i_v), o3_par_in)
202 call handle_err("nf90_get_var", ncerr, ncid_in)
203
204 if (decr_lat) o3_par_in = o3_par_in(n_lat:1:-1, :, :)
205
206 ! Regrid in latitude:
207 ! We average with respect to sine of latitude, which is
208 ! equivalent to weighting by cosine of latitude:
209 v_regr_lat(jjm+1:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
210 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
211 ! (invert order of indices in "v_regr_lat" because "rlatu" is
212 ! decreasing)
213
214 ! Duplicate January and December values, in preparation of time
215 ! interpolation:
216 v_regr_lat(:, :, 0) = v_regr_lat(:, :, 12)
217 v_regr_lat(:, :, 13) = v_regr_lat(:, :, 1)
218
219 ! Regrid in time by linear interpolation:
220 o3_par_out = regr3_lint(v_regr_lat, tmidmonth, tmidday)
221
222 ! Write to file:
223 call nf95_put_var(ncid_out, varid_out(i_v), &
224 o3_par_out(jjm+1:1:-1, :, :))
225 ! (The order of "rlatu" is inverted in the output file)
226 end do
227
228 call nf95_close(ncid_out)
229 call nf95_close(ncid_in)
230
231 end subroutine regr_lat_time_coefoz
232
233 !********************************************
234
235 subroutine prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
236 varid_out, varid_plev, varid_time)
237
238 ! This subroutine creates the NetCDF output file, defines
239 ! dimensions and variables, and writes one of the coordinate variables.
240
241 use dimens_m, only: jjm
242 use comgeom, only: rlatu
243 use comconst, only: pi
244 use numer_rec, only: assert_eq
245
246 use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
247 nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
248 use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
249
250 integer, intent(in):: ncid_in, varid_in(:), n_plev
251 character(len=*), intent(in):: name_out(:) ! of NetCDF variables
252 integer, intent(out):: ncid_out, varid_out(:), varid_plev, varid_time
253
254 ! Variables local to the procedure:
255 integer ncerr
256 integer dimid_rlatu, dimid_plev, dimid_time
257 integer varid_rlatu
258 integer i, n_o3_param
259
260 !---------------------------
261
262 print *, "Call sequence information: prepare_out"
263 n_o3_param = assert_eq(size(varid_in), size(varid_out), &
264 size(name_out), "prepare_out")
265
266 call nf95_create("coefoz_LMDZ.nc", nf90_clobber, ncid_out)
267
268 ! Dimensions:
269 call nf95_def_dim(ncid_out, "time", 360, dimid_time)
270 call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
271 call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
272
273 ! Define coordinate variables:
274
275 call nf95_def_var(ncid_out, "time", nf90_float, dimid_time, varid_time)
276 call nf95_put_att(ncid_out, varid_time, "units", "days since 2000-1-1")
277 call nf95_put_att(ncid_out, varid_time, "calendar", "360_day")
278 call nf95_put_att(ncid_out, varid_time, "standard_name", "time")
279
280 call nf95_def_var(ncid_out, "plev", nf90_float, dimid_plev, varid_plev)
281 call nf95_put_att(ncid_out, varid_plev, "units", "millibar")
282 call nf95_put_att(ncid_out, varid_plev, "standard_name", "air_pressure")
283 call nf95_put_att(ncid_out, varid_plev, "long_name", "air pressure")
284
285 call nf95_def_var(ncid_out, "rlatu", nf90_float, dimid_rlatu, varid_rlatu)
286 call nf95_put_att(ncid_out, varid_rlatu, "units", "degrees_north")
287 call nf95_put_att(ncid_out, varid_rlatu, "standard_name", "latitude")
288
289 ! Define primary variables:
290
291 do i = 1, n_o3_param
292 call nf95_def_var(ncid_out, name_out(i), nf90_float, &
293 (/dimid_rlatu, dimid_plev, dimid_time/), varid_out(i))
294
295 ! The following commands may fail. That is OK. It should just
296 ! mean that the attribute is not defined in the input file.
297
298 ncerr = nf90_copy_att(ncid_in, varid_in(i), "long_name",&
299 & ncid_out, varid_out(i))
300 call handle_err_copy_att("long_name")
301
302 ncerr = nf90_copy_att(ncid_in, varid_in(i), "units", ncid_out,&
303 & varid_out(i))
304 call handle_err_copy_att("units")
305
306 ncerr = nf90_copy_att(ncid_in, varid_in(i), "standard_name", ncid_out,&
307 & varid_out(i))
308 call handle_err_copy_att("standard_name")
309 end do
310
311 ! Global attributes:
312 call nf95_copy_att(ncid_in, nf90_global, "Conventions", ncid_out, &
313 nf90_global)
314 call nf95_copy_att(ncid_in, nf90_global, "title", ncid_out, nf90_global)
315 call nf95_copy_att(ncid_in, nf90_global, "source", ncid_out, nf90_global)
316 call nf95_put_att(ncid_out, nf90_global, "comment", "Regridded for LMDZ")
317
318 call nf95_enddef(ncid_out)
319
320 ! Write one of the coordinate variables:
321 call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
322 ! (convert from rad to degrees and sort in increasing order)
323
324 contains
325
326 subroutine handle_err_copy_att(att_name)
327
328 use netcdf, only: nf90_noerr, nf90_strerror
329
330 character(len=*), intent(in):: att_name
331
332 !----------------------------------------
333
334 if (ncerr /= nf90_noerr) then
335 print *, "prepare_out " // trim(name_out(i)) &
336 // " nf90_copy_att " // att_name // " -- " &
337 // trim(nf90_strerror(ncerr))
338 end if
339
340 end subroutine handle_err_copy_att
341
342 end subroutine prepare_out
343
344 end module regr_lat_time_coefoz_m

  ViewVC Help
Powered by ViewVC 1.1.21