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

trunk/Sources/phylmd/CV3_routines/cv3_feed.f revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC trunk/Sources/phylmd/CV30_routines/cv30_feed.f revision 195 by guez, Wed May 18 17:56:44 2016 UTC
# Line 1  Line 1 
1  module cv3_feed_m  module cv30_feed_m
2    
3    implicit none    implicit none
4    
5  contains  contains
6    
7    SUBROUTINE cv3_feed(len, nd, t, q, qs, p, ph, hm, gz, nk, icb, icbmax, &    SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, nk1, icb1, icbmax, iflag1, &
8         iflag, tnk, qnk, gznk, plcl)         tnk1, qnk1, gznk1, plcl1)
9    
10      ! Purpose: CONVECTIVE FEED      ! Purpose: convective feed
11    
12      ! Main differences with cv_feed:      use cv30_param_m, only: minorig, nl
13      ! - ph added in input      USE dimphy, ONLY: klev, klon
14      ! - here, nk(i)=minorig      use numer_rec_95, only: locate
15      ! - icb defined differently (plcl compared with ph instead of p)  
16        real, intent(in):: t1(:, :) ! (klon, klev)
17      ! Main differences with convect3:      real, intent(in):: q1(:, :), qs1(:, :), p1(:, :) ! (klon, klev)
18      ! - we do not compute dplcldt and dplcldr of CLIFT anymore      real, intent(in):: ph1(:, :) ! (klon, klev+1)
19      ! - values iflag different (but tests identical)      real, intent(in):: gz1(:, :) ! (klon, klev)
     ! - A, B explicitely defined (!)  
   
     use cv3_param_m  
   
     ! inputs:  
     integer, intent(in):: len, nd  
     real, intent(in):: t(len, nd)  
     real, intent(in):: q(len, nd), qs(len, nd), p(len, nd)  
     real hm(len, nd), gz(len, nd)  
     real, intent(in):: ph(len, nd+1)  
20    
21      ! outputs:      ! outputs:
22      integer iflag(len)      integer, intent(out):: nk1(:), icb1(:) ! (klon)
23      integer, intent(out):: nk(len), icb(len), icbmax      integer, intent(out):: icbmax
24      real tnk(len), qnk(len), gznk(len), plcl(len)      integer, intent(inout):: iflag1(klon)
25        real tnk1(klon), qnk1(klon), gznk1(klon)
26      ! local variables:      real, intent(out):: plcl1(klon)
27      integer i, k  
28      integer ihmin(len)      ! Local:
29      real work(len)      integer i
30      real pnk(len), qsnk(len), rh(len), chi(len)      real pnk(klon), qsnk(klon), rh(klon), chi(klon)
31      real A, B ! convect3      real, parameter:: A = 1669., B = 122.
32    
33      !--------------------------------------------------------------------      !--------------------------------------------------------------------
34    
35      plcl=0.0      plcl1 = 0.
36    
37      ! --- Origin level of ascending parcels for convect3:      ! Origin level of ascending parcels
38        nk1 = minorig
39    
40      do i=1, len      ! Check whether parcel level temperature and specific humidity
41         nk(i)=minorig      ! are reasonable
     end do  
   
     ! --- Check whether parcel level temperature and specific humidity  
     ! --- are reasonable  
   
     do i=1, len  
        if ((t(i, nk(i)) < 250. .or. q(i, nk(i)) <= 0.) .and. iflag(i) == 0) &  
             iflag(i)=7  
     end do  
   
     ! --- Calculate lifted condensation level of air at parcel origin level  
     ! --- (Within 0.2% of formula of Bolton, MON. WEA. REV., 1980)  
42    
43      A = 1669.0 ! convect3      do i = 1, klon
44      B = 122.0 ! convect3         if (t1(i, nk1(i)) < 250. .or. q1(i, nk1(i)) <= 0.) iflag1(i) = 7
45        end do
46      do i=1, len  
47         if (iflag(i).ne.7) then      ! Calculate lifted condensation level of air at parcel origin level
48            tnk(i)=t(i, nk(i))      ! (within 0.2 % of formula of Bolton, Mon. Wea. Rev., 1980)
49            qnk(i)=q(i, nk(i))  
50            gznk(i)=gz(i, nk(i))      do i = 1, klon
51            pnk(i)=p(i, nk(i))         if (iflag1(i) /= 7) then
52            qsnk(i)=qs(i, nk(i))            tnk1(i) = t1(i, nk1(i))
53              qnk1(i) = q1(i, nk1(i))
54            rh(i)=qnk(i)/qsnk(i)            gznk1(i) = gz1(i, nk1(i))
55            chi(i)=tnk(i)/(A-B*rh(i)-tnk(i)) ! convect3            pnk(i) = p1(i, nk1(i))
56            plcl(i)=pnk(i)*(rh(i)**chi(i))            qsnk(i) = qs1(i, nk1(i))
57            if ((plcl(i) < 200. .or. plcl(i) >= 2000.) .and. iflag(i) == 0) &  
58                 iflag(i) = 8            rh(i) = qnk1(i) / qsnk(i)
59              chi(i) = tnk1(i) / (A - B*rh(i) - tnk1(i))
60              plcl1(i) = pnk(i)*(rh(i)**chi(i))
61              if ((plcl1(i) < 200. .or. plcl1(i) >= 2000.) .and. iflag1(i) == 0) &
62                   iflag1(i) = 8
63         endif         endif
64      end do      end do
65    
66      ! --- Calculate first level above lcl (=icb)      ! Calculate first level above lcl (= icb1)
   
     do i=1, len  
        icb(i)=nlm  
     end do  
67    
68      ! la modification consiste a comparer plcl a ph et non a p:      do i = 1, klon
69      ! icb est defini par : ph(icb) < plcl < ph(icb - 1)         if (plcl1(i) <= ph1(i, nl - 2)) then
70      do k=3, nl-1 ! modification pour que icb soit supérieur ou égal à 2            ! Distinguish this case just so that icb1 = nl - 2, not nl =
71         do i=1, len            ! 3, for plcl1 exactly == ph1(i, nl - 2). Maybe not useful.
72            if(ph(i, k) < plcl(i)) icb(i) = min(icb(i), k)            icb1(i) = nl - 2
73         end do         else
74              icb1(i) = locate(- ph1(i, 3:nl - 2), - plcl1(i), my_lbound = 3)
75              ! {2 <= icb1(i) <= nl - 3}
76              ! {ph1(i, icb1(i) + 1) < plcl1(i) <= ph1(i, icb1(i))}
77           end if
78      end do      end do
79    
80      do i=1, len      do i = 1, klon
81         if((icb(i) == nlm).and.(iflag(i) == 0))iflag(i)=9         if ((icb1(i) == nl - 2).and.(iflag1(i) == 0)) iflag1(i) = 9
82      end do      end do
83    
84      do i=1, len      ! Compute icbmax
        icb(i) = icb(i)-1 ! icb sup ou egal a 2  
     end do  
85    
86      ! Compute icbmax.      icbmax = 2
87    
88      icbmax=2      do i = 1, klon
89      do i=1, len         if (iflag1(i) < 7) icbmax = max(icbmax, icb1(i))
        if (iflag(i) < 7) icbmax=max(icbmax, icb(i)) ! sb Jun7th02  
90      end do      end do
91    
92    end SUBROUTINE cv3_feed    end SUBROUTINE cv30_feed
93    
94  end module cv3_feed_m  end module cv30_feed_m

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

  ViewVC Help
Powered by ViewVC 1.1.21