/[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 180 by guez, Tue Mar 15 17:07:47 2016 UTC trunk/Sources/phylmd/CV30_routines/cv30_feed.f revision 197 by guez, Tue May 24 12:25:29 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, gz, nk, icb, icbmax, iflag, &    SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, nk1, icb1, iflag1, tnk1, &
8         tnk, qnk, gznk, plcl)         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      use cv3_param_m, only: minorig, nl, nlm      real, intent(in):: q1(:, :), qs1(:, :), p1(:, :) ! (klon, klev)
18        real, intent(in):: ph1(:, :) ! (klon, klev+1)
19      integer, intent(in):: len, nd      real, intent(in):: gz1(:, :) ! (klon, klev)
     real, intent(in):: t(len, nd)  
     real, intent(in):: q(len, nd), qs(len, nd), p(len, nd)  
     real, intent(in):: ph(len, nd+1)  
     real, intent(in):: gz(len, nd)  
20    
21      ! outputs:      ! outputs:
22      integer, intent(out):: nk(len), icb(len), icbmax  
23      integer, intent(inout):: iflag(len)      integer, intent(out):: nk1(:) ! (klon)
24      real tnk(len), qnk(len), gznk(len)  
25      real, intent(out):: plcl(len)      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)
30        real, intent(out):: plcl1(klon)
31    
32      ! Local:      ! Local:
33      integer i, k      integer i
34      real pnk(len), qsnk(len), rh(len), chi(len)      real pnk(klon), qsnk(klon), rh(klon), chi(klon)
35      real, parameter:: A = 1669., B = 122.      real, parameter:: A = 1669., B = 122.
36    
37      !--------------------------------------------------------------------      !--------------------------------------------------------------------
38    
39      plcl = 0.      iflag1 = 0
40        plcl1 = 0.
41    
42      ! Origin level of ascending parcels      ! Origin level of ascending parcels
43        nk1 = minorig
     do i = 1, len  
        nk(i) = minorig  
     end do  
44    
45      ! Check whether parcel level temperature and specific humidity      ! Check whether parcel level temperature and specific humidity
46      ! are reasonable      ! are reasonable
47    
48      do i = 1, len      do i = 1, klon
49         if ((t(i, nk(i)) < 250. .or. q(i, nk(i)) <= 0.) .and. iflag(i) == 0) &         if (t1(i, nk1(i)) < 250. .or. q1(i, nk1(i)) <= 0.) iflag1(i) = 7
             iflag(i) = 7  
50      end do      end do
51    
52      ! Calculate lifted condensation level of air at parcel origin level      ! Calculate lifted condensation level of air at parcel origin level
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, len      do i = 1, klon
56         if (iflag(i) /= 7) then         if (iflag1(i) == 0) then
57            tnk(i) = t(i, nk(i))            tnk1(i) = t1(i, nk1(i))
58            qnk(i) = q(i, nk(i))            qnk1(i) = q1(i, nk1(i))
59            gznk(i) = gz(i, nk(i))            gznk1(i) = gz1(i, nk1(i))
60            pnk(i) = p(i, nk(i))            pnk(i) = p1(i, nk1(i))
61            qsnk(i) = qs(i, nk(i))            qsnk(i) = qs1(i, nk1(i))
62    
63            rh(i) = qnk(i)/qsnk(i)            rh(i) = qnk1(i) / qsnk(i)
64            chi(i) = tnk(i)/(A-B*rh(i)-tnk(i))            chi(i) = tnk1(i) / (A - B*rh(i) - tnk1(i))
65            plcl(i) = pnk(i)*(rh(i)**chi(i))            plcl1(i) = pnk(i)*(rh(i)**chi(i))
66            if ((plcl(i) < 200. .or. plcl(i) >= 2000.) .and. iflag(i) == 0) &            if (plcl1(i) < 200. .or. plcl1(i) >= 2000.) iflag1(i) = 8
                iflag(i) = 8  
67         endif         endif
68      end do      end do
69    
70      ! Calculate first level above lcl (= icb)      ! Compute icb1:
71        do i = 1, klon
72      do i = 1, len         if (plcl1(i) <= ph1(i, nl - 2)) then
73         icb(i) = nlm            ! Distinguish this case just so that icb1 = nl - 2, not nl =
74      end do            ! 3, for plcl1 exactly == ph1(i, nl - 2). Maybe not useful.
75              icb1(i) = nl - 2
76      ! La modification consiste \`a comparer plcl \`a ph et non \`a p:         else
77      ! icb est d\'efini par : ph(icb) < plcl < ph(icb - 1)            icb1(i) = locate(- ph1(i, 3:nl - 2), - plcl1(i), my_lbound = 3)
78      do k = 3, nl-1 ! modification pour que icb soit supérieur ou égal à 2            ! {2 <= icb1(i) <= nl - 3}
79         do i = 1, len            ! {ph1(i, icb1(i) + 1) < plcl1(i)}
80            if (ph(i, k) < plcl(i)) icb(i) = min(icb(i), k)            ! {plcl1(i) <= ph1(i, icb1(i)) or icb1(i) == 2}
81         end do         end if
82      end do      end do
83    
84      do i = 1, len      where (icb1 == nl - 2 .and. iflag1 == 0) iflag1 = 9
85         if ((icb(i) == nlm).and.(iflag(i) == 0)) iflag(i) = 9  
86      end do      ! {(2 <= icb1(i) <= nl - 3 and ph1(i, icb1(i) + 1) < plcl1(i) and
87        ! (plcl1(i) <= ph1(i, icb1(i)) or icb1(i) == 2)) or iflag1(i) /=
88      do i = 1, len      ! 0}
        icb(i) = icb(i)-1 ! icb >= 2  
     end do  
   
     ! Compute icbmax  
   
     icbmax = 2  
   
     do i = 1, len  
        if (iflag(i) < 7) icbmax = max(icbmax, icb(i))  
     end do  
89    
90    end SUBROUTINE cv3_feed    end SUBROUTINE cv30_feed
91    
92  end module cv3_feed_m  end module cv30_feed_m

Legend:
Removed from v.180  
changed lines
  Added in v.197

  ViewVC Help
Powered by ViewVC 1.1.21