46 SUBROUTINE frzlvl2(ISOTHERM,ZFRZ,RHFRZ,PFRZL)
49 use vrbls3d, only: pint, t, zmid, pmid, q, zint, alpint
50 use vrbls2d, only: fis, tshltr, pshltr, qz0, qs, qshltr
51 use masks, only: lmh, sm
52 use params_mod, only: gi, d00, capa, d0065, tfrz, pq0, a2, a3, a4, d50
53 use ctlblk_mod
, only: jsta, jend, spval, lm, modelname, im, ista, iend
64 REAL,
PARAMETER::pucap=300.0e2
65 real,
intent(in) :: isotherm
66 REAL,
dimension(ista:iend,jsta:jend),
intent(out) :: rhfrz, zfrz, pfrzl
68 integer i,j,l,lice,llmh
69 real htsfc,psfc,qsfc,rhsfc,qw,qsat,delz,delt,delq,delalp,delzp, &
70 zl,zu,dzabv,qfrz,alpl,alph,alpfrz,pfrz,qsfrz,rhz,dzfr, &
81 IF(fis(i,j)<spval)
THEN
94 IF(tshltr(i,j)/=spval .AND. pshltr(i,j)/=spval)
THEN
95 tsfc=tshltr(i,j)*(pshltr(i,j)*1.e-5)**capa
98 tsfc=t(i,j,lm)+d0065*(zmid(i,j,lm)-htsfc-2.0)
104 IF (pmid(i,j,l)>=pucap .AND. &
105 (t(i,j,l)<=isotherm.AND.t(i,j,l+1)>isotherm))lice=l
110 IF (lice==llmh.AND.tsfc<=isotherm)
THEN
111 zfrz(i,j) = htsfc+2.0+(tsfc-isotherm)/d0065
112 qsfc = sm(i,j)*qz0(i,j)+(1.-sm(i,j))*qs(i,j)
113 IF(qshltr(i,j)/=spval)
THEN
122 IF(modelname ==
'GFS' .OR. modelname ==
'RAPR')
THEN
125 qsat=con_eps*es/(psfc+con_epsm1*es)
128 *exp(a2*(tsfc-a3)/(tsfc-a4))
132 rhsfc = amax1(0.01,rhsfc)
133 rhsfc = amin1(rhsfc,1.0)
138 ELSE IF (lice<llmh)
THEN
140 delz = d50*(zint(i,j,l)-zint(i,j,l+2))
141 zl = d50*(zint(i,j,l+1)+zint(i,j,l+2))
142 delt = t(i,j,l)-t(i,j,l+1)
143 zfrz(i,j) = zl+(isotherm-t(i,j,l+1))/delt*delz
146 delq = q(i,j,l)-q(i,j,l+1)
147 qfrz = q(i,j,l+1) + delq/delz*dzabv
148 qfrz = amax1(0.0,qfrz)
150 alpl = alpint(i,j,l+2)
153 delzp = zint(i,j,l)-zint(i,j,l+2)
154 dzfr = zfrz(i,j) - zint(i,j,l+2)
155 alpfrz = alpl + delalp/delzp*dzfr
158 IF(modelname ==
'GFS'.OR.modelname ==
'RAPR')
THEN
161 qsfrz=con_eps*es/(pfrz+con_epsm1*es)
164 *exp(a2*(isotherm-a3)/(isotherm-a4))
169 rhz = amax1(0.01,rhz)
178 IF(tshltr(i,j)/=spval .AND. pshltr(i,j)/=spval)
THEN
179 tsfc=tshltr(i,j)*(pshltr(i,j)*1.e-5)**capa
182 tsfc=t(i,j,lm)+d0065*(zmid(i,j,lm)-htsfc-2.0)
185 zfrz(i,j) = zl + (isotherm-tsfc)/delt*delz
189 IF(qshltr(i,j)/=spval)
THEN
195 qfrz = qsfc + delq/delz*dzabv
196 qfrz = amax1(0.0,qfrz)
201 alpfrz = alpl + delalp/delz*dzabv
204 IF(modelname ==
'GFS'.OR.modelname ==
'RAPR')
THEN
207 qsfrz=con_eps*es/(pfrz+con_epsm1*es)
210 *exp(a2*(isotherm-a3)/(isotherm-a4))
214 rhz = amax1(0.01,rhz)
222 rhfrz(i,j) = amax1(0.01,rhfrz(i,j))
223 rhfrz(i,j) = amin1(rhfrz(i,j),1.00)
224 zfrz(i,j) = amax1(0.0,zfrz(i,j))
elemental real function, public fpvsnew(t)
calcape() computes CAPE/CINS and other storm related variables.