/[lmdze]/trunk/phylmd/cv_driver.f
ViewVC logotype

Annotation of /trunk/phylmd/cv_driver.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 266 - (hide annotations)
Thu Apr 19 17:54:55 2018 UTC (6 years ago) by guez
File size: 10180 byte(s)
Define macros of the preprocessor CPP_IIM, CPP_JJM, CPP_LLM so we can
control the resolution from the compilation command, and automate
compilation for several resolutions.

In module yoethf_m, transform variables into named constants. So we do
not need procedure yoethf any longer.

Bug fix in program test_inter_barxy, missing calls to fyhyp and fxhyp,
and definition of rlatu.

Remove variable iecri of module conf_gcm_m. The files dyn_hist*.nc are
written every time step. We are simplifying the output system, pending
replacement by a whole new system.

Modify possible value of vert_sampling from "param" to
"strato_custom", following LMDZ. Default values of corresponding
namelist variables are now the values used for LMDZ CMIP6.

1 guez 52 module cv_driver_m
2 guez 3
3 guez 52 implicit none
4 guez 3
5 guez 52 contains
6 guez 3
7 guez 183 SUBROUTINE cv_driver(t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, fq1, fu1, &
8 guez 195 fv1, precip1, VPrecip1, sig1, w01, icb1, inb1, Ma1, upwd1, dnwd1, &
9 guez 205 qcondc1, cape1, da1, phi1, mp1)
10 guez 3
11 guez 91 ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3, 2005/04/15 12:36:17
12 guez 69 ! Main driver for convection
13 guez 97 ! Author: S. Bony, March 2002
14 guez 69
15 guez 72 ! Several modules corresponding to different physical processes
16    
17 guez 195 use comconst, only: dtphys
18 guez 187 use cv30_closure_m, only: cv30_closure
19 guez 185 use cv30_compress_m, only: cv30_compress
20     use cv30_feed_m, only: cv30_feed
21     use cv30_mixing_m, only: cv30_mixing
22 guez 188 use cv30_param_m, only: cv30_param, nl
23 guez 185 use cv30_prelim_m, only: cv30_prelim
24     use cv30_tracer_m, only: cv30_tracer
25 guez 189 use cv30_trigger_m, only: cv30_trigger
26 guez 185 use cv30_uncompress_m, only: cv30_uncompress
27 guez 195 use cv30_undilute1_m, only: cv30_undilute1
28 guez 185 use cv30_undilute2_m, only: cv30_undilute2
29     use cv30_unsat_m, only: cv30_unsat
30     use cv30_yield_m, only: cv30_yield
31 guez 62 USE dimphy, ONLY: klev, klon
32    
33 guez 201 real, intent(in):: t1(klon, klev) ! temperature, in K
34 guez 189 real, intent(in):: q1(klon, klev) ! specific humidity
35     real, intent(in):: qs1(klon, klev) ! saturation specific humidity
36 guez 103
37 guez 187 real, intent(in):: u1(klon, klev), v1(klon, klev)
38 guez 189 ! zonal wind and meridional velocity (m/s)
39 guez 72
40 guez 201 real, intent(in):: p1(klon, klev) ! full level pressure, in hPa
41 guez 180
42 guez 187 real, intent(in):: ph1(klon, klev + 1)
43 guez 201 ! Half level pressure, in hPa. These pressures are defined at levels
44 guez 189 ! intermediate between those of P1, T1, Q1 and QS1. The first
45     ! value of PH should be greater than (i.e. at a lower level than)
46     ! the first value of the array P1.
47 guez 180
48 guez 196 integer, intent(out):: iflag1(:) ! (klon)
49 guez 187 ! Flag for Emanuel conditions.
50 guez 3
51 guez 187 ! 0: Moist convection occurs.
52 guez 3
53 guez 187 ! 1: Moist convection occurs, but a CFL condition on the
54     ! subsidence warming is violated. This does not cause the scheme
55     ! to terminate.
56 guez 3
57 guez 187 ! 2: Moist convection, but no precipitation because ep(inb) < 1e-4
58 guez 103
59 guez 187 ! 3: No moist convection because new cbmf is 0 and old cbmf is 0.
60 guez 62
61 guez 195 ! 4: No moist convection; atmosphere is not unstable.
62 guez 62
63 guez 195 ! 6: No moist convection because ihmin <= minorig.
64 guez 62
65 guez 187 ! 7: No moist convection because unreasonable parcel level
66     ! temperature or specific humidity.
67 guez 62
68 guez 187 ! 8: No moist convection: lifted condensation level is above the
69 guez 195 ! 200 mbar level.
70 guez 62
71 guez 195 ! 9: No moist convection: cloud base is higher than the level NL-1.
72 guez 62
73 guez 189 real, intent(out):: ft1(klon, klev) ! temperature tendency (K/s)
74     real, intent(out):: fq1(klon, klev) ! specific humidity tendency (s-1)
75 guez 62
76 guez 187 real, intent(out):: fu1(klon, klev), fv1(klon, klev)
77 guez 189 ! forcing (tendency) of zonal and meridional velocity (m/s^2)
78 guez 62
79 guez 187 real, intent(out):: precip1(klon) ! convective precipitation rate (mm/day)
80 guez 62
81 guez 187 real, intent(out):: VPrecip1(klon, klev + 1)
82     ! vertical profile of convective precipitation (kg/m2/s)
83 guez 62
84 guez 189 real, intent(inout):: sig1(klon, klev) ! section of adiabatic updraft
85 guez 62
86 guez 187 real, intent(inout):: w01(klon, klev)
87     ! vertical velocity within adiabatic updraft
88 guez 62
89 guez 187 integer, intent(out):: icb1(klon)
90     integer, intent(inout):: inb1(klon)
91 guez 189 real, intent(out):: Ma1(klon, klev) ! mass flux of adiabatic updraft
92 guez 62
93 guez 187 real, intent(out):: upwd1(klon, klev)
94 guez 189 ! total upward mass flux (adiabatic + mixed)
95 guez 62
96 guez 187 real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)
97 guez 62
98 guez 189 real, intent(out):: qcondc1(klon, klev)
99     ! in-cloud mixing ratio of condensed water
100 guez 62
101 guez 189 real, intent(out):: cape1(klon)
102 guez 205 real, intent(out):: da1(:, :) ! (klon, klev)
103     real, intent(out):: phi1(:, :, :) ! (klon, klev, klev)
104 guez 62
105 guez 205 real, intent(out):: mp1(:, :) ! (klon, klev) Mass flux of the
106     ! unsaturated downdraft, defined positive downward, in kg m-2
107     ! s-1. M_p in Emanuel (1991 928).
108    
109 guez 187 ! Local:
110 guez 62
111 guez 201 real da(klon, klev), phi(klon, klev, klev)
112 guez 205
113     real, allocatable:: mp(:, :) ! (ncum, nl) Mass flux of the
114     ! unsaturated downdraft, defined positive downward, in kg m-2
115     ! s-1. M_p in Emanuel (1991 928).
116    
117 guez 97 integer i, k, il
118 guez 52 integer icbs1(klon)
119     real plcl1(klon)
120     real tnk1(klon)
121     real qnk1(klon)
122     real gznk1(klon)
123     real pbase1(klon)
124     real buoybase1(klon)
125 guez 201
126     real lv1(klon, nl)
127     ! specific latent heat of vaporization of water, in J kg-1
128    
129     real cpn1(klon, nl)
130     ! specific heat capacity at constant pressure of humid air, in J K-1 kg-1
131    
132 guez 52 real tv1(klon, klev)
133     real gz1(klon, klev)
134     real hm1(klon, klev)
135     real h1(klon, klev)
136     real tp1(klon, klev)
137     real tvp1(klon, klev)
138     real clw1(klon, klev)
139 guez 201 real th1(klon, nl) ! potential temperature, in K
140 guez 52 integer ncum
141 guez 62
142 guez 187 ! Compressed fields:
143 guez 196 integer, allocatable:: idcum(:), iflag(:) ! (ncum)
144 guez 195 integer, allocatable:: icb(:) ! (ncum)
145 guez 103 integer nent(klon, klev)
146     integer icbs(klon)
147 guez 201
148     integer, allocatable:: inb(:) ! (ncum)
149     ! first model level above the level of neutral buoyancy of the
150     ! parcel (1 <= inb <= nl - 1)
151    
152 guez 196 real, allocatable:: plcl(:) ! (ncum)
153     real tnk(klon), qnk(klon), gznk(klon)
154 guez 103 real t(klon, klev), q(klon, klev), qs(klon, klev)
155     real u(klon, klev), v(klon, klev)
156 guez 201 real gz(klon, klev), h(klon, klev)
157    
158     real, allocatable:: lv(:, :) ! (ncum, nl)
159     ! specific latent heat of vaporization of water, in J kg-1
160    
161     real, allocatable:: cpn(:, :) ! (ncum, nl)
162     ! specific heat capacity at constant pressure of humid air, in J K-1 kg-1
163    
164 guez 195 real p(klon, klev) ! pressure at full level, in hPa
165     real ph(klon, klev + 1), tv(klon, klev), tp(klon, klev)
166 guez 103 real clw(klon, klev)
167 guez 201 real pbase(klon), buoybase(klon)
168     real, allocatable:: th(:, :) ! (ncum, nl)
169 guez 103 real tvp(klon, klev)
170     real sig(klon, klev), w0(klon, klev)
171 guez 195 real hp(klon, klev), ep(klon, klev)
172 guez 183 real buoy(klon, klev)
173 guez 103 real cape(klon)
174     real m(klon, klev), ment(klon, klev, klev), qent(klon, klev, klev)
175     real uent(klon, klev, klev), vent(klon, klev, klev)
176     real ments(klon, klev, klev), qents(klon, klev, klev)
177     real sij(klon, klev, klev), elij(klon, klev, klev)
178     real qp(klon, klev), up(klon, klev), vp(klon, klev)
179 guez 195 real wt(klon, klev), water(klon, klev)
180     real, allocatable:: evap(:, :) ! (ncum, nl)
181 guez 189 real, allocatable:: b(:, :) ! (ncum, nl - 1)
182 guez 188 real ft(klon, klev), fq(klon, klev)
183 guez 103 real fu(klon, klev), fv(klon, klev)
184 guez 205 real upwd(klon, klev), dnwd(klon, klev)
185 guez 103 real Ma(klon, klev), mike(klon, klev), tls(klon, klev)
186 guez 183 real tps(klon, klev)
187 guez 103 real precip(klon)
188 guez 180 real VPrecip(klon, klev + 1)
189 guez 266 real qcondc(klon, klev) ! cloud
190 guez 3
191 guez 52 !-------------------------------------------------------------------
192 guez 3
193 guez 180 ! SET CONSTANTS AND PARAMETERS
194 guez 195 CALL cv30_param
195 guez 52
196 guez 180 ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS
197 guez 3
198 guez 205 da1 = 0.
199     mp1 = 0.
200     phi1 = 0.
201    
202 guez 103 do k = 1, klev
203     do i = 1, klon
204 guez 187 ft1(i, k) = 0.
205     fq1(i, k) = 0.
206     fu1(i, k) = 0.
207     fv1(i, k) = 0.
208     tvp1(i, k) = 0.
209     tp1(i, k) = 0.
210     clw1(i, k) = 0.
211     clw(i, k) = 0.
212 guez 103 gz1(i, k) = 0.
213 guez 52 VPrecip1(i, k) = 0.
214 guez 187 Ma1(i, k) = 0.
215     upwd1(i, k) = 0.
216     dnwd1(i, k) = 0.
217     qcondc1(i, k) = 0.
218 guez 52 end do
219     end do
220 guez 3
221 guez 195 precip1 = 0.
222     cape1 = 0.
223     VPrecip1(:, klev + 1) = 0.
224 guez 3
225 guez 181 do il = 1, klon
226     sig1(il, klev) = sig1(il, klev) + 1.
227     sig1(il, klev) = min(sig1(il, klev), 12.1)
228     enddo
229 guez 3
230 guez 198 CALL cv30_prelim(t1, q1, p1, ph1, lv1, cpn1, tv1, gz1, h1, hm1, th1)
231     CALL cv30_feed(t1, q1, qs1, p1, ph1, gz1, icb1, iflag1, tnk1, qnk1, &
232 guez 196 gznk1, plcl1)
233 guez 198 CALL cv30_undilute1(t1, q1, qs1, gz1, plcl1, p1, icb1, tp1, tvp1, clw1, &
234     icbs1)
235 guez 195 CALL cv30_trigger(icb1, plcl1, p1, th1, tv1, tvp1, pbase1, buoybase1, &
236     iflag1, sig1, w01)
237 guez 3
238 guez 196 ncum = count(iflag1 == 0)
239 guez 3
240 guez 103 IF (ncum > 0) THEN
241 guez 196 ! Moist convective adjustment is necessary
242 guez 201 allocate(idcum(ncum), plcl(ncum), inb(ncum))
243 guez 196 allocate(b(ncum, nl - 1), evap(ncum, nl), icb(ncum), iflag(ncum))
244 guez 201 allocate(th(ncum, nl), lv(ncum, nl), cpn(ncum, nl), mp(ncum, nl))
245 guez 196 idcum = pack((/(i, i = 1, klon)/), iflag1 == 0)
246 guez 201 CALL cv30_compress(idcum, iflag1, icb1, icbs1, plcl1, tnk1, qnk1, &
247     gznk1, pbase1, buoybase1, t1, q1, qs1, u1, v1, gz1, th1, h1, lv1, &
248     cpn1, p1, ph1, tv1, tp1, tvp1, clw1, sig1, w01, icb, icbs, plcl, &
249     tnk, qnk, gznk, pbase, buoybase, t, q, qs, u, v, gz, th, h, lv, &
250     cpn, p, ph, tv, tp, tvp, clw, sig, w0)
251 guez 198 CALL cv30_undilute2(icb, icbs(:ncum), tnk, qnk, gznk, t, qs, gz, p, h, &
252 guez 201 tv, lv, pbase(:ncum), buoybase(:ncum), plcl, inb, tp, tvp, &
253 guez 198 clw, hp, ep, buoy)
254 guez 201 CALL cv30_closure(icb, inb, pbase, p, ph(:ncum, :), tv, buoy, &
255 guez 196 sig, w0, cape, m)
256 guez 201 CALL cv30_mixing(icb, inb, t, q, qs, u, v, h, lv, &
257     hp, ep, clw, m, sig, ment, qent, uent, vent, nent, sij, elij, &
258     ments, qents)
259     CALL cv30_unsat(icb, inb, t(:ncum, :nl), q(:ncum, :nl), &
260 guez 198 qs(:ncum, :nl), gz, u(:ncum, :nl), v(:ncum, :nl), p, &
261 guez 201 ph(:ncum, :), th(:ncum, :nl - 1), tv, lv, cpn, ep(:ncum, :), &
262     clw(:ncum, :), m(:ncum, :), ment(:ncum, :, :), elij(:ncum, :, :), &
263     dtphys, plcl, mp, qp(:ncum, :nl), up(:ncum, :nl), vp(:ncum, :nl), &
264     wt(:ncum, :nl), water(:ncum, :nl), evap, b)
265     CALL cv30_yield(icb, inb, dtphys, t, q, u, v, gz, p, ph, h, hp, &
266 guez 195 lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp(:ncum, 2:nl), &
267     wt(:ncum, :nl - 1), water(:ncum, :nl), evap, b, ment, qent, uent, &
268     vent, nent, elij, sig, tv, tvp, iflag, precip, VPrecip, ft, fq, &
269 guez 205 fu, fv, upwd, dnwd, ma, mike, tls, tps, qcondc)
270 guez 185 CALL cv30_tracer(klon, ncum, klev, ment, sij, da, phi)
271 guez 196 CALL cv30_uncompress(idcum, iflag, precip, VPrecip, sig, w0, ft, fq, &
272 guez 205 fu, fv, inb, Ma, upwd, dnwd, qcondc, cape, da, phi, mp, iflag1, &
273     precip1, VPrecip1, sig1, w01, ft1, fq1, fu1, fv1, inb1, Ma1, &
274     upwd1, dnwd1, qcondc1, cape1, da1, phi1, mp1)
275 guez 183 ENDIF
276 guez 3
277 guez 52 end SUBROUTINE cv_driver
278 guez 3
279 guez 52 end module cv_driver_m

  ViewVC Help
Powered by ViewVC 1.1.21