Ignore:
Timestamp:
Dec 16, 2025, 4:39:24 PM (5 weeks ago)
Author:
jbclement
Message:

PEM:
Apply documentation template everywhere: standardized headers format with short description, separators between functions/subroutines, normalized code sections, aligned dependencies/arguments/variables declaration.
JBC

File:
1 edited

Legend:

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

    r3989 r3991  
    11MODULE outputs
    2 
     2!-----------------------------------------------------------------------
     3! NAME
     4!     outputs
     5!
     6! DESCRIPTION
     7!     Tools to write PEM diagnostic outputs.
     8!
     9! AUTHORS & DATE
     10!     LMDZ team
     11!     E. Leconte, 2010
     12!     F. Forget, 2011
     13!     JB Clement, 2023–2025
     14!
     15! NOTES
     16!     Uses NetCDF low-level API and supports parallel runs.
     17!-----------------------------------------------------------------------
     18
     19! DECLARATION
     20! -----------
    321implicit none
    422
     23! MODULE VARIABLES
     24! ----------------
    525integer :: output_rate ! Output rate
    626
    7 !=======================================================================
    827contains
    9 !=======================================================================
     28!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    1029
    1130SUBROUTINE write_diagpem(ngrid,nom,titre,unite,dim,px)
     
    4867!      dim : dimension de px : 0, 1, 2, ou 3 dimensions
    4968!
    50 !=================================================================
     69!-----------------------------------------------------------------------
     70! NAME
     71!     write_diagpem
     72!
     73! DESCRIPTION
     74!     Write selected diagnostic variables to NetCDF file 'diagpem.nc'.
     75!     Supports 3D, 2D, 1D (column), and 0D (scalar) variables.
     76!
     77! AUTHORS & DATE
     78!     E. Leconte, 2010
     79!     F. Forget, 2011
     80!     JB Clement, 2023–2025
     81!
     82! NOTES
     83!     Output cadence is controlled by 'output_rate' from run.def. Parallel-safe
     84!     with master task handling NetCDF I/O. Can use 'diagpem.def' to select vars.
     85!-----------------------------------------------------------------------
     86
     87! DEPENDENCIES
     88! ------------
    5189use surfdat_h,          only: phisfi
    5290use geometry_mod,       only: cell_area
     
    5492use mod_grid_phy_lmdz,  only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat, nbp_lev, grid_type, unstructured
    5593
     94! DECLARATION
     95! -----------
    5696implicit none
    5797
     
    5999include "netcdf.inc"
    60100
    61 ! Arguments on input:
     101! ARGUMENTS
     102! ---------
    62103integer,                        intent(in) :: ngrid
    63104character(len=*),               intent(in) :: nom, titre, unite
     
    65106real, dimension(ngrid,nbp_lev), intent(in) :: px
    66107
    67 ! Local variables:
     108! LOCAL VARIABLES
     109! ---------------
    68110real*4, dimension(nbp_lon + 1,nbp_lat,nbp_lev) :: dx3    ! to store a 3D data set
    69111real*4, dimension(nbp_lon + 1,nbp_lat)         :: dx2    ! to store a 2D (surface) data set
     
    117159#endif
    118160
     161! CODE
     162! ----
    119163if (grid_type == unstructured) return
    120164
     
    580624
    581625END SUBROUTINE write_diagpem
    582 
    583626!=================================================================
    584627
     628!=================================================================
    585629SUBROUTINE write_diagsoilpem(ngrid,name,title,units,dimpx,px)
     630!-----------------------------------------------------------------------
     631! NAME
     632!     write_diagsoilpem
     633!
     634! DESCRIPTION
     635!     Write soil-related diagnostic variables to 'diagsoilpem.nc'.
     636!     Supports 3D (lon,lat,depth), 2D (lon,lat), and 0D scalars.
     637!
     638! AUTHORS & DATE
     639!     E. Leconte, 2010
     640!     JB Clement, 2023–2025
     641!
     642! NOTES
     643!     Output cadence uses 'output_rate'. Only lon-lat (or 1D) grids supported.
     644!-----------------------------------------------------------------------
    586645
    587646! Write variable 'name' to NetCDF file 'diagsoilpem.nc'.
     
    596655! Modifs: Aug.2010 Ehouarn: enforce outputs to be real*4
    597656
     657! DEPENDENCIES
     658! ------------
    598659use soil,               only: mlayer_PEM, nsoilmx_PEM, inertiedat_PEM
    599660use geometry_mod,       only: cell_area
     
    603664use iniwritesoil_mod,   only: iniwritesoil
    604665
     666! DECLARATION
     667! -----------
    605668implicit none
    606669
    607670include"netcdf.inc"
    608671
    609 ! Arguments:
    610 integer,intent(in) :: ngrid ! number of (horizontal) points of physics grid
     672! ARGUMENTS
     673! ---------
     674integer,                            intent(in) :: ngrid ! number of (horizontal) points of physics grid
    611675! i.e. ngrid = 2+(jjm-1)*iim - 1/jjm
    612 character(len=*),intent(in) :: name ! 'name' of the variable
    613 character(len=*),intent(in) :: title ! 'long_name' attribute of the variable
    614 character(len=*),intent(in) :: units ! 'units' attribute of the variable
    615 integer,intent(in) :: dimpx ! dimension of the variable (3,2 or 0)
    616 real,dimension(ngrid,nsoilmx_PEM),intent(in) :: px ! variable
    617 
    618 ! Local variables:
     676character(len=*),                   intent(in) :: name  ! 'name' of the variable
     677character(len=*),                   intent(in) :: title ! 'long_name' attribute of the variable
     678character(len=*),                   intent(in) :: units ! 'units' attribute of the variable
     679integer,                            intent(in) :: dimpx ! dimension of the variable (3,2 or 0)
     680real, dimension(ngrid,nsoilmx_PEM), intent(in) :: px    ! variable
     681
     682! LOCAL VARIABLES
     683! ---------------
    619684real*4,dimension(nbp_lon+1,nbp_lat,nsoilmx_PEM) :: data3 ! to store 3D data
    620685real*4,dimension(nbp_lon+1,nbp_lat) :: data2 ! to store 2D data
     
    657722#endif
    658723
     724! CODE
     725! ----
    659726! 0. Do we ouput a diagsoilpem.nc file? If not just bail out now.
    660727
     
    9891056
    9901057END SUBROUTINE write_diagsoilpem
     1058!=================================================================
    9911059
    9921060END MODULE outputs
Note: See TracChangeset for help on using the changeset viewer.