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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 178 - (show annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 2 months ago) by guez
Original Path: trunk/Sources/phylmd/CV3_routines/cv3_undilute1.f
File size: 9256 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

1
2 SUBROUTINE cv3_undilute1(len,nd,t,q,qs,gz,plcl,p,nk,icb &
3 ,tp,tvp,clw,icbs)
4 use cv3_param_m
5 use cvthermo
6 implicit none
7
8 !----------------------------------------------------------------
9 ! Equivalent de TLIFT entre NK et ICB+1 inclus
10 !
11 ! Differences with convect4:
12 ! - specify plcl in input
13 ! - icbs is the first level above LCL (may differ from icb)
14 ! - in the iterations, used x(icbs) instead x(icb)
15 ! - many minor differences in the iterations
16 ! - tvp is computed in only one time
17 ! - icbs: first level above Plcl (IMIN de TLIFT) in output
18 ! - if icbs=icb, compute also tp(icb+1),tvp(icb+1) & clw(icb+1)
19 !----------------------------------------------------------------
20
21
22 ! inputs:
23 integer, intent(in):: len, nd
24 integer nk(len), icb(len)
25 real, intent(in):: t(len,nd)
26 real, intent(in):: q(len,nd), qs(len,nd), gz(len,nd)
27 real, intent(in):: p(len,nd)
28 real plcl(len) ! convect3
29
30 ! outputs:
31 real tp(len,nd), tvp(len,nd), clw(len,nd)
32
33 ! local variables:
34 integer i, k
35 integer icb1(len), icbs(len), icbsmax2 ! convect3
36 real tg, qg, alv, s, ahg, tc, denom, es
37 real ah0(len), cpp(len)
38 real tnk(len), qnk(len), gznk(len), ticb(len), gzicb(len)
39 real qsicb(len) ! convect3
40 real cpinv(len) ! convect3
41
42 !-------------------------------------------------------------------
43 ! --- Calculates the lifted parcel virtual temperature at nk,
44 ! --- the actual temperature, and the adiabatic
45 ! --- liquid water content. The procedure is to solve the equation.
46 ! cp*tp+L*qp+phi=cp*tnk+L*qnk+gznk.
47 !-------------------------------------------------------------------
48
49 do 320 i=1,len
50 tnk(i)=t(i,nk(i))
51 qnk(i)=q(i,nk(i))
52 gznk(i)=gz(i,nk(i))
53 ! ori ticb(i)=t(i,icb(i))
54 ! ori gzicb(i)=gz(i,icb(i))
55 320 continue
56 !
57 ! *** Calculate certain parcel quantities, including static energy ***
58 !
59 do 330 i=1,len
60 ah0(i)=(cpd*(1.-qnk(i))+cl*qnk(i))*tnk(i) &
61 +qnk(i)*(lv0-clmcpv*(tnk(i)-273.15))+gznk(i)
62 cpp(i)=cpd*(1.-qnk(i))+qnk(i)*cpv
63 cpinv(i)=1./cpp(i)
64 330 continue
65 !
66 ! *** Calculate lifted parcel quantities below cloud base ***
67 !
68 do i=1,len !convect3
69 icb1(i)=MAX(icb(i),2) !convect3
70 icb1(i)=MIN(icb(i),nl) !convect3
71 ! if icb is below LCL, start loop at ICB+1:
72 ! (icbs est le premier niveau au-dessus du LCL)
73 icbs(i)=icb1(i) !convect3
74 if (plcl(i).lt.p(i,icb1(i))) then
75 icbs(i)=MIN(icbs(i)+1,nl) !convect3
76 endif
77 enddo !convect3
78
79 do i=1,len !convect3
80 ticb(i)=t(i,icbs(i)) !convect3
81 gzicb(i)=gz(i,icbs(i)) !convect3
82 qsicb(i)=qs(i,icbs(i)) !convect3
83 enddo !convect3
84
85 !
86 ! Re-compute icbsmax (icbsmax2): !convect3
87 ! !convect3
88 icbsmax2=2 !convect3
89 do 310 i=1,len !convect3
90 icbsmax2=max(icbsmax2,icbs(i)) !convect3
91 310 continue !convect3
92
93 ! initialization outputs:
94
95 do k=1,icbsmax2 ! convect3
96 do i=1,len ! convect3
97 tp(i,k) = 0.0 ! convect3
98 tvp(i,k) = 0.0 ! convect3
99 clw(i,k) = 0.0 ! convect3
100 enddo ! convect3
101 enddo ! convect3
102
103 ! tp and tvp below cloud base:
104
105 do 350 k=minorig,icbsmax2-1
106 do 340 i=1,len
107 tp(i,k)=tnk(i)-(gz(i,k)-gznk(i))*cpinv(i)
108 tvp(i,k)=tp(i,k)*(1.+qnk(i)/eps-qnk(i)) !whole thing (convect3)
109 340 continue
110 350 continue
111 !
112 ! *** Find lifted parcel quantities above cloud base ***
113 !
114 do 360 i=1,len
115 tg=ticb(i)
116 ! ori qg=qs(i,icb(i))
117 qg=qsicb(i) ! convect3
118 !debug alv=lv0-clmcpv*(ticb(i)-t0)
119 alv=lv0-clmcpv*(ticb(i)-273.15)
120 !
121 ! First iteration.
122 !
123 ! ori s=cpd+alv*alv*qg/(rrv*ticb(i)*ticb(i))
124 s=cpd*(1.-qnk(i))+cl*qnk(i) &
125 +alv*alv*qg/(rrv*ticb(i)*ticb(i)) ! convect3
126 s=1./s
127 ! ori ahg=cpd*tg+(cl-cpd)*qnk(i)*ticb(i)+alv*qg+gzicb(i)
128 ahg=cpd*tg+(cl-cpd)*qnk(i)*tg+alv*qg+gzicb(i) ! convect3
129 tg=tg+s*(ah0(i)-ahg)
130 ! ori tg=max(tg,35.0)
131 !debug tc=tg-t0
132 tc=tg-273.15
133 denom=243.5+tc
134 denom=MAX(denom,1.0) ! convect3
135 ! ori if(tc.ge.0.0)then
136 es=6.112*exp(17.67*tc/denom)
137 ! ori else
138 ! ori es=exp(23.33086-6111.72784/tg+0.15215*log(tg))
139 ! ori endif
140 ! ori qg=eps*es/(p(i,icb(i))-es*(1.-eps))
141 qg=eps*es/(p(i,icbs(i))-es*(1.-eps))
142 !
143 ! Second iteration.
144 !
145
146 ! ori s=cpd+alv*alv*qg/(rrv*ticb(i)*ticb(i))
147 ! ori s=1./s
148 ! ori ahg=cpd*tg+(cl-cpd)*qnk(i)*ticb(i)+alv*qg+gzicb(i)
149 ahg=cpd*tg+(cl-cpd)*qnk(i)*tg+alv*qg+gzicb(i) ! convect3
150 tg=tg+s*(ah0(i)-ahg)
151 ! ori tg=max(tg,35.0)
152 !debug tc=tg-t0
153 tc=tg-273.15
154 denom=243.5+tc
155 denom=MAX(denom,1.0) ! convect3
156 ! ori if(tc.ge.0.0)then
157 es=6.112*exp(17.67*tc/denom)
158 ! ori else
159 ! ori es=exp(23.33086-6111.72784/tg+0.15215*log(tg))
160 ! ori end if
161 ! ori qg=eps*es/(p(i,icb(i))-es*(1.-eps))
162 qg=eps*es/(p(i,icbs(i))-es*(1.-eps))
163
164 alv=lv0-clmcpv*(ticb(i)-273.15)
165
166 ! ori c approximation here:
167 ! ori tp(i,icb(i))=(ah0(i)-(cl-cpd)*qnk(i)*ticb(i)
168 ! ori & -gz(i,icb(i))-alv*qg)/cpd
169
170 ! convect3: no approximation:
171 tp(i,icbs(i))=(ah0(i)-gz(i,icbs(i))-alv*qg) &
172 /(cpd+(cl-cpd)*qnk(i))
173
174 ! ori clw(i,icb(i))=qnk(i)-qg
175 ! ori clw(i,icb(i))=max(0.0,clw(i,icb(i)))
176 clw(i,icbs(i))=qnk(i)-qg
177 clw(i,icbs(i))=max(0.0,clw(i,icbs(i)))
178
179 ! convect3: (qg utilise au lieu du vrai mixing ratio rg)
180 tvp(i,icbs(i))=tp(i,icbs(i))*(1.+qg/eps-qnk(i)) !whole thing
181
182 360 continue
183 !
184 ! ori do 380 k=minorig,icbsmax2
185 ! ori do 370 i=1,len
186 ! ori tvp(i,k)=tvp(i,k)-tp(i,k)*qnk(i)
187 ! ori 370 continue
188 ! ori 380 continue
189 !
190
191 ! -- The following is only for convect3:
192 !
193 ! * icbs is the first level above the LCL:
194 ! if plcl<p(icb), then icbs=icb+1
195 ! if plcl>p(icb), then icbs=icb
196 !
197 ! * the routine above computes tvp from minorig to icbs (included).
198 !
199 ! * to compute buoybase (in cv3_trigger.F), both tvp(icb) and tvp(icb+1)
200 ! must be known. This is the case if icbs=icb+1, but not if icbs=icb.
201 !
202 ! * therefore, in the case icbs=icb, we compute tvp at level icb+1
203 ! (tvp at other levels will be computed in cv3_undilute2.F)
204 !
205
206 do i=1,len
207 ticb(i)=t(i,icb(i)+1)
208 gzicb(i)=gz(i,icb(i)+1)
209 qsicb(i)=qs(i,icb(i)+1)
210 enddo
211
212 do 460 i=1,len
213 tg=ticb(i)
214 qg=qsicb(i) ! convect3
215 !debug alv=lv0-clmcpv*(ticb(i)-t0)
216 alv=lv0-clmcpv*(ticb(i)-273.15)
217 !
218 ! First iteration.
219 !
220 ! ori s=cpd+alv*alv*qg/(rrv*ticb(i)*ticb(i))
221 s=cpd*(1.-qnk(i))+cl*qnk(i) &
222 +alv*alv*qg/(rrv*ticb(i)*ticb(i)) ! convect3
223 s=1./s
224 ! ori ahg=cpd*tg+(cl-cpd)*qnk(i)*ticb(i)+alv*qg+gzicb(i)
225 ahg=cpd*tg+(cl-cpd)*qnk(i)*tg+alv*qg+gzicb(i) ! convect3
226 tg=tg+s*(ah0(i)-ahg)
227 ! ori tg=max(tg,35.0)
228 !debug tc=tg-t0
229 tc=tg-273.15
230 denom=243.5+tc
231 denom=MAX(denom,1.0) ! convect3
232 ! ori if(tc.ge.0.0)then
233 es=6.112*exp(17.67*tc/denom)
234 ! ori else
235 ! ori es=exp(23.33086-6111.72784/tg+0.15215*log(tg))
236 ! ori endif
237 ! ori qg=eps*es/(p(i,icb(i))-es*(1.-eps))
238 qg=eps*es/(p(i,icb(i)+1)-es*(1.-eps))
239 !
240 ! Second iteration.
241 !
242
243 ! ori s=cpd+alv*alv*qg/(rrv*ticb(i)*ticb(i))
244 ! ori s=1./s
245 ! ori ahg=cpd*tg+(cl-cpd)*qnk(i)*ticb(i)+alv*qg+gzicb(i)
246 ahg=cpd*tg+(cl-cpd)*qnk(i)*tg+alv*qg+gzicb(i) ! convect3
247 tg=tg+s*(ah0(i)-ahg)
248 ! ori tg=max(tg,35.0)
249 !debug tc=tg-t0
250 tc=tg-273.15
251 denom=243.5+tc
252 denom=MAX(denom,1.0) ! convect3
253 ! ori if(tc.ge.0.0)then
254 es=6.112*exp(17.67*tc/denom)
255 ! ori else
256 ! ori es=exp(23.33086-6111.72784/tg+0.15215*log(tg))
257 ! ori end if
258 ! ori qg=eps*es/(p(i,icb(i))-es*(1.-eps))
259 qg=eps*es/(p(i,icb(i)+1)-es*(1.-eps))
260
261 alv=lv0-clmcpv*(ticb(i)-273.15)
262
263 ! ori c approximation here:
264 ! ori tp(i,icb(i))=(ah0(i)-(cl-cpd)*qnk(i)*ticb(i)
265 ! ori & -gz(i,icb(i))-alv*qg)/cpd
266
267 ! convect3: no approximation:
268 tp(i,icb(i)+1)=(ah0(i)-gz(i,icb(i)+1)-alv*qg) &
269 /(cpd+(cl-cpd)*qnk(i))
270
271 ! ori clw(i,icb(i))=qnk(i)-qg
272 ! ori clw(i,icb(i))=max(0.0,clw(i,icb(i)))
273 clw(i,icb(i)+1)=qnk(i)-qg
274 clw(i,icb(i)+1)=max(0.0,clw(i,icb(i)+1))
275
276 ! convect3: (qg utilise au lieu du vrai mixing ratio rg)
277 tvp(i,icb(i)+1)=tp(i,icb(i)+1)*(1.+qg/eps-qnk(i)) !whole thing
278
279 460 continue
280
281 return
282 end

  ViewVC Help
Powered by ViewVC 1.1.21