/[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 189 - (show annotations)
Tue Mar 29 15:20:23 2016 UTC (8 years, 1 month ago) by guez
File size: 2371 byte(s)
There was a function gr_phy_write_3d in dyn3d and a function
gr_phy_write_2d in module grid_change. Moved them into a new module
gr_phy_write_m under a generic interface gr_phy_write. Replaced calls
to gr_fi_ecrit by calls to gr_phy_write.

Removed arguments len, nloc and nd of cv30_compress.

Removed arguments wd and wd1 of cv30_uncompress, wd of cv30_yield, wd
of concvl, wd1 of cv_driver. Was just filled with 0. Removed option
ok_gust in physiq, never used.

In cv30_unsat, cv30_yield and cv_driver, we only need to define b to
level nl - 1.

1 module cv30_trigger_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE cv30_trigger(len, nd, icb, plcl, p, th, tv, tvp, pbase, buoybase, &
8 iflag, sig, w0)
9
10 ! TRIGGERING
11
12 ! - computes the cloud base
13 ! - triggering (crude in this version)
14 ! - relaxation of sig and w0 when no convection
15
16 ! Caution 1: if no convection, we set iflag=4
17 ! (it used to be 0 in convect3)
18
19 ! Caution 2: at this stage, tvp (and thus buoy) are known up
20 ! through icb only!
21 ! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy
22
23 use cv30_param_m, only: alpha, beta, dpbase, dtcrit, dttrig, nl
24
25 ! input:
26 integer, intent(in):: len, nd
27 integer icb(len)
28 real, intent(in):: plcl(len), p(len, nd)
29 real th(len, nd), tv(len, nd), tvp(len, nd)
30
31 ! output:
32 real pbase(len), buoybase(len)
33
34 ! input AND output:
35 integer iflag(len)
36 real, intent(inout):: sig(len, nd), w0(len, nd)
37
38 ! local variables:
39 integer i, k
40 real tvpbase, tvbase, tdif, ath, ath1
41
42 !---------------------------------------------------------------------
43
44 ! set cloud base buoyancy at (plcl+dpbase) level buoyancy
45
46 do i=1, len
47 pbase(i) = plcl(i) + dpbase
48 tvpbase = tvp(i, icb(i))*(pbase(i)-p(i, icb(i)+1)) &
49 /(p(i, icb(i))-p(i, icb(i)+1)) &
50 + tvp(i, icb(i)+1)*(p(i, icb(i))-pbase(i)) &
51 /(p(i, icb(i))-p(i, icb(i)+1))
52 tvbase = tv(i, icb(i))*(pbase(i)-p(i, icb(i)+1)) &
53 /(p(i, icb(i))-p(i, icb(i)+1)) &
54 + tv(i, icb(i)+1)*(p(i, icb(i))-pbase(i)) &
55 /(p(i, icb(i))-p(i, icb(i)+1))
56 buoybase(i) = tvpbase - tvbase
57 end do
58
59 ! Make sure that column is dry adiabatic between the surface and
60 ! cloud base, and that lifted air is positively buoyant at cloud
61 ! base. If not, return to calling program after resetting sig(i)
62 ! and w0(i).
63
64 do k=1, nl
65 do i=1, len
66 tdif = buoybase(i)
67 ath1 = th(i, 1)
68 ath = th(i, icb(i)-1) - dttrig
69
70 if (tdif < dtcrit .or. ath > ath1) then
71 sig(i, k) = beta*sig(i, k) - 2.*alpha*tdif*tdif
72 sig(i, k) = AMAX1(sig(i, k), 0.0)
73 w0(i, k) = beta*w0(i, k)
74 iflag(i)=4 ! pour version vectorisee
75 endif
76 end do
77 end do
78
79 end SUBROUTINE cv30_trigger
80
81 end module cv30_trigger_m

  ViewVC Help
Powered by ViewVC 1.1.21