/[lmdze]/trunk/Sources/phylmd/newmicro.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/newmicro.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 175 - (show annotations)
Fri Feb 5 16:02:34 2016 UTC (8 years, 3 months ago) by guez
File size: 8663 byte(s)
Added argument itau_phy to ini_histins, phyetat0, phytrac and
phyredem0. Removed variable itau_phy of module temps. Avoiding side
effect in etat0 and phyetat0. The procedures ini_histins, phyetat0,
phytrac and phyredem0 are all called by physiq so there is no
cascading variable penalty.

In procedure inifilr, made the condition on colat0 weaker to allow for
rounding error.

Removed arguments flux_o, flux_g and t_slab of clmain, flux_o and
flux_g of clqh and interfsurf_hq, tslab and seaice of phyetat0 and
phyredem. NetCDF variables TSLAB and SEAICE no longer in
restartphy.nc. All these variables were related to the not-implemented
slab ocean. seaice and tslab were just set to 0 in phyetat0 and never
used nor changed. flux_o and flux_g were computed in clmain but never
used in physiq.

Removed argument swnet of clqh. Was used only to compute a local
variable, swdown, which was not used.

1 module newmicro_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE newmicro (paprs, play, t, qlwp, clc, cltau, clemi, cldh, &
8 cldl, cldm, cldt, ctlwp, flwp, fiwp, flwc, fiwc, ok_aie, sulfate, &
9 sulfate_pi, bl95_b0, bl95_b1, cldtaupi, re, fl)
10
11 ! From LMDZ4/libf/phylmd/newmicro.F, version 1.2 2004/06/03 09:22:43
12
13 ! Authors: Z. X. Li (LMD/CNRS), Johannes Quaas
14 ! Date: 1993/09/10
15 ! Objet: calcul de l'épaisseur optique et de l'émissivité des nuages.
16
17 USE conf_phys_m, ONLY: rad_chau1, rad_chau2
18 USE dimphy, ONLY: klev, klon
19 USE suphec_m, ONLY: rd, rg
20 use nr_util, only: pi
21
22 REAL, intent(in):: paprs(:, :) ! (klon, klev+1)
23 real, intent(in):: play(:, :) ! (klon, klev)
24 REAL, intent(in):: t(:, :) ! (klon, klev) temperature
25
26 REAL, intent(in):: qlwp(:, :) ! (klon, klev)
27 ! eau liquide nuageuse dans l'atmosphère (kg/kg)
28
29 REAL, intent(inout):: clc(:, :) ! (klon, klev)
30 ! couverture nuageuse pour le rayonnement (0 à 1)
31
32 REAL, intent(out):: cltau(:, :) ! (klon, klev) épaisseur optique des nuages
33 REAL, intent(out):: clemi(:, :) ! (klon, klev) émissivité des nuages (0 à 1)
34
35 REAL, intent(out):: cldh(:), cldl(:), cldm(:), cldt(:) ! (klon)
36 REAL, intent(out):: ctlwp(:) ! (klon)
37 REAL, intent(out):: flwp(:), fiwp(:) ! (klon)
38 REAL, intent(out):: flwc(:, :), fiwc(:, :) ! (klon, klev)
39 LOGICAL, intent(in):: ok_aie ! apply aerosol indirect effect
40
41 REAL, intent(in):: sulfate(:, :) ! (klon, klev)
42 ! sulfate aerosol mass concentration (micro g m-3)
43
44 REAL, intent(in):: sulfate_pi(:, :) ! (klon, klev)
45 ! sulfate aerosol mass concentration (micro g m-3), pre-industrial value
46
47 REAL, intent(in):: bl95_b0, bl95_b1
48 ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus
49 ! B). They link cloud droplet number concentration to aerosol mass
50 ! concentration.
51
52 REAL, intent(out):: cldtaupi(:, :) ! (klon, klev)
53 ! pre-industrial value of cloud optical thickness, needed for the
54 ! diagnosis of the aerosol indirect radiative forcing (see
55 ! radlwsw)
56
57 REAL, intent(out):: re(:, :) ! (klon, klev)
58 ! cloud droplet effective radius multiplied by fl (micro m)
59
60 REAL, intent(out):: fl(:, :) ! (klon, klev)
61 ! Denominator to re, introduced to avoid problems in the averaging
62 ! of the output. fl is the fraction of liquid water clouds within
63 ! a grid cell.
64
65 ! Local:
66
67 REAL, PARAMETER:: cetahb = 0.45, cetamb = 0.8
68 INTEGER i, k
69 REAL zflwp(klon), fice
70 REAL radius, rad_chaud
71 REAL, PARAMETER:: coef_chau = 0.13
72 REAL, PARAMETER:: seuil_neb = 0.001, t_glace = 273. - 15.
73 real rel, tc, rei, zfiwp(klon)
74 real k_ice
75 real, parameter:: k_ice0 = 0.005 ! units=m2/g
76 real, parameter:: DF = 1.66 ! diffusivity factor
77 REAL cdnc(klon, klev) ! cloud droplet number concentration (m-3)
78
79 REAL cdnc_pi(klon, klev)
80 ! cloud droplet number concentration, pre-industrial value (m-3)
81
82 !-----------------------------------------------------------------
83
84 ! Calculer l'épaisseur optique et l'émissivité des nuages
85
86 loop_horizontal: DO i = 1, klon
87 flwp(i) = 0.
88 fiwp(i) = 0.
89
90 DO k = 1, klev
91 clc(i, k) = MAX(clc(i, k), seuil_neb)
92
93 ! liquid/ice cloud water paths:
94
95 fice = 1. - (t(i, k) - t_glace) / (273.13 - t_glace)
96 fice = MIN(MAX(fice, 0.), 1.)
97
98 zflwp(i) = 1000. * (1. - fice) * qlwp(i, k) / clc(i, k) &
99 * (paprs(i, k) - paprs(i, k + 1)) / RG
100 zfiwp(i) = 1000. * fice * qlwp(i, k) / clc(i, k) &
101 * (paprs(i, k) - paprs(i, k + 1)) / RG
102
103 flwp(i) = flwp(i) &
104 + (1. - fice) * qlwp(i, k) * (paprs(i, k) - paprs(i, k + 1)) / RG
105 fiwp(i) = fiwp(i) &
106 + fice * qlwp(i, k) * (paprs(i, k) - paprs(i, k + 1)) / RG
107
108 ! Total Liquid/Ice water content
109 flwc(i, k) = (1.-fice) * qlwp(i, k)
110 fiwc(i, k) = fice * qlwp(i, k)
111 ! In-Cloud Liquid/Ice water content
112
113 ! effective cloud droplet radius (microns):
114
115 ! for liquid water clouds:
116 IF (ok_aie) THEN
117 cdnc(i, k) = 10.**(bl95_b0 + bl95_b1 &
118 * log10(MAX(sulfate(i, k), 1e-4)) + 6.)
119 cdnc_pi(i, k) = 10.**(bl95_b0 + bl95_b1 &
120 * log10(MAX(sulfate_pi(i, k), 1e-4)) + 6.)
121
122 ! Restrict to interval [20, 1000] cm-3:
123 cdnc(i, k) = MIN(1000e6, MAX(20e6, cdnc(i, k)))
124 cdnc_pi(i, k) = MIN(1000e6, MAX(20e6, cdnc_pi(i, k)))
125
126 ! air density: play(i, k) / (RD * T(i, k))
127 ! factor 1.1: derive effective radius from volume-mean radius
128 ! factor 1000 is the water density
129 ! "_chaud" means that this is the CDR for liquid water clouds
130
131 rad_chaud = 1.1 * ((qlwp(i, k) * play(i, k) / (RD * T(i, k))) &
132 / (4./3. * PI * 1000. * cdnc(i, k)))**(1./3.)
133
134 ! Convert to micro m and set a lower limit:
135 rad_chaud = MAX(rad_chaud * 1e6, 5.)
136
137 ! Pre-industrial cloud optical thickness
138
139 ! "radius" is calculated as rad_chaud above (plus the
140 ! ice cloud contribution) but using cdnc_pi instead of
141 ! cdnc.
142 radius = 1.1 * ((qlwp(i, k) * play(i, k) / (RD * T(i, k))) &
143 / (4./3. * PI * 1000. * cdnc_pi(i, k)))**(1./3.)
144 radius = MAX(radius * 1e6, 5.)
145
146 tc = t(i, k)-273.15
147 rei = merge(3.5, 0.71 * tc + 61.29, tc <= -81.4)
148 if (zflwp(i) == 0.) radius = 1.
149 if (zfiwp(i) == 0. .or. rei <= 0.) rei = 1.
150 cldtaupi(i, k) = 3. / 2. * zflwp(i) / radius &
151 + zfiwp(i) * (3.448e-03 + 2.431 / rei)
152 else
153 rad_chaud = merge(rad_chau2, rad_chau1, k <= 3)
154 ENDIF
155 ! For output diagnostics
156
157 ! Cloud droplet effective radius (micro m)
158
159 ! we multiply here with f * xl (fraction of liquid water
160 ! clouds in the grid cell) to avoid problems in the
161 ! averaging of the output.
162 ! In the output of IOIPSL, derive the real cloud droplet
163 ! effective radius as re/fl
164
165 fl(i, k) = clc(i, k) * (1.-fice)
166 re(i, k) = rad_chaud * fl(i, k)
167
168 rel = rad_chaud
169 ! for ice clouds: as a function of the ambiant temperature
170 ! (formula used by Iacobellis and Somerville (2000), with an
171 ! asymptotical value of 3.5 microns at T<-81.4 C added to be
172 ! consistent with observations of Heymsfield et al. 1986):
173 tc = t(i, k)-273.15
174 rei = merge(3.5, 0.71 * tc + 61.29, tc <= -81.4)
175
176 ! cloud optical thickness:
177
178 ! (for liquid clouds, traditional formula,
179 ! for ice clouds, Ebert & Curry (1992))
180
181 if (zflwp(i) == 0.) rel = 1.
182 if (zfiwp(i) == 0. .or. rei <= 0.) rei = 1.
183 cltau(i, k) = 3./2. * (zflwp(i)/rel) &
184 + zfiwp(i) * (3.448e-03 + 2.431/rei)
185
186 ! cloud infrared emissivity:
187
188 ! (the broadband infrared absorption coefficient is parameterized
189 ! as a function of the effective cld droplet radius)
190
191 ! Ebert and Curry (1992) formula as used by Kiehl & Zender (1995):
192 k_ice = k_ice0 + 1. / rei
193
194 clemi(i, k) = 1. - EXP(- coef_chau * zflwp(i) - DF * k_ice * zfiwp(i))
195
196 if (clc(i, k) <= seuil_neb) then
197 clc(i, k) = 0.
198 cltau(i, k) = 0.
199 clemi(i, k) = 0.
200 cldtaupi(i, k) = 0.
201 end if
202
203 IF (.NOT. ok_aie) cldtaupi(i, k) = cltau(i, k)
204 ENDDO
205 ENDDO loop_horizontal
206
207 ! COMPUTE CLOUD LIQUID PATH AND TOTAL CLOUDINESS
208
209 DO i = 1, klon
210 cldt(i)=1.
211 cldh(i)=1.
212 cldm(i) = 1.
213 cldl(i) = 1.
214 ctlwp(i) = 0.
215 ENDDO
216
217 DO k = klev, 1, -1
218 DO i = 1, klon
219 ctlwp(i) = ctlwp(i) &
220 + qlwp(i, k) * (paprs(i, k) - paprs(i, k + 1)) / RG
221 cldt(i) = cldt(i) * (1.-clc(i, k))
222 if (play(i, k) <= cetahb * paprs(i, 1)) &
223 cldh(i) = cldh(i) * (1. - clc(i, k))
224 if (play(i, k) > cetahb * paprs(i, 1) .AND. &
225 play(i, k) <= cetamb * paprs(i, 1)) &
226 cldm(i) = cldm(i) * (1.-clc(i, k))
227 if (play(i, k) > cetamb * paprs(i, 1)) &
228 cldl(i) = cldl(i) * (1. - clc(i, k))
229 ENDDO
230 ENDDO
231
232 DO i = 1, klon
233 cldt(i)=1.-cldt(i)
234 cldh(i)=1.-cldh(i)
235 cldm(i)=1.-cldm(i)
236 cldl(i)=1.-cldl(i)
237 ENDDO
238
239 END SUBROUTINE newmicro
240
241 end module newmicro_m

  ViewVC Help
Powered by ViewVC 1.1.21