/[lmdze]/trunk/phylmd/Radlwsw/radlwsw.f90
ViewVC logotype

Contents of /trunk/phylmd/Radlwsw/radlwsw.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 346 - (show annotations)
Mon Dec 9 20:15:29 2019 UTC (4 years, 5 months ago) by guez
File size: 10040 byte(s)
Rename block to `my_block` in procedure `CLOUDS_GNO` because block is
a Fortran keyword.

Remove computation of palpbla in procedure sw. It was not used nor
output. (Not used nor output either in LMDZ.)

In procedure physiq, define `d_[uv]_con` and add them to `[uv]_seri`
only if `conv_Emanuel`. Thus, we do not need to initialize
`d_[uv]_con` to 0, we do not have to save them and we do not add 0 to
`[uv]_seri`.

In procedure physiq, no need to initialize rnebcon to 0, it is defined
by phyetat0 afterwards.

Check that `iflag_cldcon` is between - 2 and 3.

1 module radlwsw_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE radlwsw(dist, mu0, fract, paprs, play, tsol, albedo, t, q, wo, &
8 cldfra, cldemi, cldtau, heat, heat0, cool, cool0, radsol, topsw, toplw, &
9 solsw, sollw, sollwdown, topsw0, toplw0, solsw0, sollw0, lwdn0, lwdn, &
10 lwup0, lwup, swdn0, swdn, swup0, swup, ok_ade, topswad, solswad)
11
12 ! From LMDZ4/libf/phylmd/radlwsw.F, version 1.4, 2005/06/06 13:16:33
13 ! Author: Z. X. Li (LMD/CNRS)
14 ! Date: 1996/07/19
15
16 ! Objet : interface entre le modèle et les rayonnements solaire et
17 ! infrarouge
18
19 ! ATTENTION: swad has to be interpreted in the following manner:
20 ! not ok_ade zero
21 ! ok_ade aerosol direct forcing is F_{AD} = topsw - topswad
22
23 USE clesphys, ONLY: solaire
24 USE dimphy, ONLY: klev, klon
25 use lw_m, only: lw
26 USE raddim, ONLY: kdlon
27 USE suphec_m, ONLY: rg
28 use sw_m, only: sw
29 USE yoethf_m, ONLY: rvtmp2
30
31 real, intent(in):: dist ! distance Terre-Soleil, en ua
32 real, intent(in):: mu0(klon) ! cosinus de l'angle zenithal
33 real, intent(in):: fract(klon) ! duree d'ensoleillement normalisee
34 real, intent(in):: paprs(klon, klev + 1) ! pression a inter-couche (Pa)
35 real, intent(in):: play(klon, klev) ! pression au milieu de couche (Pa)
36 real, intent(in):: tsol(klon) ! temperature du sol (en K)
37 real, intent(in):: albedo(klon) ! albedo du sol (entre 0 et 1)
38 real, intent(in):: t(klon, klev) ! temperature (K)
39 real, intent(in):: q(klon, klev) ! vapeur d'eau (en kg/kg)
40
41 real, intent(in):: wo(klon, klev)
42 ! column-density of ozone in a layer, in kilo-Dobsons
43
44 real, intent(in):: cldfra(klon, klev) ! fraction nuageuse (entre 0 et 1)
45
46 real, intent(in):: cldemi(klon, klev)
47 ! emissivite des nuages dans l'IR (entre 0 et 1)
48
49 real, intent(in):: cldtau(klon, klev)
50 ! \'epaisseur optique des nuages dans le visible (present-day value)
51
52 real, intent(out):: heat(klon, klev)
53 ! échauffement atmosphérique (visible) (K/jour)
54
55 real, intent(out):: heat0(klon, klev) ! chauffage solaire ciel clair
56 real, intent(out):: cool(klon, klev) ! refroidissement dans l'IR (K/jour)
57
58 real, intent(out):: cool0(klon, klev)
59 ! refroidissement infrarouge ciel clair
60
61 real, intent(out):: radsol(klon)
62 ! bilan radiatif net au sol (W/m**2), positif vers le bas
63
64 real, intent(out):: topsw(klon) ! flux solaire net au sommet de l'atm.
65
66 real, intent(out):: toplw(klon)
67 ! rayonnement infrarouge montant au sommet de l'atmosphère
68
69 real, intent(out):: solsw(klon) ! flux solaire net à la surface
70
71 real, intent(out):: sollw(klon)
72 ! rayonnement infrarouge net à la surface
73
74 real, intent(out):: sollwdown(klon)
75 real, intent(out):: topsw0(klon)
76 real, intent(out):: toplw0(klon)
77 real, intent(out):: solsw0(klon), sollw0(klon)
78 REAL, intent(out):: lwdn0(:, :), lwdn(:, :) ! (klon, klev + 1)
79 REAL, intent(out):: lwup0(klon, klev + 1), lwup(klon, klev + 1)
80 REAL, intent(out):: swdn0(klon, klev + 1), swdn(klon, klev + 1)
81 REAL, intent(out):: swup0(klon, klev + 1), swup(klon, klev + 1)
82
83 logical, intent(in):: ok_ade ! apply the Aerosol Direct Effect
84
85 real, intent(out):: topswad(klon), solswad(klon)
86 ! aerosol direct forcing at TOA and surface
87 ! rayonnement solaire net absorb\'e
88
89 ! Local:
90
91 DOUBLE PRECISION ZFSUP(KDLON, KLEV + 1)
92 DOUBLE PRECISION ZFSDN(KDLON, KLEV + 1)
93 DOUBLE PRECISION ZFSUP0(KDLON, KLEV + 1)
94 DOUBLE PRECISION ZFSDN0(KDLON, KLEV + 1)
95
96 DOUBLE PRECISION ZFLUP(KDLON, KLEV + 1)
97 DOUBLE PRECISION ZFLDN(KDLON, KLEV + 1)
98 DOUBLE PRECISION ZFLUP0(KDLON, KLEV + 1)
99 DOUBLE PRECISION ZFLDN0(KDLON, KLEV + 1)
100
101 DOUBLE PRECISION zx_alpha1, zx_alpha2
102 INTEGER k, kk, i, iof, nb_gr
103 DOUBLE PRECISION PSCT
104
105 DOUBLE PRECISION PALBD(kdlon, 2), PALBP(kdlon, 2)
106 DOUBLE PRECISION PEMIS(kdlon), PDT0(kdlon), PVIEW(kdlon)
107 DOUBLE PRECISION PPSOL(kdlon), PDP(kdlon, klev)
108 DOUBLE PRECISION PTL(kdlon, klev + 1), PPMB(kdlon, klev + 1)
109 DOUBLE PRECISION PTAVE(kdlon, klev)
110 DOUBLE PRECISION PWV(kdlon, klev), PQS(kdlon, klev)
111 DOUBLE PRECISION POZON(kdlon, klev) ! mass fraction of ozone
112 DOUBLE PRECISION PAER(kdlon, klev, 5) ! AEROSOLS' OPTICAL THICKNESS
113 DOUBLE PRECISION PCLDLD(kdlon, klev)
114 DOUBLE PRECISION PCLDLU(kdlon, klev)
115 DOUBLE PRECISION PCLDSW(kdlon, klev)
116 DOUBLE PRECISION PTAU(kdlon, 2, klev)
117 DOUBLE PRECISION POMEGA(kdlon, 2, klev)
118 DOUBLE PRECISION PCG(kdlon, 2, klev)
119
120 DOUBLE PRECISION zfract(kdlon), zrmu0(kdlon)
121
122 DOUBLE PRECISION zheat(kdlon, klev), zcool(kdlon, klev)
123 DOUBLE PRECISION zheat0(kdlon, klev), zcool0(kdlon, klev)
124 DOUBLE PRECISION ztopsw(kdlon), ztoplw(kdlon)
125 DOUBLE PRECISION zsolsw(kdlon), zsollw(kdlon)
126 DOUBLE PRECISION zsollwdown(kdlon)
127
128 DOUBLE PRECISION ztopsw0(kdlon), ztoplw0(kdlon)
129 DOUBLE PRECISION zsolsw0(kdlon), zsollw0(kdlon)
130 DOUBLE PRECISION zznormcp
131
132 ! The following quantities are needed for the aerosol radiative forcings:
133 DOUBLE PRECISION ztopswad(kdlon), zsolswad(kdlon)
134 ! Aerosol direct forcing at TOA and surface
135
136 real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
137
138 !----------------------------------------------------------------------
139
140 nb_gr = klon / kdlon
141 IF (nb_gr * kdlon /= klon) THEN
142 PRINT *, "kdlon mauvais :", klon, kdlon, nb_gr
143 stop 1
144 ENDIF
145
146 heat = 0.
147 cool = 0.
148 heat0 = 0.
149 cool0 = 0.
150 PSCT = solaire / dist**2
151
152 loop_iof: DO iof = 0, klon - kdlon, kdlon
153 DO i = 1, kdlon
154 zfract(i) = fract(iof + i)
155 zrmu0(i) = mu0(iof + i)
156 PALBD(i, 1) = albedo(iof + i)
157 PALBD(i, 2) = albedo(iof + i)
158 PALBP(i, 1) = albedo(iof + i)
159 PALBP(i, 2) = albedo(iof + i)
160 ! cf. JLD pour etre en accord avec ORCHIDEE il faut mettre
161 ! PEMIS(i) = 0.96
162 PEMIS(i) = 1.
163 PVIEW(i) = 1.66
164 PPSOL(i) = paprs(iof + i, 1)
165 zx_alpha1 = (paprs(iof + i, 1)-play(iof + i, 2)) &
166 / (play(iof + i, 1)-play(iof + i, 2))
167 zx_alpha2 = 1. - zx_alpha1
168 PTL(i, 1) = t(iof + i, 1) * zx_alpha1 + t(iof + i, 2) * zx_alpha2
169 PTL(i, klev + 1) = t(iof + i, klev)
170 PDT0(i) = tsol(iof + i) - PTL(i, 1)
171 ENDDO
172 DO k = 2, klev
173 DO i = 1, kdlon
174 PTL(i, k) = (t(iof + i, k) + t(iof + i, k-1))*0.5
175 ENDDO
176 ENDDO
177 DO k = 1, klev
178 DO i = 1, kdlon
179 PDP(i, k) = paprs(iof + i, k)-paprs(iof + i, k + 1)
180 PTAVE(i, k) = t(iof + i, k)
181 PWV(i, k) = MAX(q(iof + i, k), 1e-12)
182 PQS(i, k) = PWV(i, k)
183 POZON(i, k) = wo(iof + i, k) * RG * dobson_u * 1e3 &
184 / (paprs(iof + i, k) - paprs(iof + i, k + 1))
185 PCLDLD(i, k) = cldfra(iof + i, k)*cldemi(iof + i, k)
186 PCLDLU(i, k) = cldfra(iof + i, k)*cldemi(iof + i, k)
187 PCLDSW(i, k) = cldfra(iof + i, k)
188 PTAU(i, 1, k) = MAX(cldtau(iof + i, k), 1e-05)
189 ! (1e-12 serait instable)
190 PTAU(i, 2, k) = MAX(cldtau(iof + i, k), 1e-05)
191 ! (pour 32-bit machines)
192 POMEGA(i, 1, k) = 0.9999 - 5e-04 * EXP(-0.5 * PTAU(i, 1, k))
193 POMEGA(i, 2, k) = 0.9988 - 2.5e-03 * EXP(-0.05 * PTAU(i, 2, k))
194 PCG(i, 1, k) = 0.865
195 PCG(i, 2, k) = 0.910
196 ENDDO
197 ENDDO
198
199 DO k = 1, klev + 1
200 DO i = 1, kdlon
201 PPMB(i, k) = paprs(iof + i, k)/100.
202 ENDDO
203 ENDDO
204
205 DO kk = 1, 5
206 DO k = 1, klev
207 DO i = 1, kdlon
208 PAER(i, k, kk) = 1E-15
209 ENDDO
210 ENDDO
211 ENDDO
212
213 CALL LW(PPMB, PDP, PDT0, PEMIS, PTL, PTAVE, PWV, POZON, PAER, PCLDLD, &
214 PCLDLU, PVIEW, zcool, zcool0, ztoplw, zsollw, ztoplw0, zsollw0, &
215 zsollwdown, ZFLUP, ZFLDN, ZFLUP0, ZFLDN0)
216 CALL SW(PSCT, zrmu0, zfract, PPMB, PDP, PPSOL, PALBD, PALBP, PTAVE, &
217 PWV, PQS, POZON, PCLDSW, PTAU, POMEGA, PCG, zheat, zheat0, ztopsw, &
218 zsolsw, ztopsw0, zsolsw0, ZFSUP, ZFSDN, ZFSUP0, ZFSDN0, ztopswad, &
219 zsolswad, ok_ade)
220
221 DO i = 1, kdlon
222 radsol(iof + i) = zsolsw(i) + zsollw(i)
223 topsw(iof + i) = ztopsw(i)
224 toplw(iof + i) = ztoplw(i)
225 solsw(iof + i) = zsolsw(i)
226 sollw(iof + i) = zsollw(i)
227 sollwdown(iof + i) = zsollwdown(i)
228
229 DO k = 1, klev + 1
230 lwdn0(iof + i, k) = ZFLDN0(i, k)
231 lwdn(iof + i, k) = ZFLDN(i, k)
232 lwup0(iof + i, k) = ZFLUP0(i, k)
233 lwup(iof + i, k) = ZFLUP(i, k)
234 ENDDO
235
236 topsw0(iof + i) = ztopsw0(i)
237 toplw0(iof + i) = ztoplw0(i)
238 solsw0(iof + i) = zsolsw0(i)
239 sollw0(iof + i) = zsollw0(i)
240
241 DO k = 1, klev + 1
242 swdn0(iof + i, k) = ZFSDN0(i, k)
243 swdn(iof + i, k) = ZFSDN(i, k)
244 swup0(iof + i, k) = ZFSUP0(i, k)
245 swup(iof + i, k) = ZFSUP(i, k)
246 ENDDO
247 ENDDO
248 ! transform the aerosol forcings, if they have to be calculated
249 IF (ok_ade) THEN
250 DO i = 1, kdlon
251 topswad(iof + i) = ztopswad(i)
252 solswad(iof + i) = zsolswad(i)
253 ENDDO
254 ELSE
255 DO i = 1, kdlon
256 topswad(iof + i) = 0.
257 solswad(iof + i) = 0.
258 ENDDO
259 ENDIF
260
261 DO k = 1, klev
262 DO i = 1, kdlon
263 ! scale factor to take into account the difference
264 ! between dry air and water vapour specific heat capacity
265 zznormcp = 1. + RVTMP2 * PWV(i, k)
266 heat(iof + i, k) = zheat(i, k) / zznormcp
267 cool(iof + i, k) = zcool(i, k)/zznormcp
268 heat0(iof + i, k) = zheat0(i, k)/zznormcp
269 cool0(iof + i, k) = zcool0(i, k)/zznormcp
270 ENDDO
271 ENDDO
272 end DO loop_iof
273
274 END SUBROUTINE radlwsw
275
276 end module radlwsw_m

  ViewVC Help
Powered by ViewVC 1.1.21