UPP  001
 All Data Structures Files Functions Pages
CALVIS.f
1 !**********************************************************************c
2  SUBROUTINE calvis(QV,QC,QR,QI,QS,TT,PP,VIS)
3 !
4 ! This routine computes horizontal visibility at the
5 ! surface or lowest model layer, from qc, qr, qi, and qs.
6 ! qv--water vapor mixing ratio (kg/kg)
7 ! qc--cloud water mixing ratio (kg/kg)
8 ! qr--rain water mixing ratio (kg/kg)
9 ! qi--cloud ice mixing ratio (kg/kg)
10 ! qs--snow mixing ratio (kg/kg)
11 ! tt--temperature (k)
12 ! pp--pressure (Pa)
13 !
14 ! If iice=0:
15 ! qprc=qr qrain=qr and qclw=qc if T>0C
16 ! qcld=qc =0 =0 if T<0C
17 ! qsnow=qs and qclice=qc if T<0C
18 ! =0 =0 if T>0C
19 ! If iice=1:
20 ! qprc=qr+qs qrain=qr and qclw=qc
21 ! qcld=qc+qi qsnow=qs and qclice=qc
22 !
23 ! Independent of the above definitions, the scheme can use different
24 ! assumptions of the state of hydrometeors:
25 ! meth='d': qprc is all frozen if T<0, liquid if T>0
26 ! meth='b': Bocchieri scheme used to determine whether qprc
27 ! is rain or snow. A temperature assumption is used to
28 ! determine whether qcld is liquid or frozen.
29 ! meth='r': Uses the four mixing ratios qrain, qsnow, qclw,
30 ! and qclice
31 !
32 ! The routine uses the following
33 ! expressions for extinction coefficient, beta (in km**-1),
34 ! with C being the mass concentration (in g/m**3):
35 !
36 ! cloud water: beta = 144.7 * C ** (0.8800)
37 ! rain water: beta = 2.24 * C ** (0.7500)
38 ! cloud ice: beta = 327.8 * C ** (1.0000)
39 ! snow: beta = 10.36 * C ** (0.7776)
40 !
41 ! These expressions were obtained from the following sources:
42 !
43 ! for cloud water: from Kunkel (1984)
44 ! for rainwater: from M-P dist'n, with No=8e6 m**-4 and
45 ! rho_w=1000 kg/m**3
46 ! for cloud ice: assume randomly oriented plates which follow
47 ! mass-diameter relationship from Rutledge and Hobbs (1983)
48 ! for snow: from Stallabrass (1985), assuming beta = -ln(.02)/vis
49 !
50 ! The extinction coefficient for each water species present is
51 ! calculated, and then all applicable betas are summed to yield
52 ! a single beta. Then the following relationship is used to
53 ! determine visibility (in km), where epsilon is the threshhold
54 ! of contrast, usually taken to be .02:
55 !
56 ! vis = -ln(epsilon)/beta [found in Kunkel (1984)]
57 !
58 ! 2021-05 Wen Meng -Add checking for undfined points invloved in
59 ! computation.
60 !------------------------------------------------------------------
61  use params_mod, only: h1, d608, rd
62  use ctlblk_mod, only: jsta, jend, im, jsta_2l, jend_2u, spval
63 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
64  implicit none
65 !
66 
67  real,dimension(IM,jsta_2l:jend_2u),intent(in) :: qv,qc,qr,qi,qs,tt,pp
68  real,dimension(IM,jsta_2l:jend_2u),intent(inout) :: vis
69 
70  CHARACTER meth*1
71  real celkel,tice,coeflc,coeflp,coeffc,coeffp,exponlc, &
72  exponlp,const1,rhoice,rhowat,qprc,qcld,qrain,qsnow, &
73  qclw,qclice,tv,rhoair,vovermd,conclc,concld,concfc, &
74  concfd,betav,exponfc,exponfp,conclp,concfp
75  integer i,j
76 !------------------------------------------------------------------
77 !------------------------------------------------------------------
78  celkel=273.15
79  tice=celkel-10.
80  coeflc=144.7
81  coeflp=2.24
82  coeffc=327.8
83  coeffp=10.36
84  exponlc=0.8800
85  exponlp=0.7500
86  exponfc=1.0000
87  exponfp=0.7776
88  const1=-log(.02)
89  rhoice=917.
90  rhowat=1000.
91 !
92  DO j=jsta,jend
93  DO i=1,im
94  vis(i,j)=spval
95 ! IF(IICE==0)THEN
96 ! QPRC=QR
97 ! QCLD=QC
98 ! IF(TT<CELKEL)THEN
99 ! QRAIN=0.
100 ! QSNOW=QPRC
101 ! QCLW=0.
102 ! QCLICE=QCLD
103 ! ELSE
104 ! QRAIN=QPRC
105 ! QSNOW=0.
106 ! QCLW=QCLD
107 ! QCLICE=0.
108 ! ENDIF
109 ! ELSE
110  IF (qr(i,j) < spval .and. qs(i,j) < spval .and. &
111  qc(i,j) < spval .and. qi(i,j) < spval .and. &
112  tt(i,j) < spval .and. qv(i,j) < spval .and. &
113  pp(i,j) < spval) THEN
114  qprc=qr(i,j)+qs(i,j)
115  qcld=qc(i,j)+qi(i,j)
116  qrain=qr(i,j)
117  qsnow=qs(i,j)
118  qclw=qc(i,j)
119  qclice=qi(i,j)
120 ! ENDIF
121 ! TV=VIRTUAL(TT,QV)
122  tv=tt(i,j)*(h1+d608*qv(i,j))
123  rhoair=pp(i,j)/(rd*tv)
124 ! IF(METH=='D')THEN
125 ! IF(TT<CELKEL)THEN
126 ! VOVERMD=(1.+QV)/RHOAIR+(QPRC+QCLD)/RHOICE
127 ! CONCLC = 0.
128 ! CONCLP = 0.
129 ! CONCFC = QCLD/VOVERMD*1000.
130 ! CONCFP = QPRC/VOVERMD*1000.
131 ! ELSE
132 ! VOVERMD=(1.+QV)/RHOAIR+(QPRC+QCLD)/RHOWAT
133 ! CONCLC = QCLD/VOVERMD*1000.
134 ! CONCLP = QPRC/VOVERMD*1000.
135 ! CONCFC = 0.
136 ! CONCFP = 0.
137 ! ENDIF
138 ! ELSEIF(METH=='B')THEN
139 ! IF(TT<TICE)THEN
140 ! VOVERMD=(1.+QV)/RHOAIR+(QPRC+QCLD)/RHOICE
141 ! CONCLC = 0.
142 ! CONCLP = 0.
143 ! CONCFC = QCLD/VOVERMD*1000.
144 ! CONCFP = QPRC/VOVERMD*1000.
145 ! ELSEIF(PRSNOW>=50.)THEN
146 ! VOVERMD=(1.+QV)/RHOAIR+QPRC/RHOICE+QCLD/RHOWAT
147 ! CONCLC = QCLD/VOVERMD*1000.
148 ! CONCLP = 0.
149 ! CONCFC = 0.
150 ! CONCFP = QPRC/VOVERMD*1000.
151 ! ELSE
152 ! VOVERMD=(1.+QV)/RHOAIR+(QPRC+QCLD)/RHOWAT
153 ! CONCLC = QCLD/VOVERMD*1000.
154 ! CONCLP = QPRC/VOVERMD*1000.
155 ! CONCFC = 0.
156 ! CONCFP = 0.
157 ! ENDIF
158 ! ELSEIF(METH=='R')THEN
159  vovermd=(1.+qv(i,j))/rhoair+(qclw+qrain)/rhowat+ &
160  (qclice+qsnow)/rhoice
161  conclc = max(0., qclw/vovermd*1000.)
162  conclp = max(0., qrain/vovermd*1000.)
163  concfc = max(0., qclice/vovermd*1000.)
164  concfp = max(0., qsnow/vovermd*1000.)
165 ! ENDIF
166  betav=coeffc*concfc**exponfc+coeffp*concfp**exponfp &
167  +coeflc*conclc**exponlc+coeflp*conclp**exponlp &
168  +1.e-10
169 ! CHANGED GSM 3-10-00 --> no point in distinguishing values
170 ! above 20 km, so make that value the max (prev max was 80)
171 ! VIS(I,J)=1.E3*MIN(20.,CONST1/BETAV) ! max of 20km
172 ! Chuang: Per Geoff, the max visibility was changed to be cosistent with visibility ceiling in obs
173  vis(i,j) = 1.e3*min(24.135,const1/betav) ! change max to be consistent with obs
174  ENDIF
175  ENDDO
176  ENDDO
177 !
178  RETURN
179  END