/[lmdze]/trunk/Sources/phylmd/Radlwsw/radlwsw.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/Radlwsw/radlwsw.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 217 - (show annotations)
Thu Mar 30 14:25:18 2017 UTC (7 years, 1 month ago) by guez
File size: 11168 byte(s)
run_off_lic downgraded from variable of module interface_surf to local
variable of fonte_neige.

Code could not work with ok_aie set to true, so removed this
possibility. tauae, piz_ae, cg_ae, topswai, solswai were then
0. cldtaupi was the same as cldtaupd.

In sw and procedures called by sw, flag_aer did not need to be double
precision, changed it to logical.

Downgraded re and fl from arguments of newmicro to local
variables. Added output of re and fl (following LMDZ).

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

  ViewVC Help
Powered by ViewVC 1.1.21