Ignore:
Timestamp:
May 26, 2025, 10:34:57 AM (3 weeks ago)
Author:
jbclement
Message:

PEM:

  • New subroutine to detect whether there is subsurface ice or not
  • Rework of the initialization/update/finalization of the situation regarding the layering data structure
  • Introduction of a threshold 'h_patchy_dust' under which the top dust layer is not considered as a stratum
  • 'deposits' is renamed as 'layerings_map'
  • Few cleanings

JBC

File:
1 edited

Legend:

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

    r3770 r3778  
    99SUBROUTINE pemetat0(filename,ngrid,nsoil_PCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,icetable_depth,icetable_thickness,ice_porefilling, &
    1010                    tsurf_avg_yr1,tsurf_avg_yr2,q_co2,q_h2o,ps_timeseries,ps_avg_global,d_h2oice,d_co2ice,co2_ice,h2o_ice,                         &
    11                     watersurf_avg,watersoil_avg,m_co2_regolith_phys,deltam_co2_regolith_phys,m_h2o_regolith_phys,deltam_h2o_regolith_phys,stratif)
     11                    watersurf_avg,watersoil_avg,m_co2_regolith_phys,deltam_co2_regolith_phys,m_h2o_regolith_phys,deltam_h2o_regolith_phys,layerings_map)
    1212
    1313use iostart_PEM,                only: open_startphy, close_startphy, get_field, get_var, inquire_dimension, inquire_dimension_length
     
    5454real, dimension(ngrid,nslope),           intent(out) :: h2o_ice                  ! h2o ice amount [kg/m^2]
    5555real, dimension(ngrid,nslope),           intent(out) :: co2_ice                  ! co2 ice amount [kg/m^2]
    56 type(layering), dimension(ngrid,nslope), intent(inout) :: stratif             ! stratification (layerings)
     56type(layering), dimension(ngrid,nslope), intent(inout) :: layerings_map             ! Layerings
    5757real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: TI_PEM              ! soil (mid-layer) thermal inertia in the PEM grid [SI]
    5858real, dimension(ngrid,nsoil_PEM,nslope), intent(inout) :: tsoil_PEM           ! soil (mid-layer) temperature [K]
     
    7171character(2)                            :: num               ! intermediate string to read PEM start sloped variables
    7272logical                                 :: startpem_file     ! boolean to check if we read the startfile or not
    73 real, dimension(:,:,:,:), allocatable   :: stratif_array     ! Array for stratification (layerings)
     73real, dimension(:,:,:,:), allocatable   :: stratif_array     ! Array for layerings
    7474
    7575#ifdef CPP_STD
     
    132132
    133133!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    134     ! Stratification (layerings)
     134    ! Layerings
    135135    nb_str_max = 68
    136136    if (layering_algo) then
     
    178178        enddo ! islope
    179179        if (.not. found) then
    180             write(*,*) 'So the deposits are initialized with sub-surface strata.'
     180            write(*,*) 'So the layerings are initialized with sub-surface strata.'
    181181            write(*,*) 'Ice is added with ''ini_huge_h2oice'' where ''watercaptag'' is true and otherwise with ''perennial_co2ice'' found in the PCM.'
    182182            do ig = 1,ngrid
    183183                if (watercaptag(ig)) then
    184184                    do islope = 1,nslope
    185                         call ini_layering(stratif(ig,islope))
    186                         call add_stratum(stratif(ig,islope),ini_huge_h2oice,0.,ini_huge_h2oice,0.,0.,0.)
     185                        call ini_layering(layerings_map(ig,islope))
     186                        call add_stratum(layerings_map(ig,islope),ini_huge_h2oice,0.,ini_huge_h2oice,0.,0.,0.)
    187187                    enddo
    188188                else
    189189                    do islope = 1,nslope
    190                         call ini_layering(stratif(ig,islope))
    191                         if (perennial_co2ice(ig,islope) > 0.) call add_stratum(stratif(ig,islope),perennial_co2ice(ig,islope),perennial_co2ice(ig,islope),0.,0.,0.,0.)
     190                        call ini_layering(layerings_map(ig,islope))
     191                        if (perennial_co2ice(ig,islope) > 0.) call add_stratum(layerings_map(ig,islope),perennial_co2ice(ig,islope),perennial_co2ice(ig,islope),0.,0.,0.,0.)
    192192                    enddo
    193193                endif
    194194            enddo
    195195        else
    196             call array2stratif(stratif_array,ngrid,nslope,stratif)
     196            call array2stratif(stratif_array,ngrid,nslope,layerings_map)
    197197        endif
    198198        deallocate(stratif_array)
     
    383383    co2_ice = perennial_co2ice
    384384
    385     ! Stratification (layerings)
     385    ! Layerings
    386386    nb_str_max = 68
    387387    if (layering_algo) then
    388         write(*,*)'So the deposits are initialized with sub-surface strata.'
     388        write(*,*)'So the layerings are initialized with sub-surface strata.'
    389389        write(*,*)'Ice is added with ''ini_huge_h2oice'' where ''watercaptag'' is true and otherwise with ''perennial_co2ice'' found in the PCM.'
    390390        do ig = 1,ngrid
    391391            if (watercaptag(ig)) then
    392392                do islope = 1,nslope
    393                     call ini_layering(stratif(ig,islope))
    394                     call add_stratum(stratif(ig,islope),ini_huge_h2oice,0.,ini_huge_h2oice,0.,0.,0.)
     393                    call ini_layering(layerings_map(ig,islope))
     394                    call add_stratum(layerings_map(ig,islope),ini_huge_h2oice,0.,ini_huge_h2oice,0.,0.,0.)
    395395                enddo
    396396            else
    397397                do islope = 1,nslope
    398                     call ini_layering(stratif(ig,islope))
    399                     if (perennial_co2ice(ig,islope) > 0.) call add_stratum(stratif(ig,islope),perennial_co2ice(ig,islope),perennial_co2ice(ig,islope),0.,0.,0.,0.)
     398                    call ini_layering(layerings_map(ig,islope))
     399                    if (perennial_co2ice(ig,islope) > 0.) call add_stratum(layerings_map(ig,islope),perennial_co2ice(ig,islope),perennial_co2ice(ig,islope),0.,0.,0.,0.)
    400400                enddo
    401401            endif
Note: See TracChangeset for help on using the changeset viewer.