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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 189 by guez, Tue Mar 29 15:20:23 2016 UTC revision 201 by guez, Mon Jun 6 17:42:15 2016 UTC
# Line 4  module cv30_trigger_m Line 4  module cv30_trigger_m
4    
5  contains  contains
6    
7    SUBROUTINE cv30_trigger(len, nd, icb, plcl, p, th, tv, tvp, pbase, buoybase, &    SUBROUTINE cv30_trigger(icb1, plcl1, p1, th1, tv1, tvp1, pbase1, buoybase1, &
8         iflag, sig, w0)         iflag1, sig1, w01)
   
     ! TRIGGERING  
9    
10        ! Triggering:
11      ! - computes the cloud base      ! - computes the cloud base
12      ! - triggering (crude in this version)      ! - triggering (crude in this version)
13      ! - relaxation of sig and w0 when no convection      ! - relaxation of sig1 and w01 when no convection
14    
15        ! Caution 1: if no convection, we set iflag1 = 4
16    
17      ! Caution 1: if no convection, we set iflag=4      ! Caution 2: at this stage, tvp1 (and thus buoy) are known up
18      ! (it used to be 0 in convect3)      ! through icb1 only!  -> the buoyancy below cloud base not (yet)
19        ! set to the cloud base buoyancy
20    
21      ! Caution 2: at this stage, tvp (and thus buoy) are known up      use cv30_param_m, only: alpha, beta, dtcrit, nl
22      ! through icb only!      USE dimphy, ONLY: klev, klon
     ! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy  
23    
24      use cv30_param_m, only: alpha, beta, dpbase, dtcrit, dttrig, nl      integer, intent(in):: icb1(klon)
25        ! first level above LCL, 2 <= icb1 <= nl - 2
26    
27      ! input:      real, intent(in):: plcl1(klon), p1(klon, klev)
28      integer, intent(in):: len, nd      real, intent(in):: th1(:, :) ! (klon, nl)
29      integer icb(len)      real, intent(in):: tv1(klon, klev), tvp1(klon, klev)
     real, intent(in):: plcl(len), p(len, nd)  
     real th(len, nd), tv(len, nd), tvp(len, nd)  
30    
31      ! output:      real, intent(out):: pbase1(klon), buoybase1(klon)
     real pbase(len), buoybase(len)  
32    
33      ! input AND output:      integer, intent(inout):: iflag1(klon)
34      integer iflag(len)      real, intent(inout):: sig1(klon, klev), w01(klon, klev)
     real, intent(inout):: sig(len, nd), w0(len, nd)  
35    
36      ! local variables:      ! 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      integer i, k
40      real tvpbase, tvbase, tdif, ath, ath1      real tvpbase, tvbase
41    
42      !---------------------------------------------------------------------      !---------------------------------------------------------------------
43    
44      ! set cloud base buoyancy at (plcl+dpbase) level buoyancy      ! Set cloud base buoyancy at plcl1 + dpbase level buoyancy:
45        do i = 1, klon
46      do i=1, len         pbase1(i) = plcl1(i) + dpbase
47         pbase(i) = plcl(i) + dpbase         tvpbase = tvp1(i, icb1(i)) * (pbase1(i) - p1(i, icb1(i) + 1)) &
48         tvpbase = tvp(i, icb(i))*(pbase(i)-p(i, icb(i)+1)) &              /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) &
49              /(p(i, icb(i))-p(i, icb(i)+1)) &              + tvp1(i, icb1(i) + 1) * (p1(i, icb1(i)) - pbase1(i)) &
50              + tvp(i, icb(i)+1)*(p(i, icb(i))-pbase(i)) &              /(p1(i, icb1(i)) - p1(i, icb1(i) + 1))
51              /(p(i, icb(i))-p(i, icb(i)+1))         tvbase = tv1(i, icb1(i)) * (pbase1(i) - p1(i, icb1(i) + 1)) &
52         tvbase = tv(i, icb(i))*(pbase(i)-p(i, icb(i)+1)) &              /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) &
53              /(p(i, icb(i))-p(i, icb(i)+1)) &              + tv1(i, icb1(i) + 1) * (p1(i, icb1(i)) - pbase1(i)) &
54              + tv(i, icb(i)+1)*(p(i, icb(i))-pbase(i)) &              /(p1(i, icb1(i)) - p1(i, icb1(i) + 1))
55              /(p(i, icb(i))-p(i, icb(i)+1))         buoybase1(i) = tvpbase - tvbase
        buoybase(i) = tvpbase - tvbase  
56      end do      end do
57    
58      ! Make sure that column is dry adiabatic between the surface and      ! Make sure that column is dry adiabatic between the surface and
59      ! cloud base, and that lifted air is positively buoyant at cloud      ! cloud base, and that lifted air is positively buoyant at cloud
60      ! base.  If not, return to calling program after resetting sig(i)      ! base.  If not, return to calling program after resetting sig1(i)
61      ! and w0(i).      ! and w01(i).
62        do k = 1, nl
63      do k=1, nl         do i = 1, klon
64         do i=1, len            if (buoybase1(i) < dtcrit .or. th1(i, icb1(i) - 1) - dttrig &
65            tdif = buoybase(i)                 > th1(i, 1)) then
66            ath1 = th(i, 1)               sig1(i, k) = MAX(beta * sig1(i, k) - 2. * alpha &
67            ath = th(i, icb(i)-1) - dttrig                    * buoybase1(i)**2, 0.)
68                 w01(i, k) = beta * w01(i, k)
69            if (tdif < dtcrit .or. ath > ath1) then               iflag1(i) = 4
              sig(i, k) = beta*sig(i, k) - 2.*alpha*tdif*tdif  
              sig(i, k) = AMAX1(sig(i, k), 0.0)  
              w0(i, k) = beta*w0(i, k)  
              iflag(i)=4 ! pour version vectorisee  
70            endif            endif
71         end do         end do
72      end do      end do

Legend:
Removed from v.189  
changed lines
  Added in v.201

  ViewVC Help
Powered by ViewVC 1.1.21