/[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

trunk/libf/phylmd/CV3_routines/cv3_trigger.f90 revision 69 by guez, Mon Feb 18 16:33:12 2013 UTC trunk/Sources/phylmd/CV30_routines/cv30_trigger.f revision 201 by guez, Mon Jun 6 17:42:15 2016 UTC
# Line 1  Line 1 
1    module cv30_trigger_m
2    
3        SUBROUTINE cv3_trigger(len,nd,icb,plcl,p,th,tv,tvp &    implicit none
                       ,pbase,buoybase,iflag,sig,w0)  
             use cv3_param_m  
       implicit none  
   
 !-------------------------------------------------------------------  
 ! --- TRIGGERING  
 !  
 !     - computes the cloud base  
 !   - triggering (crude in this version)  
 !     - relaxation of sig and w0 when no convection  
 !  
 !     Caution1: if no convection, we set iflag=4  
 !              (it used to be 0 in convect3)  
 !  
 !     Caution2: at this stage, tvp (and thus buoy) are know up  
 !             through icb only!  
 ! -> the buoyancy below cloud base not (yet) set to the cloud base buoyancy  
 !-------------------------------------------------------------------  
   
   
 ! input:  
       integer len, nd  
       integer icb(len)  
       real plcl(len), p(len,nd)  
       real th(len,nd), tv(len,nd), tvp(len,nd)  
   
 ! output:  
       real pbase(len), buoybase(len)  
   
 ! input AND output:  
       integer iflag(len)  
       real sig(len,nd), w0(len,nd)  
   
 ! local variables:  
       integer i,k  
       real tvpbase, tvbase, tdif, ath, ath1  
   
 !  
 ! ***   set cloud base buoyancy at (plcl+dpbase) level buoyancy  
 !  
       do 100 i=1,len  
        pbase(i) = plcl(i) + dpbase  
        tvpbase = tvp(i,icb(i))*(pbase(i)-p(i,icb(i)+1)) &  
                               /(p(i,icb(i))-p(i,icb(i)+1)) &  
                + tvp(i,icb(i)+1)*(p(i,icb(i))-pbase(i)) &  
                                 /(p(i,icb(i))-p(i,icb(i)+1))  
        tvbase = tv(i,icb(i))*(pbase(i)-p(i,icb(i)+1)) &  
                             /(p(i,icb(i))-p(i,icb(i)+1)) &  
               + tv(i,icb(i)+1)*(p(i,icb(i))-pbase(i)) &  
                               /(p(i,icb(i))-p(i,icb(i)+1))  
        buoybase(i) = tvpbase - tvbase  
 100   continue  
   
 !  
 !   ***   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)                       ***  
 !  
   
 ! oct3      do 200 i=1,len  
 ! oct3  
 ! oct3       tdif = buoybase(i)  
 ! oct3       ath1 = th(i,1)  
 ! oct3       ath  = th(i,icb(i)-1) - dttrig  
 ! oct3  
 ! oct3       if (tdif.lt.dtcrit .or. ath.gt.ath1) then  
 ! oct3         do 60 k=1,nl  
 ! oct3            sig(i,k) = beta*sig(i,k) - 2.*alpha*tdif*tdif  
 ! oct3            sig(i,k) = AMAX1(sig(i,k),0.0)  
 ! oct3            w0(i,k)  = beta*w0(i,k)  
 ! oct3   60    continue  
 ! oct3         iflag(i)=4 ! pour version vectorisee  
 ! oct3c convect3         iflag(i)=0  
 ! oct3cccc         return  
 ! oct3       endif  
 ! oct3  
 ! oct3200   continue  
   
 ! -- oct3: on reecrit la boucle 200 (pour la vectorisation)  
   
       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  
4    
5  200   continue  contains
  60   continue  
6    
7  ! fin oct3 --    SUBROUTINE cv30_trigger(icb1, plcl1, p1, th1, tv1, tvp1, pbase1, buoybase1, &
8           iflag1, sig1, w01)
9    
10        return      ! Triggering:
11        end      ! - 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

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

  ViewVC Help
Powered by ViewVC 1.1.21