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

Contents of /trunk/Sources/phylmd/CV30_routines/cv30_closure.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: 3891 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_closure_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE cv30_closure(icb, inb, pbase, p, ph, tv, buoy, sig, w0, cape, m)
8
9 ! CLOSURE
10 ! Vectorization: S. Bony
11
12 use cv30_param_m, only: alpha, beta, dtcrit, minorig, nl
13 use cv_thermo_m, only: rrd
14 USE dimphy, ONLY: klev, klon
15
16 ! input:
17 integer, intent(in):: icb(:), inb(:) ! (ncum)
18 real pbase(klon)
19 real p(klon, klev), ph(klon, klev+1)
20 real tv(klon, klev), buoy(klon, klev)
21
22 ! input/output:
23 real sig(klon, klev), w0(klon, klev)
24
25 ! output:
26 real cape(klon)
27 real m(klon, klev)
28
29 ! Local:
30 integer ncum
31 integer i, j, k, icbmax
32 real deltap, fac, w, amu
33 real dtmin(klon, klev), sigold(klon, klev)
34
35 !-------------------------------------------------------
36
37 ncum = size(icb)
38
39 ! Initialization
40
41 do k=1, nl
42 do i=1, ncum
43 m(i, k)=0.0
44 enddo
45 enddo
46
47 ! Reset sig(i) and w0(i) for i>inb and i<icb
48
49 ! update sig and w0 above LNB:
50
51 do k=1, nl-1
52 do i=1, ncum
53 if ((inb(i) < (nl-1)).and.(k >= (inb(i)+1)))then
54 sig(i, k)=beta*sig(i, k) &
55 +2.*alpha*buoy(i, inb(i))*ABS(buoy(i, inb(i)))
56 sig(i, k)=AMAX1(sig(i, k), 0.0)
57 w0(i, k)=beta*w0(i, k)
58 endif
59 end do
60 end do
61
62 ! compute icbmax:
63
64 icbmax=2
65 do i=1, ncum
66 icbmax=MAX(icbmax, icb(i))
67 end do
68
69 ! update sig and w0 below cloud base:
70
71 do k=1, icbmax
72 do i=1, ncum
73 if (k <= icb(i))then
74 sig(i, k)=beta*sig(i, k)-2.*alpha*buoy(i, icb(i))*buoy(i, icb(i))
75 sig(i, k)=amax1(sig(i, k), 0.0)
76 w0(i, k)=beta*w0(i, k)
77 endif
78 end do
79 end do
80
81 ! Reset fractional areas of updrafts and w0 at initial time
82 ! and after 10 time steps of no convection
83
84 do k=1, nl-1
85 do i=1, ncum
86 if (sig(i, klev) < 1.5.or.sig(i, klev) > 12.0)then
87 sig(i, k)=0.0
88 w0(i, k)=0.0
89 endif
90 end do
91 end do
92
93 ! Calculate convective available potential energy (cape),
94 ! vertical velocity (w), fractional area covered by
95 ! undilute updraft (sig), and updraft mass flux (m)
96
97 do i=1, ncum
98 cape(i)=0.0
99 end do
100
101 ! compute dtmin (minimum buoyancy between ICB and given level k):
102
103 do i=1, ncum
104 do k=1, nl
105 dtmin(i, k)=100.0
106 enddo
107 enddo
108
109 do i=1, ncum
110 do k=1, nl
111 do j=minorig, nl
112 if ((k >= (icb(i)+1)).and.(k <= inb(i)).and. &
113 (j >= icb(i)).and.(j <= (k-1)))then
114 dtmin(i, k)=AMIN1(dtmin(i, k), buoy(i, j))
115 endif
116 end do
117 end do
118 end do
119
120 ! the interval on which cape is computed starts at pbase :
121
122 do k=1, nl
123 do i=1, ncum
124
125 if ((k >= (icb(i)+1)).and.(k <= inb(i))) then
126
127 deltap = MIN(pbase(i), ph(i, k-1))-MIN(pbase(i), ph(i, k))
128 cape(i)=cape(i)+rrd*buoy(i, k-1)*deltap/p(i, k-1)
129 cape(i)=AMAX1(0.0, cape(i))
130 sigold(i, k)=sig(i, k)
131
132 sig(i, k)=beta*sig(i, k)+alpha*dtmin(i, k)*ABS(dtmin(i, k))
133 sig(i, k)=amax1(sig(i, k), 0.0)
134 sig(i, k)=amin1(sig(i, k), 0.01)
135 fac=AMIN1(((dtcrit-dtmin(i, k))/dtcrit), 1.0)
136 w=(1.-beta)*fac*SQRT(cape(i))+beta*w0(i, k)
137 amu=0.5*(sig(i, k)+sigold(i, k))*w
138 m(i, k)=amu*0.007*p(i, k)*(ph(i, k)-ph(i, k+1))/tv(i, k)
139 w0(i, k)=w
140 endif
141
142 end do
143 end do
144
145 do i=1, ncum
146 w0(i, icb(i))=0.5*w0(i, icb(i)+1)
147 m(i, icb(i))=0.5*m(i, icb(i)+1) &
148 *(ph(i, icb(i))-ph(i, icb(i)+1)) &
149 /(ph(i, icb(i)+1)-ph(i, icb(i)+2))
150 sig(i, icb(i))=sig(i, icb(i)+1)
151 sig(i, icb(i)-1)=sig(i, icb(i))
152 end do
153
154 end SUBROUTINE cv30_closure
155
156 end module cv30_closure_m

  ViewVC Help
Powered by ViewVC 1.1.21