1 | !aeropt_5wv_ecrad.F90 2022-09-20 A. Idelkadi et O. Boucher |
---|
2 | ! |
---|
3 | SUBROUTINE AEROPT_5WV_ECRAD(istartcol,iendcol,istartlev,iendlev, & |
---|
4 | config,thermodynamics,aerosol) |
---|
5 | |
---|
6 | |
---|
7 | USE DIMPHY |
---|
8 | USE aero_mod |
---|
9 | USE phys_local_var_mod, ONLY: od443aer,od550aer,od865aer |
---|
10 | ! dryod550aer, |
---|
11 | ! ec550aer,od550lt1aer,abs550aer |
---|
12 | ! USE phys_output_var_mod, ONLY: dryaod_diag |
---|
13 | ! USE YOMCST, ONLY: RD,RG |
---|
14 | USE phys_local_var_mod, ONLY: rhcl |
---|
15 | |
---|
16 | use parkind1, only : jprb |
---|
17 | use radiation_config, only : config_type |
---|
18 | use radiation_thermodynamics, only : thermodynamics_type |
---|
19 | use radiation_aerosol, only : aerosol_type |
---|
20 | use radiation_constants, only : AccelDueToGravity |
---|
21 | use radiation_aerosol_optics_data, only : aerosol_optics_type, & |
---|
22 | & IAerosolClassUndefined, IAerosolClassIgnored, & |
---|
23 | & IAerosolClassHydrophobic, IAerosolClassHydrophilic |
---|
24 | |
---|
25 | IMPLICIT NONE |
---|
26 | |
---|
27 | !---ATTENTION n_mono est a redéfinir proprement |
---|
28 | |
---|
29 | ! Range of levels over which aerosols are present |
---|
30 | integer, intent(in) :: istartlev, iendlev, istartcol,iendcol |
---|
31 | type(config_type), intent(in), target :: config |
---|
32 | type(thermodynamics_type),intent(in) :: thermodynamics |
---|
33 | type(aerosol_type), intent(in) :: aerosol |
---|
34 | type(aerosol_optics_type), pointer :: ao |
---|
35 | |
---|
36 | ! Loop indices for column, level, g point, band and aerosol type, and relative humidity |
---|
37 | integer :: jcol, jlev, jtype, irh |
---|
38 | ! indice wavelength in aerosol_optics_lmdz.nc |
---|
39 | INTEGER, PARAMETER :: la443 = 1 |
---|
40 | INTEGER, PARAMETER :: la550 = 2 |
---|
41 | ! INTEGER, PARAMETER :: la670 = 3 |
---|
42 | ! INTEGER, PARAMETER :: la765 = 4 |
---|
43 | INTEGER, PARAMETER :: la865 = 5 |
---|
44 | real(jprb) :: factor |
---|
45 | ! n_bands_sw |
---|
46 | real(jprb), dimension(config%aerosol_optics%n_mono_wl) :: od_aerosol_mono, local_od_mono |
---|
47 | |
---|
48 | !--initialization |
---|
49 | od443aer = 0.0_jprb |
---|
50 | od550aer = 0.0_jprb |
---|
51 | od865aer = 0.0_jprb |
---|
52 | |
---|
53 | ao => config%aerosol_optics |
---|
54 | |
---|
55 | ! Loop over level |
---|
56 | do jlev = istartlev,iendlev |
---|
57 | |
---|
58 | ! Loop over column |
---|
59 | do jcol = istartcol,iendcol |
---|
60 | |
---|
61 | ! Compute relative humidity with respect to liquid |
---|
62 | ! saturation and the index to the relative-humidity index of |
---|
63 | ! hydrophilic-aerosol data |
---|
64 | irh = ao%calc_rh_index(rhcl(jcol,jlev)) |
---|
65 | |
---|
66 | factor = ( thermodynamics%pressure_hl(jcol,jlev+1) & |
---|
67 | & -thermodynamics%pressure_hl(jcol,jlev ) ) & |
---|
68 | & / AccelDueToGravity |
---|
69 | |
---|
70 | ! Reset temporary arrays |
---|
71 | od_aerosol_mono = 0.0_jprb |
---|
72 | |
---|
73 | do jtype = 1,config%n_aerosol_types |
---|
74 | ! Add the optical depth for this aerosol type to the total for all aerosols. |
---|
75 | ! Note that the following expressions are array-wise |
---|
76 | if (ao%iclass(jtype) == IAerosolClassHydrophobic) then |
---|
77 | local_od_mono = factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
78 | & * ao%mass_ext_mono_phobic(:,ao%itype(jtype)) |
---|
79 | od_aerosol_mono = od_aerosol_mono + local_od_mono |
---|
80 | else if (ao%iclass(jtype) == IAerosolClassHydrophilic) then |
---|
81 | ! Hydrophilic aerosols require the look-up tables to |
---|
82 | ! be indexed with irh |
---|
83 | local_od_mono = factor * aerosol%mixing_ratio(jcol,jlev,jtype) & |
---|
84 | & * ao%mass_ext_mono_philic(:,irh,ao%itype(jtype)) |
---|
85 | od_aerosol_mono = od_aerosol_mono + local_od_mono |
---|
86 | end if |
---|
87 | |
---|
88 | end do ! Loop over aerosol type |
---|
89 | |
---|
90 | !--ATTENTION A BIEN FAIRE CORRESPONDRE LES INDICES |
---|
91 | od443aer(jcol) = od443aer(jcol) + od_aerosol_mono(la443) |
---|
92 | od550aer(jcol) = od550aer(jcol) + od_aerosol_mono(la550) |
---|
93 | od865aer(jcol) = od865aer(jcol) + od_aerosol_mono(la865) |
---|
94 | |
---|
95 | end do ! Loop over column |
---|
96 | |
---|
97 | end do ! Loop over level |
---|
98 | |
---|
99 | END SUBROUTINE AEROPT_5WV_ECRAD |
---|
100 | |
---|