1 | ! radiation_aerosol_optics.F90 - Computing aerosol optical properties |
---|
2 | ! |
---|
3 | ! (C) Copyright 2015- ECMWF. |
---|
4 | ! |
---|
5 | ! This software is licensed under the terms of the Apache Licence Version 2.0 |
---|
6 | ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0. |
---|
7 | ! |
---|
8 | ! In applying this licence, ECMWF does not waive the privileges and immunities |
---|
9 | ! granted to it by virtue of its status as an intergovernmental organisation |
---|
10 | ! nor does it submit to any jurisdiction. |
---|
11 | ! |
---|
12 | ! Author: Robin Hogan |
---|
13 | ! Email: r.j.hogan@ecmwf.int |
---|
14 | ! |
---|
15 | ! Modifications |
---|
16 | ! 2018-04-15 R. Hogan Add "direct" option |
---|
17 | ! 2020-11-14 R. Hogan Add setup_general_aerosol_optics for ecCKD compatibility |
---|
18 | ! 2022-03-27 R. Hogan Add setup_general_aerosol_optics_legacy to use RRTM aerosol files with ecCKD |
---|
19 | |
---|
20 | module radiation_aerosol_optics |
---|
21 | |
---|
22 | implicit none |
---|
23 | public |
---|
24 | |
---|
25 | contains |
---|
26 | |
---|
27 | ! Provides the elemental function "delta_eddington_extensive" |
---|
28 | #include "radiation_delta_eddington.h" |
---|
29 | |
---|
30 | !--------------------------------------------------------------------- |
---|
31 | ! Load aerosol scattering data; this subroutine delegates to one |
---|
32 | ! in radiation_aerosol_optics_data.F90 |
---|
33 | subroutine setup_aerosol_optics(config) |
---|
34 | |
---|
35 | use parkind1, only : jprb |
---|
36 | use yomhook, only : lhook, dr_hook |
---|
37 | use radiation_config, only : config_type |
---|
38 | use radiation_aerosol_optics_data, only : aerosol_optics_type |
---|
39 | use radiation_io, only : nulerr, radiation_abort |
---|
40 | use setup_aerosol_optics_lmdz_m, only: setup_aerosol_optics_lmdz |
---|
41 | |
---|
42 | type(config_type), intent(inout) :: config |
---|
43 | |
---|
44 | real(jprb) :: hook_handle |
---|
45 | |
---|
46 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_aerosol_optics',0,hook_handle) |
---|
47 | |
---|
48 | if (config%n_aerosol_types > 0) then |
---|
49 | ! Load data from file and prepare to map config%n_aerosol_types |
---|
50 | ! aerosol types |
---|
51 | if (config%use_general_aerosol_optics) then |
---|
52 | ! Read file containing high spectral resolution optical |
---|
53 | ! properties and average to the spectral intervals of the |
---|
54 | ! current gas-optics scheme |
---|
55 | ! call setup_general_aerosol_optics(config) |
---|
56 | call setup_general_aerosol_optics_lmdz(config,trim(config%aerosol_optics_file_name)) |
---|
57 | else |
---|
58 | ! Read file containing optical properties already in the bands |
---|
59 | ! of the gas-optics scheme |
---|
60 | ! call config%aerosol_optics%setup(trim(config%aerosol_optics_file_name), & |
---|
61 | ! & iverbose=config%iverbosesetup) |
---|
62 | call setup_aerosol_optics_lmdz(config%aerosol_optics, & |
---|
63 | trim(config%aerosol_optics_file_name)) |
---|
64 | end if |
---|
65 | |
---|
66 | call config%aerosol_optics%initialize_types(config%n_aerosol_types) |
---|
67 | |
---|
68 | ! Check agreement in number of bands |
---|
69 | if (config%n_bands_lw /= config%aerosol_optics%n_bands_lw) then |
---|
70 | write(nulerr,'(a,i0,a,i0,a)') '*** Error: number of longwave bands (', & |
---|
71 | & config%n_bands_lw, ') does not match aerosol optics look-up table (', & |
---|
72 | & config%aerosol_optics%n_bands_lw, ')' |
---|
73 | call radiation_abort() |
---|
74 | end if |
---|
75 | if (config%n_bands_sw /= config%aerosol_optics%n_bands_sw) then |
---|
76 | write(nulerr,'(a)') '*** Error: number of shortwave bands does not match aerosol optics look-up table' |
---|
77 | call radiation_abort() |
---|
78 | end if |
---|
79 | |
---|
80 | ! Map aerosol types to those loaded from the data file |
---|
81 | call config%aerosol_optics%set_types(config%i_aerosol_type_map(1:config%n_aerosol_types)) |
---|
82 | end if |
---|
83 | |
---|
84 | if (config%iverbosesetup >= 1) then |
---|
85 | call config%aerosol_optics%print_description(config%i_aerosol_type_map(1:config%n_aerosol_types)) |
---|
86 | end if |
---|
87 | |
---|
88 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_aerosol_optics',1,hook_handle) |
---|
89 | |
---|
90 | end subroutine setup_aerosol_optics |
---|
91 | |
---|
92 | |
---|
93 | !--------------------------------------------------------------------- |
---|
94 | ! Read file containing high spectral resolution optical properties |
---|
95 | ! and average to the spectral intervals of the current gas-optics |
---|
96 | ! scheme |
---|
97 | subroutine setup_general_aerosol_optics(config) |
---|
98 | |
---|
99 | use parkind1, only : jprb |
---|
100 | use yomhook, only : lhook, dr_hook |
---|
101 | use easy_netcdf, only : netcdf_file |
---|
102 | use radiation_config, only : config_type |
---|
103 | use radiation_aerosol_optics_data, only : aerosol_optics_type |
---|
104 | use radiation_spectral_definition, only : SolarReferenceTemperature, & |
---|
105 | & TerrestrialReferenceTemperature |
---|
106 | use radiation_io, only : nulout |
---|
107 | |
---|
108 | type(config_type), intent(inout), target :: config |
---|
109 | |
---|
110 | ! The NetCDF file containing the aerosol optics data |
---|
111 | type(netcdf_file) :: file |
---|
112 | |
---|
113 | ! Wavenumber points in NetCDF file |
---|
114 | real(jprb), allocatable :: wavenumber(:) ! cm-1 |
---|
115 | |
---|
116 | ! Hydrophilic aerosol properties |
---|
117 | real(jprb), allocatable :: mass_ext_philic(:,:,:) ! Mass-ext coefficient (m2 kg-1) |
---|
118 | real(jprb), allocatable :: ssa_philic(:,:,:) ! Single-scattering albedo |
---|
119 | real(jprb), allocatable :: g_philic(:,:,:) ! Asymmetry factor |
---|
120 | real(jprb), allocatable :: lidar_ratio_philic(:,:,:) ! Lidar ratio (sr) |
---|
121 | |
---|
122 | ! Hydrophobic aerosol properties |
---|
123 | real(jprb), allocatable :: mass_ext_phobic(:,:) ! Mass-ext coefficient (m2 kg-1) |
---|
124 | real(jprb), allocatable :: ssa_phobic(:,:) ! Single-scattering albedo |
---|
125 | real(jprb), allocatable :: g_phobic(:,:) ! Asymmetry factor |
---|
126 | real(jprb), allocatable :: lidar_ratio_phobic(:,:) ! Lidar ratio (sr) |
---|
127 | |
---|
128 | ! Mapping matrix between optical properties at the wavenumbers in |
---|
129 | ! the file, and spectral intervals used by the gas-optics scheme |
---|
130 | real(jprb), allocatable :: mapping(:,:) |
---|
131 | |
---|
132 | ! Pointer to the aerosol optics coefficients for brevity of access |
---|
133 | type(aerosol_optics_type), pointer :: ao |
---|
134 | |
---|
135 | ! Target monochromatic wavenumber for interpolation (cm-1) |
---|
136 | real(jprb) :: wavenumber_target |
---|
137 | |
---|
138 | ! Number of spectral points describing aerosol properties in the |
---|
139 | ! shortwave and longwave |
---|
140 | integer :: nspecsw, nspeclw |
---|
141 | |
---|
142 | ! Number of monochromatic wavelengths required |
---|
143 | integer :: nmono |
---|
144 | |
---|
145 | integer :: n_type_philic, n_type_phobic, nrh, nwn |
---|
146 | integer :: jtype, jwl, iwn |
---|
147 | |
---|
148 | ! Weight of first point in interpolation |
---|
149 | real(jprb) :: weight1 |
---|
150 | |
---|
151 | real(jprb) :: hook_handle |
---|
152 | |
---|
153 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_general_aerosol_optics',0,hook_handle) |
---|
154 | |
---|
155 | ao => config%aerosol_optics |
---|
156 | |
---|
157 | call file%open(trim(config%aerosol_optics_file_name), iverbose=config%iverbosesetup) |
---|
158 | |
---|
159 | if (.not. file%exists('wavenumber')) then |
---|
160 | ! Assume we have an old-style aerosol optics file with optical |
---|
161 | ! properties provided per pre-defined band |
---|
162 | call file%close() |
---|
163 | if (config%iverbosesetup >= 2) then |
---|
164 | write(nulout,'(a)') 'Legacy aerosol optics file: mapping between bands' |
---|
165 | end if |
---|
166 | call setup_general_aerosol_optics_legacy(config, trim(config%aerosol_optics_file_name)) |
---|
167 | return |
---|
168 | end if |
---|
169 | |
---|
170 | if (file%exists('mass_ext_hydrophilic')) then |
---|
171 | ao%use_hydrophilic = .true. |
---|
172 | else |
---|
173 | ao%use_hydrophilic = .false. |
---|
174 | end if |
---|
175 | |
---|
176 | call file%get('wavenumber', wavenumber) |
---|
177 | nwn = size(wavenumber) |
---|
178 | |
---|
179 | ! Read the raw scattering data |
---|
180 | call file%get('mass_ext_hydrophobic', mass_ext_phobic) |
---|
181 | call file%get('ssa_hydrophobic', ssa_phobic) |
---|
182 | call file%get('asymmetry_hydrophobic', g_phobic) |
---|
183 | call file%get('lidar_ratio_hydrophobic', lidar_ratio_phobic) |
---|
184 | |
---|
185 | call file%get_global_attribute('description_hydrophobic', & |
---|
186 | & ao%description_phobic_str) |
---|
187 | |
---|
188 | if (ao%use_hydrophilic) then |
---|
189 | call file%get('mass_ext_hydrophilic', mass_ext_philic) |
---|
190 | call file%get('ssa_hydrophilic', ssa_philic) |
---|
191 | call file%get('asymmetry_hydrophilic', g_philic) |
---|
192 | call file%get('lidar_ratio_hydrophilic', lidar_ratio_philic) |
---|
193 | |
---|
194 | call file%get('relative_humidity1', ao%rh_lower) |
---|
195 | |
---|
196 | call file%get_global_attribute('description_hydrophilic', & |
---|
197 | & ao%description_philic_str) |
---|
198 | end if |
---|
199 | |
---|
200 | ! Close aerosol scattering file |
---|
201 | call file%close() |
---|
202 | |
---|
203 | n_type_phobic = size(mass_ext_phobic, 2) |
---|
204 | if (ao%use_hydrophilic) then |
---|
205 | n_type_philic = size(mass_ext_philic, 3) |
---|
206 | nrh = size(ao%rh_lower) |
---|
207 | else |
---|
208 | n_type_philic = 0 |
---|
209 | nrh = 0 |
---|
210 | end if |
---|
211 | |
---|
212 | if (config%do_cloud_aerosol_per_sw_g_point) then |
---|
213 | nspecsw = config%gas_optics_sw%spectral_def%ng |
---|
214 | else |
---|
215 | nspecsw = config%gas_optics_sw%spectral_def%nband |
---|
216 | end if |
---|
217 | |
---|
218 | if (config%do_cloud_aerosol_per_lw_g_point) then |
---|
219 | nspeclw = config%gas_optics_lw%spectral_def%ng |
---|
220 | else |
---|
221 | nspeclw = config%gas_optics_lw%spectral_def%nband |
---|
222 | end if |
---|
223 | |
---|
224 | if (allocated(ao%wavelength_mono)) then |
---|
225 | ! Monochromatic wavelengths also required |
---|
226 | nmono = size(ao%wavelength_mono) |
---|
227 | else |
---|
228 | nmono = 0 |
---|
229 | end if |
---|
230 | |
---|
231 | call ao%allocate(n_type_phobic, n_type_philic, nrh, nspeclw, nspecsw, nmono) |
---|
232 | |
---|
233 | if (config%do_sw) then |
---|
234 | call config%gas_optics_sw%spectral_def%calc_mapping(SolarReferenceTemperature, & |
---|
235 | & wavenumber, mapping, use_bands=(.not. config%do_cloud_aerosol_per_sw_g_point)) |
---|
236 | |
---|
237 | ao%mass_ext_sw_phobic = matmul(mapping, mass_ext_phobic) |
---|
238 | ao%ssa_sw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic) & |
---|
239 | & / ao%mass_ext_sw_phobic |
---|
240 | ao%g_sw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic*g_phobic) & |
---|
241 | & / (ao%mass_ext_sw_phobic*ao%ssa_sw_phobic) |
---|
242 | |
---|
243 | if (ao%use_hydrophilic) then |
---|
244 | do jtype = 1,n_type_philic |
---|
245 | ao%mass_ext_sw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype)) |
---|
246 | ao%ssa_sw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
247 | & *ssa_philic(:,:,jtype)) & |
---|
248 | & / ao%mass_ext_sw_philic(:,:,jtype) |
---|
249 | ao%g_sw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
250 | & *ssa_philic(:,:,jtype)*g_philic(:,:,jtype)) & |
---|
251 | & / (ao%mass_ext_sw_philic(:,:,jtype)*ao%ssa_sw_philic(:,:,jtype)) |
---|
252 | end do |
---|
253 | end if |
---|
254 | end if |
---|
255 | |
---|
256 | if (config%do_lw) then |
---|
257 | call config%gas_optics_lw%spectral_def%calc_mapping(TerrestrialReferenceTemperature, & |
---|
258 | & wavenumber, mapping, use_bands=(.not. config%do_cloud_aerosol_per_lw_g_point)) |
---|
259 | |
---|
260 | ao%mass_ext_lw_phobic = matmul(mapping, mass_ext_phobic) |
---|
261 | ao%ssa_lw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic) & |
---|
262 | & / ao%mass_ext_lw_phobic |
---|
263 | ao%g_lw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic*g_phobic) & |
---|
264 | & / (ao%mass_ext_lw_phobic*ao%ssa_lw_phobic) |
---|
265 | |
---|
266 | if (ao%use_hydrophilic) then |
---|
267 | do jtype = 1,n_type_philic |
---|
268 | ao%mass_ext_lw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype)) |
---|
269 | ao%ssa_lw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
270 | & *ssa_philic(:,:,jtype)) & |
---|
271 | & / ao%mass_ext_lw_philic(:,:,jtype) |
---|
272 | ao%g_lw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
273 | & *ssa_philic(:,:,jtype)*g_philic(:,:,jtype)) & |
---|
274 | & / (ao%mass_ext_lw_philic(:,:,jtype)*ao%ssa_lw_philic(:,:,jtype)) |
---|
275 | end do |
---|
276 | end if |
---|
277 | end if |
---|
278 | |
---|
279 | if (allocated(ao%wavelength_mono)) then |
---|
280 | ! Monochromatic wavelengths also required |
---|
281 | do jwl = 1,nmono |
---|
282 | ! Wavelength (m) to wavenumber (cm-1) |
---|
283 | wavenumber_target = 0.01_jprb / ao%wavelength_mono(jwl) |
---|
284 | ! Find index to first interpolation point, and its weight |
---|
285 | if (wavenumber_target <= wavenumber(1)) then |
---|
286 | weight1 = 1.0_jprb |
---|
287 | iwn = 1 |
---|
288 | else if (wavenumber_target >= wavenumber(nwn)) then |
---|
289 | iwn = nwn-1 |
---|
290 | weight1 = 0.0_jprb |
---|
291 | else |
---|
292 | iwn = 1 |
---|
293 | do while (wavenumber(iwn+1) < wavenumber_target .and. iwn < nwn-1) |
---|
294 | iwn = iwn + 1 |
---|
295 | end do |
---|
296 | weight1 = (wavenumber(iwn+1)-wavenumber_target) & |
---|
297 | & / (wavenumber(iwn+1)-wavenumber(iwn)) |
---|
298 | end if |
---|
299 | ! Linear interpolation |
---|
300 | ao%mass_ext_mono_phobic(jwl,:) = weight1 * mass_ext_phobic(iwn,:) & |
---|
301 | & + (1.0_jprb - weight1)* mass_ext_phobic(iwn+1,:) |
---|
302 | ao%ssa_mono_phobic(jwl,:) = weight1 * ssa_phobic(iwn,:) & |
---|
303 | & + (1.0_jprb - weight1)* ssa_phobic(iwn+1,:) |
---|
304 | ao%g_mono_phobic(jwl,:) = weight1 * g_phobic(iwn,:) & |
---|
305 | & + (1.0_jprb - weight1)* g_phobic(iwn+1,:) |
---|
306 | ao%lidar_ratio_mono_phobic(jwl,:) = weight1 * lidar_ratio_phobic(iwn,:) & |
---|
307 | & + (1.0_jprb - weight1)* lidar_ratio_phobic(iwn+1,:) |
---|
308 | if (ao%use_hydrophilic) then |
---|
309 | ao%mass_ext_mono_philic(jwl,:,:) = weight1 * mass_ext_philic(iwn,:,:) & |
---|
310 | & + (1.0_jprb - weight1)* mass_ext_philic(iwn+1,:,:) |
---|
311 | ao%ssa_mono_philic(jwl,:,:) = weight1 * ssa_philic(iwn,:,:) & |
---|
312 | & + (1.0_jprb - weight1)* ssa_philic(iwn+1,:,:) |
---|
313 | ao%g_mono_philic(jwl,:,:) = weight1 * g_philic(iwn,:,:) & |
---|
314 | & + (1.0_jprb - weight1)* g_philic(iwn+1,:,:) |
---|
315 | ao%lidar_ratio_mono_philic(jwl,:,:) = weight1 * lidar_ratio_philic(iwn,:,:) & |
---|
316 | & + (1.0_jprb - weight1)* lidar_ratio_philic(iwn+1,:,:) |
---|
317 | end if |
---|
318 | end do |
---|
319 | end if |
---|
320 | |
---|
321 | ! Deallocate memory local to this routine |
---|
322 | deallocate(mass_ext_phobic) |
---|
323 | deallocate(ssa_phobic) |
---|
324 | deallocate(g_phobic) |
---|
325 | deallocate(lidar_ratio_phobic) |
---|
326 | if (ao%use_hydrophilic) then |
---|
327 | deallocate(mass_ext_philic) |
---|
328 | deallocate(ssa_philic) |
---|
329 | deallocate(g_philic) |
---|
330 | deallocate(lidar_ratio_philic) |
---|
331 | end if |
---|
332 | |
---|
333 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_general_aerosol_optics',1,hook_handle) |
---|
334 | |
---|
335 | end subroutine setup_general_aerosol_optics |
---|
336 | |
---|
337 | !--------------------------------------------------------------------- |
---|
338 | ! Read LMDZ file containing high spectral resolution optical properties |
---|
339 | ! and average to the spectral intervals of the current gas-optics |
---|
340 | ! scheme |
---|
341 | subroutine setup_general_aerosol_optics_lmdz(config,file_name) |
---|
342 | |
---|
343 | use parkind1, only : jprb |
---|
344 | use yomhook, only : lhook, dr_hook |
---|
345 | ! use easy_netcdf, only : netcdf_file |
---|
346 | use radiation_config, only : config_type |
---|
347 | use radiation_aerosol_optics_data, only : aerosol_optics_type |
---|
348 | use radiation_spectral_definition, only : SolarReferenceTemperature, & |
---|
349 | & TerrestrialReferenceTemperature |
---|
350 | use radiation_io, only : nulout |
---|
351 | use netcdf95, only: nf95_open, nf95_inq_grp_full_ncid, nf95_close, & |
---|
352 | nf95_inq_dimid, nf95_inq_varid, nf95_inquire_dimension, & |
---|
353 | nf95_get_var, nf95_gw_var |
---|
354 | use netcdf, only: nf90_nowrite |
---|
355 | |
---|
356 | |
---|
357 | type(config_type), intent(inout), target :: config |
---|
358 | |
---|
359 | ! ! The NetCDF file containing the aerosol optics data |
---|
360 | ! type(netcdf_file) :: file |
---|
361 | |
---|
362 | character(len=*), intent(in):: file_name |
---|
363 | ! NetCDF file containing the aerosol optics data |
---|
364 | |
---|
365 | ! Wavenumber points in NetCDF file |
---|
366 | real(jprb), allocatable :: wavenumber(:) ! cm-1 |
---|
367 | |
---|
368 | ! Hydrophilic aerosol properties |
---|
369 | real(jprb), allocatable :: mass_ext_philic(:,:,:) ! Mass-ext coefficient (m2 kg-1) |
---|
370 | real(jprb), allocatable :: ssa_philic(:,:,:) ! Single-scattering albedo |
---|
371 | real(jprb), allocatable :: g_philic(:,:,:) ! Asymmetry factor |
---|
372 | real(jprb), allocatable :: lidar_ratio_philic(:,:,:) ! Lidar ratio (sr) |
---|
373 | |
---|
374 | ! Hydrophobic aerosol properties |
---|
375 | real(jprb), allocatable :: mass_ext_phobic(:,:) ! Mass-ext coefficient (m2 kg-1) |
---|
376 | real(jprb), allocatable :: ssa_phobic(:,:) ! Single-scattering albedo |
---|
377 | real(jprb), allocatable :: g_phobic(:,:) ! Asymmetry factor |
---|
378 | real(jprb), allocatable :: lidar_ratio_phobic(:,:) ! Lidar ratio (sr) |
---|
379 | |
---|
380 | ! Mapping matrix between optical properties at the wavenumbers in |
---|
381 | ! the file, and spectral intervals used by the gas-optics scheme |
---|
382 | real(jprb), allocatable :: mapping(:,:) |
---|
383 | |
---|
384 | ! Pointer to the aerosol optics coefficients for brevity of access |
---|
385 | type(aerosol_optics_type), pointer :: ao |
---|
386 | |
---|
387 | ! Target monochromatic wavenumber for interpolation (cm-1) |
---|
388 | real(jprb) :: wavenumber_target |
---|
389 | |
---|
390 | ! Number of spectral points describing aerosol properties in the |
---|
391 | ! shortwave and longwave |
---|
392 | integer :: nspecsw, nspeclw |
---|
393 | |
---|
394 | ! Number of monochromatic wavelengths required |
---|
395 | integer :: nmono |
---|
396 | |
---|
397 | integer :: n_type_philic, n_type_phobic, nrh, nwn |
---|
398 | integer :: jtype, jwl, iwn |
---|
399 | |
---|
400 | ! Weight of first point in interpolation |
---|
401 | real(jprb) :: weight1 |
---|
402 | |
---|
403 | real(jprb) :: hook_handle |
---|
404 | |
---|
405 | ! Local: |
---|
406 | integer ncid, grpid, dimid, varid |
---|
407 | |
---|
408 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_general_aerosol_optics',0,hook_handle) |
---|
409 | |
---|
410 | ao => config%aerosol_optics |
---|
411 | |
---|
412 | ao%use_hydrophilic = .true. |
---|
413 | ao%use_monochromatic = .true. |
---|
414 | print*,'file_name= ',file_name |
---|
415 | call nf95_open(file_name, nf90_nowrite, ncid) |
---|
416 | call nf95_inq_grp_full_ncid(ncid, "Hydrophilic", grpid) |
---|
417 | call nf95_inq_dimid(grpid, "hur", dimid) |
---|
418 | call nf95_inquire_dimension(grpid, dimid, nclen = ao%nrh) |
---|
419 | ! allocate(ao%rh_lower(ao%nrh)) |
---|
420 | call nf95_inq_varid(grpid, "hur_bounds", varid) |
---|
421 | call nf95_get_var(grpid, varid, ao%rh_lower, count_nc = [1, ao%nrh]) |
---|
422 | |
---|
423 | ! Hydrophilic/LW_bands: |
---|
424 | call nf95_inq_grp_full_ncid(ncid, "Hydrophilic/LW_bands", grpid) |
---|
425 | call nf95_inq_varid(grpid, "asymmetry", varid) |
---|
426 | call nf95_gw_var(grpid, varid, ao%g_lw_philic) |
---|
427 | call nf95_inq_varid(grpid, "single_scat_alb", varid) |
---|
428 | call nf95_gw_var(grpid, varid, ao%ssa_lw_philic) |
---|
429 | call nf95_inq_varid(grpid, "mass_ext", varid) |
---|
430 | call nf95_gw_var(grpid, varid, ao%mass_ext_lw_philic) |
---|
431 | |
---|
432 | ! Hydrophilic/SW_bands: |
---|
433 | call nf95_inq_grp_full_ncid(ncid, "Hydrophilic/SW_bands", grpid) |
---|
434 | call nf95_inq_varid(grpid, "asymmetry", varid) |
---|
435 | call nf95_gw_var(grpid, varid, ao%g_sw_philic) |
---|
436 | ao%g_sw_philic = cshift(ao%g_sw_philic, 1) |
---|
437 | call nf95_inq_varid(grpid, "single_scat_alb", varid) |
---|
438 | call nf95_gw_var(grpid, varid, ao%ssa_sw_philic) |
---|
439 | ao%g_sw_philic = cshift(ao%ssa_sw_philic, 1) |
---|
440 | call nf95_inq_varid(grpid, "mass_ext", varid) |
---|
441 | call nf95_gw_var(grpid, varid, ao%mass_ext_sw_philic) |
---|
442 | ao%g_sw_philic = cshift(ao%mass_ext_sw_philic, 1) |
---|
443 | |
---|
444 | ! Hydrophilic/Monochromatic: |
---|
445 | call nf95_inq_grp_full_ncid(ncid, "Hydrophilic/Monochromatic", grpid) |
---|
446 | call nf95_inq_varid(grpid, "mass_ext", varid) |
---|
447 | call nf95_gw_var(grpid, varid, ao%mass_ext_mono_philic) |
---|
448 | |
---|
449 | ! Hydrophobic/LW_bands: |
---|
450 | call nf95_inq_grp_full_ncid(ncid, "Hydrophobic/LW_bands", grpid) |
---|
451 | call nf95_inq_varid(grpid, "asymmetry", varid) |
---|
452 | call nf95_gw_var(grpid, varid, ao%g_lw_phobic) |
---|
453 | call nf95_inq_varid(grpid, "single_scat_alb", varid) |
---|
454 | call nf95_gw_var(grpid, varid, ao%ssa_lw_phobic) |
---|
455 | call nf95_inq_varid(grpid, "mass_ext", varid) |
---|
456 | call nf95_gw_var(grpid, varid, ao%mass_ext_lw_phobic) |
---|
457 | |
---|
458 | ! Hydrophobic/SW_bands: |
---|
459 | call nf95_inq_grp_full_ncid(ncid, "Hydrophobic/SW_bands", grpid) |
---|
460 | call nf95_inq_varid(grpid, "asymmetry", varid) |
---|
461 | call nf95_gw_var(grpid, varid, ao%g_sw_phobic) |
---|
462 | ao%g_sw_phobic = cshift(ao%g_sw_phobic, 1) |
---|
463 | call nf95_inq_varid(grpid, "single_scat_alb", varid) |
---|
464 | call nf95_gw_var(grpid, varid, ao%ssa_sw_phobic) |
---|
465 | ao%g_sw_phobic = cshift(ao%ssa_sw_phobic, 1) |
---|
466 | call nf95_inq_varid(grpid, "mass_ext", varid) |
---|
467 | call nf95_gw_var(grpid, varid, ao%mass_ext_sw_phobic) |
---|
468 | ao%g_sw_phobic = cshift(ao%mass_ext_sw_phobic, 1) |
---|
469 | ! AI ATTENTION |
---|
470 | call nf95_inq_varid(grpid, "wavenumber", varid) |
---|
471 | call nf95_gw_var(grpid, varid, wavenumber) |
---|
472 | |
---|
473 | ! Hydrophobic/Monochromatic: |
---|
474 | call nf95_inq_grp_full_ncid(ncid, "Hydrophobic/Monochromatic", grpid) |
---|
475 | call nf95_inq_varid(grpid, "mass_ext", varid) |
---|
476 | call nf95_gw_var(grpid, varid, ao%mass_ext_mono_phobic) |
---|
477 | |
---|
478 | ! call file%get('wavenumber', wavenumber) |
---|
479 | ! nwn = size(wavenumber) |
---|
480 | |
---|
481 | ! call file%get_global_attribute('description_hydrophobic', & |
---|
482 | ! & ao%description_phobic_str) |
---|
483 | |
---|
484 | |
---|
485 | ! call file%get('relative_humidity1', ao%rh_lower) |
---|
486 | |
---|
487 | ! call file%get_global_attribute('description_hydrophilic', & |
---|
488 | ! & ao%description_philic_str) |
---|
489 | |
---|
490 | ! Close aerosol scattering file |
---|
491 | ! call file%close() |
---|
492 | |
---|
493 | call nf95_close(ncid) |
---|
494 | |
---|
495 | ! Get array sizes |
---|
496 | ! ao%n_bands_lw = size(ao%mass_ext_lw_phobic, 1) |
---|
497 | ! ao%n_bands_sw = size(ao%mass_ext_sw_phobic, 1) |
---|
498 | ! ao%n_mono_wl = size(ao%mass_ext_mono_phobic, 1) |
---|
499 | ! ao%n_type_phobic = size(ao%mass_ext_lw_phobic, 2) |
---|
500 | ! ao%n_type_philic = size(ao%mass_ext_lw_philic, 3) |
---|
501 | |
---|
502 | ! Allocate memory for mapping arrays |
---|
503 | ! ao%ntype = ao%n_type_phobic + ao%n_type_philic |
---|
504 | ! allocate(ao%iclass(ao%ntype)) |
---|
505 | ! allocate(ao%itype(ao%ntype)) |
---|
506 | |
---|
507 | ! ao%iclass = IAerosolClassUndefined |
---|
508 | ! ao%itype = 0 |
---|
509 | |
---|
510 | n_type_phobic = size(mass_ext_phobic, 2) |
---|
511 | if (ao%use_hydrophilic) then |
---|
512 | n_type_philic = size(mass_ext_philic, 3) |
---|
513 | nrh = size(ao%rh_lower) |
---|
514 | else |
---|
515 | n_type_philic = 0 |
---|
516 | nrh = 0 |
---|
517 | end if |
---|
518 | |
---|
519 | if (config%do_cloud_aerosol_per_sw_g_point) then |
---|
520 | nspecsw = config%gas_optics_sw%spectral_def%ng |
---|
521 | else |
---|
522 | nspecsw = config%gas_optics_sw%spectral_def%nband |
---|
523 | end if |
---|
524 | |
---|
525 | if (config%do_cloud_aerosol_per_lw_g_point) then |
---|
526 | nspeclw = config%gas_optics_lw%spectral_def%ng |
---|
527 | else |
---|
528 | nspeclw = config%gas_optics_lw%spectral_def%nband |
---|
529 | end if |
---|
530 | |
---|
531 | if (allocated(ao%wavelength_mono)) then |
---|
532 | ! Monochromatic wavelengths also required |
---|
533 | nmono = size(ao%wavelength_mono) |
---|
534 | else |
---|
535 | nmono = 0 |
---|
536 | end if |
---|
537 | |
---|
538 | call ao%allocate(n_type_phobic, n_type_philic, nrh, nspeclw, nspecsw, nmono) |
---|
539 | |
---|
540 | if (config%do_sw) then |
---|
541 | call config%gas_optics_sw%spectral_def%calc_mapping(SolarReferenceTemperature, & |
---|
542 | & wavenumber, mapping, use_bands=(.not. config%do_cloud_aerosol_per_sw_g_point)) |
---|
543 | |
---|
544 | ao%mass_ext_sw_phobic = matmul(mapping, mass_ext_phobic) |
---|
545 | ao%ssa_sw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic) & |
---|
546 | & / ao%mass_ext_sw_phobic |
---|
547 | ao%g_sw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic*g_phobic) & |
---|
548 | & / (ao%mass_ext_sw_phobic*ao%ssa_sw_phobic) |
---|
549 | |
---|
550 | if (ao%use_hydrophilic) then |
---|
551 | do jtype = 1,n_type_philic |
---|
552 | ao%mass_ext_sw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype)) |
---|
553 | ao%ssa_sw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
554 | & *ssa_philic(:,:,jtype)) & |
---|
555 | & / ao%mass_ext_sw_philic(:,:,jtype) |
---|
556 | ao%g_sw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
557 | & *ssa_philic(:,:,jtype)*g_philic(:,:,jtype)) & |
---|
558 | & / (ao%mass_ext_sw_philic(:,:,jtype)*ao%ssa_sw_philic(:,:,jtype)) |
---|
559 | end do |
---|
560 | end if |
---|
561 | end if |
---|
562 | if (config%do_lw) then |
---|
563 | call config%gas_optics_lw%spectral_def%calc_mapping(TerrestrialReferenceTemperature, & |
---|
564 | & wavenumber, mapping, use_bands=(.not. config%do_cloud_aerosol_per_lw_g_point)) |
---|
565 | |
---|
566 | ao%mass_ext_lw_phobic = matmul(mapping, mass_ext_phobic) |
---|
567 | ao%ssa_lw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic) & |
---|
568 | & / ao%mass_ext_lw_phobic |
---|
569 | ao%g_lw_phobic = matmul(mapping, mass_ext_phobic*ssa_phobic*g_phobic) & |
---|
570 | & / (ao%mass_ext_lw_phobic*ao%ssa_lw_phobic) |
---|
571 | |
---|
572 | if (ao%use_hydrophilic) then |
---|
573 | do jtype = 1,n_type_philic |
---|
574 | ao%mass_ext_lw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype)) |
---|
575 | ao%ssa_lw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
576 | & *ssa_philic(:,:,jtype)) & |
---|
577 | & / ao%mass_ext_lw_philic(:,:,jtype) |
---|
578 | ao%g_lw_philic(:,:,jtype) = matmul(mapping, mass_ext_philic(:,:,jtype) & |
---|
579 | & *ssa_philic(:,:,jtype)*g_philic(:,:,jtype)) & |
---|
580 | & / (ao%mass_ext_lw_philic(:,:,jtype)*ao%ssa_lw_philic(:,:,jtype)) |
---|
581 | end do |
---|
582 | end if |
---|
583 | end if |
---|
584 | |
---|
585 | if (allocated(ao%wavelength_mono)) then |
---|
586 | ! Monochromatic wavelengths also required |
---|
587 | do jwl = 1,nmono |
---|
588 | ! Wavelength (m) to wavenumber (cm-1) |
---|
589 | wavenumber_target = 0.01_jprb / ao%wavelength_mono(jwl) |
---|
590 | ! Find index to first interpolation point, and its weight |
---|
591 | if (wavenumber_target <= wavenumber(1)) then |
---|
592 | weight1 = 1.0_jprb |
---|
593 | iwn = 1 |
---|
594 | else if (wavenumber_target >= wavenumber(nwn)) then |
---|
595 | iwn = nwn-1 |
---|
596 | weight1 = 0.0_jprb |
---|
597 | else |
---|
598 | iwn = 1 |
---|
599 | do while (wavenumber(iwn+1) < wavenumber_target .and. iwn < nwn-1) |
---|
600 | iwn = iwn + 1 |
---|
601 | end do |
---|
602 | weight1 = (wavenumber(iwn+1)-wavenumber_target) & |
---|
603 | & / (wavenumber(iwn+1)-wavenumber(iwn)) |
---|
604 | end if |
---|
605 | ! Linear interpolation |
---|
606 | ao%mass_ext_mono_phobic(jwl,:) = weight1 * mass_ext_phobic(iwn,:) & |
---|
607 | & + (1.0_jprb - weight1)* mass_ext_phobic(iwn+1,:) |
---|
608 | ao%ssa_mono_phobic(jwl,:) = weight1 * ssa_phobic(iwn,:) & |
---|
609 | & + (1.0_jprb - weight1)* ssa_phobic(iwn+1,:) |
---|
610 | ao%g_mono_phobic(jwl,:) = weight1 * g_phobic(iwn,:) & |
---|
611 | & + (1.0_jprb - weight1)* g_phobic(iwn+1,:) |
---|
612 | ao%lidar_ratio_mono_phobic(jwl,:) = weight1 * lidar_ratio_phobic(iwn,:) & |
---|
613 | & + (1.0_jprb - weight1)* lidar_ratio_phobic(iwn+1,:) |
---|
614 | if (ao%use_hydrophilic) then |
---|
615 | ao%mass_ext_mono_philic(jwl,:,:) = weight1 * mass_ext_philic(iwn,:,:) & |
---|
616 | & + (1.0_jprb - weight1)* mass_ext_philic(iwn+1,:,:) |
---|
617 | ao%ssa_mono_philic(jwl,:,:) = weight1 * ssa_philic(iwn,:,:) & |
---|
618 | & + (1.0_jprb - weight1)* ssa_philic(iwn+1,:,:) |
---|
619 | ao%g_mono_philic(jwl,:,:) = weight1 * g_philic(iwn,:,:) & |
---|
620 | & + (1.0_jprb - weight1)* g_philic(iwn+1,:,:) |
---|
621 | ao%lidar_ratio_mono_philic(jwl,:,:) = weight1 * lidar_ratio_philic(iwn,:,:) & |
---|
622 | & + (1.0_jprb - weight1)* lidar_ratio_philic(iwn+1,:,:) |
---|
623 | end if |
---|
624 | end do |
---|
625 | end if |
---|
626 | |
---|
627 | ! Deallocate memory local to this routine |
---|
628 | deallocate(mass_ext_phobic) |
---|
629 | deallocate(ssa_phobic) |
---|
630 | deallocate(g_phobic) |
---|
631 | deallocate(lidar_ratio_phobic) |
---|
632 | if (ao%use_hydrophilic) then |
---|
633 | deallocate(mass_ext_philic) |
---|
634 | deallocate(ssa_philic) |
---|
635 | deallocate(g_philic) |
---|
636 | deallocate(lidar_ratio_philic) |
---|
637 | end if |
---|
638 | |
---|
639 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_general_aerosol_optics',1,hook_handle) |
---|
640 | |
---|
641 | end subroutine setup_general_aerosol_optics_lmdz |
---|
642 | |
---|
643 | |
---|
644 | !--------------------------------------------------------------------- |
---|
645 | ! Read file containing legacy-style band-wise aerosol optical |
---|
646 | ! properties and average to the spectral intervals of the current |
---|
647 | ! gas-optics scheme |
---|
648 | subroutine setup_general_aerosol_optics_legacy(config, file_name) |
---|
649 | |
---|
650 | use parkind1, only : jprb |
---|
651 | use yomhook, only : lhook, dr_hook |
---|
652 | use easy_netcdf, only : netcdf_file |
---|
653 | use radiation_config, only : config_type |
---|
654 | use radiation_aerosol_optics_data, only : aerosol_optics_type |
---|
655 | use radiation_spectral_definition, only : SolarReferenceTemperature, & |
---|
656 | & TerrestrialReferenceTemperature |
---|
657 | |
---|
658 | type(config_type), intent(inout), target :: config |
---|
659 | |
---|
660 | ! The NetCDF file containing the aerosol optics data |
---|
661 | character(len=*), intent(in) :: file_name |
---|
662 | |
---|
663 | ! Mapping matrix between optical properties at the wavenumbers in |
---|
664 | ! the file, and spectral intervals used by the gas-optics scheme |
---|
665 | real(jprb), allocatable :: mapping(:,:), mapping_transp(:,:) |
---|
666 | |
---|
667 | ! Pointer to the aerosol optics coefficients for brevity of access |
---|
668 | type(aerosol_optics_type), pointer :: ao |
---|
669 | |
---|
670 | ! Local copy of aerosol optical properties in the spectral |
---|
671 | ! intervals of the file, which is deallocated when it goes out of |
---|
672 | ! scope |
---|
673 | type(aerosol_optics_type) :: ao_legacy |
---|
674 | |
---|
675 | integer :: jtype |
---|
676 | |
---|
677 | real(jprb) :: hook_handle |
---|
678 | |
---|
679 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_general_aerosol_optics_legacy',0,hook_handle) |
---|
680 | ao => config%aerosol_optics |
---|
681 | |
---|
682 | ! Load file into a local structure |
---|
683 | call ao_legacy%setup(file_name, iverbose=config%iverbosesetup) |
---|
684 | |
---|
685 | ! Copy over scalars and coordinate variables |
---|
686 | call ao%allocate(ao_legacy%n_type_phobic, ao_legacy%n_type_philic, ao_legacy%nrh, & |
---|
687 | & config%n_bands_lw, config%n_bands_sw, ao_legacy%n_mono_wl) |
---|
688 | ao%description_phobic_str = ao_legacy%description_phobic_str |
---|
689 | ao%description_philic_str = ao_legacy%description_philic_str |
---|
690 | ao%rh_lower = ao_legacy%rh_lower |
---|
691 | |
---|
692 | ! use_hydrophilic = ao_legacy%use_hydrophilic |
---|
693 | ! ao%iclass = ao_legacy%iclass |
---|
694 | ! ao%itype = ao_legacy%itype |
---|
695 | ! ao%ntype = ao_legacy%ntype |
---|
696 | ! ao%n_type_phobic = ao_legacy%n_type_phobic |
---|
697 | ! ao%n_type_philic = ao_legacy%n_type_philic |
---|
698 | ! ao%n_mono_wl = ao_legacy%n_mono_wl |
---|
699 | ! ao%use_monochromatic = ao_legacy%use_monochromatic |
---|
700 | |
---|
701 | if (config%do_sw) then |
---|
702 | call config%gas_optics_sw%spectral_def%calc_mapping_from_wavenumber_bands(SolarReferenceTemperature, & |
---|
703 | & ao_legacy%wavenumber1_sw, ao_legacy%wavenumber2_sw, mapping_transp, & |
---|
704 | & use_bands=(.not. config%do_cloud_aerosol_per_sw_g_point)) |
---|
705 | if (allocated(mapping)) then |
---|
706 | deallocate(mapping) |
---|
707 | end if |
---|
708 | allocate(mapping(config%n_bands_sw,ao_legacy%n_bands_sw)) |
---|
709 | mapping = transpose(mapping_transp) |
---|
710 | ao%mass_ext_sw_phobic = matmul(mapping, ao_legacy%mass_ext_sw_phobic) |
---|
711 | ao%ssa_sw_phobic = matmul(mapping, ao_legacy%mass_ext_sw_phobic*ao_legacy%ssa_sw_phobic) & |
---|
712 | & / ao%mass_ext_sw_phobic |
---|
713 | ao%g_sw_phobic = matmul(mapping, ao_legacy%mass_ext_sw_phobic*ao_legacy%ssa_sw_phobic & |
---|
714 | & *ao_legacy%g_sw_phobic) & |
---|
715 | & / (ao%mass_ext_sw_phobic*ao%ssa_sw_phobic) |
---|
716 | |
---|
717 | if (ao%use_hydrophilic) then |
---|
718 | do jtype = 1,ao%n_type_philic |
---|
719 | ao%mass_ext_sw_philic(:,:,jtype) = matmul(mapping, ao_legacy%mass_ext_sw_philic(:,:,jtype)) |
---|
720 | ao%ssa_sw_philic(:,:,jtype) = matmul(mapping, ao_legacy%mass_ext_sw_philic(:,:,jtype) & |
---|
721 | & *ao_legacy%ssa_sw_philic(:,:,jtype)) & |
---|
722 | & / ao%mass_ext_sw_philic(:,:,jtype) |
---|
723 | ao%g_sw_philic(:,:,jtype) = matmul(mapping, ao_legacy%mass_ext_sw_philic(:,:,jtype) & |
---|
724 | & *ao_legacy%ssa_sw_philic(:,:,jtype)*ao_legacy%g_sw_philic(:,:,jtype)) & |
---|
725 | & / (ao%mass_ext_sw_philic(:,:,jtype)*ao%ssa_sw_philic(:,:,jtype)) |
---|
726 | end do |
---|
727 | end if |
---|
728 | end if |
---|
729 | |
---|
730 | if (config%do_lw) then |
---|
731 | if (allocated(mapping_transp)) then |
---|
732 | deallocate(mapping_transp) |
---|
733 | end if |
---|
734 | call config%gas_optics_lw%spectral_def%calc_mapping_from_wavenumber_bands(TerrestrialReferenceTemperature, & |
---|
735 | & ao_legacy%wavenumber1_lw, ao_legacy%wavenumber2_lw, mapping_transp, & |
---|
736 | & use_bands=(.not. config%do_cloud_aerosol_per_lw_g_point)) |
---|
737 | if (allocated(mapping)) then |
---|
738 | deallocate(mapping) |
---|
739 | end if |
---|
740 | allocate(mapping(config%n_bands_lw,ao_legacy%n_bands_lw)) |
---|
741 | mapping = transpose(mapping_transp) |
---|
742 | ao%mass_ext_lw_phobic = matmul(mapping, ao_legacy%mass_ext_lw_phobic) |
---|
743 | ao%ssa_lw_phobic = matmul(mapping, ao_legacy%mass_ext_lw_phobic*ao_legacy%ssa_lw_phobic) & |
---|
744 | & / ao%mass_ext_lw_phobic |
---|
745 | ao%g_lw_phobic = matmul(mapping, ao_legacy%mass_ext_lw_phobic*ao_legacy%ssa_lw_phobic & |
---|
746 | & *ao_legacy%g_lw_phobic) & |
---|
747 | & / (ao%mass_ext_lw_phobic*ao%ssa_lw_phobic) |
---|
748 | |
---|
749 | if (ao%use_hydrophilic) then |
---|
750 | do jtype = 1,ao%n_type_philic |
---|
751 | ao%mass_ext_lw_philic(:,:,jtype) = matmul(mapping, ao_legacy%mass_ext_lw_philic(:,:,jtype)) |
---|
752 | ao%ssa_lw_philic(:,:,jtype) = matmul(mapping, ao_legacy%mass_ext_lw_philic(:,:,jtype) & |
---|
753 | & *ao_legacy%ssa_lw_philic(:,:,jtype)) & |
---|
754 | & / ao%mass_ext_lw_philic(:,:,jtype) |
---|
755 | ao%g_lw_philic(:,:,jtype) = matmul(mapping, ao_legacy%mass_ext_lw_philic(:,:,jtype) & |
---|
756 | & *ao_legacy%ssa_lw_philic(:,:,jtype)*ao_legacy%g_lw_philic(:,:,jtype)) & |
---|
757 | & / (ao%mass_ext_lw_philic(:,:,jtype)*ao%ssa_lw_philic(:,:,jtype)) |
---|
758 | end do |
---|
759 | end if |
---|
760 | end if |
---|
761 | |
---|
762 | if (allocated(ao_legacy%wavelength_mono)) then |
---|
763 | ao%wavelength_mono = ao_legacy%wavelength_mono |
---|
764 | ao%mass_ext_mono_phobic = ao_legacy%mass_ext_mono_phobic |
---|
765 | ao%ssa_mono_phobic = ao_legacy%ssa_mono_phobic |
---|
766 | ao%g_mono_phobic = ao_legacy%g_mono_phobic |
---|
767 | ao%lidar_ratio_mono_phobic = ao_legacy%lidar_ratio_mono_phobic |
---|
768 | if (ao%use_hydrophilic) then |
---|
769 | ao%mass_ext_mono_philic = ao_legacy%mass_ext_mono_philic |
---|
770 | ao%ssa_mono_philic = ao_legacy%ssa_mono_philic |
---|
771 | ao%g_mono_philic = ao_legacy%g_mono_philic |
---|
772 | ao%lidar_ratio_mono_philic = ao_legacy%lidar_ratio_mono_philic |
---|
773 | end if |
---|
774 | end if |
---|
775 | |
---|
776 | if (lhook) call dr_hook('radiation_aerosol_optics:setup_general_aerosol_optics_legacy',1,hook_handle) |
---|
777 | |
---|
778 | end subroutine setup_general_aerosol_optics_legacy |
---|
779 | |
---|
780 | |
---|
781 | !--------------------------------------------------------------------- |
---|
782 | ! Compute aerosol optical properties and add to existing gas optical |
---|
783 | ! depth and scattering properties |
---|
784 | subroutine add_aerosol_optics(nlev,istartcol,iendcol, & |
---|
785 | & config, thermodynamics, gas, aerosol, & |
---|
786 | & od_lw, ssa_lw, g_lw, od_sw, ssa_sw, g_sw) |
---|
787 | |
---|
788 | use parkind1, only : jprb |
---|
789 | use radiation_io, only : nulout, nulerr, radiation_abort |
---|
790 | use yomhook, only : lhook, dr_hook |
---|
791 | use radiation_config, only : config_type |
---|
792 | use radiation_thermodynamics, only : thermodynamics_type |
---|
793 | use radiation_gas, only : gas_type, IH2O, IMassMixingRatio |
---|
794 | use radiation_aerosol, only : aerosol_type |
---|
795 | use radiation_constants, only : AccelDueToGravity |
---|
796 | use radiation_aerosol_optics_data, only : aerosol_optics_type, & |
---|
797 | & IAerosolClassUndefined, IAerosolClassIgnored, & |
---|
798 | & IAerosolClassHydrophobic, IAerosolClassHydrophilic |
---|
799 | |
---|
800 | integer, intent(in) :: nlev ! number of model levels |
---|
801 | integer, intent(in) :: istartcol, iendcol ! range of columns to process |
---|
802 | type(config_type), intent(in), target :: config |
---|
803 | type(thermodynamics_type),intent(in) :: thermodynamics |
---|
804 | type(gas_type), intent(in) :: gas |
---|
805 | type(aerosol_type), intent(in) :: aerosol |
---|
806 | ! Optical depth, single scattering albedo and asymmetry factor of |
---|
807 | ! the atmosphere (gases on input, gases and aerosols on output) |
---|
808 | ! for each g point. Note that longwave ssa and asymmetry and |
---|
809 | ! shortwave asymmetry are all zero for gases, so are not yet |
---|
810 | ! defined on input and are therefore intent(out). |
---|
811 | real(jprb), dimension(config%n_g_lw,nlev,istartcol:iendcol), & |
---|
812 | & intent(inout) :: od_lw |
---|
813 | real(jprb), dimension(config%n_g_lw_if_scattering,nlev,istartcol:iendcol), & |
---|
814 | & intent(out) :: ssa_lw, g_lw |
---|
815 | real(jprb), dimension(config%n_g_sw,nlev,istartcol:iendcol), & |
---|
816 | & intent(inout) :: od_sw, ssa_sw |
---|
817 | real(jprb), dimension(config%n_g_sw,nlev,istartcol:iendcol), & |
---|
818 | & intent(out) :: g_sw |
---|
819 | |
---|
820 | ! Extinction optical depth, scattering optical depth and |
---|
821 | ! asymmetry-times-scattering-optical-depth for all the aerosols at |
---|
822 | ! a point in space for each spectral band of the shortwave and |
---|
823 | ! longwave spectrum |
---|
824 | real(jprb), dimension(config%n_bands_sw) & |
---|
825 | & :: od_sw_aerosol, scat_sw_aerosol, scat_g_sw_aerosol, local_od_sw |
---|
826 | real(jprb), dimension(config%n_bands_lw) :: od_lw_aerosol, local_od_lw |
---|
827 | real(jprb), dimension(config%n_bands_lw_if_scattering) & |
---|
828 | & :: scat_lw_aerosol, scat_g_lw_aerosol |
---|
829 | |
---|
830 | real(jprb) :: h2o_mmr(istartcol:iendcol,nlev) |
---|
831 | |
---|
832 | real(jprb) :: rh ! Relative humidity with respect to liquid water |
---|
833 | |
---|
834 | ! Factor (kg m-2) to convert mixing ratio (kg kg-1) to mass in |
---|
835 | ! path (kg m-2) |
---|
836 | real(jprb) :: factor |
---|
837 | |
---|
838 | ! Temporary extinction and scattering optical depths of aerosol |
---|
839 | ! plus gas |
---|
840 | real(jprb) :: local_od, local_scat |
---|
841 | |
---|
842 | ! Loop indices for column, level, g point, band and aerosol type |
---|
843 | integer :: jcol, jlev, jg, jtype, jband |
---|
844 | |
---|
845 | ! Range of levels over which aerosols are present |
---|
846 | integer :: istartlev, iendlev |
---|
847 | |
---|
848 | ! Indices to spectral band and relative humidity look-up table |
---|
849 | integer :: iband, irh |
---|
850 | |
---|
851 | ! Short cut for ao%itype(jtype) |
---|
852 | integer :: itype |
---|
853 | |
---|
854 | ! Pointer to the aerosol optics coefficients for brevity of access |
---|
855 | type(aerosol_optics_type), pointer :: ao |
---|
856 | |
---|
857 | real(jprb) :: hook_handle |
---|
858 | |
---|
859 | if (lhook) call dr_hook('radiation_aerosol_optics:add_aerosol_optics',0,hook_handle) |
---|
860 | |
---|
861 | if (aerosol%is_direct) then |
---|
862 | ! Aerosol optical properties have been provided in each band |
---|
863 | ! directly by the user |
---|
864 | call add_aerosol_optics_direct(nlev,istartcol,iendcol, & |
---|
865 | & config, aerosol, & |
---|
866 | & od_lw, ssa_lw, g_lw, od_sw, ssa_sw, g_sw) |
---|
867 | else |
---|
868 | ! Aerosol mixing ratios have been provided |
---|
869 | |
---|
870 | do jtype = 1,config%n_aerosol_types |
---|
871 | if (config%aerosol_optics%iclass(jtype) == IAerosolClassUndefined) then |
---|
872 | write(nulerr,'(a)') '*** Error: not all aerosol types are defined' |
---|
873 | call radiation_abort() |
---|
874 | end if |
---|
875 | end do |
---|
876 | |
---|
877 | if (config%iverbose >= 2) then |
---|
878 | write(nulout,'(a)') 'Computing aerosol absorption/scattering properties' |
---|
879 | end if |
---|
880 | |
---|
881 | ao => config%aerosol_optics |
---|
882 | |
---|
883 | istartlev = lbound(aerosol%mixing_ratio,2) |
---|
884 | iendlev = ubound(aerosol%mixing_ratio,2) |
---|
885 | |
---|
886 | if (ubound(aerosol%mixing_ratio,3) /= config%n_aerosol_types) then |
---|
887 | write(nulerr,'(a,i0,a,i0)') '*** Error: aerosol%mixing_ratio contains ', & |
---|
888 | & ubound(aerosol%mixing_ratio,3), ' aerosol types, expected ', & |
---|
889 | & config%n_aerosol_types |
---|
890 | call radiation_abort() |
---|
891 | end if |
---|
892 | |
---|
893 | ! Set variables to zero that may not have been previously |
---|
894 | g_sw(:,:,istartcol:iendcol) = 0.0_jprb |
---|
895 | if (config%do_lw_aerosol_scattering) then |
---|
896 | ssa_lw(:,:,istartcol:iendcol) = 0.0_jprb |
---|
897 | g_lw(:,:,istartcol:iendcol) = 0.0_jprb |
---|
898 | end if |
---|
899 | |
---|
900 | call gas%get(IH2O, IMassMixingRatio, h2o_mmr, istartcol=istartcol) |
---|
901 | |
---|
902 | ! Loop over position |
---|
903 | do jlev = istartlev,iendlev |
---|
904 | do jcol = istartcol,iendcol |
---|
905 | ! Compute relative humidity with respect to liquid |
---|
906 | ! saturation and the index to the relative-humidity index of |
---|
907 | ! hydrophilic-aerosol data |
---|
908 | rh = h2o_mmr(jcol,jlev) / thermodynamics%h2o_sat_liq(jcol,jlev) |
---|
909 | irh = ao%calc_rh_index(rh) |
---|
910 | |
---|
911 | factor = ( thermodynamics%pressure_hl(jcol,jlev+1) & |
---|
912 | & -thermodynamics%pressure_hl(jcol,jlev ) ) & |
---|
913 | & / AccelDueToGravity |
---|
914 | |
---|
915 | ! Reset temporary arrays |
---|
916 | od_sw_aerosol = 0.0_jprb |
---|
917 | scat_sw_aerosol = 0.0_jprb |
---|
918 | scat_g_sw_aerosol = 0.0_jprb |
---|
919 | od_lw_aerosol = 0.0_jprb |
---|
920 | scat_lw_aerosol = 0.0_jprb |
---|
921 | scat_g_lw_aerosol = 0.0_jprb |
---|
922 | |
---|
923 | do jtype = 1,config%n_aerosol_types |
---|
924 | |
---|
925 | itype = ao%itype(jtype) |
---|
926 | |
---|
927 | ! Add the optical depth, scattering optical depth and |
---|
928 | ! scattering optical depth-weighted asymmetry factor for |
---|
929 | ! this aerosol type to the total for all aerosols. Note |
---|
930 | ! that the following expressions are array-wise, the |
---|
931 | ! dimension being spectral band. |
---|
932 | if (ao%iclass(jtype) == IAerosolClassHydrophobic) then |
---|
933 | do jband = 1,config%n_bands_sw |
---|
934 | local_od_sw(jband) = factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
935 | & * ao%mass_ext_sw_phobic(jband,itype) |
---|
936 | od_sw_aerosol(jband) = od_sw_aerosol(jband) + local_od_sw(jband) |
---|
937 | scat_sw_aerosol(jband) = scat_sw_aerosol(jband) & |
---|
938 | & + local_od_sw(jband) * ao%ssa_sw_phobic(jband,itype) |
---|
939 | scat_g_sw_aerosol(jband) = scat_g_sw_aerosol(jband) & |
---|
940 | & + local_od_sw(jband) * ao%ssa_sw_phobic(jband,itype) & |
---|
941 | & * ao%g_sw_phobic(jband,itype) |
---|
942 | end do |
---|
943 | if (config%do_lw_aerosol_scattering) then |
---|
944 | local_od_lw = factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
945 | & * ao%mass_ext_lw_phobic(:,itype) |
---|
946 | od_lw_aerosol = od_lw_aerosol + local_od_lw |
---|
947 | scat_lw_aerosol = scat_lw_aerosol & |
---|
948 | & + local_od_lw * ao%ssa_lw_phobic(:,itype) |
---|
949 | scat_g_lw_aerosol = scat_g_lw_aerosol & |
---|
950 | & + local_od_lw * ao%ssa_lw_phobic(:,itype) & |
---|
951 | & * ao%g_lw_phobic(:,itype) |
---|
952 | else |
---|
953 | ! If aerosol longwave scattering is not included then we |
---|
954 | ! weight the optical depth by the single scattering |
---|
955 | ! co-albedo |
---|
956 | od_lw_aerosol = od_lw_aerosol & |
---|
957 | & + factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
958 | & * ao%mass_ext_lw_phobic(:,itype) & |
---|
959 | & * (1.0_jprb - ao%ssa_lw_phobic(:,itype)) |
---|
960 | end if |
---|
961 | else if (ao%iclass(jtype) == IAerosolClassHydrophilic) then |
---|
962 | ! Hydrophilic aerosols require the look-up tables to |
---|
963 | ! be indexed with irh |
---|
964 | do jband = 1,config%n_bands_sw |
---|
965 | local_od_sw(jband) = factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
966 | & * ao%mass_ext_sw_philic(jband,irh,itype) |
---|
967 | od_sw_aerosol(jband) = od_sw_aerosol(jband) + local_od_sw(jband) |
---|
968 | scat_sw_aerosol(jband) = scat_sw_aerosol(jband) & |
---|
969 | & + local_od_sw(jband) * ao%ssa_sw_philic(jband,irh,itype) |
---|
970 | scat_g_sw_aerosol(jband) = scat_g_sw_aerosol(jband) & |
---|
971 | & + local_od_sw(jband) * ao%ssa_sw_philic(jband,irh,itype) & |
---|
972 | & * ao%g_sw_philic(jband,irh,itype) |
---|
973 | end do |
---|
974 | if (config%do_lw_aerosol_scattering) then |
---|
975 | local_od_lw = factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
976 | & * ao%mass_ext_lw_philic(:,irh,itype) |
---|
977 | od_lw_aerosol = od_lw_aerosol + local_od_lw |
---|
978 | scat_lw_aerosol = scat_lw_aerosol & |
---|
979 | & + local_od_lw * ao%ssa_lw_philic(:,irh,itype) |
---|
980 | scat_g_lw_aerosol = scat_g_lw_aerosol & |
---|
981 | & + local_od_lw * ao%ssa_lw_philic(:,irh,itype) & |
---|
982 | & * ao%g_lw_philic(:,irh,itype) |
---|
983 | else |
---|
984 | ! If aerosol longwave scattering is not included then we |
---|
985 | ! weight the optical depth by the single scattering |
---|
986 | ! co-albedo |
---|
987 | od_lw_aerosol = od_lw_aerosol & |
---|
988 | & + factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
989 | & * ao%mass_ext_lw_philic(:,irh,itype) & |
---|
990 | & * (1.0_jprb - ao%ssa_lw_philic(:,irh,itype)) |
---|
991 | end if |
---|
992 | end if |
---|
993 | ! Implicitly, if ao%iclass(jtype) == IAerosolClassNone, then |
---|
994 | ! no aerosol scattering properties are added |
---|
995 | |
---|
996 | end do ! Loop over aerosol type |
---|
997 | |
---|
998 | if (.not. config%do_sw_delta_scaling_with_gases) then |
---|
999 | ! Delta-Eddington scaling on aerosol only. Note that if |
---|
1000 | ! do_sw_delta_scaling_with_gases==.true. then the delta |
---|
1001 | ! scaling is done to the cloud-aerosol-gas mixture inside |
---|
1002 | ! the solver |
---|
1003 | call delta_eddington_extensive(od_sw_aerosol, scat_sw_aerosol, & |
---|
1004 | & scat_g_sw_aerosol) |
---|
1005 | end if |
---|
1006 | |
---|
1007 | ! Combine aerosol shortwave scattering properties with gas |
---|
1008 | ! properties (noting that any gas scattering will have an |
---|
1009 | ! asymmetry factor of zero) |
---|
1010 | do jg = 1,config%n_g_sw |
---|
1011 | iband = config%i_band_from_reordered_g_sw(jg) |
---|
1012 | local_od = od_sw(jg,jlev,jcol) + od_sw_aerosol(iband) |
---|
1013 | if (local_od > 0.0_jprb .and. od_sw_aerosol(iband) > 0.0_jprb) then |
---|
1014 | local_scat = ssa_sw(jg,jlev,jcol) * od_sw(jg,jlev,jcol) & |
---|
1015 | & + scat_sw_aerosol(iband) |
---|
1016 | ! Note that asymmetry_sw of gases is zero so the following |
---|
1017 | ! simply weights the aerosol asymmetry by the scattering |
---|
1018 | ! optical depth |
---|
1019 | if (local_scat > 0.0_jprb) then |
---|
1020 | g_sw(jg,jlev,jcol) = scat_g_sw_aerosol(iband) / local_scat |
---|
1021 | end if |
---|
1022 | ssa_sw(jg,jlev,jcol) = local_scat / local_od |
---|
1023 | od_sw (jg,jlev,jcol) = local_od |
---|
1024 | end if |
---|
1025 | end do |
---|
1026 | |
---|
1027 | ! Combine aerosol longwave scattering properties with gas |
---|
1028 | ! properties, noting that in the longwave, gases do not |
---|
1029 | ! scatter at all |
---|
1030 | if (config%do_lw_aerosol_scattering) then |
---|
1031 | |
---|
1032 | call delta_eddington_extensive(od_lw_aerosol, scat_lw_aerosol, & |
---|
1033 | & scat_g_lw_aerosol) |
---|
1034 | |
---|
1035 | do jg = 1,config%n_g_lw |
---|
1036 | iband = config%i_band_from_reordered_g_lw(jg) |
---|
1037 | local_od = od_lw(jg,jlev,jcol) + od_lw_aerosol(iband) |
---|
1038 | if (local_od > 0.0_jprb .and. od_lw_aerosol(iband) > 0.0_jprb) then |
---|
1039 | ! All scattering is due to aerosols, therefore the |
---|
1040 | ! asymmetry factor is equal to the value for aerosols |
---|
1041 | if (scat_lw_aerosol(iband) > 0.0_jprb) then |
---|
1042 | g_lw(jg,jlev,jcol) = scat_g_lw_aerosol(iband) & |
---|
1043 | & / scat_lw_aerosol(iband) |
---|
1044 | end if |
---|
1045 | ssa_lw(jg,jlev,jcol) = scat_lw_aerosol(iband) / local_od |
---|
1046 | od_lw (jg,jlev,jcol) = local_od |
---|
1047 | end if |
---|
1048 | end do |
---|
1049 | else |
---|
1050 | do jg = 1,config%n_g_lw |
---|
1051 | od_lw(jg,jlev,jcol) = od_lw(jg,jlev,jcol) & |
---|
1052 | & + od_lw_aerosol(config%i_band_from_reordered_g_lw(jg)) |
---|
1053 | end do |
---|
1054 | end if |
---|
1055 | |
---|
1056 | end do ! Loop over column |
---|
1057 | end do ! Loop over level |
---|
1058 | |
---|
1059 | end if |
---|
1060 | |
---|
1061 | if (lhook) call dr_hook('radiation_aerosol_optics:add_aerosol_optics',1,hook_handle) |
---|
1062 | |
---|
1063 | end subroutine add_aerosol_optics |
---|
1064 | |
---|
1065 | |
---|
1066 | !--------------------------------------------------------------------- |
---|
1067 | ! Add precomputed optical properties to gas optical depth and |
---|
1068 | ! scattering properties |
---|
1069 | subroutine add_aerosol_optics_direct(nlev,istartcol,iendcol, & |
---|
1070 | & config, aerosol, & |
---|
1071 | & od_lw, ssa_lw, g_lw, od_sw, ssa_sw, g_sw) |
---|
1072 | |
---|
1073 | use parkind1, only : jprb |
---|
1074 | use radiation_io, only : nulerr, radiation_abort |
---|
1075 | use yomhook, only : lhook, dr_hook |
---|
1076 | use radiation_config, only : config_type |
---|
1077 | use radiation_aerosol, only : aerosol_type |
---|
1078 | |
---|
1079 | integer, intent(in) :: nlev ! number of model levels |
---|
1080 | integer, intent(in) :: istartcol, iendcol ! range of columns to process |
---|
1081 | type(config_type), intent(in), target :: config |
---|
1082 | type(aerosol_type), intent(in) :: aerosol |
---|
1083 | ! Optical depth, single scattering albedo and asymmetry factor of |
---|
1084 | ! the atmosphere (gases on input, gases and aerosols on output) |
---|
1085 | ! for each g point. Note that longwave ssa and asymmetry and |
---|
1086 | ! shortwave asymmetry are all zero for gases, so are not yet |
---|
1087 | ! defined on input and are therefore intent(out). |
---|
1088 | real(jprb), dimension(config%n_g_lw,nlev,istartcol:iendcol), & |
---|
1089 | & intent(inout) :: od_lw |
---|
1090 | real(jprb), dimension(config%n_g_lw_if_scattering,nlev,istartcol:iendcol), & |
---|
1091 | & intent(out) :: ssa_lw, g_lw |
---|
1092 | real(jprb), dimension(config%n_g_sw,nlev,istartcol:iendcol), & |
---|
1093 | & intent(inout) :: od_sw, ssa_sw |
---|
1094 | real(jprb), dimension(config%n_g_sw,nlev,istartcol:iendcol), & |
---|
1095 | & intent(out) :: g_sw |
---|
1096 | |
---|
1097 | ! Temporary extinction and scattering optical depths of aerosol |
---|
1098 | ! plus gas |
---|
1099 | real(jprb) :: local_od, local_scat |
---|
1100 | |
---|
1101 | ! Extinction optical depth, scattering optical depth and |
---|
1102 | ! asymmetry-times-scattering-optical-depth for all the aerosols at |
---|
1103 | ! a point in space for each spectral band of the shortwave and |
---|
1104 | ! longwave spectrum |
---|
1105 | real(jprb), dimension(config%n_bands_sw,nlev) & |
---|
1106 | & :: od_sw_aerosol, scat_sw_aerosol, scat_g_sw_aerosol |
---|
1107 | real(jprb), dimension(config%n_bands_lw,nlev) :: od_lw_aerosol |
---|
1108 | real(jprb), dimension(config%n_bands_lw_if_scattering,nlev) & |
---|
1109 | & :: scat_lw_aerosol, scat_g_lw_aerosol |
---|
1110 | |
---|
1111 | ! Loop indices for column, level, g point and band |
---|
1112 | integer :: jcol, jlev, jg, jb |
---|
1113 | |
---|
1114 | ! Range of levels over which aerosols are present |
---|
1115 | integer :: istartlev, iendlev |
---|
1116 | |
---|
1117 | ! Indices to spectral band |
---|
1118 | integer :: iband |
---|
1119 | |
---|
1120 | real(jprb) :: hook_handle |
---|
1121 | |
---|
1122 | if (lhook) call dr_hook('radiation_aerosol_optics:add_aerosol_optics_direct',0,hook_handle) |
---|
1123 | |
---|
1124 | if (config%do_sw) then |
---|
1125 | ! Check array dimensions |
---|
1126 | if (ubound(aerosol%od_sw,1) /= config%n_bands_sw) then |
---|
1127 | write(nulerr,'(a,i0,a,i0)') '*** Error: aerosol%od_sw contains ', & |
---|
1128 | & ubound(aerosol%od_sw,1), ' band, expected ', & |
---|
1129 | & config%n_bands_sw |
---|
1130 | call radiation_abort() |
---|
1131 | end if |
---|
1132 | |
---|
1133 | istartlev = lbound(aerosol%od_sw,2) |
---|
1134 | iendlev = ubound(aerosol%od_sw,2) |
---|
1135 | |
---|
1136 | ! Set variables to zero that may not have been previously |
---|
1137 | g_sw(:,:,istartcol:iendcol) = 0.0_jprb |
---|
1138 | |
---|
1139 | ! Loop over position |
---|
1140 | do jcol = istartcol,iendcol |
---|
1141 | ! Added for DWD (2020) |
---|
1142 | !NEC$ forced_collapse |
---|
1143 | do jlev = istartlev,iendlev |
---|
1144 | do jb = 1,config%n_bands_sw |
---|
1145 | od_sw_aerosol(jb,jlev) = aerosol%od_sw(jb,jlev,jcol) |
---|
1146 | scat_sw_aerosol(jb,jlev) = aerosol%ssa_sw(jb,jlev,jcol) * od_sw_aerosol(jb,jlev) |
---|
1147 | scat_g_sw_aerosol(jb,jlev) = aerosol%g_sw(jb,jlev,jcol) * scat_sw_aerosol(jb,jlev) |
---|
1148 | |
---|
1149 | if (.not. config%do_sw_delta_scaling_with_gases) then |
---|
1150 | ! Delta-Eddington scaling on aerosol only. Note that if |
---|
1151 | ! do_sw_delta_scaling_with_gases==.true. then the delta |
---|
1152 | ! scaling is done to the cloud-aerosol-gas mixture |
---|
1153 | ! inside the solver |
---|
1154 | call delta_eddington_extensive(od_sw_aerosol(jb,jlev), scat_sw_aerosol(jb,jlev), & |
---|
1155 | & scat_g_sw_aerosol(jb,jlev)) |
---|
1156 | end if |
---|
1157 | end do |
---|
1158 | end do |
---|
1159 | ! Combine aerosol shortwave scattering properties with gas |
---|
1160 | ! properties (noting that any gas scattering will have an |
---|
1161 | ! asymmetry factor of zero) |
---|
1162 | do jlev = istartlev,iendlev |
---|
1163 | if (od_sw_aerosol(1,jlev) > 0.0_jprb) then |
---|
1164 | do jg = 1,config%n_g_sw |
---|
1165 | iband = config%i_band_from_reordered_g_sw(jg) |
---|
1166 | local_od = od_sw(jg,jlev,jcol) + od_sw_aerosol(iband,jlev) |
---|
1167 | local_scat = ssa_sw(jg,jlev,jcol) * od_sw(jg,jlev,jcol) & |
---|
1168 | & + scat_sw_aerosol(iband,jlev) |
---|
1169 | ! Note that asymmetry_sw of gases is zero so the following |
---|
1170 | ! simply weights the aerosol asymmetry by the scattering |
---|
1171 | ! optical depth |
---|
1172 | g_sw(jg,jlev,jcol) = scat_g_sw_aerosol(iband,jlev) / local_scat |
---|
1173 | local_od = od_sw(jg,jlev,jcol) + od_sw_aerosol(iband,jlev) |
---|
1174 | ssa_sw(jg,jlev,jcol) = local_scat / local_od |
---|
1175 | od_sw (jg,jlev,jcol) = local_od |
---|
1176 | end do |
---|
1177 | end if |
---|
1178 | end do |
---|
1179 | end do |
---|
1180 | |
---|
1181 | end if |
---|
1182 | |
---|
1183 | if (config%do_lw) then |
---|
1184 | |
---|
1185 | if (ubound(aerosol%od_lw,1) /= config%n_bands_lw) then |
---|
1186 | write(nulerr,'(a,i0,a,i0)') '*** Error: aerosol%od_lw contains ', & |
---|
1187 | & ubound(aerosol%od_lw,1), ' band, expected ', & |
---|
1188 | & config%n_bands_lw |
---|
1189 | call radiation_abort() |
---|
1190 | end if |
---|
1191 | |
---|
1192 | istartlev = lbound(aerosol%od_lw,2) |
---|
1193 | iendlev = ubound(aerosol%od_lw,2) |
---|
1194 | |
---|
1195 | if (config%do_lw_aerosol_scattering) then |
---|
1196 | ssa_lw(:,:,istartcol:iendcol) = 0.0_jprb |
---|
1197 | g_lw(:,:,istartcol:iendcol) = 0.0_jprb |
---|
1198 | |
---|
1199 | ! Loop over position |
---|
1200 | do jcol = istartcol,iendcol |
---|
1201 | ! Added for DWD (2020) |
---|
1202 | !NEC$ forced_collapse |
---|
1203 | do jlev = istartlev,iendlev |
---|
1204 | do jb = 1,config%n_bands_lw |
---|
1205 | od_lw_aerosol(jb,jlev) = aerosol%od_lw(jb,jlev,jcol) |
---|
1206 | scat_lw_aerosol(jb,jlev) = aerosol%ssa_lw(jb,jlev,jcol) * od_lw_aerosol(jb,jlev) |
---|
1207 | scat_g_lw_aerosol(jb,jlev) = aerosol%g_lw(jb,jlev,jcol) * scat_lw_aerosol(jb,jlev) |
---|
1208 | |
---|
1209 | call delta_eddington_extensive(od_lw_aerosol(jb,jlev), scat_lw_aerosol(jb,jlev), & |
---|
1210 | & scat_g_lw_aerosol(jb,jlev)) |
---|
1211 | end do |
---|
1212 | end do |
---|
1213 | do jlev = istartlev,iendlev |
---|
1214 | do jg = 1,config%n_g_lw |
---|
1215 | iband = config%i_band_from_reordered_g_lw(jg) |
---|
1216 | if (od_lw_aerosol(iband,jlev) > 0.0_jprb) then |
---|
1217 | ! All scattering is due to aerosols, therefore the |
---|
1218 | ! asymmetry factor is equal to the value for aerosols |
---|
1219 | if (scat_lw_aerosol(iband,jlev) > 0.0_jprb) then |
---|
1220 | g_lw(jg,jlev,jcol) = scat_g_lw_aerosol(iband,jlev) & |
---|
1221 | & / scat_lw_aerosol(iband,jlev) |
---|
1222 | end if |
---|
1223 | local_od = od_lw(jg,jlev,jcol) + od_lw_aerosol(iband,jlev) |
---|
1224 | ssa_lw(jg,jlev,jcol) = scat_lw_aerosol(iband,jlev) / local_od |
---|
1225 | od_lw (jg,jlev,jcol) = local_od |
---|
1226 | end if |
---|
1227 | end do |
---|
1228 | end do |
---|
1229 | end do |
---|
1230 | |
---|
1231 | else ! No longwave scattering |
---|
1232 | |
---|
1233 | ! Loop over position |
---|
1234 | do jcol = istartcol,iendcol |
---|
1235 | ! Added for DWD (2020) |
---|
1236 | !NEC$ forced_collapse |
---|
1237 | do jlev = istartlev,iendlev |
---|
1238 | ! If aerosol longwave scattering is not included then we |
---|
1239 | ! weight the optical depth by the single scattering |
---|
1240 | ! co-albedo |
---|
1241 | do jb = 1, config%n_bands_lw |
---|
1242 | od_lw_aerosol(jb,jlev) = aerosol%od_lw(jb,jlev,jcol) & |
---|
1243 | & * (1.0_jprb - aerosol%ssa_lw(jb,jlev,jcol)) |
---|
1244 | end do |
---|
1245 | end do |
---|
1246 | do jlev = istartlev,iendlev |
---|
1247 | do jg = 1,config%n_g_lw |
---|
1248 | od_lw(jg,jlev,jcol) = od_lw(jg,jlev,jcol) & |
---|
1249 | & + od_lw_aerosol(config%i_band_from_reordered_g_lw(jg),jlev) |
---|
1250 | end do |
---|
1251 | end do |
---|
1252 | end do |
---|
1253 | |
---|
1254 | end if |
---|
1255 | end if |
---|
1256 | |
---|
1257 | |
---|
1258 | if (lhook) call dr_hook('radiation_aerosol_optics:add_aerosol_optics_direct',1,hook_handle) |
---|
1259 | |
---|
1260 | end subroutine add_aerosol_optics_direct |
---|
1261 | |
---|
1262 | |
---|
1263 | !--------------------------------------------------------------------- |
---|
1264 | ! Sometimes it is useful to specify aerosol in terms of its optical |
---|
1265 | ! depth at a particular wavelength. This function returns the dry |
---|
1266 | ! mass-extinction coefficient, i.e. the extinction cross section per |
---|
1267 | ! unit mass, for aerosol of type "itype" at the specified wavelength |
---|
1268 | ! (m). For hydrophilic types, the value at the first relative |
---|
1269 | ! humidity bin is taken. |
---|
1270 | function dry_aerosol_mass_extinction(config, itype, wavelength) |
---|
1271 | |
---|
1272 | use parkind1, only : jprb |
---|
1273 | use radiation_io, only : nulerr, radiation_abort |
---|
1274 | use radiation_config, only : config_type |
---|
1275 | use radiation_aerosol_optics_data, only : aerosol_optics_type, & |
---|
1276 | & IAerosolClassUndefined, IAerosolClassIgnored, & |
---|
1277 | & IAerosolClassHydrophobic, IAerosolClassHydrophilic |
---|
1278 | |
---|
1279 | type(config_type), intent(in), target :: config |
---|
1280 | |
---|
1281 | ! Aerosol type |
---|
1282 | integer, intent(in) :: itype |
---|
1283 | |
---|
1284 | ! Wavelength (m) |
---|
1285 | real(jprb), intent(in) :: wavelength |
---|
1286 | |
---|
1287 | real(jprb) :: dry_aerosol_mass_extinction |
---|
1288 | |
---|
1289 | ! Index to the monochromatic wavelength requested |
---|
1290 | integer :: imono |
---|
1291 | |
---|
1292 | ! Pointer to the aerosol optics coefficients for brevity of access |
---|
1293 | type(aerosol_optics_type), pointer :: ao |
---|
1294 | |
---|
1295 | ao => config%aerosol_optics |
---|
1296 | |
---|
1297 | imono = minloc(abs(wavelength - ao%wavelength_mono), 1) |
---|
1298 | |
---|
1299 | if (abs(wavelength - ao%wavelength_mono(imono))/wavelength > 0.01_jprb) then |
---|
1300 | write(nulerr,'(a,e8.4,a)') '*** Error: requested wavelength ', & |
---|
1301 | & wavelength, ' not within 1% of stored wavelengths' |
---|
1302 | call radiation_abort() |
---|
1303 | end if |
---|
1304 | |
---|
1305 | if (ao%iclass(itype) == IAerosolClassHydrophobic) then |
---|
1306 | dry_aerosol_mass_extinction = ao%mass_ext_mono_phobic(imono,ao%itype(itype)) |
---|
1307 | else if (ao%iclass(itype) == IAerosolClassHydrophilic) then |
---|
1308 | ! Take the value at the first relative-humidity bin for the |
---|
1309 | ! "dry" aerosol value |
---|
1310 | dry_aerosol_mass_extinction = ao%mass_ext_mono_philic(imono,1,ao%itype(itype)) |
---|
1311 | else |
---|
1312 | dry_aerosol_mass_extinction = 0.0_jprb |
---|
1313 | end if |
---|
1314 | |
---|
1315 | end function dry_aerosol_mass_extinction |
---|
1316 | |
---|
1317 | |
---|
1318 | !--------------------------------------------------------------------- |
---|
1319 | ! Compute aerosol extinction coefficient at a particular wavelength |
---|
1320 | ! and a single height - this is useful for visibility diagnostics |
---|
1321 | subroutine aerosol_extinction(ncol,istartcol,iendcol, & |
---|
1322 | & config, wavelength, mixing_ratio, relative_humidity, extinction) |
---|
1323 | |
---|
1324 | use parkind1, only : jprb |
---|
1325 | use yomhook, only : lhook, dr_hook |
---|
1326 | use radiation_io, only : nulerr, radiation_abort |
---|
1327 | use radiation_config, only : config_type |
---|
1328 | use radiation_aerosol_optics_data, only : aerosol_optics_type, & |
---|
1329 | & IAerosolClassUndefined, IAerosolClassIgnored, & |
---|
1330 | & IAerosolClassHydrophobic, IAerosolClassHydrophilic |
---|
1331 | |
---|
1332 | integer, intent(in) :: ncol ! number of columns |
---|
1333 | integer, intent(in) :: istartcol, iendcol ! range of columns to process |
---|
1334 | type(config_type), intent(in), target :: config |
---|
1335 | real(jprb), intent(in) :: wavelength ! Requested wavelength (m) |
---|
1336 | real(jprb), intent(in) :: mixing_ratio(ncol,config%n_aerosol_types) |
---|
1337 | real(jprb), intent(in) :: relative_humidity(ncol) |
---|
1338 | real(jprb), intent(out) :: extinction(ncol) |
---|
1339 | |
---|
1340 | ! Local aerosol extinction |
---|
1341 | real(jprb) :: ext |
---|
1342 | |
---|
1343 | ! Index to the monochromatic wavelength requested |
---|
1344 | integer :: imono |
---|
1345 | |
---|
1346 | ! Pointer to the aerosol optics coefficients for brevity of access |
---|
1347 | type(aerosol_optics_type), pointer :: ao |
---|
1348 | |
---|
1349 | ! Loop indices for column and aerosol type |
---|
1350 | integer :: jcol, jtype |
---|
1351 | |
---|
1352 | ! Relative humidity index |
---|
1353 | integer :: irh |
---|
1354 | |
---|
1355 | real(jprb) :: hook_handle |
---|
1356 | |
---|
1357 | if (lhook) call dr_hook('radiation_aerosol_optics:aerosol_extinction',0,hook_handle) |
---|
1358 | |
---|
1359 | do jtype = 1,config%n_aerosol_types |
---|
1360 | if (config%aerosol_optics%iclass(jtype) == IAerosolClassUndefined) then |
---|
1361 | write(nulerr,'(a)') '*** Error: not all aerosol types are defined' |
---|
1362 | call radiation_abort() |
---|
1363 | end if |
---|
1364 | end do |
---|
1365 | |
---|
1366 | ao => config%aerosol_optics |
---|
1367 | |
---|
1368 | imono = minloc(abs(wavelength - ao%wavelength_mono), 1) |
---|
1369 | |
---|
1370 | if (abs(wavelength - ao%wavelength_mono(imono))/wavelength > 0.01_jprb) then |
---|
1371 | write(nulerr,'(a,e8.4,a)') '*** Error: requested wavelength ', & |
---|
1372 | & wavelength, ' not within 1% of stored wavelengths' |
---|
1373 | call radiation_abort() |
---|
1374 | end if |
---|
1375 | |
---|
1376 | ! Loop over position |
---|
1377 | do jcol = istartcol,iendcol |
---|
1378 | ext = 0.0_jprb |
---|
1379 | ! Get relative-humidity index |
---|
1380 | irh = ao%calc_rh_index(relative_humidity(jcol)) |
---|
1381 | ! Add extinction coefficients from each aerosol type |
---|
1382 | do jtype = 1,config%n_aerosol_types |
---|
1383 | if (ao%iclass(jtype) == IAerosolClassHydrophobic) then |
---|
1384 | ext = ext + mixing_ratio(jcol,jtype) & |
---|
1385 | & * ao%mass_ext_mono_phobic(imono,ao%itype(jtype)) |
---|
1386 | else if (ao%iclass(jtype) == IAerosolClassHydrophilic) then |
---|
1387 | ext = ext + mixing_ratio(jcol,jtype) & |
---|
1388 | & * ao%mass_ext_mono_philic(imono,irh,ao%itype(jtype)) |
---|
1389 | end if |
---|
1390 | end do |
---|
1391 | |
---|
1392 | extinction(jcol) = ext |
---|
1393 | end do |
---|
1394 | |
---|
1395 | if (lhook) call dr_hook('radiation_aerosol_optics:aerosol_extinction',1,hook_handle) |
---|
1396 | |
---|
1397 | end subroutine aerosol_extinction |
---|
1398 | |
---|
1399 | end module radiation_aerosol_optics |
---|