45 SUBROUTINE frzlvl2(ISOTHERM,ZFRZ,RHFRZ,PFRZL)
48 use vrbls3d, only: pint, t, zmid, pmid, q, zint, alpint
49 use vrbls2d, only: fis, tshltr, pshltr, qz0, qs, qshltr
50 use masks, only: lmh, sm
51 use params_mod, only: gi, d00, capa, d0065, tfrz, pq0, a2, a3, a4, d50
52 use ctlblk_mod
, only: jsta, jend, spval, lm, modelname, im
63 REAL,
PARAMETER::pucap=300.0e2
64 real,
intent(in) :: isotherm
65 REAL,
dimension(im,jsta:jend),
intent(out) :: rhfrz, zfrz, pfrzl
67 integer i,j,l,lice,llmh
68 real htsfc,psfc,qsfc,rhsfc,qw,qsat,delz,delt,delq,delalp,delzp, &
69 zl,zu,dzabv,qfrz,alpl,alph,alpfrz,pfrz,qsfrz,rhz,dzfr, &
80 IF(fis(i,j)<spval)
THEN
93 IF(tshltr(i,j)/=spval .AND. pshltr(i,j)/=spval)
THEN
94 tsfc=tshltr(i,j)*(pshltr(i,j)*1.e-5)**capa
97 tsfc=t(i,j,lm)+d0065*(zmid(i,j,lm)-htsfc-2.0)
103 IF (pmid(i,j,l)>=pucap .AND. &
104 (t(i,j,l)<=isotherm.AND.t(i,j,l+1)>isotherm))lice=l
109 IF (lice==llmh.AND.tsfc<=isotherm)
THEN
110 zfrz(i,j) = htsfc+2.0+(tsfc-isotherm)/d0065
111 qsfc = sm(i,j)*qz0(i,j)+(1.-sm(i,j))*qs(i,j)
112 IF(qshltr(i,j)/=spval)
THEN
121 IF(modelname ==
'GFS' .OR. modelname ==
'RAPR')
THEN
124 qsat=con_eps*es/(psfc+con_epsm1*es)
127 *exp(a2*(tsfc-a3)/(tsfc-a4))
131 rhsfc = amax1(0.01,rhsfc)
132 rhsfc = amin1(rhsfc,1.0)
137 ELSE IF (lice<llmh)
THEN
139 delz = d50*(zint(i,j,l)-zint(i,j,l+2))
140 zl = d50*(zint(i,j,l+1)+zint(i,j,l+2))
141 delt = t(i,j,l)-t(i,j,l+1)
142 zfrz(i,j) = zl+(isotherm-t(i,j,l+1))/delt*delz
145 delq = q(i,j,l)-q(i,j,l+1)
146 qfrz = q(i,j,l+1) + delq/delz*dzabv
147 qfrz = amax1(0.0,qfrz)
149 alpl = alpint(i,j,l+2)
152 delzp = zint(i,j,l)-zint(i,j,l+2)
153 dzfr = zfrz(i,j) - zint(i,j,l+2)
154 alpfrz = alpl + delalp/delzp*dzfr
157 IF(modelname ==
'GFS'.OR.modelname ==
'RAPR')
THEN
160 qsfrz=con_eps*es/(pfrz+con_epsm1*es)
163 *exp(a2*(isotherm-a3)/(isotherm-a4))
168 rhz = amax1(0.01,rhz)
177 IF(tshltr(i,j)/=spval .AND. pshltr(i,j)/=spval)
THEN
178 tsfc=tshltr(i,j)*(pshltr(i,j)*1.e-5)**capa
181 tsfc=t(i,j,lm)+d0065*(zmid(i,j,lm)-htsfc-2.0)
184 zfrz(i,j) = zl + (isotherm-tsfc)/delt*delz
188 IF(qshltr(i,j)/=spval)
THEN
194 qfrz = qsfc + delq/delz*dzabv
195 qfrz = amax1(0.0,qfrz)
200 alpfrz = alpl + delalp/delz*dzabv
203 IF(modelname ==
'GFS'.OR.modelname ==
'RAPR')
THEN
206 qsfrz=con_eps*es/(pfrz+con_epsm1*es)
209 *exp(a2*(isotherm-a3)/(isotherm-a4))
213 rhz = amax1(0.01,rhz)
221 rhfrz(i,j) = amax1(0.01,rhfrz(i,j))
222 rhfrz(i,j) = amin1(rhfrz(i,j),1.00)
223 zfrz(i,j) = amax1(0.0,zfrz(i,j))
elemental real function, public fpvsnew(t)
calcape() computes CAPE/CINS and other storm related variables.