/[lmdze]/trunk/Sources/phylmd/CV30_routines/cv30_trigger.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/CV30_routines/cv30_trigger.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 195 - (hide annotations)
Wed May 18 17:56:44 2016 UTC (8 years ago) by guez
File size: 2516 byte(s)
In cv30_feed, iflag1 is 0 on entry so we can simplify the test for
iflag1 = 7.

In cv30_feed, for the computation of icb, replaced sequential search
(with a useless end of loop on k) by a call to locate.

In CV30 routines, replaced len, nloc, nd, na by klon or
klev. Philosophy: no more generality than actually necessary.

Converted as many variables as possible to named constants in
cv30_param_m and downgraded pbcrit, ptcrit, dtovsh, dpbase, dttrig,
tau, delta to local objects in procedures. spfac, betad and omtrain
are useless and removed.

Instead of filling the array sigp with the constant spfac in
cv30_undilute2, just made sigp a constant in cv30_unsat.

In cv_driver, define as allocatable variables that are only
used on the range (ncum, nl).

1 guez 189 module cv30_trigger_m
2 guez 47
3 guez 189 implicit none
4 guez 47
5 guez 189 contains
6 guez 47
7 guez 195 SUBROUTINE cv30_trigger(icb1, plcl1, p1, th1, tv1, tvp1, pbase1, buoybase1, &
8     iflag1, sig1, w01)
9 guez 47
10 guez 195 ! Triggering:
11 guez 189 ! - computes the cloud base
12     ! - triggering (crude in this version)
13 guez 195 ! - relaxation of sig1 and w01 when no convection
14 guez 47
15 guez 195 ! Caution 1: if no convection, we set iflag1 = 4
16 guez 47
17 guez 195 ! Caution 2: at this stage, tvp1 (and thus buoy) are known up
18     ! through icb1 only! -> the buoyancy below cloud base not (yet)
19     ! set to the cloud base buoyancy
20 guez 47
21 guez 195 use cv30_param_m, only: alpha, beta, dtcrit, nl
22     USE dimphy, ONLY: klev, klon
23 guez 189
24 guez 195 integer, intent(in):: icb1(klon)
25     real, intent(in):: plcl1(klon), p1(klon, klev)
26     real, intent(in):: th1(klon, klev), tv1(klon, klev), tvp1(klon, klev)
27 guez 189
28 guez 195 real, intent(out):: pbase1(klon), buoybase1(klon)
29 guez 189
30 guez 195 integer, intent(inout):: iflag1(klon)
31     real, intent(inout):: sig1(klon, klev), w01(klon, klev)
32 guez 189
33 guez 195 ! Local:
34     real, parameter:: dttrig = 5. ! (loose) condition for triggering
35     real, parameter:: dpbase = - 40. ! definition cloud base (400 m above LCL)
36 guez 189 integer i, k
37 guez 195 real tvpbase, tvbase
38 guez 189
39     !---------------------------------------------------------------------
40    
41 guez 195 ! Set cloud base buoyancy at plcl1 + dpbase level buoyancy:
42     do i = 1, klon
43     pbase1(i) = plcl1(i) + dpbase
44     tvpbase = tvp1(i, icb1(i)) * (pbase1(i) - p1(i, icb1(i) + 1)) &
45     /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) &
46     + tvp1(i, icb1(i) + 1) * (p1(i, icb1(i)) - pbase1(i)) &
47     /(p1(i, icb1(i)) - p1(i, icb1(i) + 1))
48     tvbase = tv1(i, icb1(i)) * (pbase1(i) - p1(i, icb1(i) + 1)) &
49     /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) &
50     + tv1(i, icb1(i) + 1) * (p1(i, icb1(i)) - pbase1(i)) &
51     /(p1(i, icb1(i)) - p1(i, icb1(i) + 1))
52     buoybase1(i) = tvpbase - tvbase
53 guez 189 end do
54 guez 47
55 guez 189 ! Make sure that column is dry adiabatic between the surface and
56     ! cloud base, and that lifted air is positively buoyant at cloud
57 guez 195 ! base. If not, return to calling program after resetting sig1(i)
58     ! and w01(i).
59     do k = 1, nl
60     do i = 1, klon
61     if (buoybase1(i) < dtcrit .or. th1(i, icb1(i) - 1) - dttrig &
62     > th1(i, 1)) then
63     sig1(i, k) = MAX(beta * sig1(i, k) - 2. * alpha &
64     * buoybase1(i)**2, 0.)
65     w01(i, k) = beta * w01(i, k)
66     iflag1(i) = 4
67 guez 189 endif
68     end do
69     end do
70 guez 47
71 guez 189 end SUBROUTINE cv30_trigger
72 guez 47
73 guez 189 end module cv30_trigger_m

  ViewVC Help
Powered by ViewVC 1.1.21