Ignore:
Timestamp:
Dec 6, 2022, 12:01:16 AM (2 years ago)
Author:
lguez
Message:

Sync latest trunk changes to Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmd/ecrad/radiation_config.F90

    r3908 r4368  
    609609
    610610    integer :: iunit ! Unit number of namelist file
     611
     612    logical :: lldeb_conf = .false.
    611613
    612614    namelist /radiation/ do_sw, do_lw, do_sw_direct, &
     
    844846    this%i_lw_emiss_index              = i_lw_emiss_index
    845847
     848! AI mars 2022
     849if (lldeb_conf) then
     850print*,'**************PARAMETRES DE CONFIGURATION OFFLINE*******************'
     851print*,'config%iverbosesetup   = ', iverbosesetup
     852print*,'config%do_lw   = ', do_lw
     853print*,'config%do_sw   = ', do_sw
     854print*,'config%do_clear   = ', do_clear
     855print*,'config%do_sw_direct   = ', do_sw_direct
     856print*,'config%do_3d_effects   = ', do_3d_effects
     857print*,'config%do_3d_lw_multilayer_effects   = ', do_3d_lw_multilayer_effects
     858print*,'config%do_lw_side_emissivity   = ', do_lw_side_emissivity
     859print*,'config%use_expm_everywhere   = ', use_expm_everywhere
     860print*,'config%use_aerosols   = ', use_aerosols
     861print*,'config%do_lw_cloud_scattering   = ', do_lw_cloud_scattering
     862print*,'config%do_lw_aerosol_scattering   = ', do_lw_aerosol_scattering
     863print*,'config%nregions   = ', n_regions
     864print*,'config%do_surface_sw_spectral_flux   = ', do_surface_sw_spectral_flux
     865print*,'config%do_sw_delta_scaling_with_gases   = ', &
     866do_sw_delta_scaling_with_gases
     867print*,'config%do_fu_lw_ice_optics_bug   = ', do_fu_lw_ice_optics_bug
     868print*,'config%do_canopy_fluxes_sw   = ', do_canopy_fluxes_sw
     869print*,'config%do_canopy_fluxes_lw   = ', do_canopy_fluxes_lw
     870print*,'config%use_canopy_full_spectrum_sw   = ', use_canopy_full_spectrum_sw
     871print*,'config%use_canopy_full_spectrum_lw   = ', use_canopy_full_spectrum_lw
     872print*,'config%do_canopy_gases_sw   = ', do_canopy_gases_sw
     873print*,'config%do_canopy_gases_lw   = ', do_canopy_gases_lw
     874print*,'config%mono_lw_wavelength   = ', mono_lw_wavelength
     875print*,'config%mono_lw_total_od   = ', mono_lw_total_od
     876print*,'config%mono_sw_total_od   = ', mono_sw_total_od
     877print*,'config%mono_lw_single_scattering_albedo   = ', &
     878mono_lw_single_scattering_albedo
     879print*,'config%mono_sw_single_scattering_albedo   = ', &
     880mono_sw_single_scattering_albedo
     881print*,'config%mono_lw_asymmetry_factor   = ', mono_lw_asymmetry_factor
     882print*,'config%mono_sw_asymmetry_factor   = ', mono_sw_asymmetry_factor
     883print*,'config%use_beta_overlap   = ', use_beta_overlap
     884print*,'config%cloud_inhom_decorr_scaling   = ', cloud_inhom_decorr_scaling
     885print*,'config%clear_to_thick_fraction   = ', clear_to_thick_fraction
     886print*,'config%overhead_sun_factor   = ', overhead_sun_factor
     887print*,'config%max_gas_od_3d   = ', max_gas_od_3d
     888print*,'config%max_cloud_od   = ', max_cloud_od
     889print*,'config%max_3d_transfer_rate   = ', max_3d_transfer_rate
     890print*,'config%min_cloud_effective_size   = ', &
     891max(1.0e-6_jprb,min_cloud_effective_size)
     892print*,'config%overhang_factor   = ', encroachment_scaling
     893
     894print*,'config%directory_name  = ',directory_name
     895print*,'config%cloud_pdf_override_file_name  = ',cloud_pdf_override_file_name
     896print*,'config%liq_optics_override_file_name  = ',liq_optics_override_file_name
     897print*,'config%ice_optics_override_file_name  = ',ice_optics_override_file_name
     898print*,'config%aerosol_optics_override_file_name  = ', &
     899aerosol_optics_override_file_name
     900print*,'config%cloud_fraction_threshold  = ',cloud_fraction_threshold
     901print*,'config%cloud_mixing_ratio_threshold  = ',cloud_mixing_ratio_threshold
     902print*,'config%n_aerosol_types  = ',n_aerosol_types
     903print*,'config%do_save_radiative_properties  = ',do_save_radiative_properties
     904print*,'config%do_lw_derivatives  = ',do_lw_derivatives
     905print*,'config%do_save_spectral_flux  = ',do_save_spectral_flux
     906print*,'config%do_save_gpoint_flux  = ',do_save_gpoint_flux
     907print*,'config%do_nearest_spectral_sw_albedo  = ',do_nearest_spectral_sw_albedo
     908print*,'config%do_nearest_spectral_lw_emiss   = ',do_nearest_spectral_lw_emiss
     909print*,'config%sw_albedo_wavelength_bound     = ',sw_albedo_wavelength_bound
     910print*,'config%lw_emiss_wavelength_bound      = ',lw_emiss_wavelength_bound
     911print*,'config%i_sw_albedo_index              = ',i_sw_albedo_index
     912print*,'config%i_lw_emiss_index               = ',i_lw_emiss_index
     913print*,'************************************************************************'
     914endif
    846915    if (do_save_gpoint_flux) then
    847916      ! Saving the fluxes every g-point overrides saving as averaged
     
    850919      ! save anything
    851920      this%do_save_spectral_flux = .true.
     921      print*,'config%do_save_spectral_flux = .true.'
    852922    end if
    853923
     
    855925    call get_enum_code(liquid_model_name, LiquidModelName, &
    856926         &            'liquid_model_name', this%i_liq_model)
     927    print*,'config%i_liq_model =', this%i_liq_model
    857928
    858929    ! Determine ice optics model
    859930    call get_enum_code(ice_model_name, IceModelName, &
    860931         &            'ice_model_name', this%i_ice_model)
    861 
     932    print*,'config%i_ice_model =', this%i_ice_model
    862933    ! Determine gas optics model
    863934    call get_enum_code(gas_model_name, GasModelName, &
    864935         &            'gas_model_name', this%i_gas_model)
     936    print*,'config%%i_gas_model = ', this%i_gas_model
    865937
    866938    ! Determine solvers
    867939    call get_enum_code(sw_solver_name, SolverName, &
    868940         &            'sw_solver_name', this%i_solver_sw)
     941    print*,'config%i_solver_sw = ', this%i_solver_sw
    869942    call get_enum_code(lw_solver_name, SolverName, &
    870943         &            'lw_solver_name', this%i_solver_lw)
    871 
     944    print*,'config%i_solver_lw = ', this%i_solver_lw
    872945    if (len_trim(sw_encroachment_name) > 1) then
    873946      call get_enum_code(sw_encroachment_name, EncroachmentName, &
     
    877950      call get_enum_code(sw_entrapment_name, EntrapmentName, &
    878951           &             'sw_entrapment_name', this%i_3d_sw_entrapment)
     952      print*,'config%i_3d_sw_entrapment = ', this%i_3d_sw_entrapment
    879953    end if
    880954
     
    882956    call get_enum_code(overlap_scheme_name, OverlapName, &
    883957         &             'overlap_scheme_name', this%i_overlap_scheme)
    884    
     958    print*,'config%i_overlap_scheme = ', this%i_overlap_scheme
    885959    ! Determine cloud PDF shape
    886960    call get_enum_code(cloud_pdf_shape_name, PdfShapeName, &
    887961         &             'cloud_pdf_shape_name', this%i_cloud_pdf_shape)
    888 
     962    print*,'config%i_cloud_pdf_shape = ', this%i_cloud_pdf_shape
    889963    this%i_aerosol_type_map = 0
    890964    if (this%use_aerosols) then
    891965      this%i_aerosol_type_map(1:n_aerosol_types) &
    892966           &  = i_aerosol_type_map(1:n_aerosol_types)
     967      print*,'config%i_aerosol_type_map = ', this%i_aerosol_type_map
    893968    end if
    894969
     
    900975      this%do_clouds = .false.
    901976    end if
     977    print*,'config%do_clouds = ', this%do_clouds
    902978
    903979    ! Normal subroutine exit
  • LMDZ6/branches/Ocean_skin/libf/phylmd/ecrad/radiation_ifs_rrtm.F90

    r3908 r4368  
    9797    ! can compute UV and photosynthetically active radiation for a
    9898    ! particular wavelength range
    99    if (.not.allocated(config%wavenumber1_sw)) then
    10099    allocate(config%wavenumber1_sw(config%n_bands_sw))
    101    end if
    102    if (.not.allocated(config%wavenumber2_sw)) then
    103100    allocate(config%wavenumber2_sw(config%n_bands_sw))
    104    end if
    105    if (.not.allocated(config%wavenumber1_lw)) then
    106101    allocate(config%wavenumber1_lw(config%n_bands_lw))
    107    end if
    108    if (.not.allocated(config%wavenumber2_lw)) then
    109102    allocate(config%wavenumber2_lw(config%n_bands_lw))
    110    end if
    111103    config%wavenumber1_lw = (/ 10, 350, 500, 630, 700, 820, 980, 1080, 1180, 1390, 1480, &
    112104         &  1800, 2080, 2250, 2380, 2600 /)
     
    117109    config%wavenumber2_sw = (/ 3250, 4000, 4650, 5150, 6150, 7700, 8050, 12850, 16000, &
    118110         &  22650, 29000, 38000, 50000, 2600 /)
    119 
    120    if (.not.allocated(config%i_band_from_g_sw)) then
     111    print*,'allocate dans ifs_rrtm'
    121112    allocate(config%i_band_from_g_sw          (config%n_g_sw))
    122    end if
    123    if (.not.allocated(config%i_band_from_g_lw)) then
    124113    allocate(config%i_band_from_g_lw          (config%n_g_lw))
    125    end if
    126    if (.not.allocated(config%i_band_from_reordered_g_sw)) then
    127114    allocate(config%i_band_from_reordered_g_sw(config%n_g_sw))
    128    end if
    129    if (.not.allocated(config%i_band_from_reordered_g_lw)) then
    130115    allocate(config%i_band_from_reordered_g_lw(config%n_g_lw))
    131    end if
    132    if (.not.allocated(config%i_g_from_reordered_g_sw)) then
    133116    allocate(config%i_g_from_reordered_g_sw(config%n_g_sw))
    134    end if
    135    if (.not.allocated(config%i_g_from_reordered_g_lw)) then
    136117    allocate(config%i_g_from_reordered_g_lw(config%n_g_lw))
    137    end if
    138118
    139119    ! Shortwave starts at 16: need to start at 1
  • LMDZ6/branches/Ocean_skin/libf/phylmd/ecrad/radiation_scheme.F90

    r3946 r4368  
    2222     &  PPRESSURE, PTEMPERATURE, &
    2323     &  PPRESSURE_H, PTEMPERATURE_H, PQ, PQSAT, &
    24      &  PCO2, PCH4, PN2O, PNO2, PCFC11, PCFC12, PHCFC22, PCCL4, PO3_DP, &
     24     &  PCO2, PCH4, PN2O, PNO2, PCFC11, PCFC12, PHCFC22, &
     25     &  PCCL4, PO3, PO2, &
    2526     &  PCLOUD_FRAC, PQ_LIQUID, PQ_ICE, PQ_RAIN, PQ_SNOW, &
    2627     &  ZRE_LIQUID_UM, ZRE_ICE_UM, &
     
    9596
    9697! Modules from radiation library
    97 ! AI ATTENTION
    98 !use radiation_config,         only : config_type
    9998USE radiation_single_level,   ONLY : single_level_type
    10099USE radiation_thermodynamics, ONLY : thermodynamics_type
     
    105104USE radiation_interface,      ONLY : radiation, set_gas_units
    106105USE radiation_save,           ONLY : save_inputs
     106
     107USE mod_phys_lmdz_para
    107108
    108109IMPLICIT NONE
     
    151152! AI
    152153REAL(KIND=JPRB),   INTENT(IN) :: PQSAT(KLON,KLEV)
    153 REAL(KIND=JPRB),   INTENT(IN) :: PCO2(KLON,KLEV)
    154 REAL(KIND=JPRB),   INTENT(IN) :: PCH4(KLON,KLEV)
    155 REAL(KIND=JPRB),   INTENT(IN) :: PN2O(KLON,KLEV)
    156 REAL(KIND=JPRB),   INTENT(IN) :: PNO2(KLON,KLEV)
    157 REAL(KIND=JPRB),   INTENT(IN) :: PCFC11(KLON,KLEV)
    158 REAL(KIND=JPRB),   INTENT(IN) :: PCFC12(KLON,KLEV)
    159 REAL(KIND=JPRB),   INTENT(IN) :: PHCFC22(KLON,KLEV)
    160 REAL(KIND=JPRB),   INTENT(IN) :: PCCL4(KLON,KLEV)
    161 REAL(KIND=JPRB),   INTENT(IN) :: PO3_DP(KLON,KLEV) ! AI (kg/kg) ATTENTION (Pa*kg/kg)
     154REAL(KIND=JPRB),   INTENT(IN) :: PCO2
     155REAL(KIND=JPRB),   INTENT(IN) :: PCH4
     156REAL(KIND=JPRB),   INTENT(IN) :: PN2O
     157REAL(KIND=JPRB),   INTENT(IN) :: PNO2
     158REAL(KIND=JPRB),   INTENT(IN) :: PCFC11
     159REAL(KIND=JPRB),   INTENT(IN) :: PCFC12
     160REAL(KIND=JPRB),   INTENT(IN) :: PHCFC22
     161REAL(KIND=JPRB),   INTENT(IN) :: PCCL4
     162REAL(KIND=JPRB),   INTENT(IN) :: PO3(KLON,KLEV) ! AI (kg/kg) ATTENTION (Pa*kg/kg)
     163REAL(KIND=JPRB),   INTENT(IN) :: PO2
    162164
    163165! *** Cloud fraction and hydrometeor mass mixing ratios
     
    295297logical :: loutput=.true.
    296298logical :: lprint_input=.false.
    297 logical :: lprint_config=.true.
     299logical :: lprint_config=.false.
     300logical, save :: debut_ecrad=.true.
     301!$OMP THREADPRIVATE(debut_ecrad)
    298302
    299303! Import time functions for iseed calculation
     
    326330  print*,'PCO2, PCH4, PN2O, PNO2, PCFC11, PCFC12, PHCFC22, PCCL4 =', &
    327331        PCO2, PCH4, PN2O, PNO2, PCFC11, PCFC12, PHCFC22, PCCL4
    328   print*,'PO3_DP =',PO3_DP
     332  print*,'PO3 =',PO3
    329333  print*,'PCLOUD_FRAC, PQ_LIQUID, PQ_ICE, PQ_RAIN, PQ_SNOW =', &
    330334        PCLOUD_FRAC, PQ_LIQUID, PQ_ICE, PQ_RAIN, PQ_SNOW
     
    333337  print*,'PAEROSOL_OLD, PAEROSOL =', PAEROSOL_OLD, PAEROSOL
    334338endif
    335 ! AI ATTENTION lecture de namelist
    336 ! alternative a l appel de radiation_setup ifs
    337 !file_name="namelist_ecrad"
    338 !call rad_config%read(file_name=file_name)
    339 ! Setup the radiation scheme: load the coefficients for gas and
    340 ! cloud optics, currently from RRTMG
    341 !call setup_radiation(rad_config)
    342339
    343340IF (LHOOK) CALL DR_HOOK('RADIATION_SCHEME',0,ZHOOK_HANDLE)
    344341print*,'Entree dans radiation_scheme'
     342
     343!$OMP MASTER
     344if (debut_ecrad) then
    345345! AI appel radiation_setup
    346346call SETUP_RADIATION_SCHEME(loutput)
    347347
    348 if (lprint_config) then
     348 if (lprint_config) then
    349349  print*,'************* Parametres de configuration  ********************'
    350350  print*,'rad_config%iverbosesetup = ',rad_config%iverbosesetup
     
    371371  print*,'n_bands_lw =', rad_config%n_bands_lw
    372372  print*,'rad_config%i_emiss_from_band_lw =', rad_config%i_emiss_from_band_lw
    373 endif
    374 !stop
    375 ! A EFFACER
    376 !print*,'n_g_lw, n_g_sw =', rad_config%n_g_lw, rad_config%n_g_sw
    377 !print*,'use_canopy_full_spectrum_lw = ', rad_config%use_canopy_full_spectrum_lw
    378 !print*,'rad_config%i_band_from_reordered_g_lw =', &
    379 !       rad_config%i_band_from_reordered_g_lw
    380 !print*,'use_canopy_full_spectrum_lw =', rad_config%use_canopy_full_spectrum_lw
    381 !rad_config%use_canopy_full_spectrum_lw = .TRUE.
    382 ! AI ATTENTION
    383 !rad_config%i_band_from_reordered_g_lw = 1
    384 !rad_config%use_spectral_solar_scaling = .true.
    385 !endif
    386 ! AI ATTENTION test
    387 !rad_config%i_gas_model = IGasModelMonochromatic
    388 
     373 endif
     374 debut_ecrad=.false.
     375endif
     376!$OMP END MASTER
     377!$OMP BARRIER
     378! Fin partie initialisation et configuration
     379
     380! AI : allocation des tableaux pour chaque partie (thermo, ...)
     381!      passage des champs LMDZ aux structures Ecrad
     382!      calculs Ecrad
    389383! AI ATTENTION
    390384! Allocate memory in radiation objects
    391 CALL single_level%allocate(KLON, NSW, 2, &
     385! emissivite avec une seule bande
     386CALL single_level%allocate(KLON, NSW, 1, &
    392387     &                     use_sw_albedo_direct=.TRUE.)
    393388
     
    395390! Set thermodynamic profiles: simply copy over the half-level
    396391! pressure and temperature
    397 print*,'Appel allocate thermo'
     392!print*,'Appel allocate thermo'
    398393CALL thermodynamics%allocate(KLON, KLEV, use_h2o_sat=.true.)
    399 print*,'Definir les champs thermo'
     394!print*,'Definir les champs thermo'
    400395! AI
    401396! pressure_hl > paprs
     
    404399thermodynamics%temperature_hl(KIDIA:KFDIA,:) = PTEMPERATURE_H(KIDIA:KFDIA,:)
    405400
    406 ! IFS currently sets the half-level temperature at the surface to be
    407 ! equal to the skin temperature. The radiation scheme takes as input
    408 ! only the half-level temperatures and assumes the Planck function to
    409 ! vary linearly in optical depth between half levels. In the lowest
    410 ! atmospheric layer, where the atmospheric temperature can be much
    411 ! cooler than the skin temperature, this can lead to significant
    412 ! differences between the effective temperature of this lowest layer
    413 ! and the true value in the model.
    414 !
    415 ! We may approximate the temperature profile in the lowest model level
    416 ! as piecewise linear between the top of the layer T[k-1/2], the
    417 ! centre of the layer T[k] and the base of the layer Tskin.  The mean
    418 ! temperature of the layer is then 0.25*T[k-1/2] + 0.5*T[k] +
    419 ! 0.25*Tskin, which can be achieved by setting the atmospheric
    420 ! temperature at the half-level corresponding to the surface as
    421 ! follows:
    422 thermodynamics%temperature_hl(KIDIA:KFDIA,KLEV+1) &
    423      &  = PTEMPERATURE(KIDIA:KFDIA,KLEV) &
    424      &  + 0.5_JPRB * (PTEMPERATURE_H(KIDIA:KFDIA,KLEV+1) &
    425      &               -PTEMPERATURE_H(KIDIA:KFDIA,KLEV))
    426 
    427 ! Alternatively we respect the model's atmospheric temperature in the
    428 ! lowest model level by setting the temperature at the lowest
    429 ! half-level such that the mean temperature of the layer is correct:
    430 !thermodynamics%temperature_hl(KIDIA:KFDIA,KLEV+1) &
    431 !     &  = 2.0_JPRB * PTEMPERATURE(KIDIA:KFDIA,KLEV) &
    432 !     &             - PTEMPERATURE_H(KIDIA:KFDIA,KLEV)
    433 
     401!print*,'Compute saturation specific humidity'
    434402! Compute saturation specific humidity, used to hydrate aerosols. The
    435403! "2" for the last argument indicates that the routine is not being
    436404! called from within the convection scheme.
    437405!CALL SATUR(KIDIA, KFDIA, KLON, 1, KLEV, &
    438 !     &  PPRESSURE, PTEMPERATURE, thermodynamics%h2o_sat_liq, 2) 
     406!     &  PPRESSURE, PTEMPERATURE, thermodynamics%h2o_sat_liq, 2)
    439407! Alternative approximate version using temperature and pressure from
    440408! the thermodynamics structure
    441 print*,'Compute saturation specific humidity'
    442409CALL thermodynamics%calc_saturation_wrt_liquid(KIDIA, KFDIA)
    443410
     
    447414! Set single-level fileds
    448415single_level%solar_irradiance              = PSOLAR_IRRADIANCE
    449 !allocate(single_level%cos_sza(KIDIA:KFDIA))
    450416single_level%cos_sza(KIDIA:KFDIA)          = PMU0(KIDIA:KFDIA)
    451 !allocate(single_level%skin_temperature(KIDIA:KFDIA))
    452417single_level%skin_temperature(KIDIA:KFDIA) = PTEMPERATURE_SKIN(KIDIA:KFDIA)
    453 !allocate(single_level%sw_albedo(KIDIA:KFDIA,1))
    454418single_level%sw_albedo(KIDIA:KFDIA,:)      = PALBEDO_DIF(KIDIA:KFDIA,:)
    455 !single_level%sw_albedo(KIDIA:KFDIA,:)      = 0.2_JPRB
    456 !allocate(single_level%sw_albedo_direct(KIDIA:KFDIA,1))
    457419single_level%sw_albedo_direct(KIDIA:KFDIA,:)=PALBEDO_DIR(KIDIA:KFDIA,:)
    458 !single_level%sw_albedo_direct(KIDIA:KFDIA,:)=0.2_JPRB
    459 ! Longwave emissivity is in two bands
    460 !allocate(single_level%lw_emissivity(KIDIA:KFDIA,1))
    461 !single_level%lw_emissivity(KIDIA:KFDIA,1)  = 1.0_JPRB
    462420single_level%lw_emissivity(KIDIA:KFDIA,1)  = PEMIS(KIDIA:KFDIA)
    463 single_level%lw_emissivity(KIDIA:KFDIA,2)  = PEMIS_WINDOW(KIDIA:KFDIA)
     421!single_level%lw_emissivity(KIDIA:KFDIA,2)  = PEMIS_WINDOW(KIDIA:KFDIA)
    464422
    465423! Create the relevant seed from date and time get the starting day
     
    487445
    488446print*,'********** CLOUDS (allocate + input) *******************************************'
    489 print*,'Appel Allocate clouds'
     447!print*,'Appel Allocate clouds'
    490448CALL cloud%allocate(KLON, KLEV)
    491449! Set cloud fields
     
    494452cloud%fraction(KIDIA:KFDIA,:) = PCLOUD_FRAC(KIDIA:KFDIA,:)
    495453
     454!AI ATTENTION a voir avec JL
    496455! Compute effective radii and convert to metres
    497456!CALL LIQUID_EFFECTIVE_RADIUS(KIDIA, KFDIA, KLON, KLEV, &
     
    499458!     &  PLAND_SEA_MASK, PCCN_LAND, PCCN_SEA, &
    500459!     &  ZRE_LIQUID_UM)
    501 cloud%re_liq(KIDIA:KFDIA,:) = ZRE_LIQUID_UM(KIDIA:KFDIA,:) * 1.0e-6_JPRB
     460cloud%re_liq(KIDIA:KFDIA,:) = ZRE_LIQUID_UM(KIDIA:KFDIA,:)
    502461
    503462!CALL ICE_EFFECTIVE_RADIUS(KIDIA, KFDIA, KLON, KLEV, &
    504463!     &  PPRESSURE, PTEMPERATURE, PCLOUD_FRAC, PQ_ICE, PQ_SNOW, PGEMU, &
    505464!     &  ZRE_ICE_UM)
    506 cloud%re_ice(KIDIA:KFDIA,:) = ZRE_ICE_UM(KIDIA:KFDIA,:) * 1.0e-6_JPRB
     465cloud%re_ice(KIDIA:KFDIA,:) = ZRE_ICE_UM(KIDIA:KFDIA,:)
    507466
    508467! Get the cloud overlap decorrelation length (for cloud boundaries),
     
    513472!CALL CLOUD_OVERLAP_DECORR_LEN(KIDIA, KFDIA, KLON, PGEMU, YRERAD%NDECOLAT, &
    514473!     &    ZDECORR_LEN_KM, PDECORR_LEN_RATIO=ZDECORR_LEN_RATIO)
    515 ! AI ATTENTION a revoir
    516 ZDECORR_LEN_RATIO = 0.5_JPRB
    517 rad_config%cloud_inhom_decorr_scaling = ZDECORR_LEN_RATIO
     474
     475! AI ATTENTION (valeur lue dans namelist)
     476!ZDECORR_LEN_RATIO = 0.5_JPRB
     477!rad_config%cloud_inhom_decorr_scaling = ZDECORR_LEN_RATIO
     478!AI ATTENTION meme valeur que dans offline
    518479ZDECORR_LEN_KM = 2000.0_JPRB
    519480DO JLON = KIDIA,KFDIA
     
    527488! hard coded at 1.0.
    528489!CALL cloud%create_fractional_std(KLON, KLEV, YRERAD%RCLOUD_FRAC_STD)
     490! AI ATTENTION frac_std=0.75 meme valeur que dans la version offline
    529491CALL cloud%create_fractional_std(KLON, KLEV, frac_std)
    530492
     493! AI ! Read cloud properties needed by SPARTACUS
    531494! By default mid and high cloud effective size is 10 km
    532 CALL cloud%create_inv_cloud_effective_size(KLON,KLEV,1.0_JPRB/10000.0_JPRB)
     495!CALL cloud%create_inv_cloud_effective_size(KLON,KLEV,1.0_JPRB/10000.0_JPRB)
    533496! But for boundary clouds (eta > 0.8) we set it to 1 km
    534 DO JLEV = 1,KLEV
    535   DO JLON = KIDIA,KFDIA
    536     IF (PPRESSURE(JLON,JLEV) > 0.8_JPRB * PPRESSURE_H(JLON,KLEV+1)) THEN
    537       cloud%inv_cloud_effective_size(JLON,JLEV) = 1.0e-3_JPRB
    538     ENDIF
    539   ENDDO
    540 ENDDO
     497!DO JLEV = 1,KLEV
     498!  DO JLON = KIDIA,KFDIA
     499!    IF (PPRESSURE(JLON,JLEV) > 0.8_JPRB * PPRESSURE_H(JLON,KLEV+1)) THEN
     500!      cloud%inv_cloud_effective_size(JLON,JLEV) = 1.0e-3_JPRB
     501!    ENDIF
     502!  ENDDO
     503!ENDDO
     504!AI ATTENTION meme traitement dans le version offline
     505call cloud%create_inv_cloud_effective_size_eta(KLON, KLEV, &
     506               &  thermodynamics%pressure_hl, &
     507               &  0.005_JPRB, &
     508               &  0.0001_JPRB, &
     509               &  0.0001, 0.8_jprb, 0.45_jprb)     
    541510
    542511print*,'******** AEROSOLS (allocate + input) **************************************'
     
    597566
    598567print*,'********** GAS (allocate + input) ************************************************'
    599 print*,'Appel Allocate gas'
     568!print*,'Appel Allocate gas'
    600569CALL gas%allocate(KLON, KLEV)
    601570
     
    608577!  ENDDO
    609578!ENDDO
    610 ZO3 = PO3_DP
    611579
    612580!  Insert gas mixing ratios
    613 print*,'Insert gas mixing ratios'
     581!print*,'Insert gas mixing ratios'
    614582CALL gas%put(IH2O,    IMassMixingRatio, PQ)
    615 CALL gas%put(ICO2,    IMassMixingRatio, PCO2)
    616 CALL gas%put(ICH4,    IMassMixingRatio, PCH4)
    617 CALL gas%put(IN2O,    IMassMixingRatio, PN2O)
    618 CALL gas%put(ICFC11,  IMassMixingRatio, PCFC11)
    619 CALL gas%put(ICFC12,  IMassMixingRatio, PCFC12)
    620 CALL gas%put(IHCFC22, IMassMixingRatio, PHCFC22)
    621 CALL gas%put(ICCL4,   IMassMixingRatio, PCCL4)
    622 CALL gas%put(IO3,     IMassMixingRatio, ZO3)
    623 CALL gas%put_well_mixed(IO2, IVolumeMixingRatio, 0.20944_JPRB)
     583CALL gas%put(IO3,     IMassMixingRatio, PO3)
     584CALL gas%put_well_mixed(ICO2,    IMAssMixingRatio, PCO2)
     585CALL gas%put_well_mixed(ICH4,    IMassMixingRatio, PCH4)
     586CALL gas%put_well_mixed(IN2O,    IMassMixingRatio, PN2O)
     587CALL gas%put_well_mixed(ICFC11,  IMassMixingRatio, PCFC11)
     588CALL gas%put_well_mixed(ICFC12,  IMassMixingRatio, PCFC12)
     589CALL gas%put_well_mixed(IHCFC22, IMassMixingRatio, PHCFC22)
     590CALL gas%put_well_mixed(ICCL4,   IMassMixingRatio, PCCL4)
     591CALL gas%put_well_mixed(IO2,     IMassMixingRatio, PO2)
    624592! Ensure the units of the gas mixing ratios are what is required by
    625593! the gas absorption model
     
    677645! Compute UV fluxes as weighted sum of appropriate shortwave bands
    678646PFLUX_UV       (KIDIA:KFDIA) = 0.0_JPRB
    679 ! AI ATTENTION
    680 !DO JBAND = 1,NWEIGHT_UV
    681 !  PFLUX_UV(KIDIA:KFDIA) = PFLUX_UV(KIDIA:KFDIA) + WEIGHT_UV(JBAND) &
    682 !       &  * flux%sw_dn_surf_band(IBAND_UV(JBAND),KIDIA:KFDIA)
    683 !ENDDO
     647DO JBAND = 1,NWEIGHT_UV
     648  PFLUX_UV(KIDIA:KFDIA) = PFLUX_UV(KIDIA:KFDIA) + WEIGHT_UV(JBAND) &
     649       &  * flux%sw_dn_surf_band(IBAND_UV(JBAND),KIDIA:KFDIA)
     650ENDDO
    684651
    685652! Compute photosynthetically active radiation similarly
    686653PFLUX_PAR      (KIDIA:KFDIA) = 0.0_JPRB
    687654PFLUX_PAR_CLEAR(KIDIA:KFDIA) = 0.0_JPRB
    688 !AI ATTENTION
    689 !DO JBAND = 1,NWEIGHT_PAR
    690 !  PFLUX_PAR(KIDIA:KFDIA) = PFLUX_PAR(KIDIA:KFDIA) + WEIGHT_PAR(JBAND) &
    691 !       &  * flux%sw_dn_surf_band(IBAND_PAR(JBAND),KIDIA:KFDIA)
    692 !  PFLUX_PAR_CLEAR(KIDIA:KFDIA) = PFLUX_PAR_CLEAR(KIDIA:KFDIA) &
    693 !       &  + WEIGHT_PAR(JBAND) &
    694 !       &  * flux%sw_dn_surf_clear_band(IBAND_PAR(JBAND),KIDIA:KFDIA)
    695 !ENDDO
     655DO JBAND = 1,NWEIGHT_PAR
     656  PFLUX_PAR(KIDIA:KFDIA) = PFLUX_PAR(KIDIA:KFDIA) + WEIGHT_PAR(JBAND) &
     657       &  * flux%sw_dn_surf_band(IBAND_PAR(JBAND),KIDIA:KFDIA)
     658  PFLUX_PAR_CLEAR(KIDIA:KFDIA) = PFLUX_PAR_CLEAR(KIDIA:KFDIA) &
     659       &  + WEIGHT_PAR(JBAND) &
     660       &  * flux%sw_dn_surf_clear_band(IBAND_PAR(JBAND),KIDIA:KFDIA)
     661ENDDO
    696662
    697663! Compute effective broadband emissivity
     
    704670
    705671! Copy longwave derivatives
     672! AI ATTENTION
    706673!IF (YRERAD%LAPPROXLWUPDATE) THEN
    707674IF (rad_config%do_lw_derivatives) THEN
     
    710677
    711678! Store the shortwave downwelling fluxes in each albedo band
     679!AI ATTENTION
    712680!IF (YRERAD%LAPPROXSWUPDATE) THEN
    713681IF (rad_config%do_surface_sw_spectral_flux) THEN
  • LMDZ6/branches/Ocean_skin/libf/phylmd/ecrad/radiation_setup.F90

    r3946 r4368  
    290290!    ENDIF
    291291
    292     ! *** SETUP SOLVER ***
     292! *** SETUP SOLVER ***
    293293
    294294    ! 3D effects are off by default (ifs)
     
    412412!!    NMPSRTM(:)=(/ 6, 6, 5, 5, 5, 5, 5, 4, 4, 3, 2, 2, 1, 6 /)
    413413!!    rad_config%i_albedo_from_band_sw = NMPSRTM
    414     !call rad_config%define_sw_albedo_intervals(6, &
    415     !         &  (/ 0.25e-6_jprb, 0.44e-6_jprb, 1.19e-6_jprb, &
    416     !         &     2.38e-6_jprb, 4.00e-6_jprb /),  (/ 1,2,3,4,5,6 /))
    417    
     414!    call rad_config%define_sw_albedo_intervals(6, &
     415!             &  (/ 0.25e-6_jprb, 0.44e-6_jprb, 1.19e-6_jprb, &
     416!             &     2.38e-6_jprb, 4.00e-6_jprb /),  (/ 1,2,3,4,5,6 /))
     417    call rad_config%define_sw_albedo_intervals(6, &
     418       &  [0.25e-6_jprb, 0.44e-6_jprb, 0.69e-6_jprb, &
     419       &   1.19e-6_jprb, 2.38e-6_jprb], [1,2,3,4,5,6])
    418420    ! Likewise between the 16 RRTM longwave bands and the 2 emissivity
    419421    ! inputs (info taken from rrtm_ecrt_140gp_mcica.F90) representing
     
    425427
    426428!    ! Get spectral weightings for UV and PAR
    427 !!    call rad_config%get_sw_weights(0.2e-6_jprb, 0.4415e-6_jprb, &
    428 !!         &  NWEIGHT_UV, IBAND_UV, WEIGHT_UV, 'ultraviolet')
    429 !!    call rad_config%get_sw_weights(0.4e-6_jprb, 0.7e-6_jprb, &
    430 !!         &  NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, &
    431 !!         &  'photosynthetically active radiation, PAR')
     429    call rad_config%get_sw_weights(0.2e-6_jprb, 0.4415e-6_jprb, &
     430         &  NWEIGHT_UV, IBAND_UV, WEIGHT_UV, 'ultraviolet')
     431    call rad_config%get_sw_weights(0.4e-6_jprb, 0.7e-6_jprb, &
     432         &  NWEIGHT_PAR, IBAND_PAR, WEIGHT_PAR, &
     433         &  'photosynthetically active radiation, PAR')
    432434
    433435!    IF (YRERAD%NAERMACC > 0) THEN
  • LMDZ6/branches/Ocean_skin/libf/phylmd/ecrad/random_numbers_mix.F90

    r3908 r4368  
    239239  ! Generate uniformly distributed random numbers in the range 0.0<= px < 1.0
    240240  !--------------------------------------------------------------------------------
    241   INTEGER(KIND=JPIM), PARAMETER :: IVAR=Z"3FFFFFFF"
     241!  INTEGER(KIND=JPIM), PARAMETER :: IVAR=Z"3FFFFFFF"
     242  INTEGER(KIND=JPIM) :: IVAR
     243  DATA IVAR /Z"3FFFFFFF"/
    242244  TYPE(RANDOMNUMBERSTREAM), INTENT(INOUT) :: YD_STREAM
    243245  REAL(KIND=JPRB), DIMENSION(:),     INTENT(  OUT) :: PX
    244 
    245246  INTEGER(KIND=JPIM)                :: JJ, JK, IN, IFILLED
    246247 
  • LMDZ6/branches/Ocean_skin/libf/phylmd/ecrad/surdi.F90

    r3908 r4368  
    104104!RCCL4   =   1.E-12_JPRB*ZCL4MWG/ZAIRMWG
    105105
     106!ATTENTION AI 02 2022
     107RCCO2 = 353.E-06_JPRB
     108RCCH4 = 1.72E-06_JPRB
     109RCN2O = 310.E-09_JPRB
     110RCCFC11 = 280.E-12_JPRB
     111RCCFC12 = 484.E-12_JPRB
     112RCCFC22 = 1.E-12_JPRB
     113RCCCL4 = 1.E-12_JPRB
     114RCNO2 = 500.E-13_JPRB
     115
    106116IF( LAQUA ) THEN
    107117  RCARDI  = 348.E-06_JPRB*ZCO2MWG/ZAIRMWG
Note: See TracChangeset for help on using the changeset viewer.