Changeset 4646 for LMDZ6/branches


Ignore:
Timestamp:
Aug 2, 2023, 9:18:55 AM (10 months ago)
Author:
idelkadi
Message:

Further updates and cleaning of the Lmdz-Ecrad interface.

Location:
LMDZ6/branches/LMDZ_ECRad/libf/phylmd/ecrad
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/ecrad/radiation_scheme.F90

    r4572 r4646  
    8080USE PARKIND1 , ONLY : JPIM, JPRB
    8181USE YOMHOOK  , ONLY : LHOOK, DR_HOOK
    82 ! AI ATTENTION module propre a ifs commentes
    83 !USE YOERAD   , ONLY : YRERAD
    84 USE RADIATION_SETUP, ONLY : SETUP_RADIATION_SCHEME, rad_config, &
    85 !USE RADIATION_SETUP, ONLY : &
    86      &  NWEIGHT_UV,  IBAND_UV,  WEIGHT_UV, &
    87      &  NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, &
    88      &  ITYPE_TROP_BG_AER,  TROP_BG_AER_MASS_EXT, &
    89      &  ITYPE_STRAT_BG_AER, STRAT_BG_AER_MASS_EXT, ISolverSpartacus
     82USE RADIATION_SETUP
    9083! Commentes : jour, date de la simulation
    91 !USE YOMRIP0  , ONLY : NINDAT
    92 !USE YOMCT3   , ONLY : NSTEP
    93 !USE YOMRIP   , ONLY : YRRIP
    9484USE YOMCST   , ONLY : RSIGMA ! Stefan-Boltzmann constant
     85USE radiation_config, ONLY : config_type,ISolverSpartacus
    9586
    9687! Modules from radiation library
     
    142133!REAL(KIND=JPRB),   INTENT(IN) :: PLAND_SEA_MASK(KLON)
    143134
    144 ! *** Variables on full levels
    145 !REAL(KIND=JPRB),   INTENT(IN) :: PPRESSURE(KLON,KLEV)    ! (Pa)
    146 !REAL(KIND=JPRB),   INTENT(IN) :: PTEMPERATURE(KLON,KLEV) ! (K)
    147135! *** Variables on half levels
    148136REAL(KIND=JPRB),   INTENT(IN) :: PPRESSURE_H(KLON,KLEV+1)    ! (Pa)
     
    201189REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_UP_CLEAR(KLON,KLEV+1)
    202190
    203 ! *** Surface flux components (W m-2)
    204 ! AI ATTENTION
    205 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_SW_DN_SURF(KLON)
    206 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_DN_SURF(KLON)
    207 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_SW_DN_CLEAR_SURF(KLON)
    208 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_DN_CLEAR_SURF(KLON)
    209 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_SW_UP_SURF(KLON)
    210 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_UP_SURF(KLON)
    211 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_SW_UP_CLEAR_SURF(KLON)
    212 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_UP_CLEAR_SURF(KLON)
    213 
    214191! Direct component of surface flux into horizontal plane
    215192REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR(KLON)
     
    222199REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_PAR(KLON)
    223200REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_PAR_CLEAR(KLON)
    224 
    225 ! *** Other single-level diagnostics
    226 ! Top-of-atmosphere incident solar flux (W m-2)
    227 ! AI ATTENTION
    228 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_SW_DN_TOA(KLON)
    229 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_SW_UP_TOA(KLON)
    230 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_DN_TOA(KLON)
    231 !REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_UP_TOA(KLON)
    232201
    233202! Diagnosed longwave surface emissivity across the whole spectrum
     
    250219! LOCAL VARIABLES
    251220! AI ATTENTION
    252 !type(config_type)         :: rad_config
     221type(config_type),save         :: rad_config
     222type(driver_config_type),save  :: driver_config
    253223TYPE(single_level_type)   :: single_level
    254224TYPE(thermodynamics_type) :: thermodynamics
     
    272242!REAL(KIND=JPRB)           :: ZDECORR_LEN_RATIO = 0.5_jprb
    273243
    274 !AI mai 2023
    275 ! A mettre dans namelist
    276 !real(jprb) :: high_inv_effective_size
    277 !real(jprb) :: middle_inv_effective_size
    278 !real(jprb) :: low_inv_effective_size
    279 
    280 !real(jprb) :: cloud_inhom_separation_factor
    281 !real(jprb) :: cloud_separation_scale_surface
    282 !real(jprb) :: cloud_separation_scale_toa
    283 !real(jprb) :: cloud_separation_scale_power
    284 
    285244! The surface net longwave flux if the surface was a black body, used
    286245! to compute the effective broadband surface emissivity
     
    301260INTEGER, PARAMETER :: NAERMACC = 1
    302261
    303 ! AI ATTENTION
    304 ! A mettre dans namelist
    305 !real(jprb), parameter    :: frac_std = 0.75
    306 
    307262! Name of file names specified on command line
    308263character(len=512) :: file_name
     
    310265logical :: loutput=.true.
    311266logical :: lprint_input=.false.
    312 logical :: lprint_config=.false.
     267logical :: lprint_config=.true.
    313268logical, save :: debut_ecrad=.true.
    314269!$OMP THREADPRIVATE(debut_ecrad)
    315 
    316 type(driver_config_type) :: driver_config
    317 ! Import time functions for iseed calculation
    318 ! AI ATTENTION propre a ifs
    319 !#include "fcttim.func.h"
    320 !#include "liquid_effective_radius.intfb.h"
    321 !#include "ice_effective_radius.intfb.h"
    322 !#include "cloud_overlap_decorr_len.intfb.h"
    323 !#include "satur.intfb.h"
    324 
    325 ! Verifier les inputs
    326 print*,'=============== dans radiation_scheme : ==================='
    327 if (lprint_input) then
    328   print*,'********** Verification des entrees *************'
    329   print*,'KIDIA, KFDIA, KLON, KLEV, KAEROSOL, NSW =', &
    330         KIDIA, KFDIA, KLON, KLEV, KAEROSOL, NSW
    331   print*,'IDAY, TIME =', IDAY, TIME
    332   print*,'PSOLAR_IRRADIANCE =', PSOLAR_IRRADIANCE
    333   print*,'PMU0 =', PMU0
    334   print*,'PTEMPERATURE_SKIN =',PTEMPERATURE_SKIN
    335   print*,'PEMIS, PEMIS_WINDOW =', PEMIS, PEMIS_WINDOW
    336   print*,'PGELAM, PGEMU =', PGELAM, PGEMU
    337   print*,'PPRESSURE_H =', PPRESSURE_H
    338   print*,'PTEMPERATURE_H =', PTEMPERATURE_H
    339   print*,'PQ =', PQ
    340   print*,'PQSAT=',PQSAT
    341   print*,'PCO2, PCH4, PN2O, PNO2, PCFC11, PCFC12, PHCFC22, PCCL4 =', &
    342         PCO2, PCH4, PN2O, PNO2, PCFC11, PCFC12, PHCFC22, PCCL4
    343   print*,'PO3 =',PO3
    344   print*,'PCLOUD_FRAC, PQ_LIQUID, PQ_ICE, PQ_SNOW =', &
    345         PCLOUD_FRAC, PQ_LIQUID, PQ_ICE, PQ_SNOW
    346   print*,'ZRE_LIQUID_UM, ZRE_ICE_UM =', &
    347         ZRE_LIQUID_UM, ZRE_ICE_UM
    348   print*,'PAEROSOL_OLD, PAEROSOL =', PAEROSOL_OLD, PAEROSOL
    349 endif
     270integer, save :: itap_ecrad=1
    350271
    351272IF (LHOOK) CALL DR_HOOK('RADIATION_SCHEME',0,ZHOOK_HANDLE)
    352273print*,'Entree dans radiation_scheme'
    353274
     275! A.I juillet 2023 :
     276! Initialisation dans radiation_setup au 1er passage dans Ecrad
    354277!$OMP MASTER
    355278if (debut_ecrad) then
    356279! AI appel radiation_setup
    357 call SETUP_RADIATION_SCHEME(loutput)
    358 ! Read "radiation_driver" namelist into radiation driver config type
    359   file_name="namelist_ecrad"
    360 call driver_config%read(file_name)
    361 
    362 if (rad_config%i_solver_sw == ISolverSPARTACUS &
    363       & .or.   rad_config%i_solver_lw == ISolverSPARTACUS) then
    364        print*,'Solveur SW: ', rad_config%i_solver_sw
    365        print*,'Solveur LW: ', rad_config%i_solver_lw
    366    if (driver_config%ok_effective_size) then
    367        print*,'low_inv_effective_size = ',driver_config%low_inv_effective_size
    368        print*,'middle_inv_effective_size = ',driver_config%middle_inv_effective_size
    369        print*,'high_inv_effective_size = ',driver_config%high_inv_effective_size
    370    else if (driver_config%ok_separation) then   
    371        print*,'cloud_separation_scale_surface =',driver_config%cloud_separation_scale_surface
    372        print*,'cloud_separation_scale_toa =',driver_config%cloud_separation_scale_toa
    373        print*,'cloud_separation_scale_power =',driver_config%cloud_separation_scale_power
    374        print*,'cloud_inhom_separation_factor =',driver_config%cloud_inhom_separation_factor
    375    endif   
    376 endif   
    377 
    378  if (lprint_config) then
    379   print*,'************* Parametres de configuration  ********************'
    380   print*,'rad_config%iverbosesetup = ',rad_config%iverbosesetup
    381   print*,'rad_config%iverbose = ',rad_config%iverbose
    382   print*,'rad_config%directory_name =', rad_config%directory_name
    383   print*,'rad_config%do_lw_derivatives =',rad_config%do_lw_derivatives
    384   print*,'rad_config%do_surface_sw_spectral_flux =', &
    385         rad_config%do_surface_sw_spectral_flux
    386   print*,'rad_config%do_setup_ifsrrtm =', rad_config%do_setup_ifsrrtm
    387   print*,'rad_config%i_liq_model =',rad_config%i_liq_model
    388   print*,'rad_config%i_ice_model =',rad_config%i_ice_model
    389   print*,'rad_config%i_overlap_scheme =', rad_config%i_overlap_scheme
    390   print*,'rad_config%use_aerosols = ', rad_config%use_aerosols
    391   print*,'rad_config%n_aerosol_types = ', rad_config%n_aerosol_types
    392   print*,'rad_config%i_solver_lw =',rad_config%i_solver_lw
    393   print*,'rad_config%i_solver_sw =',rad_config%i_solver_sw
    394   print*,'rad_config%do_3d_effects =', rad_config%do_3d_effects
    395   print*,'rad_config%do_sw_delta_scaling_with_gases =', &
    396        rad_config%do_sw_delta_scaling_with_gases
    397   print*,'rad_config%do_lw_aerosol_scattering =', &
    398        rad_config%do_lw_aerosol_scattering
    399   print*,'rad_config%i_albedo_from_band_sw = ', &
    400        rad_config%i_albedo_from_band_sw
    401   print*,'n_bands_lw =', rad_config%n_bands_lw
    402   print*,'rad_config%i_emiss_from_band_lw =', rad_config%i_emiss_from_band_lw
    403  endif
     280 call SETUP_RADIATION_SCHEME(loutput,rad_config,driver_config)
    404281 debut_ecrad=.false.
    405282endif
     
    408285! Fin partie initialisation et configuration
    409286
    410 ! AI : allocation des tableaux pour chaque partie (thermo, ...)
    411 !      passage des champs LMDZ aux structures Ecrad
    412 !      calculs Ecrad
     287!AI juillet 2023 : verif des param de config :
     288if (lprint_config) then
     289   print*,'Parametres de configuration de ecrad, etape ',itap_ecrad     
     290   print*,'do_sw, do_lw, do_sw_direct, do_3d_effects = ', &
     291           rad_config%do_sw, rad_config%do_lw, rad_config%do_sw_direct, rad_config%do_3d_effects
     292   print*,'do_lw_side_emissivity, do_clear, do_save_radiative_properties = ', &
     293           rad_config%do_lw_side_emissivity, rad_config%do_clear, rad_config%do_save_radiative_properties
     294!   print*,'sw_entrapment_name, sw_encroachment_name = ', &
     295!           rad_config%sw_entrapment_name, rad_config%sw_encroachment_name
     296   print*,'do_3d_lw_multilayer_effects, do_fu_lw_ice_optics_bug = ', &
     297           rad_config%do_3d_lw_multilayer_effects, rad_config%do_fu_lw_ice_optics_bug
     298   print*,'do_save_spectral_flux, do_save_gpoint_flux = ', &
     299           rad_config%do_save_spectral_flux, rad_config%do_save_gpoint_flux
     300   print*,'do_surface_sw_spectral_flux, do_lw_derivatives = ', &
     301           rad_config%do_surface_sw_spectral_flux, rad_config%do_lw_derivatives
     302   print*,'do_lw_aerosol_scattering, do_lw_cloud_scattering = ', &
     303           rad_config%do_lw_aerosol_scattering, rad_config%do_lw_cloud_scattering
     304   print*, 'nregions, i_gas_model = ', &
     305           rad_config%nregions, rad_config%i_gas_model
     306!   print*, 'ice_optics_override_file_name, liq_optics_override_file_name = ', &
     307!           rad_config%ice_optics_override_file_name, rad_config%liq_optics_override_file_name
     308!   print*, 'aerosol_optics_override_file_name, cloud_pdf_override_file_name = ', &
     309!           rad_config%aerosol_optics_override_file_name, rad_config%cloud_pdf_override_file_name
     310!   print*, 'gas_optics_sw_override_file_name, gas_optics_lw_override_file_name = ', &
     311!           rad_config%gas_optics_sw_override_file_name, rad_config%gas_optics_lw_override_file_name
     312   print*, 'i_liq_model, i_ice_model, max_3d_transfer_rate = ', &
     313           rad_config%i_liq_model, rad_config%i_ice_model, rad_config%max_3d_transfer_rate
     314   print*, 'min_cloud_effective_size, overhang_factor = ', &
     315           rad_config%min_cloud_effective_size, rad_config%overhang_factor
     316   print*, 'use_canopy_full_spectrum_sw, use_canopy_full_spectrum_lw = ', &
     317           rad_config%use_canopy_full_spectrum_sw, rad_config%use_canopy_full_spectrum_lw
     318   print*, 'do_canopy_fluxes_sw, do_canopy_fluxes_lw = ', &
     319           rad_config%do_canopy_fluxes_sw, rad_config%do_canopy_fluxes_lw
     320   print*, 'do_canopy_gases_sw, do_canopy_gases_lw = ', &
     321           rad_config%do_canopy_gases_sw, rad_config%do_canopy_gases_lw
     322   print*, 'use_general_cloud_optics, use_general_aerosol_optics = ', &
     323           rad_config%use_general_cloud_optics, rad_config%use_general_aerosol_optics
     324   print*, 'do_sw_delta_scaling_with_gases, i_overlap_scheme = ', &
     325           rad_config%do_sw_delta_scaling_with_gases, rad_config%i_overlap_scheme
     326   print*, 'i_solver_sw, i_solver_sw, use_beta_overlap, use_vectorizable_generator = ', &
     327           rad_config%i_solver_sw, rad_config%i_solver_lw, &
     328           rad_config%use_beta_overlap, rad_config%use_vectorizable_generator
     329   print*, 'use_expm_everywhere, iverbose, iverbosesetup = ', &
     330           rad_config%use_expm_everywhere, rad_config%iverbose, rad_config%iverbosesetup
     331   print*, 'cloud_inhom_decorr_scaling, cloud_fraction_threshold = ', &
     332           rad_config%cloud_inhom_decorr_scaling, rad_config%cloud_fraction_threshold
     333   print*, 'clear_to_thick_fraction, max_gas_od_3d, max_cloud_od = ', &
     334           rad_config%clear_to_thick_fraction, rad_config%max_gas_od_3d, rad_config%max_cloud_od
     335   print*, 'cloud_mixing_ratio_threshold, overhead_sun_factor =', &
     336           rad_config%cloud_mixing_ratio_threshold, rad_config%overhead_sun_factor
     337   print*, 'n_aerosol_types, i_aerosol_type_map, use_aerosols = ', &
     338           rad_config%n_aerosol_types, rad_config%i_aerosol_type_map, rad_config%use_aerosols
     339   print*, 'mono_lw_wavelength, mono_lw_total_od, mono_sw_total_od = ', &
     340           rad_config%mono_lw_wavelength, rad_config%mono_lw_total_od,rad_config% mono_sw_total_od
     341   print*, 'mono_lw_single_scattering_albedo, mono_sw_single_scattering_albedo = ', &
     342           rad_config%mono_lw_single_scattering_albedo, rad_config%mono_sw_single_scattering_albedo
     343   print*, 'mono_lw_asymmetry_factor, mono_sw_asymmetry_factor = ', &
     344           rad_config%mono_lw_asymmetry_factor, rad_config%mono_sw_asymmetry_factor
     345   print*, 'i_cloud_pdf_shape = ', &
     346           rad_config%i_cloud_pdf_shape
     347!           cloud_type_name, use_thick_cloud_spectral_averaging = ', &
     348!           rad_config%i_cloud_pdf_shape, rad_config%cloud_type_name, &
     349!           rad_config%use_thick_cloud_spectral_averaging
     350   print*, 'do_nearest_spectral_sw_albedo, do_nearest_spectral_lw_emiss = ', &
     351           rad_config%do_nearest_spectral_sw_albedo, rad_config%do_nearest_spectral_lw_emiss
     352   print*, 'sw_albedo_wavelength_bound, lw_emiss_wavelength_bound = ', &
     353           rad_config%sw_albedo_wavelength_bound, rad_config%lw_emiss_wavelength_bound
     354   print*, 'i_sw_albedo_index, i_lw_emiss_index = ', &
     355           rad_config%i_sw_albedo_index, rad_config%i_lw_emiss_index
     356   print*, 'do_cloud_aerosol_per_lw_g_point = ', &
     357           rad_config%do_cloud_aerosol_per_lw_g_point
     358   print*, 'do_cloud_aerosol_per_sw_g_point, do_weighted_surface_mapping = ', &
     359           rad_config%do_cloud_aerosol_per_sw_g_point, rad_config%do_weighted_surface_mapping
     360   print*, 'n_bands_sw, n_bands_lw, n_g_sw, n_g_lw = ', &
     361           rad_config%n_bands_sw, rad_config%n_bands_lw, rad_config%n_g_sw, rad_config%n_g_lw
     362
     363           itap_ecrad=itap_ecrad+1
     364endif           
     365
    413366! AI ATTENTION
    414367! Allocate memory in radiation objects
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/ecrad/radiation_setup.F90

    r4444 r4646  
    22
    33! 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).
    284!
    295! AUTHOR
     
    3410! MODIFICATIONS
    3511! -------------
     12!   Abderrahmane Idelkadi LMD, juillet 2023
    3613!
    3714!-----------------------------------------------------------------------
    3815
    3916  USE PARKIND1,         ONLY : JPRB
    40   USE radiation_config, ONLY : config_type, &
    41        &                       ISolverMcICA, ISolverSpartacus, &
    42        &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
    43        &                       IIceModelFu, IIceModelBaran, &
    44        &                       IOverlapExponentialRandom
    4517
    4618  IMPLICIT NONE
    4719
    48   ! Store configuration information for the radiation scheme in a
    49   ! global variable
    50   type(config_type) :: rad_config
    5120
    5221  ! Ultraviolet weightings
     
    7746! AI At the end of the routine, the parameters are read in namelist
    7847!   
    79   SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT)
     48  SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT,rad_config,driver_config)
    8049
     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     
    8157    USE YOMHOOK,  ONLY : LHOOK, DR_HOOK
    82 ! AI (propre a IFS)   
    83 !    USE YOMLUN,   ONLY : NULNAM, NULOUT, NULERR
    8458    USE YOMLUN,   ONLY : NULOUT, NULERR
    8559    USE YOESRTWN, ONLY : NMPSRTM
    86 ! AI ATTENTION (propre a IFS)
    87 !    USE YOERAD,   ONLY : YRERAD
    8860
    8961    USE radiation_interface,      ONLY : setup_radiation
    90 !    USE radiation_aerosol_optics, ONLY : dry_aerosol_sw_mass_extinction
    91 
    92 ! AI (propre a IFS)   
    93 !#include "posname.intfb.h"
     62    USE setup_config_from_lmdz,   ONLY : driver_config_type
    9463
    9564    ! Whether or not to provide information on the radiation scheme
    9665    ! configuration
    9766    LOGICAL, INTENT(IN), OPTIONAL :: LOUTPUT
    98 
    99     ! Verbosity of configuration information 0=none, 1=warning,
    100     ! 2=info, 3=progress, 4=detailed, 5=debug
    101     INTEGER :: IVERBOSESETUP
    102     INTEGER :: ISTAT
    10367
    10468    REAL(KIND=JPRB) :: ZHOOK_HANDLE
     
    10771
    10872    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
    10978
    11079    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',0,ZHOOK_HANDLE)
     
    11685    print*,'********** Dans radiation_setup *****************'
    11786
    118     IVERBOSESETUP = 4 ! Provide plenty of information
    119     IF (PRESENT(LOUTPUT)) THEN
    120       IF (.NOT. LOUTPUT) THEN
    121         IVERBOSESETUP = 1 ! Warnings and errors only
    122       ENDIF
    123     ENDIF
    124     rad_config%iverbosesetup = IVERBOSESETUP
    125     if (lprint_setp) then
    126       print*,'Dans radiation_setup '
    127       print*,'rad_config%iverbosesetup =', rad_config%iverbosesetup
    128     endif
    129 
    130     IF (IVERBOSESETUP > 1) THEN
    131       WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------'
    132       WRITE(NULOUT,'(a)') 'RADIATION_SETUP'
    133     ENDIF
    134 
    135     ! Normal operation of the radiation scheme displays only errors
    136     ! and warnings
    137     rad_config%iverbose = 5
    138     if (lprint_setp) then
    139       print*,'rad_config%iverbose =', rad_config%iverbose
    140     endif
    141     ! For the time being, ensure a valid default directory name
    142     rad_config%directory_name = 'data'
    143     if (lprint_setp) then
    144       print*,'rad_config%directory_name =', rad_config%directory_name
    145     endif
    146 
    147     ! Do we do Hogan and Bozzo (2014) approximate longwave updates?
    148 ! AI ATTENTION (ifs : )
    149      ! AI (propre a IFS)
    150 !    rad_config%do_lw_derivatives = YRERAD%LAPPROXLWUPDATE
    151     rad_config%do_lw_derivatives = .false.
    152     if (lprint_setp) then
    153       print*,'rad_config%do_lw_derivatives =', rad_config%do_lw_derivatives   
    154     endif
    155 
    156     ! Surface spectral fluxes are needed for spectral shortwave albedo
    157     ! calculation
    158 ! AI ATTENTION test (ifs : T)
    159 !    rad_config%do_save_spectral_flux = .FALSE.
    160     rad_config%do_surface_sw_spectral_flux = .TRUE.
    161     if (lprint_setp) then
    162       print*,'rad_config%do_surface_sw_spectral_flux =', &
    163             rad_config%do_surface_sw_spectral_flux
    164     endif
    165 
    166     ! *** SETUP GAS OPTICS ***
    167 
    168 ! routine below does not have to (ifs : F)
    169     print*,'i_gas_model =',rad_config%i_gas_model
    170     rad_config%do_setup_ifsrrtm = .TRUE.
    171     if (lprint_setp) then
    172       print*,'rad_config%do_setup_ifsrrtm =', rad_config%do_setup_ifsrrtm
    173     endif
    174 
    175     ! *** SETUP CLOUD OPTICS ***
    176 
    177     ! Setup liquid optics
    178 ! AI ATTENTION
    179 ! Choix offline : liquid_model_name = "SOCRATES"
    180       rad_config%i_liq_model = ILiquidModelSOCRATES
    181       if (lprint_setp) then
    182         print*,'rad_config%i_liq_model =',rad_config%i_liq_model
    183       endif
    184 
    185     ! Setup ice optics
    186 ! Choix offline : ice_model_name    = "Fu-IFS"
    187       rad_config%i_ice_model = IIceModelFu
    188       if (lprint_setp) then
    189         print*,'rad_config%i_ice_model =', rad_config%i_ice_model
    190       endif
    191 
    192 ! AI (propre a IFS)     
    193     ! For consistency with earlier versions of the IFS radiation
    194     ! scheme, we perform shortwave delta-Eddington scaling *after* the
    195     ! merge of the cloud, aerosol and gas optical properties.  Set
    196     ! this to "false" to do the scaling on the cloud and aerosol
    197     ! properties separately before merging with gases. Note that this
    198     ! is not compatible with the SPARTACUS solver.
    199     rad_config%do_sw_delta_scaling_with_gases = .FALSE.
    200     if (lprint_setp) then
    201       print*,'rad_config%do_sw_delta_scaling_with_gases =', &
    202             rad_config%do_sw_delta_scaling_with_gases
    203     endif
    204 
    205 ! AI (propre a IFS)   
    206     ! Use Exponential-Exponential cloud overlap to match original IFS
    207     ! implementation of Raisanen cloud generator
    208     rad_config%i_overlap_scheme = IOverlapExponentialRandom
    209     if (lprint_setp) then
    210       print*,'rad_config%i_overlap_scheme =', rad_config%i_overlap_scheme
    211     endif
    212 
    213     ! *** SETUP AEROSOLS ***
    214 ! AI ATTENTION
    215 !    rad_config%use_aerosols = .TRUE. !(ifs)
    216     rad_config%use_aerosols = .FALSE.
    217     if (lprint_setp) then
    218       print*,'rad_config%use_aerosols =', rad_config%use_aerosols
    219     endif
    220 
    221 ! *** SETUP SOLVER ***
    222 
    223     ! 3D effects are off by default (ifs)
    224     rad_config%do_3d_effects = .TRUE.
    225     if (lprint_setp) then
    226       print*,'rad_config%do_3d_effects=', rad_config%do_3d_effects
    227     endif
    228 
    229     ! Select longwave solver
    230 ! AI ATTENTION
    231       rad_config%i_solver_lw = ISolverSpartacus
    232       if (lprint_setp) then
    233         print*,'rad_config%i_solver_lw =', rad_config%i_solver_lw
    234       endif
    235 
    236       rad_config%i_solver_sw = ISolverSpartacus
    237       if (lprint_setp) then
    238         print*,'rad_config%i_solver_sw =', rad_config%i_solver_sw
    239       endif
    240 
    241     ! SPARTACUS solver requires delta scaling to be done separately
    242     ! for clouds & aerosols
    243     IF (rad_config%i_solver_sw == ISolverSpartacus) THEN
    244       rad_config%do_sw_delta_scaling_with_gases = .FALSE.
    245     ENDIF
    246 
    247     ! Do we represent longwave scattering?
    248     rad_config%do_lw_cloud_scattering = .TRUE.
    249     rad_config%do_lw_aerosol_scattering = .TRUE.
    250     if (lprint_setp) then
    251       print*,'rad_config%do_lw_cloud_scattering =', &
    252            rad_config%do_lw_cloud_scattering
    253       print*,'rad_config%do_lw_aerosol_scattering =', &
    254            rad_config%do_lw_aerosol_scattering
    255     endif
    256 
    257     ! *** IMPLEMENT SETTINGS ***
    258 
    259     ! For advanced configuration, the configuration data for the
    260     ! "radiation" project can specified directly in the namelist.
    261     ! However, the variable naming convention is not consistent with
    262     ! the rest of the IFS.  For basic configuration there are specific
    263     ! variables in the NAERAD namelist available in the YRERAD
    264     ! structure.
    265 
    26687! AI ATTENTION (parameters read in namelist file)
    26788    file_name="namelist_ecrad"
    26889    call rad_config%read(file_name=file_name)
     90    call driver_config%read(file_name)
    26991
    27092    ! Use configuration data to set-up radiation scheme, including
     
    313135   rad_config%aerosol_optics_override_file_name = 'aerosol_optics_lmdz.nc'
    314136
    315 !    IF (YRERAD%NAERMACC > 0) THEN
    316       ! With the MACC aerosol climatology we need to add in the
    317       ! background aerosol afterwards using the Tegen arrays.  In this
    318       ! case we first configure the background aerosol mass-extinction
    319       ! coefficient at 550 nm, which corresponds to the 10th RRTMG
    320       ! shortwave band.
    321 !      TROP_BG_AER_MASS_EXT  = dry_aerosol_sw_mass_extinction(rad_config, &
    322 !           &                                   ITYPE_TROP_BG_AER, 10)
    323 !      STRAT_BG_AER_MASS_EXT = dry_aerosol_sw_mass_extinction(rad_config, &
    324 !           &                                   ITYPE_STRAT_BG_AER, 10)
    325      
    326 !      WRITE(NULOUT,'(a,i0)') 'Tropospheric bacground uses aerosol type ', &
    327 !           &                 ITYPE_TROP_BG_AER
    328 !      WRITE(NULOUT,'(a,i0)') 'Stratospheric bacground uses aerosol type ', &
    329 !           &                 ITYPE_STRAT_BG_AER
    330 !    ENDIF     
    331      
    332     IF (IVERBOSESETUP > 1) THEN
    333       WRITE(NULOUT,'(a)') '-------------------------------------------------------------------------------'
    334     ENDIF
    335137
    336138    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE)
Note: See TracChangeset for help on using the changeset viewer.