/[lmdze]/trunk/phylmd/concvl.f90
ViewVC logotype

Contents of /trunk/phylmd/concvl.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 346 - (show annotations)
Mon Dec 9 20:15:29 2019 UTC (4 years, 5 months ago) by guez
File size: 2635 byte(s)
Rename block to `my_block` in procedure `CLOUDS_GNO` because block is
a Fortran keyword.

Remove computation of palpbla in procedure sw. It was not used nor
output. (Not used nor output either in LMDZ.)

In procedure physiq, define `d_[uv]_con` and add them to `[uv]_seri`
only if `conv_Emanuel`. Thus, we do not need to initialize
`d_[uv]_con` to 0, we do not have to save them and we do not add 0 to
`[uv]_seri`.

In procedure physiq, no need to initialize rnebcon to 0, it is defined
by phyetat0 afterwards.

Check that `iflag_cldcon` is between - 2 and 3.

1 module concvl_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE concvl(paprs, play, t, q, u, v, sig1, w01, d_t, d_q, d_u, d_v, &
8 rain, kbas, itop_con, upwd, dnwd, ma, cape, iflag, qcondc, pmflxr, da, &
9 phi, mp)
10
11 ! From phylmd/concvl.F, version 1.3, 2005/04/15 12:36:17
12 ! Author: Z. X. Li (LMD/CNRS)
13 ! Date: 1993 August 18
14 ! Objet : schéma de convection d'Emanuel (1991), interface
15
16 use comconst, only: dtphys
17 use cv_driver_m, only: cv_driver
18 USE dimphy, ONLY: klev, klon
19 USE fcttre, ONLY: foeew
20 USE suphec_m, ONLY: retv, rtt
21 USE yoethf_m, ONLY: r2es
22
23 REAL, INTENT (IN):: paprs(klon, klev + 1)
24 REAL, INTENT (IN):: play(klon, klev)
25 REAL, intent(in):: t(klon, klev) ! temperature (K)
26 real, intent(in):: q(klon, klev) ! fraction massique de vapeur d'eau
27 real, INTENT (IN):: u(klon, klev), v(klon, klev)
28 REAL, intent(inout):: sig1(klon, klev), w01(klon, klev)
29 REAL, intent(out):: d_t(klon, klev)
30 REAL, intent(out):: d_q(klon, klev) ! incr\'ement de la vapeur d'eau
31 REAL, intent(out):: d_u(:, :), d_v(:, :) ! (klon, klev)
32 REAL, intent(out):: rain(klon) ! pluie (mm / s)
33 INTEGER, intent(out):: kbas(klon)
34 integer, intent(inout):: itop_con(klon)
35
36 REAL, intent(out):: upwd(klon, klev)
37 ! saturated updraft mass flux (kg / m2 / s)
38
39 real, intent(out):: dnwd(klon, klev)
40 ! saturated downdraft mass flux (kg / m2 / s)
41
42 REAL ma(klon, klev)
43 real cape(klon) ! output (J / kg)
44 INTEGER, intent(out):: iflag(klon)
45 REAL, intent(out):: qcondc(klon, klev) ! in-cloud water content
46 REAL, intent(out):: pmflxr(klon, klev + 1)
47 REAL, intent(out):: da(:, :) ! (klon, klev)
48 REAL, intent(out):: phi(:, :, :) ! (klon, klev, klev)
49
50 REAL, intent(out):: mp(:, :) ! (klon, klev) Mass flux of the
51 ! unsaturated downdraft, defined positive downward, in kg m-2
52 ! s-1. M_p in Emanuel (1991 928).
53
54 ! Local:
55 REAL zx_qs, cor
56 INTEGER i, k
57 REAL qs(klon, klev)
58
59 !-----------------------------------------------------------------
60
61 DO k = 1, klev
62 DO i = 1, klon
63 zx_qs = min(0.5, r2es * foeew(t(i, k), rtt >= t(i, k)) / play(i, k))
64 cor = 1. / (1. - retv * zx_qs)
65 qs(i, k) = zx_qs * cor
66 END DO
67 END DO
68
69 CALL cv_driver(t, q, qs, u, v, play / 100., paprs / 100., iflag, d_t, &
70 d_q, d_u, d_v, rain, pmflxr, sig1, w01, kbas, itop_con, ma, upwd, &
71 dnwd, qcondc, cape, da, phi, mp)
72 rain = rain / 86400.
73 d_t = dtphys * d_t
74 d_q = dtphys * d_q
75 d_u = dtphys * d_u
76 d_v = dtphys * d_v
77
78 END SUBROUTINE concvl
79
80 end module concvl_m

  ViewVC Help
Powered by ViewVC 1.1.21