source: LMDZ6/trunk/libf/phylmd/ecrad/lmdz/radiation_setup.F90 @ 4859

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