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

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

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

revision 195 by guez, Wed May 18 17:56:44 2016 UTC revision 196 by guez, Mon May 23 13:50:39 2016 UTC
# Line 4  module cv30_feed_m Line 4  module cv30_feed_m
4    
5  contains  contains
6    
7    SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, nk1, icb1, icbmax, iflag1, &    SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, nk1, icb1, iflag1, tnk1, &
8         tnk1, qnk1, gznk1, plcl1)         qnk1, gznk1, plcl1)
9    
10      ! Purpose: convective feed      ! Purpose: convective feed
11    
# Line 19  contains Line 19  contains
19      real, intent(in):: gz1(:, :) ! (klon, klev)      real, intent(in):: gz1(:, :) ! (klon, klev)
20    
21      ! outputs:      ! outputs:
22      integer, intent(out):: nk1(:), icb1(:) ! (klon)  
23      integer, intent(out):: icbmax      integer, intent(out):: nk1(:) ! (klon)
24      integer, intent(inout):: iflag1(klon)  
25        integer, intent(out):: icb1(:) ! (klon)
26        ! first level above lcl, 2 <= icb1 <= nl - 2
27    
28        integer, intent(out):: iflag1(:) ! (klon)
29      real tnk1(klon), qnk1(klon), gznk1(klon)      real tnk1(klon), qnk1(klon), gznk1(klon)
30      real, intent(out):: plcl1(klon)      real, intent(out):: plcl1(klon)
31    
# Line 32  contains Line 36  contains
36    
37      !--------------------------------------------------------------------      !--------------------------------------------------------------------
38    
39        iflag1 = 0
40      plcl1 = 0.      plcl1 = 0.
41    
42      ! Origin level of ascending parcels      ! Origin level of ascending parcels
# Line 48  contains Line 53  contains
53      ! (within 0.2 % of formula of Bolton, Mon. Wea. Rev., 1980)      ! (within 0.2 % of formula of Bolton, Mon. Wea. Rev., 1980)
54    
55      do i = 1, klon      do i = 1, klon
56         if (iflag1(i) /= 7) then         if (iflag1(i) == 0) then
57            tnk1(i) = t1(i, nk1(i))            tnk1(i) = t1(i, nk1(i))
58            qnk1(i) = q1(i, nk1(i))            qnk1(i) = q1(i, nk1(i))
59            gznk1(i) = gz1(i, nk1(i))            gznk1(i) = gz1(i, nk1(i))
# Line 58  contains Line 63  contains
63            rh(i) = qnk1(i) / qsnk(i)            rh(i) = qnk1(i) / qsnk(i)
64            chi(i) = tnk1(i) / (A - B*rh(i) - tnk1(i))            chi(i) = tnk1(i) / (A - B*rh(i) - tnk1(i))
65            plcl1(i) = pnk(i)*(rh(i)**chi(i))            plcl1(i) = pnk(i)*(rh(i)**chi(i))
66            if ((plcl1(i) < 200. .or. plcl1(i) >= 2000.) .and. iflag1(i) == 0) &            if (plcl1(i) < 200. .or. plcl1(i) >= 2000.) iflag1(i) = 8
                iflag1(i) = 8  
67         endif         endif
68      end do      end do
69    
70      ! Calculate first level above lcl (= icb1)      ! Compute icb1:
   
71      do i = 1, klon      do i = 1, klon
72         if (plcl1(i) <= ph1(i, nl - 2)) then         if (plcl1(i) <= ph1(i, nl - 2)) then
73            ! Distinguish this case just so that icb1 = nl - 2, not nl =            ! Distinguish this case just so that icb1 = nl - 2, not nl =
# Line 77  contains Line 80  contains
80         end if         end if
81      end do      end do
82    
83      do i = 1, klon      where (icb1 == nl - 2 .and. iflag1 == 0) iflag1 = 9
84         if ((icb1(i) == nl - 2).and.(iflag1(i) == 0)) iflag1(i) = 9      ! {(2 <= icb1(i) <= nl - 3 and ph1(i, icb1(i) + 1) < plcl1(i) <=
85      end do      ! ph1(i, icb1(i))) or iflag1 /= 0}
   
     ! Compute icbmax  
   
     icbmax = 2  
   
     do i = 1, klon  
        if (iflag1(i) < 7) icbmax = max(icbmax, icb1(i))  
     end do  
86    
87    end SUBROUTINE cv30_feed    end SUBROUTINE cv30_feed
88    

Legend:
Removed from v.195  
changed lines
  Added in v.196

  ViewVC Help
Powered by ViewVC 1.1.21