/[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 195 - (show annotations)
Wed May 18 17:56:44 2016 UTC (8 years ago) by guez
File size: 2597 byte(s)
In cv30_feed, iflag1 is 0 on entry so we can simplify the test for
iflag1 = 7.

In cv30_feed, for the computation of icb, replaced sequential search
(with a useless end of loop on k) by a call to locate.

In CV30 routines, replaced len, nloc, nd, na by klon or
klev. Philosophy: no more generality than actually necessary.

Converted as many variables as possible to named constants in
cv30_param_m and downgraded pbcrit, ptcrit, dtovsh, dpbase, dttrig,
tau, delta to local objects in procedures. spfac, betad and omtrain
are useless and removed.

Instead of filling the array sigp with the constant spfac in
cv30_undilute2, just made sigp a constant in cv30_unsat.

In cv_driver, define as allocatable variables that are only
used on the range (ncum, nl).

1 module cv30_feed_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE cv30_feed(t1, q1, qs1, p1, ph1, gz1, nk1, icb1, icbmax, iflag1, &
8 tnk1, qnk1, gznk1, plcl1)
9
10 ! Purpose: convective feed
11
12 use cv30_param_m, only: minorig, nl
13 USE dimphy, ONLY: klev, klon
14 use numer_rec_95, only: locate
15
16 real, intent(in):: t1(:, :) ! (klon, klev)
17 real, intent(in):: q1(:, :), qs1(:, :), p1(:, :) ! (klon, klev)
18 real, intent(in):: ph1(:, :) ! (klon, klev+1)
19 real, intent(in):: gz1(:, :) ! (klon, klev)
20
21 ! outputs:
22 integer, intent(out):: nk1(:), icb1(:) ! (klon)
23 integer, intent(out):: icbmax
24 integer, intent(inout):: iflag1(klon)
25 real tnk1(klon), qnk1(klon), gznk1(klon)
26 real, intent(out):: plcl1(klon)
27
28 ! Local:
29 integer i
30 real pnk(klon), qsnk(klon), rh(klon), chi(klon)
31 real, parameter:: A = 1669., B = 122.
32
33 !--------------------------------------------------------------------
34
35 plcl1 = 0.
36
37 ! Origin level of ascending parcels
38 nk1 = minorig
39
40 ! Check whether parcel level temperature and specific humidity
41 ! are reasonable
42
43 do i = 1, klon
44 if (t1(i, nk1(i)) < 250. .or. q1(i, nk1(i)) <= 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
50 do i = 1, klon
51 if (iflag1(i) /= 7) then
52 tnk1(i) = t1(i, nk1(i))
53 qnk1(i) = q1(i, nk1(i))
54 gznk1(i) = gz1(i, nk1(i))
55 pnk(i) = p1(i, nk1(i))
56 qsnk(i) = qs1(i, nk1(i))
57
58 rh(i) = qnk1(i) / qsnk(i)
59 chi(i) = tnk1(i) / (A - B*rh(i) - tnk1(i))
60 plcl1(i) = pnk(i)*(rh(i)**chi(i))
61 if ((plcl1(i) < 200. .or. plcl1(i) >= 2000.) .and. iflag1(i) == 0) &
62 iflag1(i) = 8
63 endif
64 end do
65
66 ! Calculate first level above lcl (= icb1)
67
68 do i = 1, klon
69 if (plcl1(i) <= ph1(i, nl - 2)) then
70 ! Distinguish this case just so that icb1 = nl - 2, not nl =
71 ! 3, for plcl1 exactly == ph1(i, nl - 2). Maybe not useful.
72 icb1(i) = nl - 2
73 else
74 icb1(i) = locate(- ph1(i, 3:nl - 2), - plcl1(i), my_lbound = 3)
75 ! {2 <= icb1(i) <= nl - 3}
76 ! {ph1(i, icb1(i) + 1) < plcl1(i) <= ph1(i, icb1(i))}
77 end if
78 end do
79
80 do i = 1, klon
81 if ((icb1(i) == nl - 2).and.(iflag1(i) == 0)) iflag1(i) = 9
82 end do
83
84 ! Compute icbmax
85
86 icbmax = 2
87
88 do i = 1, klon
89 if (iflag1(i) < 7) icbmax = max(icbmax, icb1(i))
90 end do
91
92 end SUBROUTINE cv30_feed
93
94 end module cv30_feed_m

  ViewVC Help
Powered by ViewVC 1.1.21