Ignore:
Timestamp:
Dec 11, 2025, 12:56:05 PM (5 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/xios_data.F90

    r3988 r3989  
    1 MODULE read_XIOS_data
     1MODULE xios_data
    22
    33use netcdf, only: nf90_open, nf90_close, nf90_inquire_dimension, nf90_inq_dimid, nf90_noerr, nf90_nowrite, nf90_get_var, nf90_inq_varid
     
    1919contains
    2020!=======================================================================
    21 SUBROUTINE read_PCM_data(ngrid,nslope,nsoil_PCM,nsol,h2ofrost_PCM,co2frost_PCM,ps_avg,tsurf_avg,tsurf_avg_y1,tsoil_avg,tsoil_ts,watersurf_density_avg,d_h2oice,d_co2ice, &
     21
     22!=======================================================================
     23SUBROUTINE load_xios_data(ngrid,nslope,nsoil_PCM,nsol,h2ofrost_PCM,co2frost_PCM,ps_avg,tsurf_avg,tsurf_avg_y1,tsoil_avg,tsoil_ts,watersurf_density_avg,d_h2oice,d_co2ice, &
    2224                         ps_ts,q_h2o_ts,q_co2_ts,watersoil_density_ts,min_h2oice,min_co2ice)
    2325
    24 use grid_conversion,  only: lonlat2vect
    25 use comsoil_h_PEM,    only: soil_pem
    26 use compute_tend_mod, only: compute_tend
    27 use metamorphism,     only: compute_frost
     26use grid_conversion, only: lonlat2vect
     27use soil,            only: do_soil
     28use tendencies,      only: compute_tend
     29use metamorphism,    only: compute_frost
    2830
    2931implicit none
     
    109111    call get_var('watercap'//num,var_read_2d)        ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2operice(:,islope,2))
    110112    call get_var('perennial_co2ice'//num,var_read_2d); call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2perice(:,islope,2))
    111     if (soil_pem) then
     113    if (do_soil) then
    112114        call get_var('soiltemp'//num,var_read_3d)
    113115        do isoil = 1,nsoil_PCM
     
    141143    call lonlat2vect(nlon,nlat,ngrid,var_read_3d(:,:,isol),q_co2_ts(:,isol))
    142144enddo
    143 if (soil_pem) then
     145if (do_soil) then
    144146    do islope = 1,nslope
    145147        if (nslope /= 1) then
     
    180182write(*,*) 'CO2 ice tendencies (min/max):', minval(d_co2ice), maxval(d_co2ice)
    181183
    182 END SUBROUTINE read_PCM_data
     184END SUBROUTINE load_xios_data
     185!=======================================================================
     186
     187!=======================================================================
     188SUBROUTINE get_timelen(filename,timelen)
     189
     190use netcdf
     191
     192implicit none
     193
     194! Arguments
     195! ---------
     196character(*), intent(in)  :: filename
     197integer,      intent(out) :: timelen
     198
     199! Local variables
     200! ---------------
     201integer :: ncid  ! File ID
     202integer :: dimid ! Dimension ID
     203integer :: ierr  ! Return codes
     204
     205! Code
     206! ----
     207! Open the NetCDF file
     208ierr = nf90_open(trim(filename),NF90_NOWRITE,ncid)
     209if (ierr /= nf90_noerr) then
     210    write(*,*) "Error opening file:", trim(nf90_strerror(ierr))
     211    error stop
     212endif
     213
     214! Get the dimension ID for 'time_counter'
     215ierr = nf90_inq_dimid(ncid,"time_counter",dimid)
     216if (ierr /= nf90_noerr) then
     217    write(*,*) "Error getting dimid 'time_counter':", trim(nf90_strerror(ierr))
     218    error stop
     219endif
     220
     221! Get the size of the dimension 'time_counter'
     222ierr = nf90_inquire_dimension(ncid,dimid,len = timelen)
     223if (ierr /= nf90_noerr) then
     224    write(*,*) "Error getting dimension length:", trim(nf90_strerror(ierr))
     225    error stop
     226endif
     227
     228! Close the file
     229ierr = nf90_close(ncid)
     230if (ierr /= nf90_noerr) then
     231    write(*,*) "Error closing file:", trim(nf90_strerror(ierr))
     232    error stop
     233endif
     234
     235END SUBROUTINE get_timelen
     236!=======================================================================
    183237
    184238!=======================================================================
     
    205259
    206260END SUBROUTINE error_msg
     261!=======================================================================
    207262
    208263!=======================================================================
     
    218273
    219274END SUBROUTINE get_var_1d
     275!=======================================================================
    220276
    221277!=======================================================================
     
    231287
    232288END SUBROUTINE get_var_2d
     289!=======================================================================
    233290
    234291!=======================================================================
     
    244301
    245302END SUBROUTINE get_var_3d
     303!=======================================================================
    246304
    247305!=======================================================================
     
    257315
    258316END SUBROUTINE get_var_4d
    259 
    260 END MODULE read_XIOS_data
     317!=======================================================================
     318
     319END MODULE xios_data
Note: See TracChangeset for help on using the changeset viewer.