/[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 207 - (show annotations)
Thu Sep 1 10:30:53 2016 UTC (7 years, 8 months ago) by guez
File size: 2343 byte(s)
New philosophy on compiler options.

Removed source code for thermcep = f. (Not used in LMDZ either.)

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: 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 rh(klon)
34 real, parameter:: A = 1669., B = 122.
35
36 !--------------------------------------------------------------------
37
38 ! Calculate lifted condensation level of air at parcel origin level
39 ! (within 0.2 % of formula of Bolton, Mon. Wea. Rev., 1980)
40 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
46 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
54 where (iflag1 == 0 .and. (plcl1 < 200. .or. plcl1 >= 2000.)) iflag1 = 8
55
56 ! Compute icb1:
57 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 ! {ph1(i, icb1(i) + 1) < plcl1(i)}
66 ! {plcl1(i) <= ph1(i, icb1(i)) or icb1(i) == 2}
67 end if
68 end do
69
70 where (icb1 == nl - 2 .and. iflag1 == 0) iflag1 = 9
71
72 ! {(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 end SUBROUTINE cv30_feed
77
78 end module cv30_feed_m

  ViewVC Help
Powered by ViewVC 1.1.21