Ignore:
Timestamp:
Dec 6, 2023, 4:02:06 PM (12 months ago)
Author:
jbclement
Message:

PEM:

  • Simplification of the algorithm managing the stopping criteria;
  • Complete rework of the ice management in the PEM (H2O & CO2);

    Subroutines to evolve the H2O and CO2 ice are now in the same module "evol_ice_mod.F90".
    Tendencies are computed from the variation of "ice + frost" between the 2 PCM runs.
    Evolving ice in the PEM is now called 'h2o_ice' or 'co2_ice' (not anymore in 'qsurf' and free of 'water_reservoir').
    Default value 'ini_h2o_bigreservoir' (= 10 m) initializes the H2O ice of the first PEM run where there is 'watercap'. For the next PEM runs, initialization is done with the value kept in "startpem.nc". CO2 ice is taken from 'perennial_co2ice' of the PCM (paleoclimate flag must be true).
    Simplification of the condition to compute the surface ice cover needed for the stopping criteria.
    Frost ('qsurf') is not evolved by the PEM and given back to the PCM.
    New default threshold value 'inf_h2oice_threshold' (= 2 m) to decide at the end of the PEM run if the H2O ice should be 'watercap' or not for the next PCM runs. If H2O ice cannot be 'watercap', then the remaining H2O ice is transferred to the frost ('qsurf').

  • Renaming of variables/subroutines for clarity;
  • Some cleanings throughout the code;
  • Small updates in files of the deftank.

JBC

File:
1 moved

Legend:

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

    r3148 r3149  
    1 MODULE interpolate_TIPEM_TIGCM_mod
     1MODULE interpol_TI_PEM2PCM_mod
    22
    33implicit none
     
    77!=======================================================================
    88
    9 SUBROUTINE interpolate_TIPEM_TIGCM(ngrid,nslope,nsoil_PEM,nsoil_GCM,TI_PEM,TI_GCM)
     9SUBROUTINE interpol_TI_PEM2PCM(ngrid,nslope,nsoil_PEM,nsoil_PCM,TI_PEM,TI_PCM)
    1010
    1111!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1212!!!
    13 !!! Purpose: Transfer the thermal inertia from the PEM vertical  grid to the GCM vertical grid
     13!!! Purpose: Transfer the thermal inertia from the PEM vertical grid to the PCM vertical grid
    1414!!!
    1515!!!
     
    2727integer,                                 intent(in) :: nslope    ! # of subslope wihtin the mesh
    2828integer,                                 intent(in) :: nsoil_PEM ! # of soil layers in the PEM
    29 integer,                                 intent(in) :: nsoil_GCM ! # of soil layers in the GCM
     29integer,                                 intent(in) :: nsoil_PCM ! # of soil layers in the GCM
    3030real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: TI_PEM    ! Thermal inertia in the PEM vertical grid [J/m^2/K/s^{1/2}]
    3131
    32 real, dimension(ngrid,nsoil_GCM,nslope), intent(inout) :: TI_GCM ! Thermal inertia in the GCM vertical grid [J/m^2/K/s^{1/2}]
     32real, dimension(ngrid,nsoil_PCM,nslope), intent(inout) :: TI_PCM ! Thermal inertia in the PCM vertical grid [J/m^2/K/s^{1/2}]
    3333
    3434!----- Code
    35 TI_GCM(:,:,:) = TI_PEM(:,:nsoil_GCM,:)
     35TI_PCM = TI_PEM(:,:nsoil_PCM,:)
    3636
    37 END SUBROUTINE interpolate_TIPEM_TIGCM
     37END SUBROUTINE interpol_TI_PEM2PCM
    3838
    39 END MODULE interpolate_TIPEM_TIGCM_mod
     39END MODULE interpol_TI_PEM2PCM_mod
Note: See TracChangeset for help on using the changeset viewer.