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

Diff of /trunk/Sources/phylmd/CV30_routines/cv30_undilute2.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 192 by guez, Thu May 12 13:00:07 2016 UTC
# Line 4  module cv30_undilute2_m Line 4  module cv30_undilute2_m
4    
5  contains  contains
6    
7    SUBROUTINE cv30_undilute2(nloc, ncum, nd, icb, icbs, nk, tnk, qnk, gznk, t, &    SUBROUTINE cv30_undilute2(ncum, icb, icbs, nk, tnk, qnk, gznk, t, qs, gz, &
8         qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, tvp, clw, hp, &         p, h, tv, lv, pbase, buoybase, plcl, inb, tp, tvp, clw, hp, ep, sigp, &
9         ep, sigp, buoy)         buoy)
10    
11      ! Purpose: find the rest of the lifted parcel temperatures;      ! Undilute (adiabatic) updraft, second part. Purpose: find the
12      ! compute the precipitation efficiencies and the fraction of      ! rest of the lifted parcel temperatures; compute the
13      ! precipitation falling outside of cloud; find the level of      ! precipitation efficiencies and the fraction of precipitation
14      ! neutral buoyancy.      ! falling outside of cloud; find the level of neutral buoyancy.
15    
16      ! Vertical profile of buoyancy computed here (use of buoybase).      ! Vertical profile of buoyancy computed here (use of buoybase).
17    
18      use conema3_m, only: epmax      use conema3_m, only: epmax
19      use cv30_param_m, only: dtovsh, minorig, nl, nlp, pbcrit, ptcrit, spfac      use cv30_param_m, only: dtovsh, minorig, nl, pbcrit, ptcrit, spfac
20      use cvthermo, only: cl, clmcpv, cpd, cpv, eps, lv0, rrv      use cv_thermo_m, only: cl, clmcpv, cpd, cpv, eps, lv0, rrv
21        USE dimphy, ONLY: klon, klev
22      ! inputs:  
23      integer, intent(in):: nloc, ncum, nd      integer, intent(in):: ncum
24      integer icb(nloc), icbs(nloc), nk(nloc)  
25      ! icbs (input) is the first level above LCL (may differ from icb)      integer, intent(in):: icb(klon), icbs(klon)
26      real tnk(nloc), qnk(nloc), gznk(nloc)      ! icbs is the first level above LCL (may differ from icb)
27      real t(nloc, nd), qs(nloc, nd), gz(nloc, nd)  
28      real p(nloc, nd), h(nloc, nd)      integer, intent(in):: nk(klon)
29      real tv(nloc, nd), lv(nloc, nd)      real, intent(in):: tnk(klon), qnk(klon), gznk(klon)
30      real pbase(nloc), buoybase(nloc), plcl(nloc)      real, intent(in):: t(klon, klev), qs(klon, klev), gz(klon, klev)
31        real, intent(in):: p(klon, klev), h(klon, klev)
32        real, intent(in):: tv(klon, klev), lv(klon, klev)
33        real, intent(in):: pbase(klon), buoybase(klon), plcl(klon)
34    
35      ! outputs:      ! outputs:
36      integer inb(nloc)      integer, intent(out):: inb(:) ! (ncum)
37      real tp(nloc, nd), tvp(nloc, nd), clw(nloc, nd)      ! first model level above the level of neutral buoyancy of the
38        ! parcel (1 <= inb <= nl - 1)
39    
40        real tp(klon, klev), tvp(klon, klev), clw(klon, klev)
41      ! condensed water not removed from tvp      ! condensed water not removed from tvp
42      real hp(nloc, nd), ep(nloc, nd), sigp(nloc, nd)      real hp(klon, klev), ep(klon, klev), sigp(klon, klev)
43      real buoy(nloc, nd)      real buoy(klon, klev)
44    
45      ! Local:      ! Local:
46      integer i, k      integer i, k
47      real tg, qg, ahg, alv, s, tc, es, denom      real tg, qg, ahg, alv, s, tc, es, denom
48      real pden      real pden
49      real ah0(nloc)      real ah0(klon)
50    
51      !---------------------------------------------------------------------      !---------------------------------------------------------------------
52    
# Line 125  contains Line 131  contains
131         do i = 1, ncum         do i = 1, ncum
132            pden = ptcrit - pbcrit            pden = ptcrit - pbcrit
133            ep(i, k) = (plcl(i) - p(i, k) - pbcrit) / pden * epmax            ep(i, k) = (plcl(i) - p(i, k) - pbcrit) / pden * epmax
134            ep(i, k) = amax1(ep(i, k), 0.0)            ep(i, k) = max(ep(i, k), 0.0)
135            ep(i, k) = amin1(ep(i, k), epmax)            ep(i, k) = min(ep(i, k), epmax)
136            sigp(i, k) = spfac            sigp(i, k) = spfac
137         end do         end do
138      end do      end do
# Line 137  contains Line 143  contains
143      ! tvp est calcule en une seule fois, et sans retirer      ! tvp est calcule en une seule fois, et sans retirer
144      ! l'eau condensee (~> reversible CAPE)      ! l'eau condensee (~> reversible CAPE)
145      do i = 1, ncum      do i = 1, ncum
146         tp(i, nlp) = tp(i, nl)         tp(i, nl + 1) = tp(i, nl)
147      end do      end do
148    
149      ! EFFECTIVE VERTICAL PROFILE OF BUOYANCY:      ! EFFECTIVE VERTICAL PROFILE OF BUOYANCY:
# Line 160  contains Line 166  contains
166         buoy(icb(i), k) = buoybase(i)         buoy(icb(i), k) = buoybase(i)
167      end do      end do
168    
169      ! FIND THE FIRST MODEL LEVEL (INB) ABOVE THE PARCEL'S      ! Compute inb:
     ! LEVEL OF NEUTRAL BUOYANCY  
170    
171      do i = 1, ncum      inb = nl - 1
        inb(i) = nl - 1  
     end do  
172    
173      do i = 1, ncum      do i = 1, ncum
174         do k = 1, nl - 1         do k = 1, nl - 1
# Line 177  contains Line 180  contains
180    
181      ! CALCULATE LIQUID WATER STATIC ENERGY OF LIFTED PARCEL      ! CALCULATE LIQUID WATER STATIC ENERGY OF LIFTED PARCEL
182    
183      do k = 1, nlp      do k = 1, nl + 1
184         do i = 1, ncum         do i = 1, ncum
185            hp(i, k) = h(i, k)            hp(i, k) = h(i, k)
186         enddo         enddo

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

  ViewVC Help
Powered by ViewVC 1.1.21