/[lmdze]/trunk/libf/phylmd/o3_mob_ph_m.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/o3_mob_ph_m.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 7 - (show annotations)
Mon Mar 31 12:24:17 2008 UTC (16 years, 1 month ago) by guez
File size: 5010 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 module regr_pr_coefoz
2
3 implicit none
4
5 contains
6
7 subroutine regr_pr_av_coefoz(ncid, name, julien, press_in_edg, v3)
8
9 ! "regr_pr_av_coefoz" stands for "regrid pressure averaging
10 ! coefficients ozone".
11 ! This procedure reads a single Mobidic ozone coefficient from
12 !"coefoz_LMDZ.nc", at the current day, regrids this parameter in
13 ! pressure to the LMDZ vertical grid and packs it to the LMDZ
14 ! horizontal "physics" grid.
15 ! Regridding is by averaging a step function.
16
17 use dimens_m, only: iim, jjm, llm
18 use dimphy, only: klon
19 use netcdf95, only: nf95_inq_varid, handle_err
20 use netcdf, only: nf90_get_var
21 use grid_change, only: dyn_phy
22 use regr_pr, only: regr_pr_av
23 use nrutil, only: assert
24
25 integer, intent(in):: ncid ! NetCDF ID of the file
26 character(len=*), intent(in):: name ! of the NetCDF variable
27 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
28
29 real, intent(in):: press_in_edg(:)
30 ! (edges of pressure intervals for Mobidic data, in Pa, in
31 ! strictly increasing order)
32
33 real, intent(out):: v3(:, :) ! (klon, llm)
34 ! (ozone coefficient from Mobidic on the "physics" grid)
35 ! ("v3(i, k)" is at longitude "xlon(i)", latitude
36 ! "xlat(i)", middle of layer "k".)
37
38 ! Variables local to the procedure:
39 integer varid, ncerr
40 integer k
41
42 real v1(jjm + 1, size(press_in_edg) - 1)
43 ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
44 ! ("v1(j, k)" is at latitude "rlatu(j)" and for
45 ! pressure interval "[press_in_edg(k), press_in_edg(k+1)]".)
46
47 real v2(iim + 1, jjm + 1, llm)
48 ! (ozone parameter from Mobidic on the "dynamics" grid)
49 ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
50 ! "rlatu(j)", middle of layer "k".)
51
52 !--------------------------------------------
53
54 call assert(shape(v3) == (/klon, llm/), "regr_pr_av_coefoz")
55
56 call nf95_inq_varid(ncid, name, varid)
57
58 ! Get data at the right day from the input file:
59 ncerr = nf90_get_var(ncid, varid, v1, start=(/1, 1, julien/))
60 call handle_err("regr_pr_av_coefoz nf90_get_var " // name, ncerr, ncid)
61 ! Latitudes are in increasing order in the input file while
62 ! "rlatu" is in decreasing order so we need to invert order:
63 v1 = v1(jjm+1:1:-1, :)
64
65 ! Regrid in pressure at each horizontal position:
66 v2 = regr_pr_av(v1, press_in_edg)
67
68 forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
69
70 end subroutine regr_pr_av_coefoz
71
72 !***************************************************************
73
74 subroutine regr_pr_int_coefoz(ncid, name, julien, plev, top_value, v3)
75
76 ! This procedure reads a single Mobidic ozone coefficient from
77 !"coefoz_LMDZ.nc", at the current day, regrids this parameter in
78 ! pressure to the LMDZ vertical grid and packs it to the LMDZ
79 ! horizontal "physics" grid.
80 ! Regridding is by linear interpolation.
81
82 use dimens_m, only: iim, jjm, llm
83 use dimphy, only: klon
84 use netcdf95, only: nf95_inq_varid, handle_err
85 use netcdf, only: nf90_get_var
86 use grid_change, only: dyn_phy
87 use regr_pr, only: regr_pr_int
88 use nrutil, only: assert
89
90 integer, intent(in):: ncid ! NetCDF ID of the file
91 character(len=*), intent(in):: name ! of the NetCDF variable
92 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
93
94 real, intent(in):: plev(:)
95 ! (pressure levels of Mobidic data, in Pa, in strictly increasing order)
96
97 real, intent(in):: top_value
98 ! (extra value of ozone coefficient at 0 pressure)
99
100 real, intent(out):: v3(:, :) ! (klon, llm)
101 ! (ozone parameter from Mobidic on the "physics" grid)
102 ! ("v3(i, k)" is at longitude "xlon(i)", latitude
103 ! "xlat(i)", middle of layer "k".)
104
105 ! Variables local to the procedure:
106 integer varid, ncerr
107 integer k
108
109 real v1(jjm + 1, 0:size(plev))
110 ! (ozone coefficient from "coefoz_LMDZ.nc" at day "julien")
111 ! ("v1(j, k >=1)" is at latitude "rlatu(j)" and pressure "plev(k)".)
112
113 real v2(iim + 1, jjm + 1, llm)
114 ! (ozone parameter from Mobidic on the "dynamics" grid)
115 ! "v2(i, j, k)" is at longitude "rlonv(i)", latitude
116 ! "rlatu(j)", middle of layer "k".)
117
118 !--------------------------------------------
119
120 call assert(shape(v3) == (/klon, llm/), "regr_pr_int_coefoz")
121
122 call nf95_inq_varid(ncid, name, varid)
123
124 ! Get data at the right day from the input file:
125 ncerr = nf90_get_var(ncid, varid, v1(:, 1:), start=(/1, 1, julien/))
126 call handle_err("regr_pr_int_coefoz nf90_get_var " // name, ncerr, ncid)
127 ! Latitudes are in increasing order in the input file while
128 ! "rlatu" is in decreasing order so we need to invert order:
129 v1(:, 1:) = v1(jjm+1:1:-1, 1:)
130
131 ! Complete "v1" with the value at 0 pressure:
132 v1(:, 0) = top_value
133
134 ! Regrid in pressure at each horizontal position:
135 v2 = regr_pr_int(v1, (/0., plev/))
136
137 forall (k = 1:llm) v3(:, k) = pack(v2(:, :, k), dyn_phy)
138
139 end subroutine regr_pr_int_coefoz
140
141 end module regr_pr_coefoz

  ViewVC Help
Powered by ViewVC 1.1.21