Ignore:
Timestamp:
Dec 11, 2025, 12:56:05 PM (6 weeks ago)
Author:
jbclement
Message:

PEM:
Massive structural refactor of the PEM codebase for improved readability, consistency and maintainability. The goal is to modernize, standardize and consolidate the code while removing legacy complexity. In detail, this change:

  • Performs large-scale cleanup removing unused code, obsolete routines, duplicated functionality and deprecated initialization logic;
  • Removes "*_mod" wrappers;
  • Replaces mixed naming conventions with clearer variable names, domain-based file/module names and purpose-based routine names;
  • Adds native reading/writing capabilities to the PEM removing the cumbersome dependency on Mars PCM subroutines;
  • Centralizes soil/ice/orbital/PEM configuration logic into dedicated modules;
  • Simplifies routines and updates calls/interfaces to match the new structure.

This refactor significantly clarifies the codebase and provides a cleaner foundation for forthcoming developments.
JBC

File:
1 moved

Legend:

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

    r3988 r3989  
    1 MODULE layering_mod
     1MODULE layered_deposits
    22
    33!=======================================================================
     
    88!=======================================================================
    99
    10 use glaciers_mod, only: rho_co2ice, rho_h2oice
     10use surf_ice, only: rho_co2ice, rho_h2oice
    1111
    1212implicit none
     
    7676!     > print_layering
    7777!     > get_nb_str_max
    78 !     > stratif2array
    79 !     > array2stratif
     78!     > map2array
     79!     > array2map
    8080!     > print_layerings_map
    8181! Procedures to get information about a stratum:
     
    277277SUBROUTINE ini_layering(this)
    278278
    279 use comsoil_h_PEM, only: soil_pem, nsoilmx_PEM, layer_PEM, index_breccia, index_bedrock
     279use soil, only: do_soil, nsoilmx_PEM, layer_PEM, index_breccia, index_bedrock
    280280
    281281implicit none
     
    290290!---- Code
    291291! Creation of strata at the bottom of the layering to describe the sub-surface
    292 if (soil_pem) then
     292if (do_soil) then
    293293    do i = nsoilmx_PEM,index_bedrock,-1
    294294        h_soil = layer_PEM(i) - layer_PEM(i - 1) ! No porosity
     
    391391!=======================================================================
    392392! To convert the layerings map into an array able to be outputted
    393 SUBROUTINE stratif2array(layerings_map,ngrid,nslope,stratif_array)
     393SUBROUTINE map2array(layerings_map,ngrid,nslope,layerings_array)
    394394
    395395implicit none
     
    398398integer,                                 intent(in) :: ngrid, nslope
    399399type(layering), dimension(ngrid,nslope), intent(in) :: layerings_map
    400 real, dimension(:,:,:,:), allocatable, intent(inout) :: stratif_array
     400real, dimension(:,:,:,:), allocatable, intent(inout) :: layerings_array
    401401
    402402!---- Local variables
     
    405405
    406406!---- Code
    407 stratif_array = 0.
     407layerings_array = 0.
    408408do islope = 1,nslope
    409409    do ig = 1,ngrid
     
    411411        k = 1
    412412        do while (associated(current))
    413             stratif_array(ig,islope,k,1) = current%top_elevation
    414             stratif_array(ig,islope,k,2) = current%h_co2ice
    415             stratif_array(ig,islope,k,3) = current%h_h2oice
    416             stratif_array(ig,islope,k,4) = current%h_dust
    417             stratif_array(ig,islope,k,5) = current%h_pore
    418             stratif_array(ig,islope,k,6) = current%poreice_volfrac
     413            layerings_array(ig,islope,k,1) = current%top_elevation
     414            layerings_array(ig,islope,k,2) = current%h_co2ice
     415            layerings_array(ig,islope,k,3) = current%h_h2oice
     416            layerings_array(ig,islope,k,4) = current%h_dust
     417            layerings_array(ig,islope,k,5) = current%h_pore
     418            layerings_array(ig,islope,k,6) = current%poreice_volfrac
    419419            current => current%up
    420420            k = k + 1
     
    423423enddo
    424424
    425 END SUBROUTINE stratif2array
     425END SUBROUTINE map2array
    426426
    427427!=======================================================================
    428428! To convert the stratification array into the layerings map
    429 SUBROUTINE array2stratif(stratif_array,ngrid,nslope,layerings_map)
     429SUBROUTINE array2map(layerings_array,ngrid,nslope,layerings_map)
    430430
    431431implicit none
     
    433433!---- Arguments
    434434integer,                               intent(in) :: ngrid, nslope
    435 real, dimension(:,:,:,:), allocatable, intent(in) :: stratif_array
     435real, dimension(:,:,:,:), allocatable, intent(in) :: layerings_array
    436436type(layering), dimension(ngrid,nslope), intent(inout) :: layerings_map
    437437
     
    442442do islope = 1,nslope
    443443    do ig = 1,ngrid
    444         do k = 1,size(stratif_array,3)
    445             call add_stratum(layerings_map(ig,islope),stratif_array(ig,islope,k,1),stratif_array(ig,islope,k,2),stratif_array(ig,islope,k,3),stratif_array(ig,islope,k,4),stratif_array(ig,islope,k,5),stratif_array(ig,islope,k,6))
     444        do k = 1,size(layerings_array,3)
     445            call add_stratum(layerings_map(ig,islope),layerings_array(ig,islope,k,1),layerings_array(ig,islope,k,2),layerings_array(ig,islope,k,3),layerings_array(ig,islope,k,4),layerings_array(ig,islope,k,5),layerings_array(ig,islope,k,6))
    446446        enddo
    447447    enddo
    448448enddo
    449449
    450 END SUBROUTINE array2stratif
     450END SUBROUTINE array2map
    451451
    452452!=======================================================================
     
    10181018END SUBROUTINE make_layering
    10191019
    1020 END MODULE layering_mod
     1020END MODULE layered_deposits
Note: See TracChangeset for help on using the changeset viewer.