source: LMDZ6/branches/LMDZ_ECRad/libf/phylmd/ecrad/radiation_setup.F90 @ 4647

Last change on this file since 4647 was 4647, checked in by idelkadi, 11 months ago

Implementation in the LMDZ code of the double call of the ECRAD radiative transfer code to estimate the 3D radiative effect of clouds.

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