44 SUBROUTINE lfmfld(RH3310,RH6610,RH3366,PW3310)
48 use vrbls3d, only: pint, alpint, zint, t, q, cwm
50 use params_mod, only: d00, d50, pq0, a2, a3, a4, h1, d01, gi
51 use ctlblk_mod
, only: jsta, jend, modelname, spval, im, ista, iend
59 real,
PARAMETER :: rhowat=1.e3
63 REAL alpm, dz, es, pm, pwsum, qm, qs, tm, dp, rh
64 REAL,
dimension(ista:iend,jsta:jend),
intent(inout) :: rh3310, rh6610, rh3366
65 REAL,
dimension(ista:iend,jsta:jend),
intent(inout) :: pw3310
66 real z3310,z6610,z3366,p10,p33,p66
88 p10 = pint(i,j,nint(lmh(i,j)))
98 alpm = d50*(alpint(i,j,l)+alpint(i,j,l+1))
99 dz = zint(i,j,l)-zint(i,j,l+1)
100 dp = pint(i,j,l+1)-pint(i,j,l)
107 IF(modelname ==
'GFS')
THEN
109 qs = con_eps*es/(pm+con_epsm1*es)
111 qs=pq0/pm*exp(a2*(tm-a3)/(tm-a4))
127 IF ((pm<=p10).AND.(pm>=p66))
THEN
129 rh6610(i,j) = rh6610(i,j) + rh*dz
133 IF ((pm<=p10).AND.(pm>=p33))
THEN
135 rh3310(i,j)= rh3310(i,j)+rh*dz
136 pw3310(i,j)= pw3310(i,j)+(q(i,j,l)+cwm(i,j,l))*dp*gi
140 IF ((pm<=p66).AND.(pm>=p33))
THEN
142 rh3366(i,j) = rh3366(i,j) + rh*dz
151 rh6610(i,j) = rh6610(i,j)/z6610
157 rh3310(i,j) = rh3310(i,j)/z3310
163 rh3366(i,j) = rh3366(i,j)/z3366
elemental real function, public fpvsnew(t)
calcape() computes CAPE/CINS and other storm related variables.