Ignore:
Timestamp:
Feb 5, 2025, 3:06:50 PM (9 hours ago)
Author:
jbclement
Message:

PEM:

  • The sublimation flux can now be modified by the new function 'recomp_tend_h2o' to account for the growth of a dust lag layer (see Eran Vos's note for the formula).
  • Addition of a function 'itp_tsoil' to compute the soil temperature at any point in the soil profile.

JBC

File:
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/recomp_tend_mod.F90

    r3609 r3610  
    1 MODULE recomp_tend_co2_mod
     1MODULE recomp_tend_mod
    22
    33implicit none
     
    1616!=======================================================================
    1717!
    18 !  To compute the evolution of the tendencie for co2 ice
     18!  To compute the evolution of the tendency for co2 ice
    1919!
    2020!=======================================================================
     
    6161!=======================================================================
    6262
    63 SUBROUTINE recomp_tend_h2o(ngrid,nslope,timelen,d_h2oice,PCM_temp,PEM_temp)
     63SUBROUTINE recomp_tend_h2o(icetable_depth_old,icetable_depth_new,tsurf,tsoil_PEM_timeseries_old,tsoil_PEM_timeseries_new,d_h2oice)
     64
     65use compute_soiltemp_mod, only: itp_tsoil
     66use fast_subs_mars,       only: psv
    6467
    6568implicit none
     
    6770!=======================================================================
    6871!
    69 !  To compute the evolution of the tendencie for h2o ice
     72!  To compute the evolution of the tendency for h2o ice
    7073!
    7174!=======================================================================
     
    7376! Inputs
    7477! ------
    75 integer,            intent(in) :: timelen, ngrid, nslope
    76 real, dimension(:), intent(in) :: PCM_temp, PEM_temp
     78real,                 intent(in) :: icetable_depth_old, icetable_depth_new, tsurf
     79real, dimension(:,:), intent(in) :: tsoil_PEM_timeseries_old, tsoil_PEM_timeseries_new
    7780! Outputs
    7881! -------
    79 real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! physical point field: Evolution of perennial ice over one year
     82real, intent(inout) :: d_h2oice ! Evolution of perennial ice over one year
    8083
    8184! Local:
    8285! ------
     86real            :: Rz_old, Rz_new, R_dec, hum_dec, psv_max_old, psv_max_new
     87integer         :: t
     88real, parameter :: coef_diff = 4.e-4 ! Diffusion coefficient
     89real, parameter :: zcdv = 0.0325     ! Drag coefficient
    8390
    84 write(*,*) "Update of the H2O tendency due to lag layer"
     91write(*,*) "> Updating the H2O tendency due to lag layer"
    8592
    86 ! Flux correction due to lag layer
    87 !~ Rz_old = h2oice_depth_old*0.0325/4.e-4              ! resistance from PCM
    88 !~ Rz_new = h2oice_depth_new*0.0325/4.e-4              ! new resistance based on new depth
    89 !~ R_dec = (1./Rz_old)/(1./Rz_new)                     ! decrease because of resistance
    90 !~ soil_psv_old = psv(max(PCM_temp(h2oice_depth_old))) ! the maxmimum annual mean saturation vapor pressure at the temperature of the GCM run temperature at the old ice location
    91 !~ soil_psv_new = psv(max(PEM_temp(h2oice_depth_new))) ! the maxmimum annual mean saturation vapor pressure at the temperature of the PEM run temperature at the new ice location
    92 !~ hum_dec = soil_psv_old/soil_psv_new                 ! decrease because of lower water vapor pressure at the new depth
    93 !~ d_h2oice = d_h2oice*R_dec*hum_dec                   ! decrease of flux
     93! Higher resistance due to growing lag layer (higher depth)
     94Rz_old = icetable_depth_old*zcdv/coef_diff ! Old resistance from PCM
     95Rz_new = icetable_depth_new*zcdv/coef_diff ! New resistance based on new depth
     96R_dec = Rz_new/Rz_old ! Decrease because of resistance
     97
     98! The maxmimum of the daily averages over one year for the saturation vapor pressure at the ice table location
     99psv_max_old = 0.
     100psv_max_new = 0.
     101do t = 1,size(tsoil_PEM_timeseries_old,2)
     102    psv_max_old = max(psv_max_old,psv(itp_tsoil(tsoil_PEM_timeseries_old(:,t),tsurf,icetable_depth_old)))
     103    psv_max_new = max(psv_max_new,psv(itp_tsoil(tsoil_PEM_timeseries_new(:,t),tsurf,icetable_depth_new)))
     104enddo
     105
     106! Lower humidity due to growing lag layer (higher depth)
     107hum_dec = psv_max_old/psv_max_new ! Decrease because of lower water vapor pressure at the new depth
     108
     109! Flux correction (decrease)
     110d_h2oice = d_h2oice*R_dec*hum_dec
    94111
    95112END SUBROUTINE recomp_tend_h2o
    96113
    97 END MODULE recomp_tend_co2_mod
     114END MODULE recomp_tend_mod
Note: See TracChangeset for help on using the changeset viewer.