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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 200 - (hide annotations)
Thu Jun 2 15:40:30 2016 UTC (7 years, 11 months ago) by guez
File size: 2349 byte(s)
Changes results.
1 guez 185 module cv30_feed_m
2 guez 47
3 guez 103 implicit none
4 guez 47
5 guez 103 contains
6 guez 47
7 guez 198 SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, icb1, iflag1, tnk1, qnk1, &
8     gznk1, plcl1)
9 guez 47
10 guez 180 ! Purpose: convective feed
11 guez 198 ! Assuming origin level of ascending parcels is minorig.
12 guez 47
13 guez 186 use cv30_param_m, only: minorig, nl
14 guez 195 USE dimphy, ONLY: klev, klon
15     use numer_rec_95, only: locate
16 guez 47
17 guez 195 real, intent(in):: t1(:, :) ! (klon, klev)
18     real, intent(in):: q1(:, :), qs1(:, :), p1(:, :) ! (klon, klev)
19     real, intent(in):: ph1(:, :) ! (klon, klev+1)
20     real, intent(in):: gz1(:, :) ! (klon, klev)
21 guez 47
22 guez 103 ! outputs:
23 guez 196
24     integer, intent(out):: icb1(:) ! (klon)
25     ! first level above lcl, 2 <= icb1 <= nl - 2
26    
27     integer, intent(out):: iflag1(:) ! (klon)
28 guez 198 real tnk1(:), qnk1(:), gznk1(:) ! (klon)
29 guez 200 real, intent(out):: plcl1(:) ! (klon)
30 guez 47
31 guez 180 ! Local:
32 guez 195 integer i
33 guez 200 real rh(klon)
34 guez 180 real, parameter:: A = 1669., B = 122.
35 guez 47
36 guez 103 !--------------------------------------------------------------------
37 guez 47
38 guez 180 ! Calculate lifted condensation level of air at parcel origin level
39 guez 195 ! (within 0.2 % of formula of Bolton, Mon. Wea. Rev., 1980)
40 guez 200 where (t1(:, minorig) >= 250. .and. q1(:, minorig) > 0.)
41     ! Parcel level temperature and specific humidity are reasonable.
42     tnk1 = t1(:, minorig)
43     qnk1 = q1(:, minorig)
44     gznk1 = gz1(:, minorig)
45 guez 103
46 guez 200 rh = qnk1 / qs1(:, minorig)
47     plcl1 = p1(:, minorig) * rh**(tnk1 / (A - B * rh - tnk1))
48     iflag1 = 0
49     elsewhere
50     plcl1 = 0.
51     iflag1 = 7
52     end where
53 guez 103
54 guez 200 where (iflag1 == 0 .and. (plcl1 < 200. .or. plcl1 >= 2000.)) iflag1 = 8
55    
56 guez 196 ! Compute icb1:
57 guez 195 do i = 1, klon
58     if (plcl1(i) <= ph1(i, nl - 2)) then
59     ! Distinguish this case just so that icb1 = nl - 2, not nl =
60     ! 3, for plcl1 exactly == ph1(i, nl - 2). Maybe not useful.
61     icb1(i) = nl - 2
62     else
63     icb1(i) = locate(- ph1(i, 3:nl - 2), - plcl1(i), my_lbound = 3)
64     ! {2 <= icb1(i) <= nl - 3}
65 guez 197 ! {ph1(i, icb1(i) + 1) < plcl1(i)}
66     ! {plcl1(i) <= ph1(i, icb1(i)) or icb1(i) == 2}
67 guez 195 end if
68 guez 103 end do
69 guez 47
70 guez 196 where (icb1 == nl - 2 .and. iflag1 == 0) iflag1 = 9
71 guez 47
72 guez 197 ! {(2 <= icb1(i) <= nl - 3 and ph1(i, icb1(i) + 1) < plcl1(i) and
73     ! (plcl1(i) <= ph1(i, icb1(i)) or icb1(i) == 2)) or iflag1(i) /=
74     ! 0}
75    
76 guez 185 end SUBROUTINE cv30_feed
77 guez 103
78 guez 185 end module cv30_feed_m

  ViewVC Help
Powered by ViewVC 1.1.21