/[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 190 - (show annotations)
Thu Apr 14 15:15:56 2016 UTC (8 years ago) by guez
File size: 3846 byte(s)
Created module cv_thermo_m around procedure cv_thermo. Moved variables
from module cvthermo to module cv_thermo_m, where they are defined.

In ini_histins and initphysto, using part of rlon and rlat from
phyetat0_m is pretending that we do not know about the dynamical grid,
while the way we extract zx_lon(:, 1) and zx_lat(1, :) depends on
ordering inside rlon and rlat. So we might as well simplify and
clarify by using directly rlonv and rlatu.

Removed intermediary variables in write_histins and phystokenc.

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

  ViewVC Help
Powered by ViewVC 1.1.21