UPP  001
 All Data Structures Files Functions Pages
FRZLVL2.f
Go to the documentation of this file.
1 
45  SUBROUTINE frzlvl2(ISOTHERM,ZFRZ,RHFRZ,PFRZL)
46 
47 !
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
53  use physcons_post, only: con_rd, con_rv, con_eps, con_epsm1
54  use upp_physics, only: fpvsnew
55 
56  implicit none
57 
58 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
59 ! implicit none
60 !
61 ! DECLARE VARIABLES.
62 !
63  REAL,PARAMETER::pucap=300.0e2
64  real,intent(in) :: isotherm
65  REAL,dimension(im,jsta:jend),intent(out) :: rhfrz, zfrz, pfrzl
66 !jw
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, &
70  tsfc,es
71 !
72 !*********************************************************************
73 ! START FRZLVL.
74 !
75 ! LOOP OVER HORIZONTAL GRID.
76 !
77 
78  DO 20 j=jsta,jend
79  DO 20 i=1,im
80  IF(fis(i,j)<spval)THEN
81  htsfc = fis(i,j)*gi
82  llmh = nint(lmh(i,j))
83  rhfrz(i,j) = d00
84  zfrz(i,j) = htsfc
85  psfc = pint(i,j,llmh)
86  pfrzl(i,j) = psfc
87 !
88 ! FIND THE HIGHEST LAYER WHERE THE TEMPERATURE
89 ! CHANGES FROM ABOVE TO BELOW ISOTHERM.
90 !
91 ! TSFC = (SM(I,J)*THZ0(I,J)+(1.-SM(I,J))*THS(I,J)) &
92 ! *(PINT(I,J,NINT(LMH(I,J))+1)/P1000)**CAPA
93  IF(tshltr(i,j)/=spval .AND. pshltr(i,j)/=spval)THEN
94  tsfc=tshltr(i,j)*(pshltr(i,j)*1.e-5)**capa
95  ELSE
96 ! GFS analysis does not have flux file to retrieve TSFC from
97  tsfc=t(i,j,lm)+d0065*(zmid(i,j,lm)-htsfc-2.0)
98  END IF
99  lice=llmh
100 ! Per AWC's request, put a 300 mb cap for highest isothermal level so that it
101 ! does not go into stratosphere
102  DO l = llmh-1,1,-1
103  IF (pmid(i,j,l)>=pucap .AND. &
104  (t(i,j,l)<=isotherm.AND.t(i,j,l+1)>isotherm))lice=l
105  ENDDO
106 !
107 ! CHECK IF ISOTHERM LEVEL IS AT THE GROUND.
108 !
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
113  psfc=pshltr(i,j)
114  qsfc=qshltr(i,j)
115  ELSE
116  qsfc=q(i,j,lm)
117  psfc=pmid(i,j,lm)
118  END IF
119  pfrzl(i,j) = psfc
120 !
121  IF(modelname == 'GFS' .OR. modelname == 'RAPR')THEN
122  es=fpvsnew(tsfc)
123  es=min(es,psfc)
124  qsat=con_eps*es/(psfc+con_epsm1*es)
125  ELSE
126  qsat=pq0/psfc &
127  *exp(a2*(tsfc-a3)/(tsfc-a4))
128  END IF
129 !
130  rhsfc = qsfc/qsat
131  rhsfc = amax1(0.01,rhsfc)
132  rhsfc = amin1(rhsfc,1.0)
133  rhfrz(i,j)= rhsfc
134 !
135 ! OTHERWISE, LOCATE THE ISOTHERM LEVEL ALOFT.
136 !
137  ELSE IF (lice<llmh) THEN
138  l=lice
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
143 !
144  dzabv = zfrz(i,j)-zl
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)
148 !
149  alpl = alpint(i,j,l+2)
150  alph = alpint(i,j,l)
151  delalp = alph - alpl
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
155  pfrz = exp(alpfrz)
156  pfrzl(i,j) = pfrz
157  IF(modelname == 'GFS'.OR.modelname == 'RAPR')THEN
158  es=fpvsnew(isotherm)
159  es=min(es,pfrz)
160  qsfrz=con_eps*es/(pfrz+con_epsm1*es)
161  ELSE
162  qsfrz=pq0/pfrz &
163  *exp(a2*(isotherm-a3)/(isotherm-a4))
164  END IF
165 ! QSFRZ = PQ0/PFRZ
166 !
167  rhz = qfrz/qsfrz
168  rhz = amax1(0.01,rhz)
169  rhz = amin1(rhz,1.0)
170  rhfrz(i,j) = rhz
171 !
172  ELSE
173  l=lice
174  zu = zmid(i,j,l)
175  zl = htsfc+2.0
176  delz = zu-zl
177  IF(tshltr(i,j)/=spval .AND. pshltr(i,j)/=spval)THEN
178  tsfc=tshltr(i,j)*(pshltr(i,j)*1.e-5)**capa
179  ELSE
180 ! GFS analysis does not have flux file to retrieve TSFC from
181  tsfc=t(i,j,lm)+d0065*(zmid(i,j,lm)-htsfc-2.0)
182  END IF
183  delt = t(i,j,l)-tsfc
184  zfrz(i,j) = zl + (isotherm-tsfc)/delt*delz
185 !
186  dzabv = zfrz(i,j)-zl
187 ! GFS does not output QS
188  IF(qshltr(i,j)/=spval)THEN
189  qsfc=qshltr(i,j)
190  ELSE
191  qsfc=q(i,j,lm)
192  END IF
193  delq = q(i,j,l)-qsfc
194  qfrz = qsfc + delq/delz*dzabv
195  qfrz = amax1(0.0,qfrz)
196 !
197  alph = alpint(i,j,l)
198  alpl = alog(psfc)
199  delalp = alph-alpl
200  alpfrz = alpl + delalp/delz*dzabv
201  pfrz = exp(alpfrz)
202  pfrzl(i,j) = pfrz
203  IF(modelname == 'GFS'.OR.modelname == 'RAPR')THEN
204  es=fpvsnew(isotherm)
205  es=min(es,pfrz)
206  qsfrz=con_eps*es/(pfrz+con_epsm1*es)
207  ELSE
208  qsfrz=pq0/pfrz &
209  *exp(a2*(isotherm-a3)/(isotherm-a4))
210  END IF
211 !
212  rhz = qfrz/qsfrz
213  rhz = amax1(0.01,rhz)
214  rhz = amin1(rhz,1.0)
215  rhfrz(i,j)= rhz
216  ENDIF
217 !
218 ! BOUND ISOTHERM LEVEL RH. ISOTHERM LEVEL HEIGHT IS
219 ! MEASURED WITH RESPECT TO MEAN SEA LEVEL.
220 !
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))
224  ELSE
225  rhfrz(i,j) = spval
226  zfrz(i,j) = spval
227  ENDIF
228  20 CONTINUE
229 !
230 ! END OF ROUTINE.
231 !
232  RETURN
233  END
Definition: MASKS_mod.f:1
Definition: physcons.f:1
elemental real function, public fpvsnew(t)
Definition: UPP_PHYSICS.f:341
calcape() computes CAPE/CINS and other storm related variables.
Definition: UPP_PHYSICS.f:27