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

Annotation of /trunk/phylmd/concvl.f90

Parent Directory Parent Directory | Revision Log Revision Log


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

  ViewVC Help
Powered by ViewVC 1.1.21