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

Last change on this file since 4773 was 4773, checked in by idelkadi, 7 months ago
  • Update of Ecrad in LMDZ The same organization of the Ecrad offline version is retained in order to facilitate the updating of Ecrad in LMDZ and the comparison between online and offline results. version 1.6.1 of Ecrad (https://github.com/lguez/ecrad.git)
  • Implementation of the double call of Ecrad in LMDZ


File size: 21.7 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!   derived type that contains the configuration object for the
19!   radiation scheme, plus a small number of additional variables
20!   needed for its implemenation in the IFS.
21!
22! INTERFACE
23! ---------
24!   SETUP_RADIATION_SCHEME is called from SUECRAD.  The radiation
25!   scheme is actually run using the RADIATION_SCHEME routine (not in
26!   this module).
27!
28! AUTHOR
29! ------
30!   Robin Hogan, ECMWF
31!   Original: 2015-09-16
32!
33! MODIFICATIONS
34! -------------
35!   2017-03-03  R. Hogan   Put global variables in TRADIATION derived type
36!   2017-11-17  S. Remy    Add Nitrates and SOA if NAERMACC=0
37!   2017-11-28  R. Hogan   Delta scaling applied to particles only
38!   2018-01-11  R. Hogan   Capability to scale solar spectrum in each band
39!   2018-04-20  A. Bozzo   Added capability to read in aerosol optical properties
40!                          at selected wavelengths
41!   2019-01-21  R. Hogan   Explicit albedo and emissivity spectral definitions
42!                          leading to smarter weighting in ecRad
43!
44
45!-----------------------------------------------------------------------
46
47USE PARKIND1,         ONLY :   JPRB,JPIM
48USE radiation_config, ONLY :   config_type, &
49       &                       ISolverMcICA, ISolverSpartacus, &
50       &                       ISolverTripleclouds, ISolverCloudless, &
51       &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
52       &                       IIceModelFu, IIceModelBaran, &
53       &                       IOverlapExponential, IOverlapMaximumRandom, &
54       &                       IOverlapExponentialRandom
55USE YOERAD, ONLY : TERAD
56
57IMPLICIT NONE
58
59SAVE
60
61! Background aerosol is specified in an ugly way: using the old Tegen
62! fields that are in terms of optical depth, and converted to mass
63! mixing ratio via the relevant mass-extinction coefficient. The
64! following are the indices to the aerosol types used to describe
65! tropospheric and stratospheric background aerosol.
66INTEGER(KIND=JPIM), PARAMETER :: ITYPE_TROP_BG_AER = 8 ! hydrophobic organic
67INTEGER(KIND=JPIM), PARAMETER :: ITYPE_STRAT_BG_AER=12 ! non-absorbing sulphate
68
69! This derived type contains configuration information for the
70! radiation scheme plus a few additional variables and parameters
71! needed for the IFS interface to it
72TYPE :: TRADIATION
73
74  ! Configuration for wider aspects of the radiation scheme
75  TYPE(TERAD) :: YRERAD
76
77  ! Configuration information for the ecRad radiation scheme
78  type(config_type)  :: rad_config
79
80  ! Ultraviolet weightings
81  INTEGER(KIND=JPIM) :: NWEIGHT_UV
82  INTEGER(KIND=JPIM) :: IBAND_UV(100)
83  REAL(KIND=JPRB)    :: WEIGHT_UV(100)
84  ! Photosynthetically active radiation weightings
85  INTEGER(KIND=JPIM) :: NWEIGHT_PAR
86  INTEGER(KIND=JPIM) :: IBAND_PAR(100)
87  REAL(KIND=JPRB)    :: WEIGHT_PAR(100)
88  ! Mass-extinction coefficient (m2 kg-1) of tropospheric and
89  ! stratospheric background aerosol at 550 nm
90  REAL(KIND=JPRB)    :: TROP_BG_AER_MASS_EXT
91  REAL(KIND=JPRB)    :: STRAT_BG_AER_MASS_EXT
92
93END TYPE TRADIATION
94
95! Dummy type
96TYPE :: TCOMPO
97  LOGICAL :: LAERNITRATE = .false.
98  LOGICAL :: LAERSOA = .false.
99END TYPE TCOMPO
100
101CONTAINS
102
103  ! This routine copies information between the IFS radiation
104  ! configuration (stored mostly in YDERAD) and the radiation
105  ! configuration of the modular radiation scheme (stored in
106  ! PRADIATION%rad_config).  The optional input logical LDOUTPUT
107  ! controls whether to print lots of information during the setup
108  ! stage (default is no).
109  SUBROUTINE SETUP_RADIATION_SCHEME(PRADIATION,LDOUTPUT,FILE_NAME)
110
111    USE YOMHOOK,  ONLY : LHOOK, DR_HOOK, JPHOOK
112    USE YOMLUN,   ONLY : NULOUT, NULERR
113    !USE YOESRTWN, ONLY : NMPSRTM
114    USE YOERAD,   ONLY : TERAD
115    USE YOEPHY,   ONLY : TEPHY
116    !USE YOMCOMPO, ONLY : TCOMPO
117
118    USE RADIATION_INTERFACE,      ONLY : SETUP_RADIATION
119    USE RADIATION_AEROSOL_OPTICS, ONLY : DRY_AEROSOL_MASS_EXTINCTION
120
121    ! Radiation configuration information
122    TYPE(TCOMPO) :: YDCOMPO
123    TYPE(TRADIATION)  ,INTENT(INOUT), TARGET  :: PRADIATION
124    CHARACTER(LEN=512),INTENT(IN), OPTIONAL   :: FILE_NAME
125
126    ! Whether or not to print out information on the radiation scheme
127    ! configuration
128    LOGICAL, INTENT(IN), OPTIONAL :: LDOUTPUT
129
130    ! Verbosity of configuration information 0=none, 1=warning,
131    ! 2=info, 3=progress, 4=detailed, 5=debug
132    INTEGER(KIND=JPIM) :: IVERBOSESETUP
133    !INTEGER(KIND=JPIM) :: ISTAT
134
135    ! Data directory name
136    CHARACTER(LEN=256) :: CL_DATA_DIR
137
138    ! Arrays to avoid temporaries
139    REAL(KIND=JPRB)    :: ZWAVBOUND(15)
140    INTEGER(KIND=JPIM) :: IBAND(16)
141
142    ! Do we use the nearest ecRad band to the albedo/emissivity
143    ! intervals, or a more intelligent weighting?
144    LOGICAL :: LL_DO_NEAREST_SW_ALBEDO, LL_DO_NEAREST_LW_EMISS
145
146    REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
147
148!#include "posname.intfb.h"
149#include "abor1.intfb.h"
150
151    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',0,ZHOOK_HANDLE)
152
153    ! *** GENERAL SETUP ***
154    ASSOCIATE(YDERAD=>PRADIATION%YRERAD)
155    ASSOCIATE(RAD_CONFIG=>PRADIATION%RAD_CONFIG,&
156              & LAERNITRATE=>YDCOMPO%LAERNITRATE, &
157              & LAERSOA=>YDCOMPO%LAERSOA, &
158              & YSPECTPLANCK=>YDERAD%YSPECTPLANCK)
159
160    ! Configure verbosity of setup of radiation scheme
161    IVERBOSESETUP = 4 ! Provide plenty of information
162    IF (PRESENT(LDOUTPUT)) THEN
163      IF (.NOT. LDOUTPUT) THEN
164        IVERBOSESETUP = 1 ! Warnings and errors only
165      ENDIF
166    ENDIF
167    RAD_CONFIG%IVERBOSESETUP = IVERBOSESETUP
168
169    IF (IVERBOSESETUP > 1) THEN
170      WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------'
171      WRITE(NULOUT,'(a)') 'RADIATION_SETUP: ecRad 1.5'
172    ENDIF
173
174    ! Normal operation of the radiation scheme displays only errors
175    ! and warnings
176    RAD_CONFIG%IVERBOSE = 1
177
178    ! Read data directory name from the DATA environment variable
179    CALL GETENV("DATA", CL_DATA_DIR)
180    IF (CL_DATA_DIR /= " ") THEN
181      RAD_CONFIG%DIRECTORY_NAME = TRIM(CL_DATA_DIR) // "/ifsdata"
182    ELSE
183      ! If DATA not present, use the current directory
184      RAD_CONFIG%DIRECTORY_NAME = "."
185    ENDIF
186
187    ! Do we do Hogan and Bozzo (2015) approximate longwave updates?
188    RAD_CONFIG%DO_LW_DERIVATIVES = YDERAD%LAPPROXLWUPDATE
189
190    ! If we are to perform Hogan and Bozzo (2015) approximate
191    ! shortwave updates then we need the downwelling direct and
192    ! diffuse shortwave fluxes at the surface in each albedo spectral
193    ! interval
194    RAD_CONFIG%DO_CANOPY_FLUXES_SW = YDERAD%LAPPROXSWUPDATE
195
196    ! If we are to perform approximate longwave updates and we are
197    ! using the new 6-interval longwave emissivity scheme then we need
198    ! ecRad to compute the downwelling surface longwave fluxes in each
199    ! emissivity spectral interval
200    IF (YDERAD%NLWOUT > 1) THEN
201      RAD_CONFIG%DO_CANOPY_FLUXES_LW = .TRUE.
202    ENDIF
203
204    ! Surface spectral fluxes are needed for UV and PAR calculations
205    RAD_CONFIG%DO_SURFACE_SW_SPECTRAL_FLUX = .TRUE.
206
207
208    ! *** SETUP GAS OPTICS ***
209
210    ! Assume IFS has already set-up RRTM, so the setup_radiation
211    ! routine below does not have to
212    !RAD_CONFIG%DO_SETUP_IFSRRTM = .FALSE.
213
214
215    ! *** SETUP CLOUD OPTICS ***
216
217    ! Setup liquid optics
218    IF (YDERAD%NLIQOPT == 2) THEN
219      RAD_CONFIG%I_LIQ_MODEL = ILIQUIDMODELSLINGO
220    ELSEIF (YDERAD%NLIQOPT == 4) THEN
221      RAD_CONFIG%I_LIQ_MODEL = ILIQUIDMODELSOCRATES
222    ELSE
223      WRITE(NULERR,'(a,i0)') '*** Error: Unavailable liquid optics model in modular radiation scheme: NLIQOPT=', &
224           &  YDERAD%NLIQOPT
225      CALL ABOR1('RADIATION_SETUP: error interpreting NLIQOPT')
226    ENDIF
227
228    ! Setup ice optics
229    IF (YDERAD%NICEOPT == 3) THEN
230      RAD_CONFIG%I_ICE_MODEL = IICEMODELFU
231      IF (YDERAD%LFU_LW_ICE_OPTICS_BUG) THEN
232        RAD_CONFIG%DO_FU_LW_ICE_OPTICS_BUG = .TRUE.
233      ENDIF
234    ELSEIF (YDERAD%NICEOPT == 4) THEN
235      RAD_CONFIG%I_ICE_MODEL = IICEMODELBARAN
236    ELSE
237      WRITE(NULERR,'(a,i0)') '*** Error: Unavailable ice optics model in modular radiation scheme: NICEOPT=', &
238           &  YDERAD%NICEOPT
239!!      CALL ABOR1('RADIATION_SETUP: error interpreting NICEOPT')   !db fix
240    ENDIF
241
242    ! For consistency with earlier versions of the IFS radiation
243    ! scheme, until 45R1 we performed shortwave delta-Eddington
244    ! scaling after the merge of the cloud, aerosol and gas optical
245    ! properties.  Setting this to "false" does the scaling on the
246    ! cloud and aerosol properties separately before merging with
247    ! gases, which is more physically appropriate. The impact is very
248    ! small (see item 6 of table 2 of Technical Memo 787).
249    RAD_CONFIG%DO_SW_DELTA_SCALING_WITH_GASES = .FALSE.
250
251
252    ! *** SETUP AEROSOLS ***
253
254    RAD_CONFIG%USE_AEROSOLS = .TRUE.
255
256    ! If monochromatic aerosol properties are available they will be
257    ! read in automatically so the following is not needed
258    !IF (YDEAERATM%LAERRAD) RAD_CONFIG%AEROSOL_OPTICS%READ_MONOCHROMATIC_OPTICS=.TRUE.
259
260    IF (YDERAD%NAERMACC == 1) THEN
261      ! Using MACC climatology or prognostic aerosol variables - in
262      ! this case the aerosol optics file will be chosen automatically
263
264      ! 12 IFS aerosol classes: 1-3 Sea salt, 4-6 Boucher desert dust,
265      ! 7 hydrophilic organics, 8 hydrophobic organics, 9&10
266      ! hydrophobic black carbon, 11 ammonium sulphate, 12 inactive
267      ! SO2
268      RAD_CONFIG%N_AEROSOL_TYPES = 12
269
270      ! Indices to the aerosol optical properties in
271      ! aerosol_ifs_rrtm_*.nc, for each class, where negative numbers
272      ! index hydrophilic aerosol types and positive numbers index
273      ! hydrophobic aerosol types
274      RAD_CONFIG%I_AEROSOL_TYPE_MAP = 0 ! There can be up to 256 types
275      RAD_CONFIG%I_AEROSOL_TYPE_MAP(1:12) = (/&
276           &  -1,&! Sea salt, size bin 1 (OPAC)
277           &  -2,&! Sea salt, size bin 2 (OPAC)
278           &  -3,&! Sea salt, size bin 3 (OPAC)
279           &  7,&! Desert dust, size bin 1 (Woodward 2001)
280           &  8,&! Desert dust, size bin 2 (Woodward 2001)
281           &  9,&! Desert dust, size bin 3 (Woodward 2001)
282           &  -4,&! Hydrophilic organic matter (Hess, OPAC)
283           &  10,&! Hydrophobic organic matter (Hess, OPAC)
284           &  11,&! Black carbon (Hess, OPAC)
285           &  11,&! Black carbon (Hess, OPAC)
286           &  -5,&! Ammonium sulphate (GACP)
287           &  14 /)  ! Stratospheric sulphate (GACP) [ climatology only ]
288
289      ! Background aerosol mass-extinction coefficients are obtained
290      ! after the configuration files have been read - see later in
291      ! this routine.
292
293      ! The default aerosol optics file is the following - please
294      ! update here, not in radiation/module/radiation_config.F90
295      RAD_CONFIG%AEROSOL_OPTICS_OVERRIDE_FILE_NAME = 'aerosol_ifs_rrtm_46R1_with_NI_AM.nc'
296
297    ELSE
298      ! Using Tegen climatology
299      RAD_CONFIG%N_AEROSOL_TYPES = 6
300      RAD_CONFIG%I_AEROSOL_TYPE_MAP = 0 ! There can be up to 256 types
301      RAD_CONFIG%I_AEROSOL_TYPE_MAP(1:6) = (/&
302           &  1,&! Continental background
303           &  2,&! Maritime
304           &  3,&! Desert
305           &  4,&! Urban
306           &  5,&! Volcanic active
307           &  6 /)  ! Stratospheric background
308
309      ! Manually set the aerosol optics file name (the directory will
310      ! be added automatically)
311      RAD_CONFIG%AEROSOL_OPTICS_OVERRIDE_FILE_NAME = 'aerosol_ifs_rrtm_tegen.nc'
312    ENDIF
313
314    ! *** SETUP SOLVER ***
315
316    ! 3D effects are off by default
317    RAD_CONFIG%DO_3D_EFFECTS = .FALSE.
318
319    ! Select longwave solver
320    SELECT CASE (YDERAD%NLWSOLVER)
321    CASE(0)
322      RAD_CONFIG%I_SOLVER_LW = ISOLVERMCICA
323    CASE(1)
324      RAD_CONFIG%I_SOLVER_LW = ISOLVERSPARTACUS
325    CASE(2)
326      RAD_CONFIG%I_SOLVER_LW = ISOLVERSPARTACUS
327      RAD_CONFIG%DO_3D_EFFECTS = .TRUE.
328    CASE(3)
329      RAD_CONFIG%I_SOLVER_LW = ISOLVERTRIPLECLOUDS
330    CASE(4)
331      RAD_CONFIG%I_SOLVER_LW = ISOLVERCLOUDLESS
332    CASE DEFAULT
333      WRITE(NULERR,'(a,i0)') '*** Error: Unknown value for NLWSOLVER: ', YDERAD%NLWSOLVER
334      CALL ABOR1('RADIATION_SETUP: error interpreting NLWSOLVER')
335    END SELECT
336
337    ! Select shortwave solver
338    SELECT CASE (YDERAD%NSWSOLVER)
339    CASE(0)
340      RAD_CONFIG%I_SOLVER_SW = ISOLVERMCICA
341    CASE(1)
342      RAD_CONFIG%I_SOLVER_SW = ISOLVERSPARTACUS
343      RAD_CONFIG%DO_3D_EFFECTS = .FALSE.
344      IF (YDERAD%NLWSOLVER == 2) THEN
345        CALL ABOR1('RADIATION_SETUP: cannot represent 3D effects in LW but not SW')
346      ENDIF
347    CASE(2)
348      RAD_CONFIG%I_SOLVER_SW = ISOLVERSPARTACUS
349      RAD_CONFIG%DO_3D_EFFECTS = .TRUE.
350      IF (YDERAD%NLWSOLVER == 1) THEN
351        CALL ABOR1('RADIATION_SETUP: cannot represent 3D effects in SW but not LW')
352      ENDIF
353    CASE(3)
354      RAD_CONFIG%I_SOLVER_SW = ISOLVERTRIPLECLOUDS
355    CASE(4)
356      RAD_CONFIG%I_SOLVER_SW = ISOLVERCLOUDLESS
357    CASE DEFAULT
358      WRITE(NULERR,'(a,i0)') '*** Error: Unknown value for NSWSOLVER: ', YDERAD%NSWSOLVER
359      CALL ABOR1('RADIATION_SETUP: error interpreting NSWSOLVER')
360    END SELECT
361
362    ! For stability the cloud effective size can't be too small in
363    ! SPARTACUS
364    RAD_CONFIG%MIN_CLOUD_EFFECTIVE_SIZE = 500.0_JPRB
365
366    ! SPARTACUS solver requires delta scaling to be done separately
367    ! for clouds & aerosols
368    IF (RAD_CONFIG%I_SOLVER_SW == ISOLVERSPARTACUS) THEN
369      RAD_CONFIG%DO_SW_DELTA_SCALING_WITH_GASES = .FALSE.
370    ENDIF
371
372    ! Do we represent longwave scattering?
373    RAD_CONFIG%DO_LW_CLOUD_SCATTERING = .FALSE.
374    RAD_CONFIG%DO_LW_AEROSOL_SCATTERING = .FALSE.
375    SELECT CASE (YDERAD%NLWSCATTERING)
376    CASE(1)
377      RAD_CONFIG%DO_LW_CLOUD_SCATTERING = .TRUE.
378    CASE(2)
379      RAD_CONFIG%DO_LW_CLOUD_SCATTERING = .TRUE.
380      IF (YDERAD%NAERMACC > 0) THEN
381        ! Tegen climatology omits data required to do longwave
382        ! scattering by aerosols, so only turn this on with a more
383        ! recent scattering database
384        RAD_CONFIG%DO_LW_AEROSOL_SCATTERING = .TRUE.
385      ENDIF
386    END SELECT
387
388    SELECT CASE (YDERAD%NCLOUDOVERLAP)
389    CASE (1)
390      RAD_CONFIG%I_OVERLAP_SCHEME = IOVERLAPMAXIMUMRANDOM
391    CASE (2)
392      ! Use Exponential-Exponential cloud overlap to match original IFS
393      ! implementation of Raisanen cloud generator
394      RAD_CONFIG%I_OVERLAP_SCHEME = IOVERLAPEXPONENTIAL
395    CASE (3)
396      RAD_CONFIG%I_OVERLAP_SCHEME = IOVERLAPEXPONENTIALRANDOM
397    CASE DEFAULT
398      WRITE(NULERR,'(a,i0)') '*** Error: Unknown value for NCLOUDOVERLAP: ', YDERAD%NCLOUDOVERLAP
399      CALL ABOR1('RADIATION_SETUP: error interpreting NCLOUDOVERLAP')
400    END SELECT
401
402    ! Change cloud overlap to exponential-random if Tripleclouds or
403    ! SPARTACUS selected as both the shortwave and longwave solvers
404    IF (RAD_CONFIG%I_OVERLAP_SCHEME /= IOVERLAPEXPONENTIALRANDOM &
405         & .AND. (     RAD_CONFIG%I_SOLVER_SW == ISOLVERTRIPLECLOUDS &
406         &        .OR. RAD_CONFIG%I_SOLVER_LW == ISOLVERTRIPLECLOUDS &
407         &        .OR. RAD_CONFIG%I_SOLVER_SW == ISOLVERSPARTACUS &
408         &        .OR. RAD_CONFIG%I_SOLVER_LW == ISOLVERSPARTACUS)) THEN
409      IF (RAD_CONFIG%I_SOLVER_SW == RAD_CONFIG%I_SOLVER_LW) THEN
410        WRITE(NULOUT,'(a)') 'Warning: Tripleclouds/SPARTACUS solver selected so changing cloud overlap to Exp-Ran'
411        RAD_CONFIG%I_OVERLAP_SCHEME = IOVERLAPEXPONENTIALRANDOM
412      ELSE
413        ! If the solvers are not the same and exponential-random has
414        ! not been selected then abort
415        WRITE(NULERR,'(a)') '*** Error: Tripleclouds and SPARTACUS solvers can only simulate exponential-random overlap'
416        CALL ABOR1('RADIATION_SETUP: Cloud overlap incompatible with solver')
417      ENDIF
418
419      ! For additional stability in SPARTACUS solver it helps if the
420      ! cloud fraction threshold is higher than the default of 1.0e-6
421      ! used for McICA; this is done for Tripleclouds too so that it
422      ! is a good control for SPARTACUS.
423      RAD_CONFIG%CLOUD_FRACTION_THRESHOLD = 2.5E-5_JPRB
424    ENDIF
425
426
427    ! Number of longwave surface emissivity intervals to use:
428    ! Traditional approach: one value of emissivty for parts of the
429    ! spectrum on either side of the infrared atmospheric window
430    ! (PEMIR), and one value for the window itself (PEMIW)
431    YDERAD%NLWEMISS = 2
432    ! ...and the longwave approximate update scheme uses a single
433    ! broadband emissivity
434    YDERAD%NLWOUT   = 1
435    ! Create a spectral Planck look-up table, used by RADHEATN.  Note
436    ! that this routine makes use of the length of its third argument.
437    ! The wavelength bounds (metres) allow for the first emissivity to
438    ! represent values outside the infrared atmospheric window, and the
439    ! second emissivity to represent values within it.
440    CALL YDERAD%YSPECTPLANCK%INIT(2, [ 8.0E-6_JPRB, 13.0E-6_JPRB ], &
441         &  [ 1,2,1 ])
442     
443    ! Populate the mapping between the 14 RRTM shortwave bands and the
444    ! 6 albedo inputs.
445    YDERAD%NSW = 6
446    ZWAVBOUND(1:5) = [ 0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, &
447         &             1.19e-6_jprb, 2.38e-6_jprb ]
448    IBAND(1:6)  = [ 1,2,3,4,5,6 ]
449    ! If NALBEDOSCHEME==2 then we are using the 6-component MODIS
450    ! albedo climatology, and a weighted average is used to compute
451    ! the albedos in each ecRad spectral band. If NALBEDOSCHEME==3
452    ! then we use the diffuse part of the 4 components but still with
453    ! a weighted average. Otherwise the older behaviour is followed:
454    ! the nearest albedo interval to each band is selected, resulting
455    ! in a discrete mapping that matches the one in YOESRTWN:NMPSRTM.
456    ! Note that this tends to bias albedo high because there is a lot
457    ! of energy around the interface between the UV-Vis and Near-IR
458    ! channels, so this should be close to the 0.7 microns intended by
459    ! the MODIS dataset, not shifted to the nearest RRTM band boundary
460    ! at 0.625 microns.
461    LL_DO_NEAREST_SW_ALBEDO = .FALSE.
462    CALL RAD_CONFIG%DEFINE_SW_ALBEDO_INTERVALS(YDERAD%NSW, ZWAVBOUND, IBAND, &
463         &  DO_NEAREST=LL_DO_NEAREST_SW_ALBEDO)
464
465    ! Likewise between the 16 RRTM longwave bands and the NLWEMISS
466    ! emissivity inputs - these are defined in suecrad.F90.
467    LL_DO_NEAREST_LW_EMISS = .TRUE.
468    CALL RAD_CONFIG%DEFINE_LW_EMISS_INTERVALS(UBOUND(YSPECTPLANCK%INTERVAL_MAP,1), &
469         &  YSPECTPLANCK%WAVLEN_BOUND, YSPECTPLANCK%INTERVAL_MAP, &
470         &  DO_NEAREST=LL_DO_NEAREST_LW_EMISS)
471
472    ! Do we scale the incoming solar radiation in each band?
473    IF (YDERAD%NSOLARSPECTRUM == 1) THEN
474      IF (RAD_CONFIG%N_BANDS_SW /= 14) THEN
475        WRITE(NULERR,'(a)') '*** Error: Shortwave must have 14 bands to apply spectral scaling'
476        CALL ABOR1('RADIATION_SETUP: Shortwave must have 14 bands to apply spectral scaling')
477      ELSE
478        RAD_CONFIG%USE_SPECTRAL_SOLAR_SCALING = .TRUE.
479      ENDIF
480    ENDIF
481
482    ! *** IMPLEMENT SETTINGS ***
483
484    ! For advanced configuration, the configuration data for the
485    ! "radiation" project can specified directly in the namelist.
486    ! However, the variable naming convention is not consistent with
487    ! the rest of the IFS.  For basic configuration there are specific
488    ! variables in the NAERAD namelist available in the YDERAD
489    ! structure.
490    !CALL POSNAME(NULNAM, 'RADIATION', ISTAT)
491    !SELECT CASE (ISTAT)
492    !  CASE(0)
493    !    CALL RAD_CONFIG%READ(UNIT=NULNAM)
494    !  CASE(1)
495    !    WRITE(NULOUT,'(a)') 'Namelist RADIATION not found, using settings from NAERAD only'
496    !  CASE DEFAULT
497    !    CALL ABOR1('RADIATION_SETUP: error reading RADIATION section of namelist file')
498    !END SELECT
499    IF (PRESENT(FILE_NAME)) THEN
500      CALL RAD_CONFIG%READ(FILE_NAME=FILE_NAME)
501    ENDIF
502
503    ! Print configuration
504    IF (IVERBOSESETUP > 1) THEN
505      WRITE(NULOUT,'(a)') 'Radiation scheme settings:'
506      CALL RAD_CONFIG%PRINT(IVERBOSE=IVERBOSESETUP)
507    ENDIF
508
509    ! Use configuration data to set-up radiation scheme, including
510    ! reading scattering datafiles
511    CALL SETUP_RADIATION(RAD_CONFIG)
512
513    ! Get spectral weightings for UV and PAR
514    CALL RAD_CONFIG%GET_SW_WEIGHTS(0.2E-6_JPRB, 0.4415E-6_JPRB,&
515         &  PRADIATION%NWEIGHT_UV, PRADIATION%IBAND_UV, PRADIATION%WEIGHT_UV,&
516         &  'ultraviolet')
517    CALL RAD_CONFIG%GET_SW_WEIGHTS(0.4E-6_JPRB, 0.7E-6_JPRB,&
518         &  PRADIATION%NWEIGHT_PAR, PRADIATION%IBAND_PAR, PRADIATION%WEIGHT_PAR,&
519         &  'photosynthetically active radiation, PAR')
520
521    IF (YDERAD%NAERMACC > 0) THEN
522      ! With the MACC aerosol climatology we need to add in the
523      ! background aerosol afterwards using the Tegen arrays.  In this
524      ! case we first configure the background aerosol mass-extinction
525      ! coefficient at 550 nm, which corresponds to the 10th RRTMG
526      ! shortwave band.
527      PRADIATION%TROP_BG_AER_MASS_EXT  = DRY_AEROSOL_MASS_EXTINCTION(RAD_CONFIG,&
528           &                                   ITYPE_TROP_BG_AER, 550.0E-9_JPRB)
529      PRADIATION%STRAT_BG_AER_MASS_EXT = DRY_AEROSOL_MASS_EXTINCTION(RAD_CONFIG,&
530           &                                   ITYPE_STRAT_BG_AER, 550.0E-9_JPRB)
531
532      WRITE(NULOUT,'(a,i0)') 'Tropospheric background uses aerosol type ',&
533           &                 ITYPE_TROP_BG_AER
534      WRITE(NULOUT,'(a,i0)') 'Stratospheric background uses aerosol type ',&
535           &                 ITYPE_STRAT_BG_AER
536    ELSE
537      PRADIATION%TROP_BG_AER_MASS_EXT  = 0.0_JPRB
538      PRADIATION%STRAT_BG_AER_MASS_EXT = 0.0_JPRB
539    ENDIF
540
541    IF (IVERBOSESETUP > 1) THEN
542      WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------'
543    ENDIF
544
545    END ASSOCIATE
546    END ASSOCIATE
547
548    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE)
549
550  END SUBROUTINE SETUP_RADIATION_SCHEME
551
552
553END MODULE RADIATION_SETUP
Note: See TracBrowser for help on using the repository browser.