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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 201 - (show annotations)
Mon Jun 6 17:42:15 2016 UTC (7 years, 10 months ago) by guez
File size: 2595 byte(s)
Removed intermediary objects of cv_thermo_m, access suphec_m
directly. Procedure cv_thermo disappeared, all objects are named
constants.

In cv_driver and below, limited extents of arrays to what is needed.

lv, cpn and th in cv30_compress were set at level nl + 1 but lv1, cpn1
and th1 are not defined at this level. This did not lead to an error
because values at nl + 1 were not used.

Removed test on ok_sync in phystokenc because it is not read at run
time. Printing min and max of output NetCDF variables is heavy and
archaic.

Used histwrite_phy in phytrac.

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

  ViewVC Help
Powered by ViewVC 1.1.21