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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 52 - (show annotations)
Fri Sep 23 12:28:01 2011 UTC (12 years, 7 months ago) by guez
File size: 5238 byte(s)
Split "conflx.f" into single-procedure files in directory "Conflx".

Split "cv_routines.f" into single-procedure files in directory
"CV_routines". Made module "cvparam" from included file
"cvparam.h". No included file other than "netcdf.inc" left in LMDZE.

1 module o3_chem_m
2
3 IMPLICIT none
4
5 private o3_prod
6
7 contains
8
9 subroutine o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, q)
10
11 ! This procedure evolves the ozone mass fraction through a time
12 ! step taking only chemistry into account.
13
14 ! All the 2-dimensional arrays are on the "physics" grid.
15 ! Their shape is "(/klon, llm/)".
16 ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
17
18 use nr_util, only: assert, pi
19 use dimphy, only: klon
20 use dimens_m, only: llm
21 use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm
22 use orbite_m, only: orbite, zenang
23
24 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
25 real, intent(in):: gmtime ! heure de la journée en fraction de jour
26 real, intent(in):: t_seri(:, :) ! (klon, llm) temperature, in K
27
28 real, intent(in):: zmasse(:, :) ! (klon, llm)
29 ! (column-density of mass of air in a cell, in kg m-2)
30 ! "zmasse(:, k)" is for layer "k".)
31
32 real, intent(in):: pdtphys ! time step for physics, in s
33
34 real, intent(inout):: q(:, :) ! (klon, llm) mass fraction of ozone
35 ! "q(:, k)" is at middle of layer "k".)
36
37 ! Variables local to the procedure:
38 integer k
39
40 real c(klon, llm)
41 ! (constant term during a time step in the net mass production
42 ! rate of ozone by chemistry, per unit mass of air, in s-1)
43 ! "c(:, k)" is at middle of layer "k".)
44
45 real b(klon, llm)
46 ! (coefficient of "q" in the net mass production
47 ! rate of ozone by chemistry, per unit mass of air, in s-1)
48 ! "b(:, k)" is at middle of layer "k".)
49
50 real dq_o3_chem(klon, llm)
51 ! (variation of ozone mass fraction due to chemistry during a time step)
52 ! "dq_o3_chem(:, k)" is at middle of layer "k".)
53
54 real earth_long
55 ! (longitude vraie de la Terre dans son orbite solaire, par
56 ! rapport au point vernal (21 mars), en degrés)
57
58 real pmu0(klon) ! mean of cosine of solar zenith angle during "pdtphys"
59
60 !-------------------------------------------------------------
61
62 call assert(klon == (/size(q, 1), size(t_seri, 1), size(zmasse, 1)/), &
63 "o3_chem klon")
64 call assert(llm == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
65 "o3_chem llm")
66
67 c = c_Mob + a4_mass * t_seri
68
69 ! Compute coefficient "b":
70
71 ! Heterogeneous chemistry is only at low temperature:
72 where (t_seri < 195.)
73 b = r_het_interm
74 elsewhere
75 b = 0.
76 end where
77
78 ! Heterogeneous chemistry is only during daytime:
79 call orbite(real(julien), earth_long)
80 call zenang(earth_long, gmtime, pdtphys, pmu0)
81 forall (k = 1: llm)
82 where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.
83 end forall
84
85 b = b + a2
86
87 ! Midpoint method:
88
89 ! Trial step to the midpoint:
90 dq_o3_chem = o3_prod(q, zmasse, c, b) * pdtphys / 2
91 ! "Real" step across the whole interval:
92 dq_o3_chem = o3_prod(q + dq_o3_chem, zmasse, c, b) * pdtphys
93 q = q + dq_o3_chem
94
95 ! Confine the mass fraction:
96 q = min(max(q, 0.), .01)
97
98 end subroutine o3_chem
99
100 !*************************************************
101
102 function o3_prod(q, zmasse, c, b)
103
104 ! This function computes the production rate of ozone by chemistry.
105
106 ! All the 2-dimensional arrays are on the "physics" grid.
107 ! Their shape is "(/klon, llm/)".
108 ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
109
110 use regr_pr_comb_coefoz_m, only: a6_mass
111 use nr_util, only: assert
112 use dimens_m, only: llm
113 use dimphy, only: klon
114
115 real, intent(in):: q(:, :) ! mass fraction of ozone
116 ! "q(:, k)" is at middle of layer "k".)
117
118 real, intent(in):: zmasse(:, :)
119 ! (column-density of mass of air in a layer, in kg m-2)
120 ! ("zmasse(:, k)" is for layer "k".)
121
122 real, intent(in):: c(:, :)
123 ! (constant term during a time step in the net mass production
124 ! rate of ozone by chemistry, per unit mass of air, in s-1)
125 ! "c(:, k)" is at middle of layer "k".)
126
127 real, intent(in):: b(:, :)
128 ! (coefficient of "q" in the net mass production rate of ozone by
129 ! chemistry, per unit mass of air, in s-1)
130 ! ("b(:, k)" is at middle of layer "k".)
131
132 real o3_prod(klon, llm)
133 ! (net mass production rate of ozone by chemistry, per unit mass
134 ! of air, in s-1)
135 ! ("o3_prod(:, k)" is at middle of layer "k".)
136
137 ! Variables local to the procedure:
138
139 real sigma_mass(klon, llm)
140 ! (mass column-density of ozone above point, in kg m-2)
141 ! ("sigma_mass(:, k)" is at middle of layer "k".)
142
143 integer k
144
145 !-------------------------------------------------------------------
146
147 call assert(klon == (/size(q, 1), size(zmasse, 1), size(c, 1), &
148 size(b, 1)/), "o3_prod 1")
149 call assert(llm == (/size(q, 2), size(zmasse, 2), size(c, 2), &
150 size(b, 2)/), "o3_prod 2")
151
152 ! Compute the column-density above the base of layer
153 ! "k", and, as a first approximation, take it as column-density
154 ! above the middle of layer "k":
155 sigma_mass(:, llm) = zmasse(:, llm) * q(:, llm) ! top layer
156 do k = llm - 1, 1, -1
157 sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k)
158 end do
159
160 o3_prod = c + b * q + a6_mass * sigma_mass
161
162 end function o3_prod
163
164 end module o3_chem_m

  ViewVC Help
Powered by ViewVC 1.1.21