UPP (upp-srw-2.2.0)
Loading...
Searching...
No Matches
CALMICT.f
Go to the documentation of this file.
1
36 SUBROUTINE calmict_new(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL, &
37 QW1,QI1,QR1,QS1,DBZ1,DBZR1,DBZI1,DBZC1,NLICE1,NRAIN1)
38
39!
40 use params_mod, only: dbzmin, epsq, tfrz, eps, rd, d608
41 use ctlblk_mod, only: jsta, jend, jsta_2l, jend_2u,im, &
42 ista, iend, ista_2l, iend_2u
43 use cmassi_mod, only: t_ice, rqr_drmin, n0rmin, cn0r_dmrmin, &
44 mdrmin, rqr_drmax, cn0r_dmrmax, mdrmax, n0r0, xmrmin, &
45 xmrmax, massi, cn0r0, mdimin, xmimax, mdimax
46!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
47 implicit none
48!
49 INTEGER INDEXS, INDEXR
50!aligo
51 REAL, PARAMETER :: Cice=1.634e13, cwet=1./.189, cboth=cice/.224, &
52 & nli_min=1.e3, rfmax=45.259, rqmix=0.1e-3,nsi_max=250.e3
53!aligo
54 real,dimension(ista_2l:iend_2u,jsta_2l:jend_2u),intent(in) :: P1D,T1D,Q1D,C1D,FI1D,FR1D, &
55 fs1d,curefl
56 real,dimension(ista_2l:iend_2u,jsta_2l:jend_2u),intent(inout) :: QW1,QI1,QR1,QS1,DBZ1,DBZR1,&
57 dbzi1,dbzc1,nlice1,nrain1
58
59 integer I,J
60 real :: TC,Frain,Fice,RimeF,Xsimass,Qice,Qsat,ESAT,WV,RHO,RRHO, &
61 & rqr,drmm,qsigrd,wvqw,dum,xli,qlice,wc,dli,nlimax,nsimax, &
62 & rqlice, n0r,ztot,zrain,zice,zconv,zmin,zmix,nlice,nsmice, &
63 & qsmice,nrain,nmix,zsmice
64 logical :: LARGE_RF, HAIL
65 real,external :: fpvs
66!************************************************************************
67!--- Determine composition of condensate in the form of cloud water,
68! total ice (cloud ice & snow), & rain following GSMDRIVE in NMM model
69!
70 zmin=10.**(0.1*dbzmin)
71 DO j=jsta,jend
72 DO i=ista,iend
73 qw1(i,j)=0.
74 qi1(i,j)=0.
75 qr1(i,j)=0.
76 qs1(i,j)=0.
77 nlice1(i,j)=0.
78 nrain1(i,j)=0.
79 dbz1(i,j)=dbzmin
80 dbzr1(i,j)=dbzmin
81 dbzi1(i,j)=dbzmin
82 dbzc1(i,j)=dbzmin
83 ENDDO
84 ENDDO
85 DO j=jsta,jend
86 DO i=ista,iend
87 ztot=0. !--- Total radar reflectivity
88 zrain=0. !--- Radar reflectivity from rain
89 zice=0. !--- Radar reflectivity from ice
90 zsmice=0. !--- Radar reflectivity from small ice
91 zconv=curefl(i,j) !--- Radar reflectivity from convection
92 IF (c1d(i,j) <= epsq) THEN
93!
94!--- Skip rest of calculatiions if no condensate is present
95!
96 GO TO 10
97 ELSE
98 wc=c1d(i,j)
99 ENDIF
100!
101!--- Code below is from GSMDRIVE for determining:
102! QI1 - total ice (cloud ice & snow) mixing ratio
103! QW1 - cloud water mixing ratio
104! QR1 - rain mixing ratio
105!
106 tc=t1d(i,j)-tfrz
107 fice=fi1d(i,j)
108 frain=fr1d(i,j)
109 IF (tc<=t_ice .OR. fice>=1.) THEN
110! IF (Fice>=1.) THEN
111 qi1(i,j)=wc
112 ELSE IF (fice <= 0.) THEN
113 qw1(i,j)=wc
114 ELSE
115 qi1(i,j)=fice*wc
116 qw1(i,j)=wc-qi1(i,j)
117 ENDIF
118 IF (qw1(i,j)>0. .AND. frain>0.) THEN
119 IF (frain >= 1.) THEN
120 qr1(i,j)=qw1(i,j)
121 qw1(i,j)=0.
122 ELSE
123 qr1(i,j)=frain*qw1(i,j)
124 qw1(i,j)=qw1(i,j)-qr1(i,j)
125 ENDIF
126 ENDIF
127 wv=q1d(i,j)/(1.-q1d(i,j))
128!
129!--- Saturation vapor pressure w/r/t water ( >=0C ) or ice ( <0C )
130!
131 esat=1000.*fpvs(t1d(i,j))
132 qsat=eps*esat/(p1d(i,j)-esat)
133 rho=p1d(i,j)/(rd*t1d(i,j)*(1.+d608*q1d(i,j)))
134 rrho=1./rho
135 !
136 !--- Based on code from GSMCOLUMN in model to determine reflectivity from rain
137 !
138 rqr=0.
139 IF (qr1(i,j) > epsq) THEN
140 rqr=rho*qr1(i,j)
141 IF (rqr <= rqr_drmin) THEN
142 n0r=max(n0rmin, cn0r_dmrmin*rqr)
143 indexr=mdrmin
144 ELSE IF (rqr >= rqr_drmax) THEN
145 n0r=cn0r_dmrmax*rqr
146 indexr=mdrmax
147 ELSE
148 n0r=n0r0
149 indexr=max( xmrmin, min(cn0r0*rqr**.25, xmrmax) )
150 ENDIF
151 !
152 !--- INDEXR is the mean drop size in microns; convert to mm
153 !
154 drmm=1.e-3*real(indexr)
155 !
156 !--- Number concentration of rain drops (convert INDEXR to m)
157 !
158 nrain=n0r*1.e-6*real(indexr)
159 nrain1(i,j)=nrain
160 zrain=0.72*n0r*drmm*drmm*drmm*drmm*drmm*drmm*drmm
161 ENDIF !--- End IF (QR1(I,J) > EPSQ) block
162!
163!--- Based on code from GSMCOLUMN in model to determine partition of
164! total ice into cloud ice & snow (precipitation ice)
165!
166 rqlice=0.
167 IF (qi1(i,j) > epsq) THEN
168 qice=qi1(i,j)
169!
170! -> Small ice particles are assumed to have a mean diameter of 50 microns.
171! * INDEXS - mean size of snow to the nearest micron (units of microns)
172! * RimeF - Rime Factor, which is the mass ratio of total (unrimed &
173! rimed) ice mass to the unrimed ice mass (>=1)
174! * QTICE - time-averaged mixing ratio of total ice
175! * QLICE - mixing ratio of large ice
176! * RQLICE - mass content of large ice
177! * NLICE1 - time-averaged number concentration of large ice
178!
179 IF (tc>=0.) THEN
180 !
181 !--- Eliminate small ice particle contributions for melting & sublimation
182 !
183 nsmice=0.
184 qsmice=0.
185 ELSE
186!
187!--- Max # conc of small ice crystals based on 10% of total ice content
188!
189! NSImax=0.1*RHO*QICE/MASSI(MDImin)
190!aligo
191 nsimax=max(nsi_max,0.1*rho*qice/massi(mdimin) )
192!aligo
193!
194!-- Specify Fletcher, Cooper, Meyers, etc. here for ice nuclei concentrations
195!
196 nsmice=min(0.01*exp(-0.6*tc), nsimax) !- Fletcher (1962)
197 dum=rrho*massi(mdimin)
198 nsmice=min(nsmice, qice/dum)
199 qsmice=nsmice*dum
200 ENDIF ! End IF (TC>=0.) THEN
201 qlice=max(0., qice-qsmice)
202 qs1(i,j)=qlice
203 qi1(i,j)=qsmice
204 rimef=amax1(1., fs1d(i,j) )
205 rimef=min(rimef, rfmax)
206 rqlice=rho*qlice
207 dum=xmimax*exp(.0536*tc)
208 indexs=min(mdimax, max(mdimin, int(dum) ) )
209!
210!-- Specify NLImax depending on presence of high density ice (rime factors >10)
211!
212 IF (rimef>10.) THEN
213 large_rf=.true. !-- For convective precipitation
214 nlimax=1.e3
215 ELSE
216 large_rf=.false. !-- For non-convective precipitation
217 dum=max(tc, t_ice)
218 nlimax=10.e3*exp(-0.017*dum)
219 ENDIF
220 nlice=rqlice/(rimef*massi(indexs))
221 dum=nli_min*massi(mdimin) !-- Minimum large ice mixing ratio
222new_nlice: IF (rqlice<dum) THEN
223 nlice=rqlice/massi(mdimin)
224 ELSE IF (nlice<nli_min .OR. nlice>nlimax) THEN new_nlice
225!
226!--- Force NLICE to be between NLI_min and NLImax, but allow for exceptions
227!
228 hail=.false.
229 nlice=max(nli_min, min(nlimax, nlice) )
230 xli=rqlice/(nlice*rimef)
231new_size: IF (xli <= massi(mdimin) ) THEN
232 indexs=mdimin
233 ELSE IF (xli <= massi(450) ) THEN new_size
234 dli=9.5885e5*xli**.42066 ! DLI in microns
235 indexs=min(mdimax, max(mdimin, int(dli) ) )
236 ELSE IF (xli <= massi(mdimax) ) THEN new_size
237 dli=3.9751e6*xli**.49870 ! DLI in microns
238 indexs=min(mdimax, max(mdimin, int(dli) ) )
239 ELSE new_size
240 indexs=mdimax
241 IF (large_rf) hail=.true.
242 ENDIF new_size
243no_hail: IF (.NOT. hail) THEN
244 nlice=rqlice/(rimef*massi(indexs)) !-- NLICE > NLImax
245 ENDIF no_hail
246 ENDIF new_nlice
247 nlice1(i,j)=nlice
248 !
249 !--- Equation (C.8) in Ferrier (1994, JAS, p. 272), which when
250 ! converted from cgs units to mks units results in the same
251 ! value for Cice, which is equal to the {} term below:
252 !
253 ! Zi={.224*720*(10**18)/[(PI*RHOL)**2]}*(RHO*QLICE)**2/NLICE1(I,J),
254 ! where RHOL=1000 kg/m**3 is the density of liquid water
255 !
256 !--- Valid only for exponential ice distributions
257 !
258 IF (nsmice > 0.) THEN
259 zsmice=cice*rho*rho*qsmice*qsmice/nsmice
260 ENDIF
261 if (nlice1(i,j) /= 0.0) zice=cice*rqlice*rqlice/nlice1(i,j)
262 IF (tc>=0.) zice=cwet*zice ! increased for wet ice
263 ENDIF ! End IF (QI1(I,J) > 0.) THEN
264!
265!--- Assumed enhanced radar reflectivity when rain and ice coexist
266! above an assumed threshold mass content, RQmix
267!
268dbz_mix: IF (rqr>rqmix .AND. rqlice>rqmix) THEN
269 IF (rqr>rqlice) THEN
270 nmix=nrain
271 ELSE
272 nmix=nlice1(i,j)
273 ENDIF
274 dum=rqr+rqlice
275 zmix=cboth*dum*dum/nmix
276 IF (zmix > zrain+zice) THEN
277 IF (rqr>rqlice) THEN
278 zrain=zmix-zice
279 ELSE
280 zice=zmix-zrain
281 ENDIF
282 ENDIF
283 ENDIF dbz_mix
284!
285!--- Calculate total (convective + grid-scale) radar reflectivity
286!
28710 zice=zice+zsmice
288 ztot=zrain+zice+zconv
289 IF (ztot > zmin) dbz1(i,j)= 10.*alog10(ztot)
290 IF (zrain > zmin) dbzr1(i,j)=10.*alog10(zrain)
291 IF (zice > zmin) dbzi1(i,j)=10.*alog10(zice)
292! IF (Zconv > Zmin) DBZC1(I,J)=10.*ALOG10(Zsmice)
293 IF (zconv > zmin) dbzc1(i,j)=10.*alog10(zconv)
294 ENDDO
295 ENDDO
296!
297 RETURN
298 END
299!
300!-- For the old version of the microphysics:
301!
302 SUBROUTINE calmict_old(P1D,T1D,Q1D,C1D,FI1D,FR1D,FS1D,CUREFL, &
303 QW1,QI1,QR1,QS1,DBZ1,DBZR1,DBZI1,DBZC1,NLICE1,NRAIN1)
304
337 use params_mod, only: dbzmin, epsq, tfrz, eps, rd, d608, oneps, nlimin
338 use ctlblk_mod, only: jsta, jend, jsta_2l, jend_2u, im, &
339 ista, iend, ista_2l, iend_2u
340 use rhgrd_mod, only: rhgrd
341 use cmassi_mod, only: t_ice, rqr_drmin, n0rmin, cn0r_dmrmin, mdrmin, &
342 rqr_drmax,cn0r_dmrmax, mdrmax, n0r0, xmrmin, xmrmax,flarge2, &
343 massi, cn0r0, mdimin, xmimax, mdimax,nlimax
344!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
345 implicit none
346!
347 INTEGER INDEXS, INDEXR
348 REAL, PARAMETER :: Cice=1.634e13
349
350 real,dimension(ista_2l:iend_2u,jsta_2l:jend_2u),intent(in) :: P1D,T1D,Q1D,C1D,FI1D,FR1D, &
351 FS1D,CUREFL
352 real,dimension(ista_2l:iend_2u,jsta_2l:jend_2u),intent(inout) :: QW1,QI1,QR1,QS1,DBZ1,DBZR1,&
353 dbzi1,dbzc1,nlice1,nrain1
354
355 REAL N0r,Ztot,Zrain,Zice,Zconv,Zmin
356 integer I,J
357 real TC, Frain,Fice,Flimass,FLARGE, &
358 fsmall,rimef,xsimass,qice,qsat,esat,wv,rho,rrho,rqr, &
359 drmm,qsigrd,wvqw,dum,xli,qlice,wc,dli,xlimass
360 real,external :: fpvs
361!************************************************************************
362!--- Determine composition of condensate in the form of cloud water,
363! total ice (cloud ice & snow), & rain following GSMDRIVE in NMM model
364!
365 zmin=10.**(0.1*dbzmin)
366 DO j=jsta,jend
367 DO i=ista,iend
368 qw1(i,j)=0.
369 qi1(i,j)=0.
370 qr1(i,j)=0.
371 qs1(i,j)=0.
372 nlice1(i,j)=0.
373 nrain1(i,j)=0.
374 dbz1(i,j)=dbzmin
375 dbzr1(i,j)=dbzmin
376 dbzi1(i,j)=dbzmin
377 dbzc1(i,j)=dbzmin
378 ENDDO
379 ENDDO
380 DO j=jsta,jend
381 DO i=ista,iend
382 zrain=0. !--- Radar reflectivity from rain
383 zice=0. !--- Radar reflectivity from ice
384 zconv=curefl(i,j) !--- Radar reflectivity from convection
385 IF (c1d(i,j) <= epsq) THEN
386!
387!--- Skip rest of calculatiions if no condensate is present
388!
389 GO TO 10
390 ELSE
391 wc=c1d(i,j)
392 ENDIF
393!
394!--- Code below is from GSMDRIVE for determining:
395! QI1 - total ice (cloud ice & snow) mixing ratio
396! QW1 - cloud water mixing ratio
397! QR1 - rain mixing ratio
398!
399 tc=t1d(i,j)-tfrz
400 fice=fi1d(i,j)
401 frain=fr1d(i,j)
402 IF (tc<=t_ice .OR. fice>=1.) THEN
403! IF (Fice>=1.) THEN
404 qi1(i,j)=wc
405 ELSE IF (fice <= 0.) THEN
406 qw1(i,j)=wc
407 ELSE
408 qi1(i,j)=fice*wc
409 qw1(i,j)=wc-qi1(i,j)
410 ENDIF
411 IF (qw1(i,j)>0. .AND. frain>0.) THEN
412 IF (frain >= 1.) THEN
413 qr1(i,j)=qw1(i,j)
414 qw1(i,j)=0.
415 ELSE
416 qr1(i,j)=frain*qw1(i,j)
417 qw1(i,j)=qw1(i,j)-qr1(i,j)
418 ENDIF
419 ENDIF
420 wv=q1d(i,j)/(1.-q1d(i,j))
421!
422!--- Saturation vapor pressure w/r/t water ( >=0C ) or ice ( <0C )
423!
424 esat=1000.*fpvs(t1d(i,j))
425 qsat=eps*esat/(p1d(i,j)-esat)
426 rho=p1d(i,j)/(rd*t1d(i,j)*(1.+d608*q1d(i,j)))
427 rrho=1./rho
428 !
429 !--- Based on code from GSMCOLUMN in model to determine reflectivity from rain
430 !
431 IF (qr1(i,j) > epsq) THEN
432 rqr=rho*qr1(i,j)
433 IF (rqr <= rqr_drmin) THEN
434 n0r=max(n0rmin, cn0r_dmrmin*rqr)
435 indexr=mdrmin
436 ELSE IF (rqr >= rqr_drmax) THEN
437 n0r=cn0r_dmrmax*rqr
438 indexr=mdrmax
439 ELSE
440 n0r=n0r0
441 indexr=max( xmrmin, min(cn0r0*rqr**.25, xmrmax) )
442 ENDIF
443 !
444 !--- INDEXR is the mean drop size in microns; convert to mm
445 !
446 drmm=1.e-3*real(indexr)
447 zrain=0.72*n0r*drmm*drmm*drmm*drmm*drmm*drmm*drmm
448 !
449 !--- Number concentration of rain drops (convert INDEXR to m)
450 !
451 nrain1(i,j)=n0r*1.e-6*real(indexr)
452 ENDIF !--- End IF (QR1(I,J) > EPSQ) block
453!
454!--- Based on code from GSMCOLUMN in model to determine partition of
455! total ice into cloud ice & snow (precipitation ice)
456!
457 IF (qi1(i,j) > epsq) THEN
458 qice=qi1(i,j)
459 rho=p1d(i,j)/(rd*t1d(i,j)*(1.+oneps*q1d(i,j)))
460 rrho=1./rho
461 qsigrd=rhgrd*qsat
462 wvqw=wv+qw1(i,j)
463!
464! * FLARGE - ratio of number of large ice to total (large & small) ice
465! * FSMALL - ratio of number of small ice crystals to large ice particles
466! -> Small ice particles are assumed to have a mean diameter of 50 microns.
467! * XSIMASS - used for calculating small ice mixing ratio
468! * XLIMASS - used for calculating large ice mixing ratio
469! * INDEXS - mean size of snow to the nearest micron (units of microns)
470! * RimeF - Rime Factor, which is the mass ratio of total (unrimed &
471! rimed) ice mass to the unrimed ice mass (>=1)
472! * FLIMASS - mass fraction of large ice
473! * QTICE - time-averaged mixing ratio of total ice
474! * QLICE - time-averaged mixing ratio of large ice
475! * NLICE1 - time-averaged number concentration of large ice
476!
477 IF (tc>=0. .OR. wvqw<qsigrd) THEN
478 flarge=1.
479 ELSE
480 flarge=flarge2 !-- specified in MICROINIT.f
481!! IF (TC>=-8. .AND. TC<=-3.) FLARGE=.5*FLARGE
482 ENDIF
483 fsmall=(1.-flarge)/flarge
484 xsimass=rrho*massi(mdimin)*fsmall
485 dum=xmimax*exp(.0536*tc)
486 indexs=min(mdimax, max(mdimin, int(dum) ) )
487 rimef=amax1(1., fs1d(i,j) )
488 xlimass=rrho*rimef*massi(indexs)
489 flimass=xlimass/(xlimass+xsimass)
490 qlice=flimass*qice
491 nlice1(i,j)=qlice/xlimass
492 IF (nlice1(i,j)<nlimin .OR. nlice1(i,j)>nlimax) THEN
493!
494!--- Force NLICE1 to be between NLImin and NLImax
495!
496 dum=max(nlimin, min(nlimax, nlice1(i,j)) )
497 xli=rho*(qice/dum-xsimass)/rimef
498 IF (xli <= massi(mdimin) ) THEN
499 indexs=mdimin
500 ELSE IF (xli <= massi(450) ) THEN
501 dli=9.5885e5*xli**.42066 ! DLI in microns
502 indexs=min(mdimax, max(mdimin, int(dli) ) )
503 ELSE IF (xli <= massi(mdimax) ) THEN
504 dli=3.9751e6*xli**.49870 ! DLI in microns
505 indexs=min(mdimax, max(mdimin, int(dli) ) )
506 ELSE
507 indexs=mdimax
508!
509!--- 8/22/01: Increase density of large ice if maximum limits
510! are reached for number concentration (NLImax) and mean size
511! (MDImax). Done to increase fall out of ice.
512!
513 IF (dum >= nlimax) &
514 rimef=rho*(qice/nlimax-xsimass)/massi(indexs)
515 ENDIF ! End IF (XLI <= MASSI(MDImin) )
516 xlimass=rrho*rimef*massi(indexs)
517 flimass=xlimass/(xlimass+xsimass)
518 qlice=flimass*qice
519 nlice1(i,j)=qlice/xlimass
520 ENDIF ! End IF (NLICE<NLImin ...
521 qs1(i,j)=amin1(qi1(i,j), qlice)
522 qi1(i,j)=amax1(0., qi1(i,j)-qs1(i,j))
523 !
524 !--- Equation (C.8) in Ferrier (1994, JAS, p. 272), which when
525 ! converted from cgs units to mks units results in the same
526 ! value for Cice, which is equal to the {} term below:
527 !
528 ! Zi={.224*720*(10**18)/[(PI*RHOL)**2]}*(RHO*QLICE)**2/NLICE1(I,J),
529 ! where RHOL=1000 kg/m**3 is the density of liquid water
530 !
531 !--- Valid only for exponential ice distributions
532 !
533 zice=cice*rho*rho*qlice*qlice/nlice1(i,j)
534 ENDIF ! End IF (QI1(I,J) > 0.) THEN
535!
536!--- Calculate total (convective + grid-scale) radar reflectivity
53710 ztot=zrain+zice+zconv
538 IF (ztot > zmin) dbz1(i,j)= 10.*alog10(ztot)
539 IF (zrain > zmin) dbzr1(i,j)=10.*alog10(zrain)
540 IF (zice > zmin) dbzi1(i,j)=10.*alog10(zice)
541 IF (zconv > zmin) dbzc1(i,j)=10.*alog10(zconv)
542 ENDDO
543 ENDDO
544!
545 RETURN
546 END
subroutine calmict_old(p1d, t1d, q1d, c1d, fi1d, fr1d, fs1d, curefl, qw1, qi1, qr1, qs1, dbz1, dbzr1, dbzi1, dbzc1, nlice1, nrain1)
Definition CALMICT.f:304
real function fpvs(t)
Definition GPVS.f:55