Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (7 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/ecrad/lmdz/radiation_scheme_mod.f90

    r5268 r5791  
    6565
    6666USE mod_phys_lmdz_para
     67use geometry_mod, only: longitude_deg, latitude_deg
    6768
    6869IMPLICIT NONE
     
    160161
    161162! Direct component of surface flux into horizontal plane
    162 REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR(KLON)
    163 REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR_CLEAR(KLON)
     163REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR(KLON,KLEV+1)
     164REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR_CLEAR(KLON,KLEV+1)
    164165! As PFLUX_DIR but into a plane perpendicular to the sun
    165166REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR_INTO_SUN(KLON)
     
    260261  if (debut_ecrad) then
    261262   call SETUP_RADIATION_SCHEME(loutput,namelist_file,rad_config,driver_config)
    262    debut_ecrad=.false.
    263263  endif
    264264!$OMP END MASTER
     
    541541!    endif
    542542!   endif
     543if (debut_ecrad .and. driver_config%do_save_inputs) &
     544     call save_inputs('inputs.nc', rad_config, single_level, thermodynamics, &
     545     gas, cloud, aerosol, lat = latitude_deg, lon = longitude_deg)
     546
    543547CALL radiation(KLON, KLEV, KIDIA, KFDIA, rad_config, &
    544548     &  single_level, thermodynamics, gas, cloud, aerosol, flux)
     
    585589!PFLUX_SW_UP_CLEAR_SURF(KIDIA:KFDIA) = flux%sw_up_clear(KIDIA:KFDIA,KLEV+1)
    586590!PFLUX_LW_UP_CLEAR_SURF(KIDIA:KFDIA) = flux%lw_up_clear(KIDIA:KFDIA,KLEV+1)
    587 PFLUX_DIR(KIDIA:KFDIA) = flux%sw_dn_direct(KIDIA:KFDIA,KLEV+1)
    588 PFLUX_DIR_CLEAR(KIDIA:KFDIA) = flux%sw_dn_direct_clear(KIDIA:KFDIA,KLEV+1)
     591! Direct component of flux into horizontal plane
     592PFLUX_DIR(KIDIA:KFDIA,:) = flux%sw_dn_direct(KIDIA:KFDIA,:)
     593PFLUX_DIR_CLEAR(KIDIA:KFDIA,:) = flux%sw_dn_direct_clear(KIDIA:KFDIA,:)
    589594PFLUX_DIR_INTO_SUN(KIDIA:KFDIA) = 0.0_JPRB
    590595WHERE (PMU0(KIDIA:KFDIA) > EPSILON(1.0_JPRB))
    591   PFLUX_DIR_INTO_SUN(KIDIA:KFDIA) = PFLUX_DIR(KIDIA:KFDIA) / PMU0(KIDIA:KFDIA)
     596! Direct Surface component of flux into a plane perpendicular to the sun       
     597  PFLUX_DIR_INTO_SUN(KIDIA:KFDIA) = PFLUX_DIR(KIDIA:KFDIA,KLEV+1) / PMU0(KIDIA:KFDIA)
    592598END WHERE
    593599! Top-of-atmosphere downwelling flux
     
    656662
    657663IF (LHOOK) CALL DR_HOOK('RADIATION_SCHEME',1,ZHOOK_HANDLE)
     664debut_ecrad=.false.
    658665
    659666END SUBROUTINE RADIATION_SCHEME
     
    849856
    850857! Direct component of surface flux into horizontal plane
    851 REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR(KLON)
    852 REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR_CLEAR(KLON)
     858REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR(KLON,KLEV+1)
     859REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR_CLEAR(KLON,KLEV+1)
    853860! As PFLUX_DIR but into a plane perpendicular to the sun
    854861REAL(KIND=JPRB),  INTENT(OUT) :: PFLUX_DIR_INTO_SUN(KLON)
     
    12831290!PFLUX_SW_UP_CLEAR_SURF(KIDIA:KFDIA) = flux%sw_up_clear(KIDIA:KFDIA,KLEV+1)
    12841291!PFLUX_LW_UP_CLEAR_SURF(KIDIA:KFDIA) = flux%lw_up_clear(KIDIA:KFDIA,KLEV+1)
    1285 PFLUX_DIR(KIDIA:KFDIA) = flux%sw_dn_direct(KIDIA:KFDIA,KLEV+1)
    1286 PFLUX_DIR_CLEAR(KIDIA:KFDIA) = flux%sw_dn_direct_clear(KIDIA:KFDIA,KLEV+1)
     1292PFLUX_DIR(KIDIA:KFDIA,:) = flux%sw_dn_direct(KIDIA:KFDIA,:)
     1293PFLUX_DIR_CLEAR(KIDIA:KFDIA,:) = flux%sw_dn_direct_clear(KIDIA:KFDIA,:)
    12871294PFLUX_DIR_INTO_SUN(KIDIA:KFDIA) = 0.0_JPRB
    12881295WHERE (PMU0(KIDIA:KFDIA) > EPSILON(1.0_JPRB))
    1289   PFLUX_DIR_INTO_SUN(KIDIA:KFDIA) = PFLUX_DIR(KIDIA:KFDIA) / PMU0(KIDIA:KFDIA)
     1296  PFLUX_DIR_INTO_SUN(KIDIA:KFDIA) = PFLUX_DIR(KIDIA:KFDIA,KLEV+1) / PMU0(KIDIA:KFDIA)
    12901297END WHERE
    12911298! Top-of-atmosphere downwelling flux
  • LMDZ6/branches/contrails/libf/phylmd/ecrad/lmdz/radiation_setup.f90

    r5268 r5791  
    11MODULE RADIATION_SETUP
    22
    3 ! RADIATION_SETUP - Setting up modular radiation scheme
    4 !
    5 ! AUTHOR
    6 ! ------
    7 !   Robin Hogan, ECMWF
    8 !   Original: 2015-09-16
    9 !
    10 ! MODIFICATIONS
    11 ! -------------
    12 !   Abderrahmane Idelkadi LMD, juillet 2023
    13 !
    14 !-----------------------------------------------------------------------
     3  ! RADIATION_SETUP - Setting up modular radiation scheme
     4  !
     5  ! AUTHOR
     6  ! ------
     7  !   Robin Hogan, ECMWF
     8  !   Original: 2015-09-16
     9  !
     10  ! MODIFICATIONS
     11  ! -------------
     12  !   Abderrahmane Idelkadi LMD, juillet 2023
     13  !
     14  !-----------------------------------------------------------------------
    1515
    1616  USE PARKIND1,         ONLY : JPRB
     
    5252  ! to print lots of information during the setup stage (default is
    5353  ! no).
    54 ! AI At the end of the routine, the parameters are read in namelist
    55 !   
     54  ! AI At the end of the routine, the parameters are read in namelist
     55  !
    5656  SUBROUTINE SETUP_RADIATION_SCHEME(LOUTPUT,file_name,rad_config,driver_config)
    5757
    58 !    USE radiation_config, ONLY : config_type, &
    59 !        &                       ISolverMcICA, ISolverSpartacus, &
    60 !        &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
    61 !        &                       IIceModelFu, IIceModelBaran, &
    62 !        &                       IOverlapExponentialRandom
     58    !    USE radiation_config, ONLY : config_type, &
     59    !        &                       ISolverMcICA, ISolverSpartacus, &
     60    !        &                       ILiquidModelSlingo, ILiquidModelSOCRATES, &
     61    !        &                       IIceModelFu, IIceModelBaran, &
     62    !        &                       IOverlapExponentialRandom
    6363    USE mod_phys_lmdz_para
    64      
     64
    6565    USE YOMHOOK,  ONLY : LHOOK, DR_HOOK
    6666    USE YOMLUN,   ONLY : NULOUT, NULERR
    6767    USE YOESRTWN, ONLY : NMPSRTM
    6868
    69  !   USE radiation_interface,      ONLY : setup_radiation
    70  !   USE setup_config_from_lmdz,   ONLY : driver_config_type
     69    !   USE radiation_interface,      ONLY : setup_radiation
     70    !   USE setup_config_from_lmdz,   ONLY : driver_config_type
    7171
    7272    ! Whether or not to provide information on the radiation scheme
     
    9090
    9191    ! Configure verbosity of setup of radiation scheme
    92  
     92
    9393    print*,'********** Dans radiation_setup *****************'
    9494
    95 ! AI ATTENTION (parameters read in namelist file)
    96 !    file_name="namelist_ecrad"
    97     call rad_config%read(file_name=file_name)
    98     call driver_config%read(file_name)
    99 
    100     ! Use configuration data to set-up radiation scheme, including
    101     ! reading scattering datafiles
    102     CALL setup_radiation(rad_config)
     95    rad_config%i_aerosol_type_map(1:13) = (/ &
     96         &  -1, &
     97         &  -2, &
     98         &  -3, &
     99         &  -4, &
     100         &  -5, &
     101         &  -6, &
     102         &  -7, &
     103         &   1, &
     104         &   2, &
     105         &   3, &
     106         &  -8, &
     107         &  -9, &
     108         &   4 /)
    103109
    104110    ! Populate the mapping between the 14 RRTM shortwave bands and the
     
    108114    ! results...
    109115    ! Note that NMPSRTM(:)=(/  6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 2, 2, 1, 6 /)
    110 ! AI (6 albedo SW bands)
     116    ! AI (6 albedo SW bands)
    111117    call rad_config%define_sw_albedo_intervals(6, &
    112        &  [0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, &
    113        &   1.19e-6_jprb, 2.38e-6_jprb], [1,2,3,4,5,6])
     118         &  [0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, &
     119         &   1.19e-6_jprb, 2.38e-6_jprb], [1,2,3,4,5,6])
    114120    ! Likewise between the 16 RRTM longwave bands and the 2 emissivity
    115121    ! inputs (info taken from rrtm_ecrt_140gp_mcica.F90) representing
    116122    ! outside and inside the window region of the spectrum
    117 !     rad_config%i_emiss_from_band_lw = (/ 1,1,1,1,1,2,2,2,1,1,1,1,1,1,1,1 /)
    118 ! AI ATTENTION ?????
    119 !!    call rad_config%define_lw_emiss_intervals(3, &
    120 !!         &  (/ 8.0e-6_jprb,13.0e-6_jprb /),  (/ 1,2,1 /))
     123    !     rad_config%i_emiss_from_band_lw = (/ 1,1,1,1,1,2,2,2,1,1,1,1,1,1,1,1 /)
     124    ! AI ATTENTION ?????
     125    !!    call rad_config%define_lw_emiss_intervals(3, &
     126    !!         &  (/ 8.0e-6_jprb,13.0e-6_jprb /),  (/ 1,2,1 /))
    121127
    122 !    ! Get spectral weightings for UV and PAR
     128    ! AI ATTENTION (parameters read in namelist file)
     129    !    file_name="namelist_ecrad"
     130    call rad_config%read(file_name=file_name)
     131    call driver_config%read(file_name)
     132    call rad_config%print(iverbose = 2)
     133
     134    ! Use configuration data to set-up radiation scheme, including
     135    ! reading scattering datafiles
     136    CALL setup_radiation(rad_config)
     137
     138    !    ! Get spectral weightings for UV and PAR
    123139    call rad_config%get_sw_weights(0.2e-6_jprb, 0.4415e-6_jprb, &
    124140         &  NWEIGHT_UV, IBAND_UV, WEIGHT_UV, 'ultraviolet')
     
    127143         &  'photosynthetically active radiation, PAR')
    128144
    129      rad_config%i_aerosol_type_map(1:13) = (/ &
    130            &  -1, &
    131            &  -2, &
    132            &  -3, &
    133            &  -4, &
    134            &  -5, &
    135            &  -6, &
    136            &  -7, &
    137            &   1, &
    138            &   2, &
    139            &   3, &
    140            &  -8, &
    141            &  -9, &
    142            &   4 /)
    143 
    144 
    145145    IF (LHOOK) CALL DR_HOOK('RADIATION_SETUP:SETUP_RADIATION_SCHEME',1,ZHOOK_HANDLE)
    146146
  • LMDZ6/branches/contrails/libf/phylmd/ecrad/lmdz/setup_config_from_lmdz.f90

    r5268 r5791  
    2727     real(jprb) :: high_decorrelation_length = 2000.0_jprb
    2828
     29     ! Save inputs in "inputs.nc"
     30     logical :: do_save_inputs
    2931 contains
    3032 procedure :: read => read_config_from_namelist
     
    5759    real(jprb) :: mid_decorrelation_length
    5860    real(jprb) :: high_decorrelation_length
     61    logical :: do_save_inputs
    5962
    6063    namelist /radiation_driver/ ok_effective_size, ok_separation, &
     
    6366         &  high_inv_effective_size, middle_inv_effective_size, low_inv_effective_size, &
    6467         &  cloud_inhom_separation_factor, cloud_separation_scale_surface, &
    65          &  cloud_separation_scale_toa, cloud_separation_scale_power
     68         &  cloud_separation_scale_toa, cloud_separation_scale_power, &
     69         do_save_inputs
    6670
    6771    ok_effective_size = .false.
     
    8084    mid_decorrelation_length = 2000.0_jprb
    8185    high_decorrelation_length = 2000.0_jprb
     86    do_save_inputs = .false.
    8287
    8388    ! Open the namelist file and read the radiation_driver namelist
     
    118123    this%middle_inv_effective_size = middle_inv_effective_size
    119124    this%low_inv_effective_size = low_inv_effective_size
     125    this%do_save_inputs = do_save_inputs
    120126
    121127  end subroutine read_config_from_namelist         
Note: See TracChangeset for help on using the changeset viewer.