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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 8 - (show annotations)
Mon Mar 31 12:51:21 2008 UTC (16 years, 1 month ago) by guez
File size: 2876 byte(s)
This revision is not in working order. Pending some moving of files.
Moving files around.

1 module regr_pr_o3_m
2
3 implicit none
4
5 contains
6
7 subroutine regr_pr_o3(o3_mob_regr)
8
9 ! "regr_pr_o3" stands for "regrid pressure ozone".
10 ! This procedure reads Mobidic ozone mole fraction from
11 ! "coefoz_LMDZ.nc" at the initial day and regrids it in pressure.
12 ! Regridding is by averaging, assuming a step function.
13 ! We assume that, in the input file, the pressure levels are in hPa
14 ! and strictly increasing.
15
16 use conf_gcm_m, only: dayref
17 use dimens_m, only: iim, jjm, llm
18 use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err, &
19 nf95_get_coord
20 use netcdf, only: nf90_nowrite, nf90_get_var
21 use regr_pr, only: regr_pr_av
22 use nrutil, only: assert
23
24 real, intent(out):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)
25 ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)
26 ! ("o3_mob_regr(i, j, l)" is at longitude "rlonv(i)", latitude
27 ! "rlatu(j)" and pressure level "pls(i, j, l)")
28
29 ! Variables local to the procedure:
30
31 real, pointer:: plev(:)
32 ! (pressure levels of Mobidic data, in Pa, in strictly increasing order)
33
34 real, allocatable:: press_in_edg(:)
35 ! (edges of pressure intervals for Mobidic data, in Pa, in strictly
36 ! increasing order)
37
38 integer ncid, varid, ncerr ! for NetCDF
39 integer n_plev ! number of pressure levels in Mobidic data
40 integer j
41
42 real, allocatable:: r_mob(:, :)! (jjm + 1, n_plev)
43 ! (ozone mole fraction from Mobidic at day "dayref")
44 ! (r_mob(j, k) is at latitude "rlatu(j)" and pressure level "plev(k)".)
45
46 !------------------------------------------------------------
47
48 call assert(shape(o3_mob_regr) == (/iim + 1, jjm + 1, llm/), "regr_pr_o3")
49
50 call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
51
52 call nf95_get_coord(ncid, "plev", plev)
53 ! Convert from hPa to Pa because "regr_pr_av" requires so:
54 plev = plev * 100.
55 n_plev = size(plev)
56
57 ! Compute edges of pressure intervals:
58 allocate(press_in_edg(n_plev + 1))
59 press_in_edg(1) = 0.
60 ! We choose edges halfway in logarithm:
61 forall (j = 2:n_plev) press_in_edg(j) = sqrt(plev(j - 1) * plev(j))
62 press_in_edg(n_plev + 1) = huge(0.)
63 ! (infinity, but any value guaranteed to be greater than the
64 ! surface pressure would do)
65
66 deallocate(plev) ! pointer
67
68 call nf95_inq_varid(ncid, "r_Mob", varid)
69 allocate(r_mob(jjm + 1, n_plev))
70
71 ! Get data at the right day from the input file:
72 ncerr = nf90_get_var(ncid, varid, r_mob, start=(/1, 1, dayref/))
73 call handle_err("nf90_get_var r_Mob", ncerr)
74 ! Latitudes are in increasing order in the input file while
75 ! "rlatu" is in decreasing order so we need to invert order:
76 r_mob = r_mob(jjm+1:1:-1, :)
77
78 call nf95_close(ncid)
79
80 o3_mob_regr = regr_pr_av(r_mob, press_in_edg)
81
82 end subroutine regr_pr_o3
83
84 end module regr_pr_o3_m

  ViewVC Help
Powered by ViewVC 1.1.21