/[lmdze]/trunk/phylmd/newmicro.f90
ViewVC logotype

Contents of /trunk/phylmd/newmicro.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 337 - (show annotations)
Mon Sep 16 16:54:50 2019 UTC (4 years, 7 months ago) by guez
File size: 6052 byte(s)
In procedure newmicro, rename dummy argument cltau to cldtau. In
procedure nuage, rename dummy argument pcltau to cldtau. In procedure
radlwsw, rename dummy argument cldtaupd to cldtau. Motivation: same
variable name across procedures.

In procedure newmicro, no need for arrays zflwp and zfiwp: scalars are
sufficient (following LMDZ).

1 module newmicro_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE newmicro (paprs, play, t, qlwp, clc, cldtau, clemi, cldh, cldl, &
8 cldm, cldt, ctlwp, flwp, fiwp, flwc, fiwc)
9
10 ! From LMDZ4/libf/phylmd/newmicro.F, version 1.2 2004/06/03 09:22:43
11
12 ! Authors: Z. X. Li (LMD/CNRS), Johannes Quaas
13 ! Date: 1993/09/10
14 ! Objet: calcul de l'\'epaisseur optique et de l'\'emissivit\'e des nuages.
15
16 USE conf_phys_m, ONLY: rad_chau1, rad_chau2
17 USE dimphy, ONLY: klev, klon
18 USE histwrite_phy_m, ONLY: histwrite_phy
19 USE suphec_m, ONLY: rg
20
21 REAL, intent(in):: paprs(:, :) ! (klon, klev+1)
22 real, intent(in):: play(:, :) ! (klon, klev)
23 REAL, intent(in):: t(:, :) ! (klon, klev) temperature
24
25 REAL, intent(in):: qlwp(:, :) ! (klon, klev)
26 ! eau liquide nuageuse dans l'atmosphère (kg / kg)
27
28 REAL, intent(inout):: clc(:, :) ! (klon, klev)
29 ! couverture nuageuse pour le rayonnement (0 à 1)
30
31 REAL, intent(out):: cldtau(:, :) ! (klon, klev)
32 ! \'epaisseur optique des nuages
33
34 REAL, intent(out):: clemi(:, :) ! (klon, klev)
35 ! \'emissivit\'e des nuages (0 à 1)
36
37 REAL, intent(out):: cldh(:), cldl(:), cldm(:), cldt(:) ! (klon)
38 REAL, intent(out):: ctlwp(:) ! (klon)
39 REAL, intent(out):: flwp(:), fiwp(:) ! (klon)
40 REAL, intent(out):: flwc(:, :), fiwc(:, :) ! (klon, klev)
41
42 ! Local:
43
44 REAL re(klon, klev)
45 ! cloud droplet effective radius multiplied by fl (micro m)
46
47 REAL fl(klon, klev)
48 ! Denominator to re, introduced to avoid problems in the averaging
49 ! of the output. fl is the fraction of liquid water clouds within
50 ! a grid cell.
51
52 REAL, PARAMETER:: cetahb = 0.45, cetamb = 0.8
53 INTEGER i, k
54 REAL zflwp
55 real fice ! fraction of ice in cloud
56 REAL rad_chaud
57 REAL, PARAMETER:: coef_chau = 0.13
58 REAL, PARAMETER:: seuil_neb = 0.001, t_glace = 258.
59 real rel, tc, rei, zfiwp
60 real k_ice
61 real, parameter:: k_ice0 = 0.005 ! units=m2 / g
62 real, parameter:: DF = 1.66 ! diffusivity factor
63
64 !-----------------------------------------------------------------
65
66 ! Calculer l'\'epaisseur optique et l'\'emissivit\'e des nuages
67
68 loop_horizontal: DO i = 1, klon
69 flwp(i) = 0.
70 fiwp(i) = 0.
71
72 loop_vertical: DO k = 1, klev
73 clc(i, k) = MAX(clc(i, k), seuil_neb)
74
75 ! liquid/ice cloud water paths:
76
77 ! Linear transition:
78 fice = 1. - (t(i, k) - t_glace) / (273.13 - t_glace)
79 fice = MIN(MAX(fice, 0.), 1.)
80
81 zflwp = 1000. * (1. - fice) * qlwp(i, k) / clc(i, k) &
82 * (paprs(i, k) - paprs(i, k + 1)) / RG
83 zfiwp = 1000. * fice * qlwp(i, k) / clc(i, k) &
84 * (paprs(i, k) - paprs(i, k + 1)) / RG
85
86 flwp(i) = flwp(i) &
87 + (1. - fice) * qlwp(i, k) * (paprs(i, k) - paprs(i, k + 1)) / RG
88 fiwp(i) = fiwp(i) &
89 + fice * qlwp(i, k) * (paprs(i, k) - paprs(i, k + 1)) / RG
90
91 ! Total Liquid/Ice water content
92 flwc(i, k) = (1.-fice) * qlwp(i, k)
93 fiwc(i, k) = fice * qlwp(i, k)
94 ! In-Cloud Liquid/Ice water content
95
96 ! effective cloud droplet radius (microns):
97
98 ! for liquid water clouds:
99 rad_chaud = merge(rad_chau2, rad_chau1, k <= 3)
100
101 ! For output diagnostics
102
103 ! Cloud droplet effective radius (micro m)
104
105 ! we multiply here with f * xl (fraction of liquid water
106 ! clouds in the grid cell) to avoid problems in the
107 ! averaging of the output.
108 ! In the output of IOIPSL, derive the real cloud droplet
109 ! effective radius as re/fl
110
111 fl(i, k) = clc(i, k) * (1.-fice)
112 re(i, k) = rad_chaud * fl(i, k)
113
114 rel = rad_chaud
115 ! for ice clouds: as a function of the ambiant temperature
116 ! (formula used by Iacobellis and Somerville (2000), with an
117 ! asymptotical value of 3.5 microns at T<-81.4 C added to be
118 ! consistent with observations of Heymsfield et al. 1986):
119 tc = t(i, k)-273.15
120 rei = merge(3.5, 0.71 * tc + 61.29, tc <= -81.4)
121
122 ! Cloud optical thickness:
123 ! (for liquid clouds, traditional formula, for ice clouds,
124 ! Ebert and Curry (1992))
125 if (zflwp == 0.) rel = 1.
126 if (zfiwp == 0. .or. rei <= 0.) rei = 1.
127 cldtau(i, k) = 3. / 2. * (zflwp / rel) &
128 + zfiwp * (3.448e-03 + 2.431 / rei)
129
130 ! cloud infrared emissivity:
131
132 ! (the broadband infrared absorption coefficient is parameterized
133 ! as a function of the effective cld droplet radius)
134
135 ! Ebert and Curry (1992) formula as used by Kiehl & Zender (1995):
136 k_ice = k_ice0 + 1. / rei
137
138 clemi(i, k) = 1. - EXP(- coef_chau * zflwp - DF * k_ice * zfiwp)
139
140 if (clc(i, k) <= seuil_neb) then
141 clc(i, k) = 0.
142 cldtau(i, k) = 0.
143 clemi(i, k) = 0.
144 end if
145 ENDDO loop_vertical
146 ENDDO loop_horizontal
147
148 ! COMPUTE CLOUD LIQUID PATH AND TOTAL CLOUDINESS
149
150 DO i = 1, klon
151 cldt(i)=1.
152 cldh(i)=1.
153 cldm(i) = 1.
154 cldl(i) = 1.
155 ctlwp(i) = 0.
156 ENDDO
157
158 DO k = klev, 1, -1
159 DO i = 1, klon
160 ctlwp(i) = ctlwp(i) &
161 + qlwp(i, k) * (paprs(i, k) - paprs(i, k + 1)) / RG
162 cldt(i) = cldt(i) * (1.-clc(i, k))
163 if (play(i, k) <= cetahb * paprs(i, 1)) &
164 cldh(i) = cldh(i) * (1. - clc(i, k))
165 if (play(i, k) > cetahb * paprs(i, 1) .AND. &
166 play(i, k) <= cetamb * paprs(i, 1)) &
167 cldm(i) = cldm(i) * (1.-clc(i, k))
168 if (play(i, k) > cetamb * paprs(i, 1)) &
169 cldl(i) = cldl(i) * (1. - clc(i, k))
170 ENDDO
171 ENDDO
172
173 DO i = 1, klon
174 cldt(i)=1.-cldt(i)
175 cldh(i)=1.-cldh(i)
176 cldm(i)=1.-cldm(i)
177 cldl(i)=1.-cldl(i)
178 ENDDO
179
180 CALL histwrite_phy("re", re)
181 CALL histwrite_phy("fl", fl)
182
183 END SUBROUTINE newmicro
184
185 end module newmicro_m

  ViewVC Help
Powered by ViewVC 1.1.21