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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 198 - (show annotations)
Tue May 31 16:17:35 2016 UTC (7 years, 11 months ago) by guez
File size: 2540 byte(s)
Removed variables nk1 and nk in cv_driver and below. These arrays were
just equal to the constant minorig. (This is also the case in LMDZ.)

In cv_thermo, removed some variables which were copies of variables of
suphec_m. Changed some variables to named constants.

1 module cv30_feed_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, icb1, iflag1, tnk1, qnk1, &
8 gznk1, plcl1)
9
10 ! Purpose: convective feed
11 ! Assuming origin level of ascending parcels is minorig.
12
13 use cv30_param_m, only: minorig, nl
14 USE dimphy, ONLY: klev, klon
15 use numer_rec_95, only: locate
16
17 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
22 ! outputs:
23
24 integer, intent(out):: icb1(:) ! (klon)
25 ! first level above lcl, 2 <= icb1 <= nl - 2
26
27 integer, intent(out):: iflag1(:) ! (klon)
28 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 !--------------------------------------------------------------------
37
38 iflag1 = 0
39 plcl1 = 0.
40
41 ! Check whether parcel level temperature and specific humidity
42 ! are reasonable
43 do i = 1, klon
44 if (t1(i, minorig) < 250. .or. q1(i, minorig) <= 0.) iflag1(i) = 7
45 end do
46
47 ! Calculate lifted condensation level of air at parcel origin level
48 ! (within 0.2 % of formula of Bolton, Mon. Wea. Rev., 1980)
49 do i = 1, klon
50 if (iflag1(i) == 0) then
51 tnk1(i) = t1(i, minorig)
52 qnk1(i) = q1(i, minorig)
53 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
61 end do
62
63 ! Compute icb1:
64 do i = 1, klon
65 if (plcl1(i) <= ph1(i, nl - 2)) then
66 ! Distinguish this case just so that icb1 = nl - 2, not nl =
67 ! 3, for plcl1 exactly == ph1(i, nl - 2). Maybe not useful.
68 icb1(i) = nl - 2
69 else
70 icb1(i) = locate(- ph1(i, 3:nl - 2), - plcl1(i), my_lbound = 3)
71 ! {2 <= icb1(i) <= nl - 3}
72 ! {ph1(i, icb1(i) + 1) < plcl1(i)}
73 ! {plcl1(i) <= ph1(i, icb1(i)) or icb1(i) == 2}
74 end if
75 end do
76
77 where (icb1 == nl - 2 .and. iflag1 == 0) iflag1 = 9
78
79 ! {(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 ! 0}
82
83 end SUBROUTINE cv30_feed
84
85 end module cv30_feed_m

  ViewVC Help
Powered by ViewVC 1.1.21