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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 7 - (hide annotations)
Mon Mar 31 12:24:17 2008 UTC (16 years, 1 month ago) by guez
Original Path: trunk/libf/dyn3d/rrltwc.f90
File size: 11910 byte(s)
This revision is not in working order. Pending some moving of files.

Important changes. In the program "etat0_lim": ozone coefficients from
Mobidic are regridded in time instead of pressure ; consequences in
"etat0". In the program "gcm", ozone coefficients from Mobidic are
read once per day only for the current day and regridded in pressure ;
consequences in "o3_chem_m", "regr_pr_coefoz", "phytrac" and
"regr_pr_comb_coefoz_m".

NetCDF95 is a library and does not export NetCDF.

New variables "nag_gl_options", "nag_fcalls_options" and
"nag_cross_options" in "nag_tools.mk".

"check_coefoz.jnl" rewritten entirely for new version of
"coefoz_LMDZ.nc".

Target "obj_etat0_lim" moved from "GNUmakefile" to "nag_rules.mk".

Added some "intent" attributes in "calfis", "clmain", "clqh",
"cltrac", "cltracrn", "cvltr", "ini_undefSTD", "moy_undefSTD",
"nflxtr", "phystokenc", "phytrac", "readsulfate", "readsulfate_preind"
and "undefSTD".

In "dynetat0", "dynredem0" and "gcm", "phis" has rank 2 instead of
1. "phis" has assumed shape in "dynredem0".

Added module containing "dynredem0". Changed some calls with NetCDF
Fortran 77 interface to calls with NetCDF95 interface.

Replaced calls to "ssum" by calls to "sum" in "inigeom".

In "make.sh", new option "-c" to change compiler.

In "aaam_bud", argument "rjour" deleted.

In "physiq": renamed some variables; deleted variable "xjour".

In "phytrac": renamed some variables; new argument "lmt_pas".

