source: LMDZ6/trunk/libf/phylmd/ecrad/lmdz/radiation_setup.f90 @ 5880

Last change on this file since 5880 was 5760, checked in by lguez, 5 months ago

Move the call to define_sw_albedo_intervals

Move the call to define_sw_albedo_intervals before the call to
rad_config%read. We avoid a double call to
radiation_config::consolidate_sw_albedo_intervals since, now,
define_sw_albedo_intervals is called before
radiation_interface::setup_radiation, so this%is_consolidated in
define_sw_albedo_intervals is false. Also, the values of shortwave
albedo bounds defined by define_sw_albedo_intervals are now default
values and we avoid silenlty overwriting the values of
sw_albedo_wavelength_bound and i_sw_albedo_index chosen by the
user in the namelist. Note that this new ordering of statements is the
same than in file ecrad/ifs/radiation_setup.F90.

File size: 5.3 KB
Line 
1MODULE RADIATION_SETUP
2
3  ! RADIATION_SETUP - Setting up modular radiation scheme
4  !
5  ! AUTHOR
6  ! ------
7  !   Robin Hogan, ECMWF
8  !   Original: 2015-09-16
9  !
10  ! MODIFICATIONS
11  ! -------------
12  !   Abderrahmane Idelkadi LMD, juillet 2023
13  !
14  !-----------------------------------------------------------------------
15
16  USE PARKIND1,         ONLY : JPRB
17  USE radiation_config, ONLY : config_type, &
18       &                       ISolverMcICA, ISolverSpartacus, &
19       &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
20       &                       IIceModelFu, IIceModelBaran, IGasModelECCKD, &
21       &                       IGasModelIFSRRTMG, IOverlapExponentialRandom
22
23  USE radiation_interface,      ONLY : setup_radiation
24  USE setup_config_from_lmdz,   ONLY : driver_config_type
25
26  IMPLICIT NONE
27
28
29  ! Ultraviolet weightings
30  INTEGER         :: NWEIGHT_UV
31  INTEGER         :: IBAND_UV(100)
32  REAL(KIND=JPRB) :: WEIGHT_UV(100)
33  ! Photosynthetically active radiation weightings
34  INTEGER         :: NWEIGHT_PAR
35  INTEGER         :: IBAND_PAR(100)
36  REAL(KIND=JPRB) :: WEIGHT_PAR(100)
37
38  ! Background aerosol is specified in an ugly way: using the old
39  ! Tegen fields that are in terms of optical depth, and converted to
40  ! mass mixing ratio via the relevant mass-extinction coefficient
41  INTEGER, PARAMETER :: ITYPE_TROP_BG_AER = 8 ! hydrophobic organic
42  INTEGER, PARAMETER :: ITYPE_STRAT_BG_AER=12 ! non-absorbing sulphate
43  REAL(KIND=JPRB)    :: TROP_BG_AER_MASS_EXT
44  REAL(KIND=JPRB)    :: STRAT_BG_AER_MASS_EXT
45
46CONTAINS
47
48  ! This routine copies information between the LMDZ radiation
49  ! configuration (stored in global variables) and the radiation
50  ! configuration of the modular radiation scheme (stored in
51  ! rad_config).  The optional input logical LOUTPUT controls whether
52  ! to print lots of information during the setup stage (default is
53  ! no).
54  ! AI At the end of the routine, the parameters are read in namelist
55  !
56  SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT,file_name,rad_config,driver_config)
57
58    !    USE radiation_config, ONLY : config_type, &
59    !        &                       ISolverMcICA, ISolverSpartacus, &
60    !        &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
61    !        &                       IIceModelFu, IIceModelBaran, &
62    !        &                       IOverlapExponentialRandom
63    USE mod_phys_lmdz_para
64
65    USE YOMHOOK,  ONLY : LHOOK, DR_HOOK
66    USE YOMLUN,   ONLY : NULOUT, NULERR
67    USE YOESRTWN, ONLY : NMPSRTM
68
69    !   USE radiation_interface,      ONLY : setup_radiation
70    !   USE setup_config_from_lmdz,   ONLY : driver_config_type
71
72    ! Whether or not to provide information on the radiation scheme
73    ! configuration
74    LOGICAL, INTENT(IN), OPTIONAL :: LOUTPUT
75
76    REAL(KIND=JPRB) :: ZHOOK_HANDLE
77
78    character(len=512) :: file_name
79
80    logical :: lprint_setp=.TRUE.
81
82    ! Store configuration information for the radiation scheme in a
83    ! global variable
84    type(config_type) :: rad_config
85    type(driver_config_type) :: driver_config
86
87    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',0,ZHOOK_HANDLE)
88
89    ! *** GENERAL SETUP ***
90
91    ! Configure verbosity of setup of radiation scheme
92
93    print*,'********** Dans radiation_setup *****************'
94
95    rad_config%i_aerosol_type_map(1:13) = (/ &
96         &  -1, &
97         &  -2, &
98         &  -3, &
99         &  -4, &
100         &  -5, &
101         &  -6, &
102         &  -7, &
103         &   1, &
104         &   2, &
105         &   3, &
106         &  -8, &
107         &  -9, &
108         &   4 /)
109
110    ! Populate the mapping between the 14 RRTM shortwave bands and the
111    ! 6 albedo inputs. The mapping according to the stated wavelength
112    ! ranges of the 6-band model does not match the hard-wired mapping
113    ! in NMPSRTM, but only the hard-wired values produce sensible
114    ! results...
115    ! Note that NMPSRTM(:)=(/  6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 2, 2, 1, 6 /)
116    ! AI (6 albedo SW bands)
117    call rad_config%define_sw_albedo_intervals(6, &
118         &  [0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, &
119         &   1.19e-6_jprb, 2.38e-6_jprb], [1,2,3,4,5,6])
120    ! Likewise between the 16 RRTM longwave bands and the 2 emissivity
121    ! inputs (info taken from rrtm_ecrt_140gp_mcica.F90) representing
122    ! outside and inside the window region of the spectrum
123    !     rad_config%i_emiss_from_band_lw = (/ 1,1,1,1,1,2,2,2,1,1,1,1,1,1,1,1 /)
124    ! AI ATTENTION ?????
125    !!    call rad_config%define_lw_emiss_intervals(3, &
126    !!         &  (/ 8.0e-6_jprb,13.0e-6_jprb /),  (/ 1,2,1 /))
127
128    ! AI ATTENTION (parameters read in namelist file)
129    !    file_name="namelist_ecrad"
130    call rad_config%read(file_name=file_name)
131    call driver_config%read(file_name)
132    call rad_config%print(iverbose = 2)
133
134    ! Use configuration data to set-up radiation scheme, including
135    ! reading scattering datafiles
136    CALL setup_radiation(rad_config)
137
138    !    ! Get spectral weightings for UV and PAR
139    call rad_config%get_sw_weights(0.2e-6_jprb, 0.4415e-6_jprb, &
140         &  NWEIGHT_UV, IBAND_UV, WEIGHT_UV, 'ultraviolet')
141    call rad_config%get_sw_weights(0.4e-6_jprb, 0.7e-6_jprb, &
142         &  NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, &
143         &  'photosynthetically active radiation, PAR')
144
145    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE)
146
147  END SUBROUTINE SETUP_RADIATION_SCHEME
148
149END MODULE RADIATION_SETUP
Note: See TracBrowser for help on using the repository browser.