Changeset 4677


Ignore:
Timestamp:
Sep 7, 2023, 1:07:27 PM (8 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.
Location:
LMDZ6/trunk/libf/phylmd
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/clesphys.h

    r4537 r4677  
    105105       INTEGER :: iflag_phytrac
    106106
     107!AI flags pour ECRAD       
     108       LOGICAL :: ok_3Deffect
     109       CHARACTER(len=512) :: namelist_ecrad_file
     110
    107111       COMMON/clesphys/                                                 &
    108112! REAL FIRST
     
    154158     &     , iflag_phytrac, ok_new_lscp, ok_bs, ok_rad_bs               &
    155159     &     ,  iflag_thermals,nsplit_thermals, tau_thermals              &
    156      &     , iflag_physiq
     160     &     , iflag_physiq, ok_3Deffect, namelist_ecrad_file
    157161       save /clesphys/
    158162!$OMP THREADPRIVATE(/clesphys/)
  • LMDZ6/trunk/libf/phylmd/ecrad/radiation_ecckd.F90

    r4489 r4677  
    147147    this%d_log_pressure = log(pressure_lut(2)) - this%log_pressure1
    148148    call file%get('temperature', temperature_full)
     149    if (allocated(this%temperature1)) deallocate(this%temperature1)
    149150    allocate(this%temperature1(this%npress));
    150151    this%temperature1 = temperature_full(:,1)
     
    179180    ! Read gases
    180181    call file%get('n_gases', this%ngas)
     182    if (allocated(this%single_gas)) deallocate(this%single_gas) 
    181183    allocate(this%single_gas(this%ngas))
    182184    call file%get_global_attribute('constituent_id', constituent_id)
  • LMDZ6/trunk/libf/phylmd/ecrad/radiation_ecckd_interface.F90

    r4489 r4677  
    5252      end if
    5353
    54       allocate(config%i_band_from_g_sw          (config%n_g_sw))
     54      if (allocated(config%i_band_from_g_sw)) deallocate(config%i_band_from_g_sw)
     55      allocate(config%i_band_from_g_sw(config%n_g_sw))
     56      if (allocated(config%i_band_from_reordered_g_sw)) deallocate(config%i_band_from_reordered_g_sw)
    5557      allocate(config%i_band_from_reordered_g_sw(config%n_g_sw))
    56       allocate(config%i_g_from_reordered_g_sw   (config%n_g_sw))
     58      if (allocated(config%i_g_from_reordered_g_sw)) deallocate(config%i_g_from_reordered_g_sw)
     59      allocate(config%i_g_from_reordered_g_sw(config%n_g_sw))
    5760       
    5861      if (config%do_cloud_aerosol_per_sw_g_point) then
     
    9194      end if
    9295
     96      if (allocated(config%i_band_from_g_lw)) deallocate(config%i_band_from_g_lw)
    9397      allocate(config%i_band_from_g_lw          (config%n_g_lw))
     98      if (allocated(config%i_band_from_reordered_g_lw)) deallocate(config%i_band_from_reordered_g_lw)
    9499      allocate(config%i_band_from_reordered_g_lw(config%n_g_lw))
     100      if (allocated(config%i_g_from_reordered_g_lw)) deallocate(config%i_g_from_reordered_g_lw)
    95101      allocate(config%i_g_from_reordered_g_lw   (config%n_g_lw))
    96102
  • LMDZ6/trunk/libf/phylmd/ecrad/radiation_general_cloud_optics.F90

    r4489 r4677  
    7575    ! Allocate structures
    7676    if (config%do_sw) then
     77      if (allocated(config%cloud_optics_sw)) deallocate(config%cloud_optics_sw)     
    7778      allocate(config%cloud_optics_sw(config%n_cloud_types))
    7879    end if
    7980
    8081    if (config%do_lw) then
     82      if (allocated(config%cloud_optics_lw)) deallocate(config%cloud_optics_lw)       
    8183      allocate(config%cloud_optics_lw(config%n_cloud_types))
    8284    end if
  • LMDZ6/trunk/libf/phylmd/ecrad/radiation_general_cloud_optics_data.F90

    r4489 r4677  
    185185    call delta_eddington(mass_ext, ssa, asymmetry)
    186186
     187
    187188    ! Thin averaging
     189   ! AI juillet 2023
     190    allocate(this%mass_ext(nre,nwav))
    188191    this%mass_ext  = matmul(mapping, mass_ext)
    189192    this%ssa       = matmul(mapping, mass_ext*ssa) / this%mass_ext
  • LMDZ6/trunk/libf/phylmd/ecrad/radiation_scheme.F90

    r4570 r4677  
    99!             3. Configuration a partir de namelist
    1010!             4. frac_std = 0.75     
     11! Juillet 2023 :
     12!             
    1113! ============================================================================
    1214
     
    1416! Inputs
    1517     & (KIDIA, KFDIA, KLON, KLEV, KAEROSOL, NSW, &
    16      &  IDAY, TIME, &
     18     &  namelist_file, ok_3Deffect, IDAY, TIME, &
    1719     &  PSOLAR_IRRADIANCE, &
    1820     &  PMU0, PTEMPERATURE_SKIN, &
     
    8082USE PARKIND1 , ONLY : JPIM, JPRB
    8183USE 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
    90 ! Commentes : jour, date de la simulation
    91 !USE YOMRIP0  , ONLY : NINDAT
    92 !USE YOMCT3   , ONLY : NSTEP
    93 !USE YOMRIP   , ONLY : YRRIP
     84USE RADIATION_SETUP
    9485USE YOMCST   , ONLY : RSIGMA ! Stefan-Boltzmann constant
     86USE RADIATION_SETUP, ONLY : SETUP_RADIATION_SCHEME, &
     87                         &  config_type, driver_config_type, &
     88                         &  NWEIGHT_UV,  IBAND_UV,  WEIGHT_UV, &
     89                         &  NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, &
     90                         &  ITYPE_TROP_BG_AER,  TROP_BG_AER_MASS_EXT, &
     91                         &  ITYPE_STRAT_BG_AER, STRAT_BG_AER_MASS_EXT, &
     92                         &  ISolverSpartacus
    9593
    9694! Modules from radiation library
     
    105103
    106104USE mod_phys_lmdz_para
    107 USE setup_config_from_lmdz,   ONLY : driver_config_type
    108105
    109106IMPLICIT NONE
     
    142139!REAL(KIND=JPRB),   INTENT(IN) :: PLAND_SEA_MASK(KLON)
    143140
    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)
    147141! *** Variables on half levels
    148142REAL(KIND=JPRB),   INTENT(IN) :: PPRESSURE_H(KLON,KLEV+1)    ! (Pa)
     
    201195REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_LW_UP_CLEAR(KLON,KLEV+1)
    202196
    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 
    214197! Direct component of surface flux into horizontal plane
    215198REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR(KLON)
     
    222205REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_PAR(KLON)
    223206REAL(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)
    232207
    233208! Diagnosed longwave surface emissivity across the whole spectrum
     
    250225! LOCAL VARIABLES
    251226! AI ATTENTION
    252 !type(config_type)         :: rad_config
     227type(config_type),save         :: rad_config
     228!!$OMP THREADPRIVATE(rad_config)
     229type(driver_config_type),save  :: driver_config
     230!!$OMP THREADPRIVATE(driver_config)
     231!type(config_type)        :: rad_config
     232!type(driver_config_type)  :: driver_config
    253233TYPE(single_level_type)   :: single_level
    254234TYPE(thermodynamics_type) :: thermodynamics
     
    272252!REAL(KIND=JPRB)           :: ZDECORR_LEN_RATIO = 0.5_jprb
    273253
    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 
    285254! The surface net longwave flux if the surface was a black body, used
    286255! to compute the effective broadband surface emissivity
     
    301270INTEGER, PARAMETER :: NAERMACC = 1
    302271
    303 ! AI ATTENTION
    304 ! A mettre dans namelist
    305 !real(jprb), parameter    :: frac_std = 0.75
    306 
    307272! Name of file names specified on command line
    308 character(len=512) :: file_name
     273character(len=512) :: namelist_file
    309274
    310275logical :: loutput=.true.
    311276logical :: lprint_input=.false.
    312 logical :: lprint_config=.false.
     277logical :: lprint_config=.true.
    313278logical, save :: debut_ecrad=.true.
    314279!$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
     280integer, save :: itap_ecrad=1
     281logical :: ok_3Deffect
     282
     283IF (LHOOK) CALL DR_HOOK('RADIATION_SCHEME',0,ZHOOK_HANDLE)
     284
     285! A.I juillet 2023 :
     286! Initialisation dans radiation_setup au 1er passage dans Ecrad
     287!$OMP MASTER
     288if (.not.ok_3Deffect) then
     289  if (debut_ecrad) then
     290   call SETUP_RADIATION_SCHEME(loutput,namelist_file,rad_config,driver_config)
     291   debut_ecrad=.false.
     292  endif
     293else
     294   call SETUP_RADIATION_SCHEME(loutput,namelist_file,rad_config,driver_config)
    349295endif
    350 
    351 IF (LHOOK) CALL DR_HOOK('RADIATION_SCHEME',0,ZHOOK_HANDLE)
    352 print*,'Entree dans radiation_scheme'
    353 
    354 !$OMP MASTER
    355 if (debut_ecrad) then
    356 ! 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
    404  debut_ecrad=.false.
    405 endif
    406296!$OMP END MASTER
    407297!$OMP BARRIER
    408298! Fin partie initialisation et configuration
    409299
    410 ! AI : allocation des tableaux pour chaque partie (thermo, ...)
    411 !      passage des champs LMDZ aux structures Ecrad
    412 !      calculs Ecrad
     300!AI juillet 2023 : verif des param de config :
     301if (lprint_config) then
     302! IF (is_master) THEN       
     303   print*,'Parametres de configuration de ecrad, etape ',itap_ecrad     
     304   print*,'Entree dans radiation_scheme'
     305   print*,'ok_3Deffect = ',ok_3Deffect
     306   print*,'Fichier namelist = ',namelist_file
     307
     308   print*,'do_sw, do_lw, do_sw_direct, do_3d_effects = ', &
     309           rad_config%do_sw, rad_config%do_lw, rad_config%do_sw_direct, rad_config%do_3d_effects
     310   print*,'do_lw_side_emissivity, do_clear, do_save_radiative_properties = ', &
     311           rad_config%do_lw_side_emissivity, rad_config%do_clear, rad_config%do_save_radiative_properties
     312!   print*,'sw_entrapment_name, sw_encroachment_name = ', &
     313!           rad_config%sw_entrapment_name, rad_config%sw_encroachment_name
     314   print*,'do_3d_lw_multilayer_effects, do_fu_lw_ice_optics_bug = ', &
     315           rad_config%do_3d_lw_multilayer_effects, rad_config%do_fu_lw_ice_optics_bug
     316   print*,'do_save_spectral_flux, do_save_gpoint_flux = ', &
     317           rad_config%do_save_spectral_flux, rad_config%do_save_gpoint_flux
     318   print*,'do_surface_sw_spectral_flux, do_lw_derivatives = ', &
     319           rad_config%do_surface_sw_spectral_flux, rad_config%do_lw_derivatives
     320   print*,'do_lw_aerosol_scattering, do_lw_cloud_scattering = ', &
     321           rad_config%do_lw_aerosol_scattering, rad_config%do_lw_cloud_scattering
     322   print*, 'nregions, i_gas_model = ', &
     323           rad_config%nregions, rad_config%i_gas_model
     324!   print*, 'ice_optics_override_file_name, liq_optics_override_file_name = ', &
     325!           rad_config%ice_optics_override_file_name, rad_config%liq_optics_override_file_name
     326!   print*, 'aerosol_optics_override_file_name, cloud_pdf_override_file_name = ', &
     327!           rad_config%aerosol_optics_override_file_name, rad_config%cloud_pdf_override_file_name
     328!   print*, 'gas_optics_sw_override_file_name, gas_optics_lw_override_file_name = ', &
     329!           rad_config%gas_optics_sw_override_file_name, rad_config%gas_optics_lw_override_file_name
     330   print*, 'i_liq_model, i_ice_model, max_3d_transfer_rate = ', &
     331           rad_config%i_liq_model, rad_config%i_ice_model, rad_config%max_3d_transfer_rate
     332   print*, 'min_cloud_effective_size, overhang_factor = ', &
     333           rad_config%min_cloud_effective_size, rad_config%overhang_factor
     334   print*, 'use_canopy_full_spectrum_sw, use_canopy_full_spectrum_lw = ', &
     335           rad_config%use_canopy_full_spectrum_sw, rad_config%use_canopy_full_spectrum_lw
     336   print*, 'do_canopy_fluxes_sw, do_canopy_fluxes_lw = ', &
     337           rad_config%do_canopy_fluxes_sw, rad_config%do_canopy_fluxes_lw
     338   print*, 'do_canopy_gases_sw, do_canopy_gases_lw = ', &
     339           rad_config%do_canopy_gases_sw, rad_config%do_canopy_gases_lw
     340   print*, 'use_general_cloud_optics, use_general_aerosol_optics = ', &
     341           rad_config%use_general_cloud_optics, rad_config%use_general_aerosol_optics
     342   print*, 'do_sw_delta_scaling_with_gases, i_overlap_scheme = ', &
     343           rad_config%do_sw_delta_scaling_with_gases, rad_config%i_overlap_scheme
     344   print*, 'i_solver_sw, i_solver_sw, use_beta_overlap, use_vectorizable_generator = ', &
     345           rad_config%i_solver_sw, rad_config%i_solver_lw, &
     346           rad_config%use_beta_overlap, rad_config%use_vectorizable_generator
     347   print*, 'use_expm_everywhere, iverbose, iverbosesetup = ', &
     348           rad_config%use_expm_everywhere, rad_config%iverbose, rad_config%iverbosesetup
     349   print*, 'cloud_inhom_decorr_scaling, cloud_fraction_threshold = ', &
     350           rad_config%cloud_inhom_decorr_scaling, rad_config%cloud_fraction_threshold
     351   print*, 'clear_to_thick_fraction, max_gas_od_3d, max_cloud_od = ', &
     352           rad_config%clear_to_thick_fraction, rad_config%max_gas_od_3d, rad_config%max_cloud_od
     353   print*, 'cloud_mixing_ratio_threshold, overhead_sun_factor =', &
     354           rad_config%cloud_mixing_ratio_threshold, rad_config%overhead_sun_factor
     355   print*, 'n_aerosol_types, i_aerosol_type_map, use_aerosols = ', &
     356           rad_config%n_aerosol_types, rad_config%i_aerosol_type_map, rad_config%use_aerosols
     357   print*, 'mono_lw_wavelength, mono_lw_total_od, mono_sw_total_od = ', &
     358           rad_config%mono_lw_wavelength, rad_config%mono_lw_total_od,rad_config% mono_sw_total_od
     359   print*, 'mono_lw_single_scattering_albedo, mono_sw_single_scattering_albedo = ', &
     360           rad_config%mono_lw_single_scattering_albedo, rad_config%mono_sw_single_scattering_albedo
     361   print*, 'mono_lw_asymmetry_factor, mono_sw_asymmetry_factor = ', &
     362           rad_config%mono_lw_asymmetry_factor, rad_config%mono_sw_asymmetry_factor
     363   print*, 'i_cloud_pdf_shape = ', &
     364           rad_config%i_cloud_pdf_shape
     365!           cloud_type_name, use_thick_cloud_spectral_averaging = ', &
     366!           rad_config%i_cloud_pdf_shape, rad_config%cloud_type_name, &
     367!           rad_config%use_thick_cloud_spectral_averaging
     368   print*, 'do_nearest_spectral_sw_albedo, do_nearest_spectral_lw_emiss = ', &
     369           rad_config%do_nearest_spectral_sw_albedo, rad_config%do_nearest_spectral_lw_emiss
     370   print*, 'sw_albedo_wavelength_bound, lw_emiss_wavelength_bound = ', &
     371           rad_config%sw_albedo_wavelength_bound, rad_config%lw_emiss_wavelength_bound
     372   print*, 'i_sw_albedo_index, i_lw_emiss_index = ', &
     373           rad_config%i_sw_albedo_index, rad_config%i_lw_emiss_index
     374   print*, 'do_cloud_aerosol_per_lw_g_point = ', &
     375           rad_config%do_cloud_aerosol_per_lw_g_point
     376   print*, 'do_cloud_aerosol_per_sw_g_point, do_weighted_surface_mapping = ', &
     377           rad_config%do_cloud_aerosol_per_sw_g_point, rad_config%do_weighted_surface_mapping
     378   print*, 'n_bands_sw, n_bands_lw, n_g_sw, n_g_lw = ', &
     379           rad_config%n_bands_sw, rad_config%n_bands_lw, rad_config%n_g_sw, rad_config%n_g_lw
     380
     381           itap_ecrad=itap_ecrad+1
     382!   ENDIF         
     383endif           
     384
    413385! AI ATTENTION
    414386! Allocate memory in radiation objects
  • 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)
  • LMDZ6/trunk/libf/phylmd/phys_local_var_mod.F90

    r4639 r4677  
    272272!$OMP THREADPRIVATE(toplwad0_aerop, sollwad0_aerop)
    273273
     274!AI 08 2023 ajout pour Ecrad
     275      REAL,ALLOCATABLE,SAVE :: topswad_aero_s2(:), solswad_aero_s2(:)
     276!$OMP THREADPRIVATE(topswad_aero_s2, solswad_aero_s2)
     277      REAL,ALLOCATABLE,SAVE :: topswai_aero_s2(:), solswai_aero_s2(:)
     278!$OMP THREADPRIVATE(topswai_aero_s2, solswai_aero_s2)
     279      REAL,ALLOCATABLE,SAVE :: topswad0_aero_s2(:), solswad0_aero_s2(:)
     280!$OMP THREADPRIVATE(topswad0_aero_s2, solswad0_aero_s2)
     281      REAL,ALLOCATABLE,SAVE :: topsw_aero_s2(:,:), topsw0_aero_s2(:,:)
     282!$OMP THREADPRIVATE(topsw_aero_s2, topsw0_aero_s2)
     283      REAL,ALLOCATABLE,SAVE :: solsw_aero_s2(:,:), solsw0_aero_s2(:,:)
     284!$OMP THREADPRIVATE(solsw_aero_s2, solsw0_aero_s2)
     285      REAL,ALLOCATABLE,SAVE :: topswcf_aero_s2(:,:), solswcf_aero_s2(:,:)
     286!$OMP THREADPRIVATE(topswcf_aero_s2, solswcf_aero_s2)
     287! additional LW variables CK
     288      REAL,ALLOCATABLE,SAVE :: toplwad_aero_s2(:), sollwad_aero_s2(:)
     289!$OMP THREADPRIVATE(toplwad_aero_s2, sollwad_aero_s2)
     290      REAL,ALLOCATABLE,SAVE :: toplwai_aero_s2(:), sollwai_aero_s2(:)
     291!$OMP THREADPRIVATE(toplwai_aero_s2, sollwai_aero_s2)
     292      REAL,ALLOCATABLE,SAVE :: toplwad0_aero_s2(:), sollwad0_aero_s2(:)
     293!$OMP THREADPRIVATE(toplwad0_aero_s2, sollwad0_aero_s2)
     294
    274295!Ajout de celles n??cessaires au phys_output_write_mod
    275296      REAL, SAVE, ALLOCATABLE :: tal1(:), pal1(:), pab1(:), pab2(:)
     
    538559      !$OMP THREADPRIVATE(distcltop)
    539560      REAL, SAVE, ALLOCATABLE :: temp_cltop(:,:)
    540       !$OMP THREADPRIVATE(temp_cltop)     
     561      !$OMP THREADPRIVATE(temp_cltop)
    541562
    542563
     
    617638      REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: budg_sed_part
    618639!$OMP THREADPRIVATE(budg_sed_part)
    619 #endif
    620 #ifdef REPROBUS
    621       REAL,SAVE,ALLOCATABLE    :: d_q_emiss(:,:)
    622 !$OMP THREADPRIVATE(d_q_emiss)
    623640#endif
    624641
     
    774791      ALLOCATE(toplwad0_aerop(klon), sollwad0_aerop(klon))
    775792
     793!AI Ajout Ecrad (3Deffect)
     794      ALLOCATE(topswad_aero_s2(klon), solswad_aero_s2(klon))
     795      ALLOCATE(topswai_aero_s2(klon), solswai_aero_s2(klon))
     796      ALLOCATE(topswad0_aero_s2(klon), solswad0_aero_s2(klon))
     797      ALLOCATE(topsw_aero_s2(klon,naero_grp), topsw0_aero_s2(klon,naero_grp))
     798      ALLOCATE(solsw_aero_s2(klon,naero_grp), solsw0_aero_s2(klon,naero_grp))
     799      ALLOCATE(topswcf_aero_s2(klon,naero_grp), solswcf_aero_s2(klon,naero_grp))
     800! additional LW variables CK
     801      ALLOCATE(toplwad_aero_s2(klon), sollwad_aero_s2(klon))
     802      ALLOCATE(toplwai_aero_s2(klon), sollwai_aero_s2(klon))
     803      ALLOCATE(toplwad0_aero_s2(klon), sollwad0_aero_s2(klon))
     804
     805
    776806! FH Ajout de celles necessaires au phys_output_write_mod
    777807
     
    911941      ALLOCATE(distcltop(klon,klev))
    912942      ALLOCATE(temp_cltop(klon,klev))
     943
    913944
    914945      ALLOCATE (zxsnow(klon),snowhgt(klon),qsnow(klon),to_ice(klon))
     
    11041135      DEALLOCATE(toplwad0_aerop, sollwad0_aerop)
    11051136
     1137!AI Ajout pour Ecrad (3Deffect)
     1138      DEALLOCATE(topswad_aero_s2, solswad_aero_s2)
     1139      DEALLOCATE(topswai_aero_s2, solswai_aero_s2)
     1140      DEALLOCATE(topswad0_aero_s2, solswad0_aero_s2)
     1141      DEALLOCATE(topsw_aero_s2, topsw0_aero_s2)
     1142      DEALLOCATE(solsw_aero_s2, solsw0_aero_s2)
     1143      DEALLOCATE(topswcf_aero_s2, solswcf_aero_s2)
     1144!CK LW diagnostics
     1145      DEALLOCATE(toplwad_aero_s2, sollwad_aero_s2)
     1146      DEALLOCATE(toplwai_aero_s2, sollwai_aero_s2)
     1147      DEALLOCATE(toplwad0_aero_s2, sollwad0_aero_s2)     
     1148
    11061149! FH Ajout de celles necessaires au phys_output_write_mod
    11071150      DEALLOCATE(tal1, pal1, pab1, pab2)
  • LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r4619 r4677  
    536536  TYPE(ctrl_out), SAVE :: o_tauy = ctrl_out((/ 1, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
    537537    'tauy', 'Meridional wind stress', 'Pa', (/ ('', i=1, 10) /))
     538
     539!AI Ecrad 3Deffect
     540#ifdef CPP_ECRAD
     541  TYPE(ctrl_out), SAVE :: o_sols_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     542    'sols_s2', 'Solar rad. at surf.', 'W/m2', (/ ('', i=1, 10) /))
     543  TYPE(ctrl_out), SAVE :: o_sols0_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     544    'sols0_s2', 'Solar rad. at surf.', 'W/m2', (/ ('', i=1, 10) /))
     545  TYPE(ctrl_out), SAVE :: o_soll_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     546    'soll_s2', 'IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     547  TYPE(ctrl_out), SAVE :: o_soll0_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     548    'soll0_s2', 'IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     549  TYPE(ctrl_out), SAVE :: o_tops_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     550    'tops_s2', 'Solar rad. at TOA', 'W/m2', (/ ('', i=1, 10) /))
     551  TYPE(ctrl_out), SAVE :: o_tops0_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     552    'tops0_s2', 'CS Solar rad. at TOA', 'W/m2', (/ ('', i=1, 10) /))
     553  TYPE(ctrl_out), SAVE :: o_topl_s2 = ctrl_out((/ 11, 11, 10, 11, 10, 10, 11, 11, 11, 11/), &
     554    'topl_s2', 'IR rad. at TOA', 'W/m2', (/ ('', i=1, 10) /))
     555  TYPE(ctrl_out), SAVE :: o_topl0_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     556    'topl0_s2', 'IR rad. at TOA', 'W/m2', (/ ('', i=1, 10) /))
     557  TYPE(ctrl_out), SAVE :: o_SWupTOA_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     558    'SWupTOA_s2', 'SWup at TOA', 'W/m2', (/ ('', i=1, 10) /))
     559  TYPE(ctrl_out), SAVE :: o_SWupTOAclr_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     560    'SWupTOAclr_s2', 'SWup clear sky at TOA', 'W/m2', (/ ('', i=1, 10) /))
     561  TYPE(ctrl_out), SAVE :: o_SWupTOAcleanclr_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     562    'SWupTOAcleanclr_s2', 'SWup clear sky clean (no aerosol) at TOA', 'W/m2', (/ ('', i=1, 10) /))
     563  TYPE(ctrl_out), SAVE :: o_SWdnTOA_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     564    'SWdnTOA_s2', 'SWdn at TOA', 'W/m2', (/ ('', i=1, 10) /))
     565  TYPE(ctrl_out), SAVE :: o_SWdnTOAclr_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     566    'SWdnTOAclr_s2', 'SWdn clear sky at TOA', 'W/m2', (/ ('', i=1, 10) /))
     567  TYPE(ctrl_out), SAVE :: o_nettop_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     568    'nettop_s2', 'Net dn radiatif flux at TOA', 'W/m2', (/ ('', i=1, 10) /))
     569  TYPE(ctrl_out), SAVE :: o_LWdnSFC_s2 = ctrl_out((/ 11, 11, 10, 10, 11, 10, 11, 11, 11, 11/), &
     570    'LWdnSFC_s2', 'Down. IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     571  TYPE(ctrl_out), SAVE :: o_LWdnSFCclr_s2 = ctrl_out((/ 11, 11, 10, 10, 11, 10, 11, 11, 11, 11/), &
     572    'LWdnSFCclr_s2', 'Down. CS IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     573  TYPE(ctrl_out), SAVE :: o_SWupSFC_s2 = ctrl_out((/ 11, 11, 10, 10, 11, 10, 11, 11, 11, 11/), &
     574    'SWupSFC_s2', 'SWup at surface', 'W/m2', (/ ('', i=1, 10) /))
     575  TYPE(ctrl_out), SAVE :: o_SWupSFCclr_s2 = ctrl_out((/ 11, 11, 10, 10, 11, 10, 11, 11, 11, 11/), &
     576    'SWupSFCclr_s2', 'SWup clear sky at surface', 'W/m2', (/ ('', i=1, 10) /))
     577  TYPE(ctrl_out), SAVE :: o_SWupSFCcleanclr_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     578    'SWupSFCcleanclr_s2', 'SWup clear sky clean (no aerosol) at surface', 'W/m2', (/ ('', i=1, 10) /))
     579  TYPE(ctrl_out), SAVE :: o_fdiffSWdnSFC_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     580    'fdiffSWdnSFC_s2', 'Fraction of diffuse SWdn at surface', 'W/m2', (/ ('', i=1, 10) /))
     581  TYPE(ctrl_out), SAVE :: o_SWdnSFC_s2 = ctrl_out((/ 11, 11, 11, 10, 11, 10, 11, 11, 11, 11/), &
     582    'SWdnSFC_s2', 'SWdn at surface', 'W/m2', (/ ('', i=1, 10) /))
     583  TYPE(ctrl_out), SAVE :: o_SWdnSFCclr_s2 = ctrl_out((/ 11, 11, 10, 10, 11, 10, 11, 11, 11, 11/), &
     584    'SWdnSFCclr_s2', 'SWdn clear sky at surface', 'W/m2', (/ ('', i=1, 10) /))
     585  TYPE(ctrl_out), SAVE :: o_SWdnSFCcleanclr_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     586    'SWdnSFCcleanclr_s2', 'SWdn clear sky clean (no aerosol) at surface', 'W/m2', (/ ('', i=1, 10) /))
     587  TYPE(ctrl_out), SAVE :: o_LWupSFC_s2 = ctrl_out((/ 11, 11, 10, 10, 11, 10, 11, 11, 11, 11/), &
     588    'LWupSFC_s2', 'Upwd. IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     589  TYPE(ctrl_out), SAVE :: o_LWupSFCclr_s2 = ctrl_out((/ 11, 11, 10, 10, 10, 10, 11, 11, 11, 11/), &
     590    'LWupSFCclr_s2', 'CS Upwd. IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     591  TYPE(ctrl_out), SAVE :: o_LWupTOAcleanclr_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     592    'LWupTOAcleanclr_s2', 'Upward CS clean (no aerosol) IR rad. at TOA', 'W/m2', (/ ('', i=1, 10) /))
     593  TYPE(ctrl_out), SAVE :: o_LWdnSFCcleanclr_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     594    'LWdnSFCcleanclr_s2', 'Downward CS clean (no aerosol) IR rad. at surface', 'W/m2', (/ ('', i=1, 10) /))
     595  TYPE(ctrl_out), SAVE :: o_rsu_s2 = ctrl_out((/ 11, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
     596    'rsu_s2', 'SW upward radiation', 'W m-2', (/ ('', i=1, 10) /))
     597  TYPE(ctrl_out), SAVE :: o_rsd_s2 = ctrl_out((/ 11, 10, 10, 10, 10, 10, 11, 11, 11, 11/), &
     598    'rsd_s2', 'SW downward radiation', 'W m-2', (/ ('', i=1, 10) /))
     599  TYPE(ctrl_out), SAVE :: o_rlu_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     600    'rlu_s2', 'LW upward radiation', 'W m-2', (/ ('', i=1, 10) /))
     601  TYPE(ctrl_out), SAVE :: o_rld_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     602    'rld_s2', 'LW downward radiation', 'W m-2', (/ ('', i=1, 10) /))
     603  TYPE(ctrl_out), SAVE :: o_rsucs_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     604    'rsucs_s2', 'SW CS upward radiation', 'W m-2', (/ ('', i=1, 10) /))
     605  TYPE(ctrl_out), SAVE :: o_rsdcs_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     606    'rsdcs_s2', 'SW CS downward radiation', 'W m-2', (/ ('', i=1, 10) /))
     607  TYPE(ctrl_out), SAVE :: o_rlucs_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     608    'rlucs_s2', 'LW CS upward radiation', 'W m-2', (/ ('', i=1, 10) /))
     609  TYPE(ctrl_out), SAVE :: o_rldcs_s2 = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), &
     610    'rldcs_s2', 'LW CS downward radiation', 'W m-2', (/ ('', i=1, 10) /))
     611#endif
     612
    538613
    539614  TYPE(ctrl_out), SAVE, DIMENSION(4) :: o_taux_srf = (/           &
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r4619 r4677  
    228228         o_zxfluxt,o_zxfluxq
    229229
     230#ifdef CPP_ECRAD
     231    USE phys_output_ctrlout_mod, ONLY:  &
     232         o_soll0_s2,o_soll_s2,o_sols0_s2,o_sols_s2, &
     233         o_topl0_s2,o_topl_s2,o_tops0_s2,o_tops_s2   
     234#endif
     235
    230236#ifdef CPP_StratAer
    231237    USE phys_output_ctrlout_mod, ONLY:  &
     
    279285#endif
    280286         dt_ns, delta_sst, dter, dser
     287         
     288! AI 08 2023 pour ECRAD 3Deffect
     289#ifdef CPP_ECRAD
     290    USE phys_state_var_mod, ONLY: &
     291        sollw0_s2,sollw_s2,solsw0_s2,solsw_s2, &
     292        toplw0_s2,toplw_s2,topsw0_s2,topsw_s2
     293#endif
     294
    281295
    282296    USE phys_local_var_mod, ONLY: zxfluxlat, slp, ptstar, pt0, zxtsol, zt2m, &
     
    10511065       ENDIF
    10521066
     1067!AI 08 2023 Ecrad 3Deffect
     1068#ifdef CPP_ECRAD
     1069     if (ok_3Deffect) then
     1070        IF (vars_defined) THEN
     1071          zx_tmp_fi2d = solsw_s2*swradcorr
     1072       ENDIF
     1073       CALL histwrite_phy(o_sols_s2, zx_tmp_fi2d)
     1074       IF (vars_defined) THEN
     1075          zx_tmp_fi2d = solsw0_s2*swradcorr
     1076       ENDIF
     1077       CALL histwrite_phy(o_sols0_s2, zx_tmp_fi2d)
     1078       CALL histwrite_phy(o_soll_s2, sollw_s2)
     1079       CALL histwrite_phy(o_soll0_s2, sollw0_s2)
     1080       IF (vars_defined) THEN
     1081         zx_tmp_fi2d = topsw_s2*swradcorr
     1082       ENDIF
     1083       CALL histwrite_phy(o_tops_s2, zx_tmp_fi2d)
     1084
     1085       IF (vars_defined) THEN
     1086         zx_tmp_fi2d = topsw0_s2*swradcorr
     1087       ENDIF
     1088       CALL histwrite_phy(o_tops0_s2, zx_tmp_fi2d)
     1089
     1090       CALL histwrite_phy(o_topl_s2, toplw_s2)
     1091       CALL histwrite_phy(o_topl0_s2, toplw0_s2)
     1092     endif
     1093#endif       
     1094
    10531095       CALL histwrite_phy(o_bils, bils)
    10541096       CALL histwrite_phy(o_bils_diss, bils_diss)
  • LMDZ6/trunk/libf/phylmd/phys_state_var_mod.F90

    r4613 r4677  
    399399!$OMP THREADPRIVATE(swdnc0p, swdn0p, swdnp, swupc0p, swup0p, swupp)
    400400
     401!AI ajout variables double appel Ecrad (3Deffect)
     402      REAL,ALLOCATABLE,SAVE :: heat_s2(:,:), cool_s2(:,:)
     403!$OMP THREADPRIVATE(heat_s2, cool_s2)
     404      REAL,ALLOCATABLE,SAVE :: heat0_s2(:,:), cool0_s2(:,:)
     405!$OMP THREADPRIVATE(heat0_s2, cool0_s2)
     406      REAL,ALLOCATABLE,SAVE :: radsol_s2(:), topsw_s2(:), toplw_s2(:)
     407!$OMP THREADPRIVATE(radsol_s2, topsw_s2, toplw_s2)
     408      REAL,ALLOCATABLE,SAVE :: albpla_s2(:)
     409!$OMP THREADPRIVATE(albpla_s2)
     410      REAL,ALLOCATABLE,SAVE :: solsw_s2(:), solswfdiff_s2(:), sollw_s2(:)
     411!$OMP THREADPRIVATE(solsw_s2, solswfdiff_s2, sollw_s2)
     412      REAL,ALLOCATABLE,SAVE :: sollwdown_s2(:)
     413!$OMP THREADPRIVATE(sollwdown_s2)
     414      REAL,ALLOCATABLE,SAVE :: topsw0_s2(:),toplw0_s2(:)
     415      REAL,ALLOCATABLE,SAVE :: solsw0_s2(:),sollw0_s2(:)
     416!$OMP THREADPRIVATE(topsw0_s2,toplw0_s2,solsw0_s2,sollw0_s2)
     417      REAL,ALLOCATABLE,SAVE :: lwdnc0_s2(:,:), lwdn0_s2(:,:), lwdn_s2(:,:)
     418      REAL,ALLOCATABLE,SAVE :: lwupc0_s2(:,:), lwup0_s2(:,:), lwup_s2(:,:)
     419!$OMP THREADPRIVATE(lwdnc0_s2,lwdn0_s2,lwdn_s2,lwupc0_s2,lwup0_s2,lwup_s2)       
     420      REAL,ALLOCATABLE,SAVE :: swdnc0_s2(:,:), swdn0_s2(:,:), swdn_s2(:,:)
     421      REAL,ALLOCATABLE,SAVE :: swupc0_s2(:,:), swup0_s2(:,:), swup_s2(:,:)
     422!$OMP THREADPRIVATE(swdnc0_s2, swdn0_s2, swdn_s2, swupc0_s2, swup0_s2, swup_s2)
     423
    401424! pbase : cloud base pressure
    402425! bbase : cloud base buoyancy
     
    697720      ALLOCATE(swdnc0p(klon,klevp1), swdn0p(klon,klevp1), swdnp(klon,klevp1))
    698721      ALLOCATE(swupc0p(klon,klevp1), swup0p(klon,klevp1), swupp(klon,klevp1))
     722
     723!AI Ajout pour Ecrad (3Deffect)       
     724      ALLOCATE(heat_s2(klon,klev), cool_s2(klon,klev))
     725      ALLOCATE(heat0_s2(klon,klev), cool0_s2(klon,klev))
     726      ALLOCATE(radsol_s2(klon), topsw_s2(klon), toplw_s2(klon))
     727      ALLOCATE(albpla_s2(klon))
     728      ALLOCATE(solsw_s2(klon), solswfdiff_s2(klon), sollw_s2(klon))
     729      ALLOCATE(sollwdown_s2(klon))
     730      ALLOCATE(topsw0_s2(klon),toplw0_s2(klon))
     731      ALLOCATE(solsw0_s2(klon),sollw0_s2(klon))
     732      ALLOCATE(lwdnc0_s2(klon,klevp1), lwdn0_s2(klon,klevp1), lwdn_s2(klon,klevp1))
     733      ALLOCATE(lwupc0_s2(klon,klevp1), lwup0_s2(klon,klevp1), lwup_s2(klon,klevp1))
     734      ALLOCATE(swdnc0_s2(klon,klevp1), swdn0_s2(klon,klevp1), swdn_s2(klon,klevp1))
     735      ALLOCATE(swupc0_s2(klon,klevp1), swup0_s2(klon,klevp1), swup_s2(klon,klevp1))
    699736
    700737      ALLOCATE(cape(klon))
     
    856893      DEALLOCATE(topsw0,toplw0,solsw0,sollw0)
    857894      DEALLOCATE(albpla)
     895
     896!AI Ajout pour Ecrad (3Deffect)
     897      DEALLOCATE(heat_s2, cool_s2)
     898      DEALLOCATE(heat0_s2, cool0_s2)
     899      DEALLOCATE(radsol_s2, topsw_s2, toplw_s2)
     900      DEALLOCATE(albpla_s2)
     901      DEALLOCATE(solsw_s2, solswfdiff_s2, sollw_s2)
     902      DEALLOCATE(sollwdown_s2)
     903      DEALLOCATE(topsw0_s2,toplw0_s2)
     904      DEALLOCATE(solsw0_s2,sollw0_s2)
     905      DEALLOCATE(lwdnc0_s2, lwdn0_s2, lwdn_s2)
     906      DEALLOCATE(lwupc0_s2, lwup0_s2, lwup_s2)
     907      DEALLOCATE(swdnc0_s2, swdn0_s2, swdn_s2)
     908      DEALLOCATE(swupc0_s2, swup0_s2, swup_s2)
     909
    858910!IM ajout variables CFMIP2/CMIP5
    859911      DEALLOCATE(heatp, coolp)
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r4666 r4677  
    203203       toplwai_aero,sollwai_aero,   &
    204204       toplwad0_aero,sollwad0_aero, &
     205       !pour Ecrad
     206       topswad_aero_s2, solswad_aero_s2,   &
     207       topswai_aero_s2, solswai_aero_s2,   &
     208       topswad0_aero_s2, solswad0_aero_s2, &
     209       topsw_aero_s2, topsw0_aero_s2,      &
     210       solsw_aero_s2, solsw0_aero_s2,      &
     211       topswcf_aero_s2, solswcf_aero_s2,   &
     212       !LW diagnostics
     213       toplwad_aero_s2, sollwad_aero_s2,   &
     214       toplwai_aero_s2, sollwai_aero_s2,   &
     215       toplwad0_aero_s2, sollwad0_aero_s2, &
    205216       !
    206217       topsw_aero,solsw_aero,       &
     
    221232       toplwai_aerop, sollwai_aerop,   &
    222233       toplwad0_aerop, sollwad0_aerop, &
     234       !pour Ecrad
     235       topswad_aero_s2, solswad_aero_s2,   &
     236       topswai_aero_s2, solswai_aero_s2,   &
     237       topswad0_aero_s2, solswad0_aero_s2, &
     238       topsw_aero_s2, topsw0_aero_s2,      &
     239       solsw_aero_s2, solsw0_aero_s2,      &
     240       topswcf_aero_s2, solswcf_aero_s2,   &
     241       !LW diagnostics
     242       toplwad_aero_s2, sollwad_aero_s2,   &
     243       toplwai_aero_s2, sollwai_aero_s2,   &
     244       toplwad0_aero_s2, sollwad0_aero_s2, &
    223245       !
    224246       ptstar, pt0, slp, &
     
    14971519       WRITE(lunout,*) 'Call to infocfields from physiq'
    14981520       CALL infocfields_init
     1521
     1522       !AI 08 2023
     1523#ifdef CPP_ECRAD
     1524       ok_3Deffect=.false.
     1525       CALL getin_p('ok_3Deffect',ok_3Deffect)
     1526       namelist_ecrad_file='namelist_ecrad'
     1527#endif
    14991528
    15001529    ENDIF
     
    45814610                     ZSWFT0_i, ZFSDN0, ZFSUP0)
    45824611          ENDIF !ok_4xCO2atm
     4612
     4613! A.I aout 2023
     4614! Effet 3D des nuages Ecrad
     4615! a passer : nom du ficher namelist et cles ok_3Deffect
     4616! a declarer comme iflag_rrtm et a lire dans physiq.def
     4617#ifdef CPP_ECRAD
     4618          IF (ok_3Deffect) then
     4619!                print*,'ok_3Deffect = ',ok_3Deffect 
     4620                namelist_ecrad_file='namelist_ecrad_s2'
     4621                CALL radlwsw &
     4622                     (dist, rmu0, fract,  &
     4623                     paprs, pplay,zxtsol,SFRWL,albsol_dir, albsol_dif, &
     4624                     t_seri,q_seri,wo, &
     4625                     cldfrarad, cldemirad, cldtaurad, &
     4626                     ok_ade.OR.flag_aerosol_strat.GT.0, ok_aie,  ok_volcan, flag_volc_surfstrat, &
     4627                     flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
     4628                     tau_aero, piz_aero, cg_aero, &
     4629                     tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm, &
     4630                     tau_aero_lw_rrtm, &
     4631                     cldtaupi, &
     4632                     zqsat, flwc, fiwc, &
     4633                     ref_liq, ref_ice, ref_liq_pi, ref_ice_pi, &
     4634! A modifier             
     4635                     heat_s2,heat0_s2,cool_s2,cool0_s2,albpla_s2, &
     4636                     heat_volc,cool_volc, &
     4637                     topsw_s2,toplw_s2,solsw_s2,solswfdiff_s2,sollw_s2, &
     4638                     sollwdown_s2, &
     4639                     topsw0_s2,toplw0_s2,solsw0_s2,sollw0_s2, &
     4640                     lwdnc0_s2, lwdn0_s2, lwdn_s2, lwupc0_s2, lwup0_s2, lwup_s2,  &
     4641                     swdnc0_s2, swdn0_s2, swdn_s2, swupc0_s2, swup0_s2, swup_s2, &
     4642                     topswad_aero_s2, solswad_aero_s2, &
     4643                     topswai_aero_s2, solswai_aero_s2, &
     4644                     topswad0_aero_s2, solswad0_aero_s2, &
     4645                     topsw_aero_s2, topsw0_aero_s2, &
     4646                     solsw_aero_s2, solsw0_aero_s2, &
     4647                     topswcf_aero_s2, solswcf_aero_s2, &
     4648                                !-C. Kleinschmitt for LW diagnostics
     4649                     toplwad_aero_s2, sollwad_aero_s2,&
     4650                     toplwai_aero_s2, sollwai_aero_s2, &
     4651                     toplwad0_aero_s2, sollwad0_aero_s2,&
     4652                                !-end
     4653                     ZLWFT0_i, ZFLDN0, ZFLUP0, &
     4654                     ZSWFT0_i, ZFSDN0, ZFSUP0)
     4655             namelist_ecrad_file='namelist_ecrad'
     4656          ENDIF ! ok_3Deffect
     4657#endif
     4658
    45834659       ENDIF ! aerosol_couple
    45844660       itaprad = 0
  • LMDZ6/trunk/libf/phylmd/radlwsw_m.F90

    r4489 r4677  
    13481348      CALL RADIATION_SCHEME &
    13491349      & (ist, iend, klon, klev, naero_grp, NSW, &
     1350      & namelist_ecrad_file, ok_3Deffect, &
    13501351      & day_cur, current_time, &
    13511352!       Cste solaire/(d_Terre-Soleil)**2
Note: See TracChangeset for help on using the changeset viewer.