/[lmdze]/trunk/phylmd/CV_routines/cv_undilute1.f
ViewVC logotype

Annotation of /trunk/phylmd/CV_routines/cv_undilute1.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 97 - (hide annotations)
Fri Apr 25 14:58:31 2014 UTC (10 years ago) by guez
File size: 3215 byte(s)
Module pressure_var is now only used in gcm. Created local variables
pls and p3d in etat0, added argument p3d to regr_pr_o3.

In leapfrog, moved computation of p3d and exner function immediately
after integrd, for clarity (does not change the execution).

Removed unused arguments: ntra, tra1 and tra of cv3_compress; ntra,
tra and traent of cv3_mixing; ntra, ftra, ftra1 of cv3_uncompress;
ntra, tra, trap of cv3_unsat; ntra, tra, trap, traent, ftra of
cv3_yield; tra, tvp, pbase, bbase, dtvpdt1, dtvpdq1, dplcldt,
dplcldr, ntra of concvl; ndp1, ntra, tra1 of cv_driver

Removed argument d_tra and computation of d_tra in concvl. Removed
argument ftra1 and computation of ftra1 in cv_driver. ftra1 was just
set to 0 in cv_driver, associated to d_tra in concvl, and set again to
zero in concvl.

1 guez 52
2     SUBROUTINE cv_undilute1(len,nd,t,q,qs,gz,p,nk,icb,icbmax &
3     ,tp,tvp,clw)
4     use cvthermo
5     use cvparam
6     implicit none
7    
8    
9     ! inputs:
10 guez 97 integer, intent(in):: len, nd
11 guez 52 integer nk(len), icb(len), icbmax
12     real, intent(in):: t(len,nd)
13     real q(len,nd), qs(len,nd), gz(len,nd)
14     real p(len,nd)
15    
16     ! outputs:
17     real tp(len,nd), tvp(len,nd), clw(len,nd)
18    
19     ! local variables:
20     integer i, k
21     real tg, qg, alv, s, ahg, tc, denom, es, rg
22     real ah0(len), cpp(len)
23     real tnk(len), qnk(len), gznk(len), ticb(len), gzicb(len)
24    
25     !-------------------------------------------------------------------
26     ! --- Calculates the lifted parcel virtual temperature at nk,
27     ! --- the actual temperature, and the adiabatic
28     ! --- liquid water content. The procedure is to solve the equation.
29     ! cp*tp+L*qp+phi=cp*tnk+L*qnk+gznk.
30     !-------------------------------------------------------------------
31    
32     do 320 i=1,len
33     tnk(i)=t(i,nk(i))
34     qnk(i)=q(i,nk(i))
35     gznk(i)=gz(i,nk(i))
36     ticb(i)=t(i,icb(i))
37     gzicb(i)=gz(i,icb(i))
38     320 continue
39     !
40     ! *** Calculate certain parcel quantities, including static energy ***
41     !
42     do 330 i=1,len
43     ah0(i)=(cpd*(1.-qnk(i))+cl*qnk(i))*tnk(i) &
44     +qnk(i)*(lv0-clmcpv*(tnk(i)-273.15))+gznk(i)
45     cpp(i)=cpd*(1.-qnk(i))+qnk(i)*cpv
46     330 continue
47     !
48     ! *** Calculate lifted parcel quantities below cloud base ***
49     !
50     do 350 k=minorig,icbmax-1
51     do 340 i=1,len
52     tp(i,k)=tnk(i)-(gz(i,k)-gznk(i))/cpp(i)
53     tvp(i,k)=tp(i,k)*(1.+qnk(i)*epsi)
54     340 continue
55     350 continue
56     !
57     ! *** Find lifted parcel quantities above cloud base ***
58     !
59     do 360 i=1,len
60     tg=ticb(i)
61     qg=qs(i,icb(i))
62     alv=lv0-clmcpv*(ticb(i)-t0)
63     !
64     ! First iteration.
65     !
66     s=cpd+alv*alv*qg/(rrv*ticb(i)*ticb(i))
67     s=1./s
68     ahg=cpd*tg+(cl-cpd)*qnk(i)*ticb(i)+alv*qg+gzicb(i)
69     tg=tg+s*(ah0(i)-ahg)
70     tg=max(tg,35.0)
71     tc=tg-t0
72     denom=243.5+tc
73     if(tc.ge.0.0)then
74     es=6.112*exp(17.67*tc/denom)
75     else
76     es=exp(23.33086-6111.72784/tg+0.15215*log(tg))
77     endif
78     qg=eps*es/(p(i,icb(i))-es*(1.-eps))
79     !
80     ! Second iteration.
81     !
82     s=cpd+alv*alv*qg/(rrv*ticb(i)*ticb(i))
83     s=1./s
84     ahg=cpd*tg+(cl-cpd)*qnk(i)*ticb(i)+alv*qg+gzicb(i)
85     tg=tg+s*(ah0(i)-ahg)
86     tg=max(tg,35.0)
87     tc=tg-t0
88     denom=243.5+tc
89     if(tc.ge.0.0)then
90     es=6.112*exp(17.67*tc/denom)
91     else
92     es=exp(23.33086-6111.72784/tg+0.15215*log(tg))
93     end if
94     qg=eps*es/(p(i,icb(i))-es*(1.-eps))
95     !
96     alv=lv0-clmcpv*(ticb(i)-273.15)
97     tp(i,icb(i))=(ah0(i)-(cl-cpd)*qnk(i)*ticb(i) &
98     -gz(i,icb(i))-alv*qg)/cpd
99     clw(i,icb(i))=qnk(i)-qg
100     clw(i,icb(i))=max(0.0,clw(i,icb(i)))
101     rg=qg/(1.-qnk(i))
102     tvp(i,icb(i))=tp(i,icb(i))*(1.+rg*epsi)
103     360 continue
104     !
105     do 380 k=minorig,icbmax
106     do 370 i=1,len
107     tvp(i,k)=tvp(i,k)-tp(i,k)*qnk(i)
108     370 continue
109     380 continue
110     !
111     return
112     end

  ViewVC Help
Powered by ViewVC 1.1.21