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

Last change on this file since 4115 was 4115, checked in by idelkadi, 2 years ago

Implementation of Ecrad in LMDZ (continued) :

  • Switch to the first call only in the configuration and initializations part of Ecrad
  • Added instructions for parallelization
  • Initializations


File size: 16.8 KB
Line 
1MODULE RADIATION_SETUP
2
3! RADIATION_SETUP - Setting up modular radiation scheme
4!
5! (C) Copyright 2015- ECMWF.
6!
7! This software is licensed under the terms of the Apache Licence Version 2.0
8! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
9!
10! In applying this licence, ECMWF does not waive the privileges and immunities
11! granted to it by virtue of its status as an intergovernmental organisation
12! nor does it submit to any jurisdiction.
13!
14! PURPOSE
15! -------
16!   The modular radiation scheme is contained in a separate
17!   library. SETUP_RADIATION_SCHEME in this module sets up a small
18!   number of global variables needed to store the information for it.
19!
20!   Lower case is used for variables and types taken from the
21!   radiation library
22!
23! INTERFACE
24! ---------
25!   SETUP_RADIATION_SCHEME is called from SUECRAD.  The radiation
26!   scheme is actually run using the RADIATION_SCHEME routine (not in
27!   this module).
28!
29! AUTHOR
30! ------
31!   Robin Hogan, ECMWF
32!   Original: 2015-09-16
33!
34! MODIFICATIONS
35! -------------
36!
37!-----------------------------------------------------------------------
38
39  USE PARKIND1,         ONLY : JPRB
40  USE radiation_config, ONLY : config_type, &
41       &                       ISolverMcICA, ISolverSpartacus, &
42       &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
43       &                       IIceModelFu, IIceModelBaran, &
44       &                       IOverlapExponentialRandom
45
46  IMPLICIT NONE
47
48  ! Store configuration information for the radiation scheme in a
49  ! global variable
50  type(config_type) :: rad_config
51
52  ! Ultraviolet weightings
53  INTEGER         :: NWEIGHT_UV
54  INTEGER         :: IBAND_UV(100)
55  REAL(KIND=JPRB) :: WEIGHT_UV(100)
56  ! Photosynthetically active radiation weightings
57  INTEGER         :: NWEIGHT_PAR
58  INTEGER         :: IBAND_PAR(100)
59  REAL(KIND=JPRB) :: WEIGHT_PAR(100)
60
61  ! Background aerosol is specified in an ugly way: using the old
62  ! Tegen fields that are in terms of optical depth, and converted to
63  ! mass mixing ratio via the relevant mass-extinction coefficient
64  INTEGER, PARAMETER :: ITYPE_TROP_BG_AER = 8 ! hydrophobic organic
65  INTEGER, PARAMETER :: ITYPE_STRAT_BG_AER=12 ! non-absorbing sulphate
66  REAL(KIND=JPRB)    :: TROP_BG_AER_MASS_EXT
67  REAL(KIND=JPRB)    :: STRAT_BG_AER_MASS_EXT
68
69CONTAINS
70
71  ! This routine copies information between the IFS radiation
72  ! configuration (stored in global variables) and the radiation
73  ! configuration of the modular radiation scheme (stored in
74  ! rad_config).  The optional input logical LOUTPUT controls whether
75  ! to print lots of information during the setup stage (default is
76  ! no).
77  SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT)
78
79    USE YOMHOOK,  ONLY : LHOOK, DR_HOOK
80!    USE YOMLUN,   ONLY : NULNAM, NULOUT, NULERR
81    USE YOMLUN,   ONLY : NULOUT, NULERR
82    USE YOESRTWN, ONLY : NMPSRTM
83! AI ATTENTION
84!    USE YOERAD,   ONLY : YRERAD
85
86    USE radiation_interface,      ONLY : setup_radiation
87    USE radiation_aerosol_optics, ONLY : dry_aerosol_sw_mass_extinction
88
89!#include "posname.intfb.h"
90
91    ! Whether or not to provide information on the radiation scheme
92    ! configuration
93    LOGICAL, INTENT(IN), OPTIONAL :: LOUTPUT
94
95    ! Verbosity of configuration information 0=none, 1=warning,
96    ! 2=info, 3=progress, 4=detailed, 5=debug
97    INTEGER :: IVERBOSESETUP
98    INTEGER :: ISTAT
99
100    REAL(KIND=JPRB) :: ZHOOK_HANDLE
101
102    character(len=512) :: file_name
103
104    logical :: lprint_setp=.TRUE.
105
106    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',0,ZHOOK_HANDLE)
107
108    ! *** GENERAL SETUP ***
109
110    ! Configure verbosity of setup of radiation scheme
111 
112    print*,'********** Dans radiation_setup *****************'
113
114    IVERBOSESETUP = 4 ! Provide plenty of information
115    IF (PRESENT(LOUTPUT)) THEN
116      IF (.NOT. LOUTPUT) THEN
117        IVERBOSESETUP = 1 ! Warnings and errors only
118      ENDIF
119    ENDIF
120    rad_config%iverbosesetup = IVERBOSESETUP
121    if (lprint_setp) then
122      print*,'Dans radiation_setup '
123      print*,'rad_config%iverbosesetup =', rad_config%iverbosesetup
124    endif
125
126    IF (IVERBOSESETUP > 1) THEN
127      WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------'
128      WRITE(NULOUT,'(a)') 'RADIATION_SETUP'
129    ENDIF
130
131    ! Normal operation of the radiation scheme displays only errors
132    ! and warnings
133    rad_config%iverbose = 5
134    if (lprint_setp) then
135      print*,'rad_config%iverbose =', rad_config%iverbose
136    endif
137    ! For the time being, ensure a valid default directory name
138    rad_config%directory_name = 'data'
139    if (lprint_setp) then
140      print*,'rad_config%directory_name =', rad_config%directory_name
141    endif
142
143    ! Do we do Hogan and Bozzo (2014) approximate longwave updates?
144! AI ATTENTION (ifs : )
145!    rad_config%do_lw_derivatives = YRERAD%LAPPROXLWUPDATE
146    rad_config%do_lw_derivatives = .false.
147    if (lprint_setp) then
148      print*,'rad_config%do_lw_derivatives =', rad_config%do_lw_derivatives   
149    endif
150
151    ! Surface spectral fluxes are needed for spectral shortwave albedo
152    ! calculation
153! AI ATTENTION test (ifs : T)
154!    rad_config%do_save_spectral_flux = .FALSE.
155    rad_config%do_surface_sw_spectral_flux = .TRUE.
156    if (lprint_setp) then
157      print*,'rad_config%do_surface_sw_spectral_flux =', &
158            rad_config%do_surface_sw_spectral_flux
159    endif
160
161    ! *** SETUP GAS OPTICS ***
162
163    ! Assume IFS has already set-up RRTM, so the setup_radiation
164    ! routine below does not have to (ifs : F)
165    print*,'i_gas_model =',rad_config%i_gas_model
166    rad_config%do_setup_ifsrrtm = .TRUE.
167    if (lprint_setp) then
168      print*,'rad_config%do_setup_ifsrrtm =', rad_config%do_setup_ifsrrtm
169    endif
170
171    ! *** SETUP CLOUD OPTICS ***
172
173    ! Setup liquid optics
174! AI ATTENTION
175! Choix offline : liquid_model_name = "SOCRATES"
176!    IF (YRERAD%NLIQOPT == 2) THEN
177!      rad_config%i_liq_model = ILiquidModelSlingo
178!    ELSEIF (YRERAD%NLIQOPT == 3) THEN
179      rad_config%i_liq_model = ILiquidModelSOCRATES
180      if (lprint_setp) then
181        print*,'rad_config%i_liq_model =',rad_config%i_liq_model
182      endif
183
184!    ELSE
185!      WRITE(NULERR,'(a,i0)') 'Unavailable liquid optics model in modular radiation scheme: NLIQOPT=', &
186!           &  YRERAD%NLIQOPT
187!      CALL ABOR1('RADIATION_SETUP: error interpreting NLIQOPT')   
188!    ENDIF
189
190    ! Setup ice optics
191! Choix offline : ice_model_name    = "Fu-IFS"
192!    IF (YRERAD%NICEOPT == 3) THEN
193      rad_config%i_ice_model = IIceModelFu
194      if (lprint_setp) then
195        print*,'rad_config%i_ice_model =', rad_config%i_ice_model
196      endif
197!    ELSEIF (YRERAD%NICEOPT == 4) THEN
198!      rad_config%i_ice_model = IIceModelBaran
199!    ELSE
200!      WRITE(NULERR,'(a,i0)') 'Unavailable ice optics model in modular radiation scheme: NICEOPT=', &
201!           &  YRERAD%NICEOPT
202!      CALL ABOR1('RADIATION_SETUP: error interpreting NICEOPT')   
203!    ENDIF
204
205    ! For consistency with earlier versions of the IFS radiation
206    ! scheme, we perform shortwave delta-Eddington scaling *after* the
207    ! merge of the cloud, aerosol and gas optical properties.  Set
208    ! this to "false" to do the scaling on the cloud and aerosol
209    ! properties separately before merging with gases. Note that this
210    ! is not compatible with the SPARTACUS solver.
211    rad_config%do_sw_delta_scaling_with_gases = .FALSE.
212    if (lprint_setp) then
213      print*,'rad_config%do_sw_delta_scaling_with_gases =', &
214            rad_config%do_sw_delta_scaling_with_gases
215    endif
216
217    ! Use Exponential-Exponential cloud overlap to match original IFS
218    ! implementation of Raisanen cloud generator
219    rad_config%i_overlap_scheme = IOverlapExponentialRandom
220    if (lprint_setp) then
221      print*,'rad_config%i_overlap_scheme =', rad_config%i_overlap_scheme
222    endif
223
224    ! *** SETUP AEROSOLS ***
225! AI ATTENTION
226!    rad_config%use_aerosols = .TRUE. !(ifs)
227    rad_config%use_aerosols = .FALSE.
228    if (lprint_setp) then
229      print*,'rad_config%use_aerosols =', rad_config%use_aerosols
230    endif
231
232!    IF (YRERAD%NAERMACC > 0) THEN
233      ! Using MACC climatology - in this case the aerosol optics file
234      ! will be chosen automatically
235
236      ! 12 IFS aerosol classes: 1-3 Sea salt, 4-6 Boucher desert dust,
237      ! 7 hydrophilic organics, 8 hydrophobic organics, 9&10
238      ! hydrophobic black carbon, 11 ammonium sulphate, 12 inactive
239      ! SO2
240      rad_config%n_aerosol_types = 12
241      if (lprint_setp) then
242        print*,'rad_config%n_aerosol_types =', rad_config%n_aerosol_types
243      endif
244
245      ! Indices to the aerosol optical properties in
246      ! aerosol_ifs_rrtm_*.nc, for each class, where negative numbers
247      ! index hydrophilic aerosol types and positive numbers index
248      ! hydrophobic aerosol types
249      rad_config%i_aerosol_type_map = 0 ! There can be up to 256 types
250!      if (lprint_setp) then
251!        print*,'rad_config%i_aerosol_type_map =', rad_config%i_aerosol_type_map
252!      endif
253
254      rad_config%i_aerosol_type_map(1:12) = (/ &
255           &  -1, &  ! Sea salt, size bin 1 (OPAC)
256           &  -2, &  ! Sea salt, size bin 2 (OPAC)
257           &  -3, &  ! Sea salt, size bin 3 (OPAC)
258           &   7, &  ! Desert dust, size bin 1 (Woodward 2001)
259           &   8, &  ! Desert dust, size bin 2 (Woodward 2001)
260           &   9, &  ! Desert dust, size bin 3 (Woodward 2001)
261           &  -4, &  ! Hydrophilic organic matter (OPAC)
262           &  10, &  ! Hydrophobic organic matter (OPAC)
263           &  11, &  ! Black carbon (Boucher)
264           &  11, &  ! Black carbon (Boucher)
265           &  -5, &  ! Ammonium sulphate (OPAC)
266           &  14 /)  ! Stratospheric sulphate (hand edited from OPAC)
267!     if (lprint_setp) then
268!       print*,'rad_config%i_aerosol_type_map =', rad_config%i_aerosol_type_map
269!     endif
270
271      ! Background aerosol mass-extinction coefficients are obtained
272      ! after the configuration files have been read - see later in
273      ! this routine.
274
275!    ELSE
276      ! Using Tegen climatology
277!      rad_config%n_aerosol_types = 6
278!      rad_config%i_aerosol_type_map = 0 ! There can be up to 256 types
279!      rad_config%i_aerosol_type_map(1:6) = (/ &
280!           &  1, &  ! Continental background
281!           &  2, &  ! Maritime
282!           &  3, &  ! Desert
283!           &  4, &  ! Urban
284 !          &  5, &  ! Volcanic active
285!           &  6 /)  ! Stratospheric background
286
287      ! Manually set the aerosol optics file name (the directory will
288      ! be added automatically)
289!      rad_config%aerosol_optics_override_file_name = 'aerosol_ifs_rrtm_tegen.nc'
290!    ENDIF
291
292! *** SETUP SOLVER ***
293
294    ! 3D effects are off by default (ifs)
295    rad_config%do_3d_effects = .TRUE.
296    if (lprint_setp) then
297      print*,'rad_config%do_3d_effects=', rad_config%do_3d_effects
298    endif
299
300    ! Select longwave solver
301! AI ATTENTION
302!    SELECT CASE (YRERAD%NLWSOLVER)
303!    CASE(0)
304!      rad_config%i_solver_lw = ISolverMcICA
305!    CASE(1)
306      rad_config%i_solver_lw = ISolverSpartacus
307      if (lprint_setp) then
308        print*,'rad_config%i_solver_lw =', rad_config%i_solver_lw
309      endif
310
311!    CASE(2)
312!      rad_config%i_solver_lw = ISolverSpartacus
313!      rad_config%do_3d_effects = .TRUE.
314!    CASE DEFAULT
315!      WRITE(NULERR,'(a,i0)') 'Unknown value for NLWSOLVER: ', YRERAD%NLWSOLVER
316!      CALL ABOR1('RADIATION_SETUP: error interpreting NLWSOLVER')
317!    END SELECT
318
319    ! Select shortwave solver
320!    SELECT CASE (YRERAD%NSWSOLVER)
321!    CASE(0)
322!      rad_config%i_solver_sw = ISolverMcICA
323!    CASE(1)
324      rad_config%i_solver_sw = ISolverSpartacus
325      if (lprint_setp) then
326        print*,'rad_config%i_solver_sw =', rad_config%i_solver_sw
327      endif
328
329!      rad_config%do_3d_effects = .FALSE.
330!      IF (YRERAD%NLWSOLVER == 2) THEN
331!        CALL ABOR1('RADIATION_SETUP: cannot represent 3D effects in LW but not SW')
332!      ENDIF
333!    CASE(2)
334!      rad_config%i_solver_sw = ISolverSpartacus
335!      rad_config%do_3d_effects = .TRUE.
336!      IF (YRERAD%NLWSOLVER == 1) THEN
337!        CALL ABOR1('RADIATION_SETUP: cannot represent 3D effects in SW but not LW')
338!      ENDIF
339!    CASE DEFAULT
340!      WRITE(NULERR,'(a,i0)') 'Unknown value for NSWSOLVER: ', YRERAD%NSWSOLVER
341!      CALL ABOR1('RADIATION_SETUP: error interpreting NSWSOLVER')
342!    END SELECT
343
344    ! SPARTACUS solver requires delta scaling to be done separately
345    ! for clouds & aerosols
346    IF (rad_config%i_solver_sw == ISolverSpartacus) THEN
347      rad_config%do_sw_delta_scaling_with_gases = .FALSE.
348    ENDIF
349
350    ! Do we represent longwave scattering?
351    rad_config%do_lw_cloud_scattering = .TRUE.
352    rad_config%do_lw_aerosol_scattering = .TRUE.
353    if (lprint_setp) then
354      print*,'rad_config%do_lw_cloud_scattering =', &
355           rad_config%do_lw_cloud_scattering
356      print*,'rad_config%do_lw_aerosol_scattering =', &
357           rad_config%do_lw_aerosol_scattering
358    endif
359
360!    SELECT CASE (YRERAD%NLWSCATTERING)
361!    CASE(1)
362!      rad_config%do_lw_cloud_scattering = .TRUE.
363!    CASE(2)
364!      rad_config%do_lw_cloud_scattering = .TRUE.
365!      IF (YRERAD%NAERMACC > 0) THEN
366        ! Tegen climatology omits data required to do longwave
367        ! scattering by aerosols, so only turn this on with a more
368        ! recent scattering database
369!      ENDIF
370!    END SELECT
371
372
373    ! *** IMPLEMENT SETTINGS ***
374
375    ! For advanced configuration, the configuration data for the
376    ! "radiation" project can specified directly in the namelist.
377    ! However, the variable naming convention is not consistent with
378    ! the rest of the IFS.  For basic configuration there are specific
379    ! variables in the NAERAD namelist available in the YRERAD
380    ! structure.
381!    CALL POSNAME(NULNAM, 'RADIATION', ISTAT)
382!    SELECT CASE (ISTAT)
383!      CASE(0)
384!        CALL rad_config%read(unit=NULNAM)
385!      CASE(1)
386!        WRITE(NULOUT,'(a)') 'Namelist RADIATION not found, using settings from NAERAD only'
387!      CASE DEFAULT
388!        CALL ABOR1('RADIATION_SETUP: error reading RADIATION section of namelist file')
389!    END SELECT
390
391! AI ATTENTION test
392    file_name="namelist_ecrad"
393    call rad_config%read(file_name=file_name)
394
395    ! Print configuration
396!    IF (IVERBOSESETUP > 1) THEN
397!      WRITE(NULOUT,'(a)') 'Radiation scheme settings:'
398!      CALL rad_config%print(IVERBOSE=IVERBOSESETUP)
399!    ENDIF
400
401    ! Use configuration data to set-up radiation scheme, including
402    ! reading scattering datafiles
403    CALL setup_radiation(rad_config)
404
405    ! Populate the mapping between the 14 RRTM shortwave bands and the
406    ! 6 albedo inputs. The mapping according to the stated wavelength
407    ! ranges of the 6-band model does not match the hard-wired mapping
408    ! in NMPSRTM, but only the hard-wired values produce sensible
409    ! results...
410    ! Note that NMPSRTM(:)=(/  6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 2, 2, 1, 6 /)
411! AI
412!!    NMPSRTM(:)=(/ 6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 2, 2, 1, 6 /)
413!!    rad_config%i_albedo_from_band_sw = NMPSRTM
414!    call rad_config%define_sw_albedo_intervals(6, &
415!             &  (/ 0.25e-6_jprb, 0.44e-6_jprb, 1.19e-6_jprb, &
416!             &     2.38e-6_jprb, 4.00e-6_jprb /),  (/ 1,2,3,4,5,6 /))
417    call rad_config%define_sw_albedo_intervals(6, &
418       &  [0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, &
419       &   1.19e-6_jprb, 2.38e-6_jprb], [1,2,3,4,5,6])
420    ! Likewise between the 16 RRTM longwave bands and the 2 emissivity
421    ! inputs (info taken from rrtm_ecrt_140gp_mcica.F90) representing
422    ! outside and inside the window region of the spectrum
423!     rad_config%i_emiss_from_band_lw = (/ 1,1,1,1,1,2,2,2,1,1,1,1,1,1,1,1 /)
424! AI
425!!    call rad_config%define_lw_emiss_intervals(3, &
426!!         &  (/ 8.0e-6_jprb,13.0e-6_jprb /),  (/ 1,2,1 /))
427
428!    ! Get spectral weightings for UV and PAR
429    call rad_config%get_sw_weights(0.2e-6_jprb, 0.4415e-6_jprb, &
430         &  NWEIGHT_UV, IBAND_UV, WEIGHT_UV, 'ultraviolet')
431    call rad_config%get_sw_weights(0.4e-6_jprb, 0.7e-6_jprb, &
432         &  NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, &
433         &  'photosynthetically active radiation, PAR')
434
435!    IF (YRERAD%NAERMACC > 0) THEN
436      ! With the MACC aerosol climatology we need to add in the
437      ! background aerosol afterwards using the Tegen arrays.  In this
438      ! case we first configure the background aerosol mass-extinction
439      ! coefficient at 550 nm, which corresponds to the 10th RRTMG
440      ! shortwave band.
441!      TROP_BG_AER_MASS_EXT  = dry_aerosol_sw_mass_extinction(rad_config, &
442!           &                                   ITYPE_TROP_BG_AER, 10)
443!      STRAT_BG_AER_MASS_EXT = dry_aerosol_sw_mass_extinction(rad_config, &
444!           &                                   ITYPE_STRAT_BG_AER, 10)
445     
446!      WRITE(NULOUT,'(a,i0)') 'Tropospheric bacground uses aerosol type ', &
447!           &                 ITYPE_TROP_BG_AER
448!      WRITE(NULOUT,'(a,i0)') 'Stratospheric bacground uses aerosol type ', &
449!           &                 ITYPE_STRAT_BG_AER
450!    ENDIF     
451     
452    IF (IVERBOSESETUP > 1) THEN
453      WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------'
454    ENDIF
455
456    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE)
457
458  END SUBROUTINE SETUP_RADIATION_SCHEME
459
460END MODULE RADIATION_SETUP
Note: See TracBrowser for help on using the repository browser.