/[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 185 by guez, Wed Mar 16 15:04:46 2016 UTC revision 189 by guez, Tue Mar 29 15:20:23 2016 UTC
# Line 1  Line 1 
1    module cv30_trigger_m
2    
3        SUBROUTINE cv30_trigger(len,nd,icb,plcl,p,th,tv,tvp &    implicit none
4                        ,pbase,buoybase,iflag,sig,w0)  
5              use cv30_param_m  contains
6        implicit none  
7      SUBROUTINE cv30_trigger(len, nd, icb, plcl, p, th, tv, tvp, pbase, buoybase, &
8  !-------------------------------------------------------------------         iflag, sig, w0)
9  ! --- TRIGGERING  
10  !      ! TRIGGERING
11  !     - computes the cloud base  
12  !   - triggering (crude in this version)      ! - computes the cloud base
13  !     - relaxation of sig and w0 when no convection      ! - triggering (crude in this version)
14  !      ! - relaxation of sig and w0 when no convection
15  !     Caution1: if no convection, we set iflag=4  
16  !              (it used to be 0 in convect3)      ! Caution 1: if no convection, we set iflag=4
17  !      ! (it used to be 0 in convect3)
18  !     Caution2: at this stage, tvp (and thus buoy) are know up  
19  !             through icb only!      ! Caution 2: at this stage, tvp (and thus buoy) are known up
20  ! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy      ! 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  ! input:  
25        integer, intent(in):: len, nd      ! input:
26        integer icb(len)      integer, intent(in):: len, nd
27        real, intent(in):: plcl(len), p(len,nd)      integer icb(len)
28        real th(len,nd), tv(len,nd), tvp(len,nd)      real, intent(in):: plcl(len), p(len, nd)
29        real th(len, nd), tv(len, nd), tvp(len, nd)
30  ! output:  
31        real pbase(len), buoybase(len)      ! output:
32        real pbase(len), buoybase(len)
33  ! input AND output:  
34        integer iflag(len)      ! input AND output:
35        real, intent(inout):: sig(len,nd), w0(len,nd)      integer iflag(len)
36        real, intent(inout):: sig(len, nd), w0(len, nd)
37  ! local variables:  
38        integer i,k      ! local variables:
39        real tvpbase, tvbase, tdif, ath, ath1      integer i, k
40        real tvpbase, tvbase, tdif, ath, ath1
41  !  
42  ! ***   set cloud base buoyancy at (plcl+dpbase) level buoyancy      !---------------------------------------------------------------------
43  !  
44        do 100 i=1,len      ! set cloud base buoyancy at (plcl+dpbase) level buoyancy
45    
46        do i=1, len
47         pbase(i) = plcl(i) + dpbase         pbase(i) = plcl(i) + dpbase
48         tvpbase = tvp(i,icb(i))*(pbase(i)-p(i,icb(i)+1)) &         tvpbase = tvp(i, icb(i))*(pbase(i)-p(i, icb(i)+1)) &
49                                /(p(i,icb(i))-p(i,icb(i)+1)) &              /(p(i, icb(i))-p(i, icb(i)+1)) &
50                 + tvp(i,icb(i)+1)*(p(i,icb(i))-pbase(i)) &              + tvp(i, icb(i)+1)*(p(i, icb(i))-pbase(i)) &
51                                  /(p(i,icb(i))-p(i,icb(i)+1))              /(p(i, icb(i))-p(i, icb(i)+1))
52         tvbase = tv(i,icb(i))*(pbase(i)-p(i,icb(i)+1)) &         tvbase = tv(i, icb(i))*(pbase(i)-p(i, icb(i)+1)) &
53                              /(p(i,icb(i))-p(i,icb(i)+1)) &              /(p(i, icb(i))-p(i, icb(i)+1)) &
54                + tv(i,icb(i)+1)*(p(i,icb(i))-pbase(i)) &              + tv(i, icb(i)+1)*(p(i, icb(i))-pbase(i)) &
55                                /(p(i,icb(i))-p(i,icb(i)+1))              /(p(i, icb(i))-p(i, icb(i)+1))
56         buoybase(i) = tvpbase - tvbase         buoybase(i) = tvpbase - tvbase
57  100   continue      end do
   
 !  
 !   ***   make sure that column is dry adiabatic between the surface  ***  
 !   ***    and cloud base, and that lifted air is positively buoyant  ***  
 !   ***                         at cloud base                         ***  
 !   ***       if not, return to calling program after resetting       ***  
 !   ***                        sig(i) and w0(i)                       ***  
 !  
   
       do  60 k=1,nl  
       do 200 i=1,len  
   
        tdif = buoybase(i)  
        ath1 = th(i,1)  
        ath  = th(i,icb(i)-1) - dttrig  
   
        if (tdif.lt.dtcrit .or. ath.gt.ath1) then  
             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  
 ! convect3         iflag(i)=0  
        endif  
58    
59  200   continue      ! Make sure that column is dry adiabatic between the surface and
60   60   continue      ! 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  ! fin oct3 --    end SUBROUTINE cv30_trigger
80    
81        return  end module cv30_trigger_m
       end  

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

  ViewVC Help
Powered by ViewVC 1.1.21