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

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

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

  ViewVC Help
Powered by ViewVC 1.1.21