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

Annotation of /trunk/phylmd/newmicro.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 337 - (hide annotations)
Mon Sep 16 16:54:50 2019 UTC (4 years, 8 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 guez 68 module newmicro_m
2 guez 3
3 guez 52 IMPLICIT none
4 guez 3
5 guez 68 contains
6 guez 3
7 guez 337 SUBROUTINE newmicro (paprs, play, t, qlwp, clc, cldtau, clemi, cldh, cldl, &
8 guez 217 cldm, cldt, ctlwp, flwp, fiwp, flwc, fiwc)
9 guez 3
10 guez 68 ! From LMDZ4/libf/phylmd/newmicro.F, version 1.2 2004/06/03 09:22:43
11 guez 3
12 guez 69 ! Authors: Z. X. Li (LMD/CNRS), Johannes Quaas
13     ! Date: 1993/09/10
14 guez 337 ! Objet: calcul de l'\'epaisseur optique et de l'\'emissivit\'e des nuages.
15 guez 69
16     USE conf_phys_m, ONLY: rad_chau1, rad_chau2
17     USE dimphy, ONLY: klev, klon
18 guez 217 USE histwrite_phy_m, ONLY: histwrite_phy
19     USE suphec_m, ONLY: rg
20 guez 69
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 guez 337 ! eau liquide nuageuse dans l'atmosphère (kg / kg)
27 guez 69
28     REAL, intent(inout):: clc(:, :) ! (klon, klev)
29     ! couverture nuageuse pour le rayonnement (0 à 1)
30    
31 guez 337 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 guez 69
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 guez 217 ! Local:
43 guez 69
44 guez 217 REAL re(klon, klev)
45 guez 69 ! cloud droplet effective radius multiplied by fl (micro m)
46    
47 guez 217 REAL fl(klon, klev)
48 guez 69 ! 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 guez 68 INTEGER i, k
54 guez 337 REAL zflwp
55     real fice ! fraction of ice in cloud
56 guez 217 REAL rad_chaud
57 guez 69 REAL, PARAMETER:: coef_chau = 0.13
58 guez 337 REAL, PARAMETER:: seuil_neb = 0.001, t_glace = 258.
59     real rel, tc, rei, zfiwp
60 guez 69 real k_ice
61 guez 337 real, parameter:: k_ice0 = 0.005 ! units=m2 / g
62 guez 69 real, parameter:: DF = 1.66 ! diffusivity factor
63 guez 3
64 guez 69 !-----------------------------------------------------------------
65 guez 3
66 guez 337 ! Calculer l'\'epaisseur optique et l'\'emissivit\'e des nuages
67 guez 3
68 guez 69 loop_horizontal: DO i = 1, klon
69     flwp(i) = 0.
70     fiwp(i) = 0.
71    
72 guez 217 loop_vertical: DO k = 1, klev
73 guez 69 clc(i, k) = MAX(clc(i, k), seuil_neb)
74 guez 3
75 guez 69 ! liquid/ice cloud water paths:
76 guez 3
77 guez 337 ! Linear transition:
78 guez 69 fice = 1. - (t(i, k) - t_glace) / (273.13 - t_glace)
79     fice = MIN(MAX(fice, 0.), 1.)
80 guez 3
81 guez 337 zflwp = 1000. * (1. - fice) * qlwp(i, k) / clc(i, k) &
82 guez 69 * (paprs(i, k) - paprs(i, k + 1)) / RG
83 guez 337 zfiwp = 1000. * fice * qlwp(i, k) / clc(i, k) &
84 guez 69 * (paprs(i, k) - paprs(i, k + 1)) / RG
85 guez 3
86 guez 69 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 guez 3
91 guez 69 ! 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 guez 3
96 guez 69 ! effective cloud droplet radius (microns):
97 guez 3
98 guez 69 ! for liquid water clouds:
99 guez 217 rad_chaud = merge(rad_chau2, rad_chau1, k <= 3)
100    
101 guez 69 ! For output diagnostics
102 guez 52
103 guez 69 ! Cloud droplet effective radius (micro m)
104 guez 52
105 guez 69 ! 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 guez 52
111 guez 69 fl(i, k) = clc(i, k) * (1.-fice)
112     re(i, k) = rad_chaud * fl(i, k)
113 guez 52
114 guez 69 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 guez 52
122 guez 337 ! 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 guez 68
130 guez 69 ! 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 guez 337 clemi(i, k) = 1. - EXP(- coef_chau * zflwp - DF * k_ice * zfiwp)
139 guez 69
140     if (clc(i, k) <= seuil_neb) then
141     clc(i, k) = 0.
142 guez 337 cldtau(i, k) = 0.
143 guez 69 clemi(i, k) = 0.
144     end if
145 guez 217 ENDDO loop_vertical
146 guez 69 ENDDO loop_horizontal
147    
148 guez 68 ! COMPUTE CLOUD LIQUID PATH AND TOTAL CLOUDINESS
149 guez 69
150 guez 68 DO i = 1, klon
151 guez 69 cldt(i)=1.
152     cldh(i)=1.
153     cldm(i) = 1.
154     cldl(i) = 1.
155     ctlwp(i) = 0.
156 guez 68 ENDDO
157 guez 69
158 guez 68 DO k = klev, 1, -1
159     DO i = 1, klon
160 guez 69 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 guez 68 ENDDO
171     ENDDO
172 guez 69
173 guez 68 DO i = 1, klon
174 guez 69 cldt(i)=1.-cldt(i)
175     cldh(i)=1.-cldh(i)
176     cldm(i)=1.-cldm(i)
177     cldl(i)=1.-cldl(i)
178 guez 68 ENDDO
179    
180 guez 217 CALL histwrite_phy("re", re)
181     CALL histwrite_phy("fl", fl)
182    
183 guez 68 END SUBROUTINE newmicro
184    
185     end module newmicro_m

  ViewVC Help
Powered by ViewVC 1.1.21