1 guez 7 module regr_lat_time_coefoz_m
2 guez 3
3     ! This module is clean: no C preprocessor directive, no include line.
4 guez 4 ! Author: Lionel GUEZ
5 guez 3
6     implicit none
7    
8     private
9 guez 7 public read_regr_lat_time_write_coefoz
10 guez 3
11     contains
12    
13 guez 7 subroutine regr_lat_time_coefoz
14 guez 3
15 guez 7 ! "regr_lat_time_coefoz" stands for "regrid latitude time
16     ! coefficients ozone".
17 guez 3
18 guez 7 ! 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 guez 3 ! 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 guez 7 ! 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 guez 3 ! The values of "rlatu" are taken to be the centers of intervals.
30 guez 7 ! 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 guez 3
34 guez 7 ! 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 guez 3
40 guez 7 use dimens_m, only: jjm
41 guez 3 use comgeom, only: rlatv
42     use comconst, only: pi
43     use regr1_step_av_m, only: regr1_step_av
44 guez 7 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 guez 3
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 guez 7 real, pointer:: plev(:) ! pressure level of input data
63 guez 3 logical decr_lat ! decreasing latitude in the input file
64    
65 guez 7 real, allocatable:: o3_par_in(:, :, :) ! (n_lat, n_plev, 12)
66 guez 3 ! (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 guez 7 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 guez 3
84 guez 7 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 guez 3 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 guez 7 ! (name of NetCDF primary variable in the input file)
96 guez 4
97 guez 3 character(len=9) name_out(n_o3_param)
98 guez 7 ! (name of NetCDF primary variable in the output file)
99 guez 3
100 guez 7 integer varid_in(n_o3_param), varid_out(n_o3_param), varid_plev, varid_time
101     integer ncerr
102     ! (for NetCDF)
103 guez 3
104 guez 7 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 guez 3
110 guez 7 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 guez 3
114     !---------------------------------
115    
116     print *, "Call sequence information: regr_coefoz"
117    
118 guez 7 ! Names of ozone parameters:
119 guez 3 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 guez 7 call nf95_get_coord(ncid_in, "latitude", latitude)
158 guez 3 ! Convert from degrees to rad, because "rlatv" is in rad:
159 guez 4 latitude = latitude / 180. * pi
160 guez 3 n_lat = size(latitude)
161 guez 7 ! We need to supply the latitudes to "regr1_step_av" in
162 guez 3 ! increasing order, so invert order if necessary:
163     decr_lat = latitude(1) > latitude(n_lat)
164 guez 4 if (decr_lat) latitude = latitude(n_lat:1:-1)
165 guez 3
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 guez 7 call nf95_get_coord(ncid_in, "plev", plev)
174 guez 3 n_plev = size(plev)
175 guez 7 ! (We only need the pressure coordinate to copy it to the output file.)
176 guez 3
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 guez 7 ! 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 guez 3
186 guez 7 ! 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 guez 3 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 guez 7 v_regr_lat(jjm+1:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
208 guez 3 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
209 guez 4 ! (invert order of indices in "v_regr_lat" because "rlatu" is
210     ! decreasing)
211 guez 3
212 guez 7 ! 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 guez 3
217 guez 7 ! Regrid in time by linear interpolation:
218     o3_par_out = regr3_lint(v_regr_lat, tmidmonth, tmidday)
219 guez 3
220     ! Write to file:
221 guez 7 call nf95_put_var(ncid_out, varid_out(i_v), &
222     o3_par_out(jjm+1:1:-1, :, :))
223 guez 3 ! (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 guez 7 end subroutine regr_lat_time_coefoz
230 guez 3
231     !********************************************
232    
233 guez 7 subroutine prepare_out(ncid_in, varid_in, n_plev, name_out, ncid_out, &
234     varid_out, varid_plev, varid_time)
235 guez 3
236     ! This subroutine creates the NetCDF output file, defines
237 guez 7 ! dimensions and variables, and writes one of the coordinate variables.
238 guez 3
239 guez 7 use dimens_m, only: jjm
240     use comgeom, only: rlatu
241 guez 3 use comconst, only: pi
242     use nrutil, only: assert_eq
243    
244 guez 7 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 guez 3
248 guez 7 integer, intent(in):: ncid_in, varid_in(:), n_plev
249 guez 3 character(len=*), intent(in):: name_out(:) ! of NetCDF variables
250 guez 7 integer, intent(out):: ncid_out, varid_out(:), varid_plev, varid_time
251 guez 3
252     ! Variables local to the procedure:
253     integer ncerr
254 guez 7 integer dimid_rlatu, dimid_plev, dimid_time
255     integer varid_rlatu
256 guez 3 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 guez 7 call nf95_def_dim(ncid_out, "time", 360, dimid_time)
268     call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
269 guez 3 call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
270    
271 guez 7 ! Define coordinate variables:
272 guez 3
273 guez 7 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 guez 3
278 guez 7 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 guez 3
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 guez 7 call nf95_put_att(ncid_out, varid_rlatu, "standard_name", "latitude")
286 guez 3
287 guez 7 ! Define primary variables:
288 guez 3
289     do i = 1, n_o3_param
290     call nf95_def_var(ncid_out, name_out(i), nf90_float, &
291 guez 7 (/dimid_rlatu, dimid_plev, dimid_time/), varid_out(i))
292    
293 guez 3 ! The following commands may fail. That is OK. It should just
294     ! mean that the attribute is not defined in the input file.
295 guez 7
296 guez 3 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 guez 7
300 guez 3 ncerr = nf90_copy_att(ncid_in, varid_in(i), "units", ncid_out,&
301     & varid_out(i))
302     call handle_err_copy_att("units")
303 guez 7
304 guez 3 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 guez 7 call nf95_copy_att(ncid_in, nf90_global, "Conventions", ncid_out, &
311     nf90_global)
312 guez 3 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 guez 7 ! Write one of the coordinate variables:
319     call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
320 guez 3 ! (convert from rad to degrees and sort in increasing order)
321    
322     contains
323    
324     subroutine handle_err_copy_att(att_name)
325    
326 guez 7 use netcdf, only: nf90_noerr, nf90_strerror
327 guez 3
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 guez 7 end module regr_lat_time_coefoz_m

  ViewVC Help
Powered by ViewVC 1.1.21