Ignore:
Timestamp:
Sep 7, 2023, 1:07:27 PM (9 months ago)
Author:
idelkadi
Message:

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:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/ecrad/radiation_setup.F90

    r4489 r4677  
    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!-----------------------------------------------------------------------
     
    4421       &                       IOverlapExponentialRandom
    4522
     23  USE radiation_interface,      ONLY : setup_radiation
     24  USE setup_config_from_lmdz,   ONLY : driver_config_type
     25
    4626  IMPLICIT NONE
    4727
    48   ! Store configuration information for the radiation scheme in a
    49   ! global variable
    50   type(config_type) :: rad_config
    5128
    5229  ! Ultraviolet weightings
     
    7754! AI At the end of the routine, the parameters are read in namelist
    7855!   
    79   SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT)
     56  SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT,file_name,rad_config,driver_config)
    8057
     58!    USE radiation_config, ONLY : config_type, &
     59!        &                       ISolverMcICA, ISolverSpartacus, &
     60!        &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
     61!        &                       IIceModelFu, IIceModelBaran, &
     62!        &                       IOverlapExponentialRandom
     63    USE mod_phys_lmdz_para
     64     
    8165    USE YOMHOOK,  ONLY : LHOOK, DR_HOOK
    82 ! AI (propre a IFS)   
    83 !    USE YOMLUN,   ONLY : NULNAM, NULOUT, NULERR
    8466    USE YOMLUN,   ONLY : NULOUT, NULERR
    8567    USE YOESRTWN, ONLY : NMPSRTM
    86 ! AI ATTENTION (propre a IFS)
    87 !    USE YOERAD,   ONLY : YRERAD
    8868
    89     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"
     69 !   USE radiation_interface,      ONLY : setup_radiation
     70 !   USE setup_config_from_lmdz,   ONLY : driver_config_type
    9471
    9572    ! Whether or not to provide information on the radiation scheme
    9673    ! configuration
    9774    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
    10375
    10476    REAL(KIND=JPRB) :: ZHOOK_HANDLE
     
    10779
    10880    logical :: lprint_setp=.TRUE.
     81
     82    ! Store configuration information for the radiation scheme in a
     83    ! global variable
     84    type(config_type) :: rad_config
     85    type(driver_config_type) :: driver_config
    10986
    11087    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',0,ZHOOK_HANDLE)
     
    11693    print*,'********** Dans radiation_setup *****************'
    11794
    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 
    26695! AI ATTENTION (parameters read in namelist file)
    267     file_name="namelist_ecrad"
     96!    file_name="namelist_ecrad"
    26897    call rad_config%read(file_name=file_name)
     98    call driver_config%read(file_name)
    26999
    270100    ! Use configuration data to set-up radiation scheme, including
     
    313143   rad_config%aerosol_optics_override_file_name = 'aerosol_optics_lmdz.nc'
    314144
    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
    335145
    336146    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE)
Note: See TracChangeset for help on using the changeset viewer.