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