/[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 13 - (show annotations)
Fri Jul 25 19:59:34 2008 UTC (15 years, 10 months ago) by guez
File size: 11911 byte(s)
-- Minor change of behaviour:

"etat0" does not compute "rugsrel" nor "radpas". Deleted arguments
"radpas" and "rugsrel" of "phyredem". Deleted argument "rugsrel" of
"phyetat0". "startphy.nc" does not contain the variable "RUGSREL". In
"physiq", "rugoro" is set to 0 if not "ok_orodr". The whole program
"etat0_lim" does not use "clesphys2".

-- Minor modification of input/output:

Created subroutine "read_clesphys2". Variables of "clesphys2" are read
in "read_clesphys2" instead of "conf_gcm". "printflag" does not print
variables of "clesphys2".

-- Should not change any result at run time:

References to module "numer_rec" instead of individual modules of
"Numer_rec_Lionel".

Deleted argument "clesphy0" of "calfis", "physiq", "conf_gcm",
"leapfrog", "phyetat0". Deleted variable "clesphy0" in
"gcm". "phyetat0" does not modify variables of "clesphys2".

The program unit "gcm" does not modify "itau_phy".

Added some "intent" attributes.

"regr11_lint" does not call "polint".

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_get_coord, 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
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) = "r"
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_v2_3.nc", nf90_nowrite, ncid_in)
154
155 ! Get coordinates from the input file:
156
157 call nf95_get_coord(ncid_in, "latitude", latitude)
158 ! Convert from degrees to rad, because "rlatv" is in rad:
159 latitude = latitude / 180. * pi
160 n_lat = size(latitude)
161 ! We need to supply the latitudes to "regr1_step_av" in
162 ! increasing order, so invert order if necessary:
163 decr_lat = latitude(1) > latitude(n_lat)
164 if (decr_lat) latitude = latitude(n_lat:1:-1)
165
166 ! Compute edges of latitude intervals:
167 allocate(lat_in_edg(n_lat + 1))
168 lat_in_edg(1) = - pi / 2
169 forall (j = 2:n_lat) lat_in_edg(j) = (latitude(j - 1) + latitude(j)) / 2
170 lat_in_edg(n_lat + 1) = pi / 2
171 deallocate(latitude) ! pointer
172
173 call nf95_get_coord(ncid_in, "plev", plev)
174 n_plev = size(plev)
175 ! (We only need the pressure coordinate to copy it to the output file.)
176
177 ! Get the IDs of ozone parameters in the input file:
178 do i_v = 1, n_o3_param
179 call nf95_inq_varid(ncid_in, trim(name_in(i_v)), varid_in(i_v))
180 end do
181
182 ! Create the output file and get the variable IDs:
183 call prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
184 varid_out, varid_plev, varid_time)
185
186 ! Write remaining coordinate variables:
187 call nf95_put_var(ncid_out, varid_time, tmidday)
188 call nf95_put_var(ncid_out, varid_plev, plev)
189
190 deallocate(plev) ! pointer
191
192 allocate(o3_par_in(n_lat, n_plev, 12))
193 allocate(v_regr_lat(jjm + 1, n_plev, 0:13))
194 allocate(o3_par_out(jjm + 1, n_plev, 360))
195
196 do i_v = 1, n_o3_param
197 ! Process ozone parameter "name_in(i_v)"
198
199 ncerr = nf90_get_var(ncid_in, varid_in(i_v), o3_par_in)
200 call handle_err("nf90_get_var", ncerr, ncid_in)
201
202 if (decr_lat) o3_par_in = o3_par_in(n_lat:1:-1, :, :)
203
204 ! Regrid in latitude:
205 ! We average with respect to sine of latitude, which is
206 ! equivalent to weighting by cosine of latitude:
207 v_regr_lat(jjm+1:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
208 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
209 ! (invert order of indices in "v_regr_lat" because "rlatu" is
210 ! decreasing)
211
212 ! Duplicate January and December values, in preparation of time
213 ! interpolation:
214 v_regr_lat(:, :, 0) = v_regr_lat(:, :, 12)
215 v_regr_lat(:, :, 13) = v_regr_lat(:, :, 1)
216
217 ! Regrid in time by linear interpolation:
218 o3_par_out = regr3_lint(v_regr_lat, tmidmonth, tmidday)
219
220 ! Write to file:
221 call nf95_put_var(ncid_out, varid_out(i_v), &
222 o3_par_out(jjm+1:1:-1, :, :))
223 ! (The order of "rlatu" is inverted in the output file)
224 end do
225
226 call nf95_close(ncid_out)
227 call nf95_close(ncid_in)
228
229 end subroutine regr_lat_time_coefoz
230
231 !********************************************
232
233 subroutine prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
234 varid_out, varid_plev, varid_time)
235
236 ! This subroutine creates the NetCDF output file, defines
237 ! dimensions and variables, and writes one of the coordinate variables.
238
239 use dimens_m, only: jjm
240 use comgeom, only: rlatu
241 use comconst, only: pi
242 use numer_rec, only: assert_eq
243
244 use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
245 nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
246 use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
247
248 integer, intent(in):: ncid_in, varid_in(:), n_plev
249 character(len=*), intent(in):: name_out(:) ! of NetCDF variables
250 integer, intent(out):: ncid_out, varid_out(:), varid_plev, varid_time
251
252 ! Variables local to the procedure:
253 integer ncerr
254 integer dimid_rlatu, dimid_plev, dimid_time
255 integer varid_rlatu
256 integer i, n_o3_param
257
258 !---------------------------
259
260 print *, "Call sequence information: prepare_out"
261 n_o3_param = assert_eq(size(varid_in), size(varid_out), &
262 size(name_out), "prepare_out")
263
264 call nf95_create("coefoz_LMDZ.nc", nf90_clobber, ncid_out)
265
266 ! Dimensions:
267 call nf95_def_dim(ncid_out, "time", 360, dimid_time)
268 call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
269 call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
270
271 ! Define coordinate variables:
272
273 call nf95_def_var(ncid_out, "time", nf90_float, dimid_time, varid_time)
274 call nf95_put_att(ncid_out, varid_time, "units", "days since 2000-1-1")
275 call nf95_put_att(ncid_out, varid_time, "calendar", "360_day")
276 call nf95_put_att(ncid_out, varid_time, "standard_name", "time")
277
278 call nf95_def_var(ncid_out, "plev", nf90_float, dimid_plev, varid_plev)
279 call nf95_put_att(ncid_out, varid_plev, "units", "millibar")
280 call nf95_put_att(ncid_out, varid_plev, "standard_name", "air_pressure")
281 call nf95_put_att(ncid_out, varid_plev, "long_name", "air pressure")
282
283 call nf95_def_var(ncid_out, "rlatu", nf90_float, dimid_rlatu, varid_rlatu)
284 call nf95_put_att(ncid_out, varid_rlatu, "units", "degrees_north")
285 call nf95_put_att(ncid_out, varid_rlatu, "standard_name", "latitude")
286
287 ! Define primary variables:
288
289 do i = 1, n_o3_param
290 call nf95_def_var(ncid_out, name_out(i), nf90_float, &
291 (/dimid_rlatu, dimid_plev, dimid_time/), varid_out(i))
292
293 ! The following commands may fail. That is OK. It should just
294 ! mean that the attribute is not defined in the input file.
295
296 ncerr = nf90_copy_att(ncid_in, varid_in(i), "long_name",&
297 & ncid_out, varid_out(i))
298 call handle_err_copy_att("long_name")
299
300 ncerr = nf90_copy_att(ncid_in, varid_in(i), "units", ncid_out,&
301 & varid_out(i))
302 call handle_err_copy_att("units")
303
304 ncerr = nf90_copy_att(ncid_in, varid_in(i), "standard_name", ncid_out,&
305 & varid_out(i))
306 call handle_err_copy_att("standard_name")
307 end do
308
309 ! Global attributes:
310 call nf95_copy_att(ncid_in, nf90_global, "Conventions", ncid_out, &
311 nf90_global)
312 call nf95_copy_att(ncid_in, nf90_global, "title", ncid_out, nf90_global)
313 call nf95_copy_att(ncid_in, nf90_global, "source", ncid_out, nf90_global)
314 call nf95_put_att(ncid_out, nf90_global, "comment", "Regridded for LMDZ")
315
316 call nf95_enddef(ncid_out)
317
318 ! Write one of the coordinate variables:
319 call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
320 ! (convert from rad to degrees and sort in increasing order)
321
322 contains
323
324 subroutine handle_err_copy_att(att_name)
325
326 use netcdf, only: nf90_noerr, nf90_strerror
327
328 character(len=*), intent(in):: att_name
329
330 !----------------------------------------
331
332 if (ncerr /= nf90_noerr) then
333 print *, "prepare_out " // trim(name_out(i)) &
334 // " nf90_copy_att " // att_name // " -- " &
335 // trim(nf90_strerror(ncerr))
336 end if
337
338 end subroutine handle_err_copy_att
339
340 end subroutine prepare_out
341
342 end module regr_lat_time_coefoz_m

  ViewVC Help
Powered by ViewVC 1.1.21