1 | MODULE RADIATION_SETUP |
---|
2 | |
---|
3 | ! RADIATION_SETUP - Setting up modular radiation scheme |
---|
4 | ! |
---|
5 | ! (C) Copyright 2015- ECMWF. |
---|
6 | ! |
---|
7 | ! This software is licensed under the terms of the Apache Licence Version 2.0 |
---|
8 | ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0. |
---|
9 | ! |
---|
10 | ! In applying this licence, ECMWF does not waive the privileges and immunities |
---|
11 | ! granted to it by virtue of its status as an intergovernmental organisation |
---|
12 | ! nor does it submit to any jurisdiction. |
---|
13 | ! |
---|
14 | ! PURPOSE |
---|
15 | ! ------- |
---|
16 | ! The modular radiation scheme is contained in a separate |
---|
17 | ! library. SETUP_RADIATION_SCHEME in this module sets up a small |
---|
18 | ! number of global variables needed to store the information for it. |
---|
19 | ! |
---|
20 | ! Lower case is used for variables and types taken from the |
---|
21 | ! radiation library |
---|
22 | ! |
---|
23 | ! INTERFACE |
---|
24 | ! --------- |
---|
25 | ! SETUP_RADIATION_SCHEME is called from SUECRAD. The radiation |
---|
26 | ! scheme is actually run using the RADIATION_SCHEME routine (not in |
---|
27 | ! this module). |
---|
28 | ! |
---|
29 | ! AUTHOR |
---|
30 | ! ------ |
---|
31 | ! Robin Hogan, ECMWF |
---|
32 | ! Original: 2015-09-16 |
---|
33 | ! |
---|
34 | ! MODIFICATIONS |
---|
35 | ! ------------- |
---|
36 | ! |
---|
37 | !----------------------------------------------------------------------- |
---|
38 | |
---|
39 | USE PARKIND1, ONLY : JPRB |
---|
40 | USE radiation_config, ONLY : config_type, & |
---|
41 | & ISolverMcICA, ISolverSpartacus, & |
---|
42 | & ILiquidModelSlingo, ILiquidModelSOCRATES, & |
---|
43 | & IIceModelFu, IIceModelBaran, & |
---|
44 | & IOverlapExponentialRandom |
---|
45 | |
---|
46 | IMPLICIT NONE |
---|
47 | |
---|
48 | ! Store configuration information for the radiation scheme in a |
---|
49 | ! global variable |
---|
50 | type(config_type) :: rad_config |
---|
51 | |
---|
52 | ! Ultraviolet weightings |
---|
53 | INTEGER :: NWEIGHT_UV |
---|
54 | INTEGER :: IBAND_UV(100) |
---|
55 | REAL(KIND=JPRB) :: WEIGHT_UV(100) |
---|
56 | ! Photosynthetically active radiation weightings |
---|
57 | INTEGER :: NWEIGHT_PAR |
---|
58 | INTEGER :: IBAND_PAR(100) |
---|
59 | REAL(KIND=JPRB) :: WEIGHT_PAR(100) |
---|
60 | |
---|
61 | ! Background aerosol is specified in an ugly way: using the old |
---|
62 | ! Tegen fields that are in terms of optical depth, and converted to |
---|
63 | ! mass mixing ratio via the relevant mass-extinction coefficient |
---|
64 | INTEGER, PARAMETER :: ITYPE_TROP_BG_AER = 8 ! hydrophobic organic |
---|
65 | INTEGER, PARAMETER :: ITYPE_STRAT_BG_AER=12 ! non-absorbing sulphate |
---|
66 | REAL(KIND=JPRB) :: TROP_BG_AER_MASS_EXT |
---|
67 | REAL(KIND=JPRB) :: STRAT_BG_AER_MASS_EXT |
---|
68 | |
---|
69 | CONTAINS |
---|
70 | |
---|
71 | ! This routine copies information between the LMDZ radiation |
---|
72 | ! configuration (stored in global variables) and the radiation |
---|
73 | ! configuration of the modular radiation scheme (stored in |
---|
74 | ! rad_config). The optional input logical LOUTPUT controls whether |
---|
75 | ! to print lots of information during the setup stage (default is |
---|
76 | ! no). |
---|
77 | ! AI At the end of the routine, the parameters are read in namelist |
---|
78 | ! |
---|
79 | SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT) |
---|
80 | |
---|
81 | USE YOMHOOK, ONLY : LHOOK, DR_HOOK |
---|
82 | ! AI (propre a IFS) |
---|
83 | ! USE YOMLUN, ONLY : NULNAM, NULOUT, NULERR |
---|
84 | USE YOMLUN, ONLY : NULOUT, NULERR |
---|
85 | USE YOESRTWN, ONLY : NMPSRTM |
---|
86 | ! AI ATTENTION (propre a IFS) |
---|
87 | ! USE YOERAD, ONLY : YRERAD |
---|
88 | |
---|
89 | USE radiation_interface, ONLY : setup_radiation |
---|
90 | ! USE radiation_aerosol_optics, ONLY : dry_aerosol_sw_mass_extinction |
---|
91 | |
---|
92 | ! AI (propre a IFS) |
---|
93 | !#include "posname.intfb.h" |
---|
94 | |
---|
95 | ! Whether or not to provide information on the radiation scheme |
---|
96 | ! configuration |
---|
97 | LOGICAL, INTENT(IN), OPTIONAL :: LOUTPUT |
---|
98 | |
---|
99 | ! Verbosity of configuration information 0=none, 1=warning, |
---|
100 | ! 2=info, 3=progress, 4=detailed, 5=debug |
---|
101 | INTEGER :: IVERBOSESETUP |
---|
102 | INTEGER :: ISTAT |
---|
103 | |
---|
104 | REAL(KIND=JPRB) :: ZHOOK_HANDLE |
---|
105 | |
---|
106 | character(len=512) :: file_name |
---|
107 | |
---|
108 | logical :: lprint_setp=.TRUE. |
---|
109 | |
---|
110 | IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',0,ZHOOK_HANDLE) |
---|
111 | |
---|
112 | ! *** GENERAL SETUP *** |
---|
113 | |
---|
114 | ! Configure verbosity of setup of radiation scheme |
---|
115 | |
---|
116 | print*,'********** Dans radiation_setup *****************' |
---|
117 | |
---|
118 | IVERBOSESETUP = 4 ! Provide plenty of information |
---|
119 | IF (PRESENT(LOUTPUT)) THEN |
---|
120 | IF (.NOT. LOUTPUT) THEN |
---|
121 | IVERBOSESETUP = 1 ! Warnings and errors only |
---|
122 | ENDIF |
---|
123 | ENDIF |
---|
124 | rad_config%iverbosesetup = IVERBOSESETUP |
---|
125 | if (lprint_setp) then |
---|
126 | print*,'Dans radiation_setup ' |
---|
127 | print*,'rad_config%iverbosesetup =', rad_config%iverbosesetup |
---|
128 | endif |
---|
129 | |
---|
130 | IF (IVERBOSESETUP > 1) THEN |
---|
131 | WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------' |
---|
132 | WRITE(NULOUT,'(a)') 'RADIATION_SETUP' |
---|
133 | ENDIF |
---|
134 | |
---|
135 | ! Normal operation of the radiation scheme displays only errors |
---|
136 | ! and warnings |
---|
137 | rad_config%iverbose = 5 |
---|
138 | if (lprint_setp) then |
---|
139 | print*,'rad_config%iverbose =', rad_config%iverbose |
---|
140 | endif |
---|
141 | ! For the time being, ensure a valid default directory name |
---|
142 | rad_config%directory_name = 'data' |
---|
143 | if (lprint_setp) then |
---|
144 | print*,'rad_config%directory_name =', rad_config%directory_name |
---|
145 | endif |
---|
146 | |
---|
147 | ! Do we do Hogan and Bozzo (2014) approximate longwave updates? |
---|
148 | ! AI ATTENTION (ifs : ) |
---|
149 | ! AI (propre a IFS) |
---|
150 | ! rad_config%do_lw_derivatives = YRERAD%LAPPROXLWUPDATE |
---|
151 | rad_config%do_lw_derivatives = .false. |
---|
152 | if (lprint_setp) then |
---|
153 | print*,'rad_config%do_lw_derivatives =', rad_config%do_lw_derivatives |
---|
154 | endif |
---|
155 | |
---|
156 | ! Surface spectral fluxes are needed for spectral shortwave albedo |
---|
157 | ! calculation |
---|
158 | ! AI ATTENTION test (ifs : T) |
---|
159 | ! rad_config%do_save_spectral_flux = .FALSE. |
---|
160 | rad_config%do_surface_sw_spectral_flux = .TRUE. |
---|
161 | if (lprint_setp) then |
---|
162 | print*,'rad_config%do_surface_sw_spectral_flux =', & |
---|
163 | rad_config%do_surface_sw_spectral_flux |
---|
164 | endif |
---|
165 | |
---|
166 | ! *** SETUP GAS OPTICS *** |
---|
167 | |
---|
168 | ! routine below does not have to (ifs : F) |
---|
169 | print*,'i_gas_model =',rad_config%i_gas_model |
---|
170 | rad_config%do_setup_ifsrrtm = .TRUE. |
---|
171 | if (lprint_setp) then |
---|
172 | print*,'rad_config%do_setup_ifsrrtm =', rad_config%do_setup_ifsrrtm |
---|
173 | endif |
---|
174 | |
---|
175 | ! *** SETUP CLOUD OPTICS *** |
---|
176 | |
---|
177 | ! Setup liquid optics |
---|
178 | ! AI ATTENTION |
---|
179 | ! Choix offline : liquid_model_name = "SOCRATES" |
---|
180 | rad_config%i_liq_model = ILiquidModelSOCRATES |
---|
181 | if (lprint_setp) then |
---|
182 | print*,'rad_config%i_liq_model =',rad_config%i_liq_model |
---|
183 | endif |
---|
184 | |
---|
185 | ! Setup ice optics |
---|
186 | ! Choix offline : ice_model_name = "Fu-IFS" |
---|
187 | rad_config%i_ice_model = IIceModelFu |
---|
188 | if (lprint_setp) then |
---|
189 | print*,'rad_config%i_ice_model =', rad_config%i_ice_model |
---|
190 | endif |
---|
191 | |
---|
192 | ! AI (propre a IFS) |
---|
193 | ! For consistency with earlier versions of the IFS radiation |
---|
194 | ! scheme, we perform shortwave delta-Eddington scaling *after* the |
---|
195 | ! merge of the cloud, aerosol and gas optical properties. Set |
---|
196 | ! this to "false" to do the scaling on the cloud and aerosol |
---|
197 | ! properties separately before merging with gases. Note that this |
---|
198 | ! is not compatible with the SPARTACUS solver. |
---|
199 | rad_config%do_sw_delta_scaling_with_gases = .FALSE. |
---|
200 | if (lprint_setp) then |
---|
201 | print*,'rad_config%do_sw_delta_scaling_with_gases =', & |
---|
202 | rad_config%do_sw_delta_scaling_with_gases |
---|
203 | endif |
---|
204 | |
---|
205 | ! AI (propre a IFS) |
---|
206 | ! Use Exponential-Exponential cloud overlap to match original IFS |
---|
207 | ! implementation of Raisanen cloud generator |
---|
208 | rad_config%i_overlap_scheme = IOverlapExponentialRandom |
---|
209 | if (lprint_setp) then |
---|
210 | print*,'rad_config%i_overlap_scheme =', rad_config%i_overlap_scheme |
---|
211 | endif |
---|
212 | |
---|
213 | ! *** SETUP AEROSOLS *** |
---|
214 | ! AI ATTENTION |
---|
215 | ! rad_config%use_aerosols = .TRUE. !(ifs) |
---|
216 | rad_config%use_aerosols = .FALSE. |
---|
217 | if (lprint_setp) then |
---|
218 | print*,'rad_config%use_aerosols =', rad_config%use_aerosols |
---|
219 | endif |
---|
220 | |
---|
221 | ! *** SETUP SOLVER *** |
---|
222 | |
---|
223 | ! 3D effects are off by default (ifs) |
---|
224 | rad_config%do_3d_effects = .TRUE. |
---|
225 | if (lprint_setp) then |
---|
226 | print*,'rad_config%do_3d_effects=', rad_config%do_3d_effects |
---|
227 | endif |
---|
228 | |
---|
229 | ! Select longwave solver |
---|
230 | ! AI ATTENTION |
---|
231 | rad_config%i_solver_lw = ISolverSpartacus |
---|
232 | if (lprint_setp) then |
---|
233 | print*,'rad_config%i_solver_lw =', rad_config%i_solver_lw |
---|
234 | endif |
---|
235 | |
---|
236 | rad_config%i_solver_sw = ISolverSpartacus |
---|
237 | if (lprint_setp) then |
---|
238 | print*,'rad_config%i_solver_sw =', rad_config%i_solver_sw |
---|
239 | endif |
---|
240 | |
---|
241 | ! SPARTACUS solver requires delta scaling to be done separately |
---|
242 | ! for clouds & aerosols |
---|
243 | IF (rad_config%i_solver_sw == ISolverSpartacus) THEN |
---|
244 | rad_config%do_sw_delta_scaling_with_gases = .FALSE. |
---|
245 | ENDIF |
---|
246 | |
---|
247 | ! Do we represent longwave scattering? |
---|
248 | rad_config%do_lw_cloud_scattering = .TRUE. |
---|
249 | rad_config%do_lw_aerosol_scattering = .TRUE. |
---|
250 | if (lprint_setp) then |
---|
251 | print*,'rad_config%do_lw_cloud_scattering =', & |
---|
252 | rad_config%do_lw_cloud_scattering |
---|
253 | print*,'rad_config%do_lw_aerosol_scattering =', & |
---|
254 | rad_config%do_lw_aerosol_scattering |
---|
255 | endif |
---|
256 | |
---|
257 | ! *** IMPLEMENT SETTINGS *** |
---|
258 | |
---|
259 | ! For advanced configuration, the configuration data for the |
---|
260 | ! "radiation" project can specified directly in the namelist. |
---|
261 | ! However, the variable naming convention is not consistent with |
---|
262 | ! the rest of the IFS. For basic configuration there are specific |
---|
263 | ! variables in the NAERAD namelist available in the YRERAD |
---|
264 | ! structure. |
---|
265 | |
---|
266 | ! AI ATTENTION (parameters read in namelist file) |
---|
267 | file_name="namelist_ecrad" |
---|
268 | call rad_config%read(file_name=file_name) |
---|
269 | |
---|
270 | ! Use configuration data to set-up radiation scheme, including |
---|
271 | ! reading scattering datafiles |
---|
272 | CALL setup_radiation(rad_config) |
---|
273 | |
---|
274 | ! Populate the mapping between the 14 RRTM shortwave bands and the |
---|
275 | ! 6 albedo inputs. The mapping according to the stated wavelength |
---|
276 | ! ranges of the 6-band model does not match the hard-wired mapping |
---|
277 | ! in NMPSRTM, but only the hard-wired values produce sensible |
---|
278 | ! results... |
---|
279 | ! Note that NMPSRTM(:)=(/ 6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 2, 2, 1, 6 /) |
---|
280 | ! AI (6 albedo SW bands) |
---|
281 | call rad_config%define_sw_albedo_intervals(6, & |
---|
282 | & [0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, & |
---|
283 | & 1.19e-6_jprb, 2.38e-6_jprb], [1,2,3,4,5,6]) |
---|
284 | ! Likewise between the 16 RRTM longwave bands and the 2 emissivity |
---|
285 | ! inputs (info taken from rrtm_ecrt_140gp_mcica.F90) representing |
---|
286 | ! outside and inside the window region of the spectrum |
---|
287 | ! rad_config%i_emiss_from_band_lw = (/ 1,1,1,1,1,2,2,2,1,1,1,1,1,1,1,1 /) |
---|
288 | ! AI ATTENTION ????? |
---|
289 | !! call rad_config%define_lw_emiss_intervals(3, & |
---|
290 | !! & (/ 8.0e-6_jprb,13.0e-6_jprb /), (/ 1,2,1 /)) |
---|
291 | |
---|
292 | ! ! Get spectral weightings for UV and PAR |
---|
293 | call rad_config%get_sw_weights(0.2e-6_jprb, 0.4415e-6_jprb, & |
---|
294 | & NWEIGHT_UV, IBAND_UV, WEIGHT_UV, 'ultraviolet') |
---|
295 | call rad_config%get_sw_weights(0.4e-6_jprb, 0.7e-6_jprb, & |
---|
296 | & NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, & |
---|
297 | & 'photosynthetically active radiation, PAR') |
---|
298 | |
---|
299 | rad_config%i_aerosol_type_map(1:13) = (/ & |
---|
300 | & -1, & ! Sea salt, size bin 1 (OPAC) |
---|
301 | & -2, & ! Sea salt, size bin 2 (OPAC) |
---|
302 | & -3, & ! Sea salt, size bin 3 (OPAC) |
---|
303 | & -4, & ! Hydrophilic organic matter (OPAC) |
---|
304 | & -5, & ! Ammonium sulphate (OPAC) |
---|
305 | & -6, & |
---|
306 | & -7, & |
---|
307 | & 1, & |
---|
308 | & 2, & |
---|
309 | & 3, & |
---|
310 | & -8, & |
---|
311 | & -9, & |
---|
312 | & 4 /) ! Stratospheric sulphate (hand edited from OPAC) |
---|
313 | rad_config%aerosol_optics_override_file_name = 'aerosol_optics_lmdz.nc' |
---|
314 | |
---|
315 | ! IF (YRERAD%NAERMACC > 0) THEN |
---|
316 | ! With the MACC aerosol climatology we need to add in the |
---|
317 | ! background aerosol afterwards using the Tegen arrays. In this |
---|
318 | ! case we first configure the background aerosol mass-extinction |
---|
319 | ! coefficient at 550 nm, which corresponds to the 10th RRTMG |
---|
320 | ! shortwave band. |
---|
321 | ! TROP_BG_AER_MASS_EXT = dry_aerosol_sw_mass_extinction(rad_config, & |
---|
322 | ! & ITYPE_TROP_BG_AER, 10) |
---|
323 | ! STRAT_BG_AER_MASS_EXT = dry_aerosol_sw_mass_extinction(rad_config, & |
---|
324 | ! & ITYPE_STRAT_BG_AER, 10) |
---|
325 | |
---|
326 | ! WRITE(NULOUT,'(a,i0)') 'Tropospheric bacground uses aerosol type ', & |
---|
327 | ! & ITYPE_TROP_BG_AER |
---|
328 | ! WRITE(NULOUT,'(a,i0)') 'Stratospheric bacground uses aerosol type ', & |
---|
329 | ! & ITYPE_STRAT_BG_AER |
---|
330 | ! ENDIF |
---|
331 | |
---|
332 | IF (IVERBOSESETUP > 1) THEN |
---|
333 | WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------' |
---|
334 | ENDIF |
---|
335 | |
---|
336 | IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE) |
---|
337 | |
---|
338 | END SUBROUTINE SETUP_RADIATION_SCHEME |
---|
339 | |
---|
340 | END MODULE RADIATION_SETUP |
---|