--- trunk/phylmd/CV3_routines/cv3_trigger.f 2014/08/29 13:00:05 103 +++ trunk/Sources/phylmd/CV30_routines/cv30_trigger.f 2016/06/06 17:42:15 201 @@ -1,85 +1,76 @@ +module cv30_trigger_m - SUBROUTINE cv3_trigger(len,nd,icb,plcl,p,th,tv,tvp & - ,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, intent(in):: len, nd - integer icb(len) - real, intent(in):: 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, intent(inout):: 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) *** -! - - 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 + implicit none -200 continue - 60 continue +contains -! fin oct3 -- + SUBROUTINE cv30_trigger(icb1, plcl1, p1, th1, tv1, tvp1, pbase1, buoybase1, & + iflag1, sig1, w01) - return - end + ! Triggering: + ! - computes the cloud base + ! - triggering (crude in this version) + ! - relaxation of sig1 and w01 when no convection + + ! Caution 1: if no convection, we set iflag1 = 4 + + ! Caution 2: at this stage, tvp1 (and thus buoy) are known up + ! through icb1 only! -> the buoyancy below cloud base not (yet) + ! set to the cloud base buoyancy + + use cv30_param_m, only: alpha, beta, dtcrit, nl + USE dimphy, ONLY: klev, klon + + integer, intent(in):: icb1(klon) + ! first level above LCL, 2 <= icb1 <= nl - 2 + + real, intent(in):: plcl1(klon), p1(klon, klev) + real, intent(in):: th1(:, :) ! (klon, nl) + real, intent(in):: tv1(klon, klev), tvp1(klon, klev) + + real, intent(out):: pbase1(klon), buoybase1(klon) + + integer, intent(inout):: iflag1(klon) + real, intent(inout):: sig1(klon, klev), w01(klon, klev) + + ! Local: + real, parameter:: dttrig = 5. ! (loose) condition for triggering + real, parameter:: dpbase = - 40. ! definition cloud base (400 m above LCL) + integer i, k + real tvpbase, tvbase + + !--------------------------------------------------------------------- + + ! Set cloud base buoyancy at plcl1 + dpbase level buoyancy: + do i = 1, klon + pbase1(i) = plcl1(i) + dpbase + tvpbase = tvp1(i, icb1(i)) * (pbase1(i) - p1(i, icb1(i) + 1)) & + /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) & + + tvp1(i, icb1(i) + 1) * (p1(i, icb1(i)) - pbase1(i)) & + /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) + tvbase = tv1(i, icb1(i)) * (pbase1(i) - p1(i, icb1(i) + 1)) & + /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) & + + tv1(i, icb1(i) + 1) * (p1(i, icb1(i)) - pbase1(i)) & + /(p1(i, icb1(i)) - p1(i, icb1(i) + 1)) + buoybase1(i) = tvpbase - tvbase + 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 sig1(i) + ! and w01(i). + do k = 1, nl + do i = 1, klon + if (buoybase1(i) < dtcrit .or. th1(i, icb1(i) - 1) - dttrig & + > th1(i, 1)) then + sig1(i, k) = MAX(beta * sig1(i, k) - 2. * alpha & + * buoybase1(i)**2, 0.) + w01(i, k) = beta * w01(i, k) + iflag1(i) = 4 + endif + end do + end do + + end SUBROUTINE cv30_trigger + +end module cv30_trigger_m