diff --git a/src/LIB/SURCOUCHE/src/modd_field.f90 b/src/LIB/SURCOUCHE/src/modd_field.f90
index 75901ba3d45efaa341b8d49623a1ec6333b9db1b..1fa797e41cd2d72ad01eb47c507cb04ada291773 100644
--- a/src/LIB/SURCOUCHE/src/modd_field.f90
+++ b/src/LIB/SURCOUCHE/src/modd_field.f90
@@ -9,8 +9,8 @@
 !  P. Wautelet 12/04/2019: added pointers for C1D, L1D, N1D, X5D and X6D structures in TFIELDDATA
 !  P. Wautelet 12/07/2019: add pointers for T1D structure in TFIELDDATA
 !  P. Wautelet 23/01/2020: split in modd_field.f90 and mode_field.f90
-!  P. Wautelet 27/01/2020: create the tfield_metadata_base abstract datatype
-!  P. Wautelet 14/09/2020: add ndimlist field to tfield_metadata_base
+!  P. Wautelet 27/01/2020: create the tfieldmetadata_base abstract datatype
+!  P. Wautelet 14/09/2020: add ndimlist field to tfieldmetadata_base
 !  P. Wautelet 10/11/2020: new data structures for netCDF dimensions
 !  P. Wautelet 24/09/2021: add Fill_tfielddata and use it as a custom constructor for tfielddata type
 !  P. Wautelet 08/10/2021: add 2 new dimensions: LW_bands (NMNHDIM_NLWB) and SW_bands (NMNHDIM_NSWB)
@@ -189,7 +189,7 @@ TYPE TFIELDPTR_T1D
   TYPE(DATE_TIME), DIMENSION(:), POINTER :: DATA => NULL()
 END TYPE TFIELDPTR_T1D
 !
-type :: tfield_metadata_base
+type :: tfieldmetadata_base
   CHARACTER(LEN=NMNHNAMELGTMAX)  :: CMNHNAME  = '' !Name of the field (for MesoNH, non CF convention)
   CHARACTER(LEN=NSTDNAMELGTMAX)  :: CSTDNAME  = '' !Standard name (CF convention)
   CHARACTER(LEN=NLONGNAMELGTMAX) :: CLONGNAME = '' !Long name (CF convention)
@@ -214,9 +214,9 @@ type :: tfield_metadata_base
   INTEGER            :: NVALIDMAX  =  2147483647 !Maximum valid value for integer fields
   REAL               :: XVALIDMIN  = -1.E36 !Minimum valid value for real fields
   REAL               :: XVALIDMAX  =  1.E36 !Maximum valid value for real fields
-end type tfield_metadata_base
+end type tfieldmetadata_base
 
-TYPE, extends( tfield_metadata_base ) :: TFIELDMETADATA
+TYPE, extends( tfieldmetadata_base ) :: TFIELDMETADATA
   CHARACTER(LEN=2)   :: CDIR      = '' !Type of the data field (XX,XY,--...)
   CHARACTER(LEN=4)   :: CLBTYPE   = 'NONE' !Type of the lateral boundary (LBX,LBY,LBXU,LBYV)
   LOGICAL            :: LTIMEDEP  = .FALSE. !Is the field time-dependent?
diff --git a/src/MNH/les_specn.f90 b/src/MNH/les_specn.f90
index 9be8e1f806c535837045c3199af39c14bac9815a..7bbdadc48adc06f7fbc306ecf66851b742cb656d 100644
--- a/src/MNH/les_specn.f90
+++ b/src/MNH/les_specn.f90
@@ -1,16 +1,16 @@
-!MNH_LIC Copyright 2000-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2000-2021 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
 ! Modifications:
-!  P. Wautelet 12/10/2020: restructure Les_diachro_spec subroutine to use tfield_metadata_base type
+!  P. Wautelet 12/10/2020: restructure Les_diachro_spec subroutine to use tfieldmetadata_base type
 !-----------------------------------------------------------------
 !     ######################
       MODULE MODE_LES_SPEC_n
 !     ######################
 
-use modd_field, only: tfield_metadata_base
+use modd_field, only: tfieldmetadata_base
 
 implicit none
 
@@ -22,8 +22,8 @@ public :: Les_spec_n
 real, dimension(:,:,:,:), allocatable :: xspectrax ! spectra coeffcients for
 real, dimension(:,:,:,:), allocatable :: xspectray ! x and y direction spectra
 
-type(tfield_metadata_base) :: tlesfieldx
-type(tfield_metadata_base) :: tlesfieldy
+type(tfieldmetadata_base) :: tlesfieldx
+type(tfieldmetadata_base) :: tlesfieldy
 
 
 CONTAINS
diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90
index 7442dfd3e0184598cd4ee7687456a5e31b900e5b..39366e0226f558b09964f5a55bb099010b03ac77 100644
--- a/src/MNH/modd_budget.f90
+++ b/src/MNH/modd_budget.f90
@@ -35,7 +35,7 @@
 !  P. Wautelet 19/07/2019: parameters to identify budget number
 !  P. Wautelet 15/11/2019: remove unused CBURECORD variable
 !  P. Wautelet 17/01/2020: add new budget data types
-!  P. Wautelet 27/01/2020: use the tfield_metadata_base abstract datatype
+!  P. Wautelet 27/01/2020: use the tfieldmetadata_base abstract datatype
 !  P. Wautelet 28/01/2020: add trhodj in tbudgetdata datatype
 !  P. Wautelet 09/03/2020: add tburhodj variable
 !  P. Wautelet 17/04/2020: set default values for budgets switch values
@@ -53,7 +53,7 @@
 !*       0.   DECLARATIONS
 !             ------------
 
-use modd_field,      only: tfield_metadata_base
+use modd_field,      only: tfieldmetadata_base
 use modd_parameters, only: NBUNAMELGTMAX, NCOMMENTLGTMAX
 
 implicit none
@@ -102,7 +102,7 @@ character(len=*), dimension(NMAXLEVELS), parameter :: CNCGROUPNAMES = [ &
 integer :: nbudgets ! Number of budget categories
 
 
-type, extends( tfield_metadata_base ) :: tbusourcedata
+type, extends( tfieldmetadata_base ) :: tbusourcedata
   integer :: ngroup = 0 ! Number of the source term group in which storing the source term
                         !  (0: no store, 1: individual store, >1: number of the group)
   logical :: lavailable = .false. ! If true, the source is available in the run (conditions to access it are met),
@@ -114,16 +114,17 @@ type, extends( tfield_metadata_base ) :: tbusourcedata
                                   ! It may be true only if the source term is in a group not containing other sources
 end type tbusourcedata
 
-type, extends( tfield_metadata_base ) :: tbugroupdata
+type, extends( tfieldmetadata_base ) :: tbugroupdata
   integer :: nsources = 0 ! Number of source terms composing this group
   integer, dimension(:),     allocatable :: nsourcelist ! List of the source terms composing this group
   real,    dimension(:,:,:), allocatable :: xdata ! Array to store the budget data
 end type tbugroupdata
 
-type, extends( tfield_metadata_base ) :: tburhodata
+type, extends( tfieldmetadata_base ) :: tburhodata
   real, dimension(:,:,:), allocatable :: xdata ! Array to store the budget data
 end type tburhodata
 
+!PW: a commenter + renommer???
 type :: tbudiachrometadata
   character(len=NBUNAMELGTMAX),  dimension(NMAXLEVELS) :: clevels  = '' !Name of the different groups/levels in the netCDF file
   character(len=NCOMMENTLGTMAX), dimension(NMAXLEVELS) :: ccomments ='' !Comments for the different groups/levels in the netCDF file
diff --git a/src/MNH/mode_les_diachro.f90 b/src/MNH/mode_les_diachro.f90
index f56b2ce0f607015dde207609bd257cbdcf1050da..a9dda2c89a23d872f5e8b23f6b84fcb626639893 100644
--- a/src/MNH/mode_les_diachro.f90
+++ b/src/MNH/mode_les_diachro.f90
@@ -9,7 +9,7 @@
 !  P. Wautelet 13/09/2019: budget: simplify and modernize date/time management
 !  P. Wautelet 20/09/2019: rewrite normalization of LES budgets
 !  P. Wautelet 14/08/2020: deduplicate LES_DIACHRO* subroutines
-!  P. Wautelet    10/2020: restructure subroutines to use tfield_metadata_base type
+!  P. Wautelet    10/2020: restructure subroutines to use tfieldmetadata_base type
 !  P. Wautelet 03/03/2021: budgets: add tbudiachrometadata type (useful to pass more information to Write_diachro)
 !  P. Wautelet 11/03/2021: budgets: remove ptrajx/y/z optional dummy arguments of Write_diachro
 !-----------------------------------------------------------------
@@ -658,18 +658,18 @@ end function Les_time_avg_1pt
 subroutine Les_diachro_1D( tpdiafile, tpfield, hgroup, hgroupcomment, odoavg, odonorm, pfield )
 !##############################################################################################
 
-use modd_field, only: NMNHDIM_BUDGET_LES_TIME, NMNHDIM_UNUSED, tfield_metadata_base
+use modd_field, only: NMNHDIM_BUDGET_LES_TIME, NMNHDIM_UNUSED, tfieldmetadata_base
 use modd_io,    only: tfiledata
 
 type(tfiledata),                       intent(in) :: tpdiafile  ! File to write
-type(tfield_metadata_base),            intent(in) :: tpfield    ! Metadata of field
+type(tfieldmetadata_base),             intent(in) :: tpfield    ! Metadata of field
 character(len=*),                      intent(in) :: hgroup     ! Group of the field
 character(len=*),                      intent(in) :: hgroupcomment
 logical,                               intent(in) :: odoavg     ! Compute and store time average
 logical,                               intent(in) :: odonorm    ! Compute and store normalized field
 real,                    dimension(:), intent(in) :: pfield     ! Data array
 
-type(tfield_metadata_base) :: tzfield
+type(tfieldmetadata_base) :: tzfield
 
 tzfield = tpfield
 
@@ -703,18 +703,18 @@ subroutine Les_diachro_2D( tpdiafile, tpfield, hgroup, hgroupcomment, odoavg, od
 !##############################################################################################
 
 use modd_field, only: NMNHDIM_BUDGET_LES_LEVEL, NMNHDIM_BUDGET_LES_SV, NMNHDIM_BUDGET_LES_TIME, NMNHDIM_UNUSED, &
-                      tfield_metadata_base
+                      tfieldmetadata_base
 use modd_io,    only: tfiledata
 
 type(tfiledata),                         intent(in) :: tpdiafile  ! File to write
-type(tfield_metadata_base),              intent(in) :: tpfield    ! Metadata of field
+type(tfieldmetadata_base),               intent(in) :: tpfield    ! Metadata of field
 character(len=*),                        intent(in) :: hgroup     ! Group of the field
 character(len=*),                        intent(in) :: hgroupcomment
 logical,                                 intent(in) :: odoavg     ! Compute and store time average
 logical,                                 intent(in) :: odonorm    ! Compute and store normalized field
 real,                    dimension(:,:), intent(in) :: pfield     ! Data array
 
-type(tfield_metadata_base) :: tzfield
+type(tfieldmetadata_base) :: tzfield
 
 tzfield = tpfield
 
@@ -760,11 +760,11 @@ subroutine Les_diachro_3D( tpdiafile, tpfield, hgroup, hgroupcomment, odoavg, od
 
 use modd_field, only: NMNHDIM_BUDGET_LES_LEVEL, NMNHDIM_BUDGET_LES_MASK, NMNHDIM_BUDGET_LES_SV, &
                       NMNHDIM_BUDGET_LES_TIME,  NMNHDIM_BUDGET_TERM,     NMNHDIM_UNUSED,        &
-                      tfield_metadata_base
+                      tfieldmetadata_base
 use modd_io,    only: tfiledata
 
 type(tfiledata),                           intent(in) :: tpdiafile  ! File to write
-type(tfield_metadata_base),                intent(in) :: tpfield    ! Metadata of field
+type(tfieldmetadata_base),                 intent(in) :: tpfield    ! Metadata of field
 character(len=*),                          intent(in) :: hgroup     ! Group of the field
 character(len=*),                          intent(in) :: hgroupcomment
 logical,                                   intent(in) :: odoavg     ! Compute and store time average
@@ -774,7 +774,7 @@ character(len=*),        dimension(:),     optional, intent(in) :: hfieldnames
 character(len=*),        dimension(:),     optional, intent(in) :: hfieldcomments
 character(len=*),        dimension(:),     optional, intent(in) :: hmasks
 
-type(tfield_metadata_base) :: tzfield
+type(tfieldmetadata_base) :: tzfield
 
 tzfield = tpfield
 
@@ -858,11 +858,11 @@ subroutine Les_diachro_4D( tpdiafile, tpfield, hgroup, hgroupcomment, odoavg, od
 
 use modd_field, only: NMNHDIM_BUDGET_LES_LEVEL, NMNHDIM_BUDGET_LES_MASK, NMNHDIM_BUDGET_LES_PDF,  NMNHDIM_BUDGET_LES_SV, &
                       NMNHDIM_BUDGET_LES_TIME,  NMNHDIM_BUDGET_TERM,     NMNHDIM_UNUSED,                                 &
-                      tfield_metadata_base
+                      tfieldmetadata_base
 use modd_io,    only: tfiledata
 
 type(tfiledata),                             intent(in) :: tpdiafile  ! File to write
-type(tfield_metadata_base),                  intent(in) :: tpfield ! Metadata of field
+type(tfieldmetadata_base),                   intent(in) :: tpfield ! Metadata of field
 character(len=*),                            intent(in) :: hgroup     ! Group of the field
 character(len=*),                            intent(in) :: hgroupcomment
 logical,                                     intent(in) :: odoavg     ! Compute and store time average
@@ -872,7 +872,7 @@ character(len=*),        dimension(:),     optional, intent(in) :: hfieldnames
 character(len=*),        dimension(:),     optional, intent(in) :: hfieldcomments
 character(len=*),        dimension(:),     optional, intent(in) :: hmasks
 
-type(tfield_metadata_base) :: tzfield
+type(tfieldmetadata_base) :: tzfield
 
 tzfield = tpfield
 
@@ -962,7 +962,7 @@ subroutine Les_diachro_common( tpdiafile, tpfield, hgroup, hgroupcomment, pfield
                                hfieldnames, hfieldcomments, hmasks )
 !###################################################################################################
 
-use modd_field,         only: tfield_metadata_base
+use modd_field,         only: tfieldmetadata_base
 use modd_io,            only: tfiledata
 use modd_les,           only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
                               nles_levels, xles_current_z
@@ -971,25 +971,25 @@ use modd_type_date,     only: date_time
 
 implicit none
 
-type(tfiledata),                                          intent(in) :: tpdiafile ! File to write
-type(tfield_metadata_base),                               intent(in) :: tpfield
-character(len=*),                                         intent(in) :: hgroup    ! Group of the field
-character(len=*),                                         intent(in) :: hgroupcomment
-real,                       dimension(:,:,:,:),           intent(in) :: pfield    ! Data array
-logical,                                                  intent(in) :: odoavg    ! Compute and store time average
-logical,                                                  intent(in) :: odonorm   ! Compute and store normalized field
-character(len=*),           dimension(:),       optional, intent(in) :: hfieldnames
-character(len=*),           dimension(:),       optional, intent(in) :: hfieldcomments
-character(len=*),           dimension(:),       optional, intent(in) :: hmasks
-
-character(len=100),         dimension(:),     allocatable :: ycomment                      ! Comment string
-character(len=100),         dimension(:),     allocatable :: ytitle                        ! Title
-integer                                                   :: iles_k                        ! Number of vertical levels
-integer                                                   :: iil, iih, ijl, ijh, ikl, ikh  ! Cartesian area relatively to the
-                                                                                           ! entire domain
-integer                                                   :: jp                            ! Process loop counter
-real,                       dimension(:,:,:), allocatable :: ztrajz                        ! x and y are not used for LES
-type(tfield_metadata_base), dimension(:),     allocatable :: tzfields
+type(tfiledata),                                         intent(in) :: tpdiafile ! File to write
+type(tfieldmetadata_base),                               intent(in) :: tpfield
+character(len=*),                                        intent(in) :: hgroup    ! Group of the field
+character(len=*),                                        intent(in) :: hgroupcomment
+real,                      dimension(:,:,:,:),           intent(in) :: pfield    ! Data array
+logical,                                                 intent(in) :: odoavg    ! Compute and store time average
+logical,                                                 intent(in) :: odonorm   ! Compute and store normalized field
+character(len=*),          dimension(:),       optional, intent(in) :: hfieldnames
+character(len=*),          dimension(:),       optional, intent(in) :: hfieldcomments
+character(len=*),          dimension(:),       optional, intent(in) :: hmasks
+
+character(len=100),        dimension(:),     allocatable :: ycomment                      ! Comment string
+character(len=100),        dimension(:),     allocatable :: ytitle                        ! Title
+integer                                                  :: iles_k                        ! Number of vertical levels
+integer                                                  :: iil, iih, ijl, ijh, ikl, ikh  ! Cartesian area relatively to the
+                                                                                          ! entire domain
+integer                                                  :: jp                            ! Process loop counter
+real,                      dimension(:,:,:), allocatable :: ztrajz                        ! x and y are not used for LES
+type(tfieldmetadata_base), dimension(:),     allocatable :: tzfields
 !------------------------------------------------------------------------------
 
 iles_k = Size( pfield, 1 )
@@ -1242,7 +1242,7 @@ subroutine Les_diachro_2pt( tpdiafile, tpfieldx, tpfieldy, pfieldx, pfieldy )
 !
 !
 use modd_conf,       only: l2d
-use modd_field,      only: tfield_metadata_base
+use modd_field,      only: tfieldmetadata_base
 use modd_io,         only: tfiledata
 use modd_les,        only: xles_temp_mean_start, xles_temp_mean_end
 use modd_parameters, only: XUNDEF
@@ -1253,8 +1253,8 @@ IMPLICIT NONE
 !*      0.1  declarations of arguments
 !
 type(tfiledata),                    intent(in) :: tpdiafile! file to write
-type(tfield_metadata_base),         intent(in) :: tpfieldx ! Metadata of field pfieldx
-type(tfield_metadata_base),         intent(in) :: tpfieldy ! Metadata of field pfieldy
+type(tfieldmetadata_base),          intent(in) :: tpfieldx ! Metadata of field pfieldx
+type(tfieldmetadata_base),          intent(in) :: tpfieldy ! Metadata of field pfieldy
 real,             dimension(:,:,:), intent(in) :: pfieldx
 real,             dimension(:,:,:), intent(in) :: pfieldy
 !-------------------------------------------------------------------------------
@@ -1277,7 +1277,7 @@ subroutine Les_diachro_2pt_1d_intern( tpdiafile, tpfield, gavg, pfield )
 
 use modd_field,         only: NMNHDIM_BUDGET_LES_AVG_TIME, NMNHDIM_BUDGET_LES_TIME, NMNHDIM_UNUSED, &
                               NMNHDIM_SPECTRA_2PTS_NI, NMNHDIM_SPECTRA_2PTS_NJ,                     &
-                              NMNHMAXDIMS, tfield_metadata_base
+                              NMNHMAXDIMS, tfieldmetadata_base
 use modd_io,            only: tfiledata
 use modd_les,           only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
                               nles_current_times, nspectra_k, xles_current_domegax, xles_current_domegay
@@ -1286,7 +1286,7 @@ use modd_type_date,     only: date_time
 use mode_write_diachro, only: Write_diachro
 
 type(tfiledata),                    intent(in) :: tpdiafile! file to write
-type(tfield_metadata_base),         intent(in) :: tpfield ! Metadata of field pfield
+type(tfieldmetadata_base),          intent(in) :: tpfield ! Metadata of field pfield
 logical,                            intent(in) :: gavg
 real,             dimension(:,:,:), intent(in) :: pfield
 
@@ -1301,7 +1301,7 @@ integer                                              :: jk       ! level counter
 real,            dimension(:,:,:,:,:,:), allocatable :: zwork6 ! contains physical field
 type(date_time), dimension(:),           allocatable :: tzdates
 type(tbudiachrometadata)                             :: tzbudiachro
-type(tfield_metadata_base)                           :: tzfield
+type(tfieldmetadata_base)                            :: tzfield
 
 !*      1.0  Initialization of diachro variables for LES (z,t) profiles
 !            ----------------------------------------------------------
@@ -1450,14 +1450,14 @@ subroutine Les_diachro_spec( tpdiafile, tpfieldx, tpfieldy, pspectrax, pspectray
 !
 !
 use modd_conf,  only: l2d
-use modd_field, only: tfield_metadata_base
+use modd_field, only: tfieldmetadata_base
 use modd_io,    only: tfiledata
 
 implicit none
 
 type(tfiledata),                      intent(in) :: tpdiafile! file to write
-type(tfield_metadata_base),           intent(in) :: tpfieldx ! metadata of field pfieldx
-type(tfield_metadata_base),           intent(in) :: tpfieldy ! metadata of field pfieldy
+type(tfieldmetadata_base),            intent(in) :: tpfieldx ! metadata of field pfieldx
+type(tfieldmetadata_base),            intent(in) :: tpfieldy ! metadata of field pfieldy
 real,             dimension(:,:,:,:), intent(in) :: pspectrax! spectra in x
 real,             dimension(:,:,:,:), intent(in) :: pspectray! and y directions
 
@@ -1473,7 +1473,7 @@ subroutine Les_diachro_spec_1D_intern( tpdiafile, tpfield, pspectra )
 
 use modd_field,         only: NMNHDIM_BUDGET_LES_AVG_TIME, NMNHDIM_BUDGET_LES_TIME, NMNHDIM_UNUSED, &
                               NMNHDIM_SPECTRA_SPEC_NI, NMNHDIM_SPECTRA_SPEC_NJ,                     &
-                              NMNHMAXDIMS, tfield_metadata_base
+                              NMNHMAXDIMS, tfieldmetadata_base
 use modd_io,            only: tfiledata
 use modd_les,           only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
                               nles_current_times, nspectra_k, &
@@ -1486,7 +1486,7 @@ use mode_write_diachro, only: Write_diachro
 implicit none
 
 type(tfiledata),             intent(in) :: tpdiafile ! file to write
-type(tfield_metadata_base),  intent(in) :: tpfield   ! metadata of field pfield
+type(tfieldmetadata_base),   intent(in) :: tpfield   ! metadata of field pfield
 real, dimension(:,:,:,:),    intent(in) :: pspectra
 
 character(len=10)                                    :: ygroup   ! group title
@@ -1500,7 +1500,7 @@ integer                                              :: jk       ! level counter
 real,            dimension(:,:,:,:,:,:), allocatable :: zwork6   ! physical field
 type(date_time), dimension(:),           allocatable :: tzdates
 type(tbudiachrometadata)                             :: tzbudiachro
-type(tfield_metadata_base)                           :: tzfield
+type(tfieldmetadata_base)                            :: tzfield
 !
 !*      1.0  Initialization of diachro variables for LES (z,t) profiles
 !            ----------------------------------------------------------
diff --git a/src/MNH/write_aircraft_balloon.f90 b/src/MNH/write_aircraft_balloon.f90
index e132daa83eac80abbaaf8df6e561a57598729e15..cd693d89c60852c4af091a60c56add3aabd12771 100644
--- a/src/MNH/write_aircraft_balloon.f90
+++ b/src/MNH/write_aircraft_balloon.f90
@@ -179,7 +179,7 @@ SUBROUTINE FLYER_DIACHRO(TPFLYER)
 use modd_budget, only: NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK, &
                        tbudiachrometadata
 use modd_field,  only: NMNHDIM_LEVEL, NMNHDIM_FLYER_PROC, NMNHDIM_FLYER_TIME, NMNHDIM_UNUSED, &
-                       tfield_metadata_base, TYPEREAL
+                       tfieldmetadata_base, TYPEREAL
 
 use modi_aircraft_balloon, only: Aircraft_balloon_longtype_get
 
@@ -217,7 +217,7 @@ INTEGER :: IKU, IK
 CHARACTER(LEN=2)  :: INDICE
 INTEGER :: JLOOP
 type(tbudiachrometadata) :: tzbudiachro
-type(tfield_metadata_base), dimension(:), allocatable :: tzfields
+type(tfieldmetadata_base), dimension(:), allocatable :: tzfields
 !
 !----------------------------------------------------------------------------
 !
diff --git a/src/MNH/write_diachro.f90 b/src/MNH/write_diachro.f90
index 46984a2c533690d52d8f4d33a64876d9df01c257..9265bd855dbac115e3b46c3162184b40b70fa5ba 100644
--- a/src/MNH/write_diachro.f90
+++ b/src/MNH/write_diachro.f90
@@ -97,7 +97,7 @@ subroutine Write_diachro( tpdiafile, tpbudiachro, tpfields,       &
 use modd_aircraft_balloon, only: flyer
 use modd_budget,           only: tbudiachrometadata
 use modd_conf,             only: lpack
-use modd_field,            only: tfield_metadata_base
+use modd_field,            only: tfieldmetadata_base
 use modd_io,               only: tfiledata
 use modd_type_date,        only: date_time
 !
@@ -105,13 +105,13 @@ IMPLICIT NONE
 !
 !*       0.1   Dummy arguments
 !              ---------------
-TYPE(TFILEDATA),                                     INTENT(IN)           :: TPDIAFILE    ! file to write
-type(tbudiachrometadata),                            intent(in)           :: tpbudiachro
-class(tfield_metadata_base), dimension(:),           intent(in)           :: tpfields
-type(date_time),             dimension(:),           intent(in)           :: tpdates  !Used only for LFI files
-REAL,                        DIMENSION(:,:,:,:,:,:), INTENT(IN)           :: PVAR
-logical,                                             intent(in), optional :: osplit
-type(flyer),                                         intent(in), optional :: tpflyer
+TYPE(TFILEDATA),                                    INTENT(IN)           :: TPDIAFILE    ! file to write
+type(tbudiachrometadata),                           intent(in)           :: tpbudiachro
+class(tfieldmetadata_base), dimension(:),           intent(in)           :: tpfields
+type(date_time),            dimension(:),           intent(in)           :: tpdates  !Used only for LFI files
+REAL,                       DIMENSION(:,:,:,:,:,:), INTENT(IN)           :: PVAR
+logical,                                            intent(in), optional :: osplit
+type(flyer),                                        intent(in), optional :: tpflyer
 !
 !*       0.1   Local variables
 !              ---------------
@@ -146,7 +146,7 @@ use modd_budget,         only: NLVL_CATEGORY, NLVL_GROUP, NLVL_SHAPE, nbumask, n
 use modd_field,          only: NMNHDIM_ONE, NMNHDIM_UNKNOWN, NMNHDIM_BUDGET_LES_MASK, &
                                NMNHDIM_FLYER_TIME, NMNHDIM_NOTLISTED, NMNHDIM_UNUSED, &
                                TYPECHAR, TYPEINT, TYPEREAL,                           &
-                               tfield_metadata_base, tfielddata
+                               tfieldmetadata_base, tfielddata
 use modd_io,             only: tfiledata
 use modd_les,            only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
                                nles_k, xles_current_z
@@ -161,12 +161,12 @@ use mode_menu_diachro,   only: Menu_diachro
 use mode_tools_ll,       only: Get_globaldims_ll
 
 
-type(tfiledata),                                     intent(in)           :: tpdiafile        ! File to write
-type(tbudiachrometadata),                            intent(in)           :: tpbudiachro
-class(tfield_metadata_base), dimension(:),           intent(in)           :: tpfields
-type(date_time),             dimension(:),           intent(in)           :: tpdates
-real,                        dimension(:,:,:,:,:,:), intent(in)           :: pvar
-type(flyer),                                         intent(in), optional :: tpflyer
+type(tfiledata),                                    intent(in)           :: tpdiafile        ! File to write
+type(tbudiachrometadata),                           intent(in)           :: tpbudiachro
+class(tfieldmetadata_base), dimension(:),           intent(in)           :: tpfields
+type(date_time),            dimension(:),           intent(in)           :: tpdates
+real,                       dimension(:,:,:,:,:,:), intent(in)           :: pvar
+type(flyer),                                        intent(in), optional :: tpflyer
 
 integer, parameter :: LFITITLELGT = 100
 integer, parameter :: LFIUNITLGT = 100
@@ -807,12 +807,12 @@ use modd_type_date,        only: date_time
 use mode_io_field_write,   only: IO_Field_create, IO_Field_write, IO_Field_write_box
 use mode_io_tools_nc4,     only: IO_Err_handle_nc4
 
-type(tfiledata),                                     intent(in)           :: tpdiafile        ! File to write
-type(tbudiachrometadata),                            intent(in)           :: tpbudiachro
-class(tfield_metadata_base), dimension(:),           intent(in)           :: tpfields
-real,                        dimension(:,:,:,:,:,:), intent(in)           :: pvar
-logical,                                             intent(in), optional :: osplit
-type(flyer),                                         intent(in), optional :: tpflyer
+type(tfiledata),                                    intent(in)           :: tpdiafile        ! File to write
+type(tbudiachrometadata),                           intent(in)           :: tpbudiachro
+class(tfieldmetadata_base), dimension(:),           intent(in)           :: tpfields
+real,                       dimension(:,:,:,:,:,:), intent(in)           :: pvar
+logical,                                            intent(in), optional :: osplit
+type(flyer),                                        intent(in), optional :: tpflyer
 
 character(len=:), allocatable :: ycategory
 character(len=:), allocatable :: ylevelname
@@ -1523,22 +1523,22 @@ end  subroutine Write_diachro_nc4
 subroutine Diachro_one_field_write_nc4( tpfile, tpbudiachro, tpfield, pvar, kdims, osplit, odistributed, &
                                         kil, kih, kjl, kjh, kkl, kkh )
 use modd_budget,      only: NLVL_CATEGORY, NLVL_GROUP, NLVL_SHAPE, nbutshift, nbusubwrite, tbudiachrometadata
-use modd_field,       only: tfielddata, tfield_metadata_base
+use modd_field,       only: tfielddata, tfieldmetadata_base
 use modd_io,          only: isp, tfiledata
 use modd_parameters,  only: jphext
 
 use mode_io_field_write, only: IO_Field_create, IO_Field_write, IO_Field_write_box
 
-type(tfiledata),                                     intent(in)  :: tpfile        !File to write
-type(tbudiachrometadata),                            intent(in)  :: tpbudiachro
-class(tfield_metadata_base),                         intent(in)  :: tpfield
-real,                        dimension(:,:,:,:,:,:), intent(in)  :: pvar
-integer, dimension(:),                               intent(in)  :: kdims        !List of indices of dimensions to use
-logical,                                             intent(in)  :: osplit
-logical,                                             intent(in)  :: odistributed !.T. if data is distributed among all processes
-integer,                                             intent(in), optional :: kil, kih
-integer,                                             intent(in), optional :: kjl, kjh
-integer,                                             intent(in), optional :: kkl, kkh
+type(tfiledata),                                    intent(in)  :: tpfile        !File to write
+type(tbudiachrometadata),                           intent(in)  :: tpbudiachro
+class(tfieldmetadata_base),                         intent(in)  :: tpfield
+real,                       dimension(:,:,:,:,:,:), intent(in)  :: pvar
+integer, dimension(:),                              intent(in)  :: kdims        !List of indices of dimensions to use
+logical,                                            intent(in)  :: osplit
+logical,                                            intent(in)  :: odistributed !.T. if data is distributed among all processes
+integer,                                            intent(in), optional :: kil, kih
+integer,                                            intent(in), optional :: kjl, kjh
+integer,                                            intent(in), optional :: kkl, kkh
 
 integer                                                    :: idims
 integer                                                    :: ibutimepos
@@ -1770,14 +1770,14 @@ end subroutine Diachro_one_field_write_nc4
 
 
 subroutine Prepare_diachro_write( tpfieldin, tpfieldout, kdims, osplit, odistributed, kbutimepos )
-use modd_field, only: NMNHDIM_BUDGET_TIME, NMNHDIM_UNUSED, NMNHMAXDIMS, tfielddata, tfield_metadata_base
-
-class(tfield_metadata_base), intent(in)  :: tpfieldin
-type(tfielddata),            intent(out) :: tpfieldout
-integer, dimension(:),       intent(in)  :: kdims ! List of indices of dimensions to use
-logical,                     intent(in)  :: osplit
-logical,                     intent(in)  :: odistributed ! .true. if data is distributed among all the processes
-integer,                     intent(out) :: kbutimepos
+use modd_field, only: NMNHDIM_BUDGET_TIME, NMNHDIM_UNUSED, NMNHMAXDIMS, tfielddata, tfieldmetadata_base
+
+class(tfieldmetadata_base), intent(in)  :: tpfieldin
+type(tfielddata),           intent(out) :: tpfieldout
+integer, dimension(:),      intent(in)  :: kdims ! List of indices of dimensions to use
+logical,                    intent(in)  :: osplit
+logical,                    intent(in)  :: odistributed ! .true. if data is distributed among all the processes
+integer,                    intent(out) :: kbutimepos
 
 integer :: idims
 integer :: jdim
diff --git a/src/MNH/write_les_budgetn.f90 b/src/MNH/write_les_budgetn.f90
index 7827ba184b18d710839d63155d807c186b67eb01..cb76368d557662da8392476b6585bb55c43b34b8 100644
--- a/src/MNH/write_les_budgetn.f90
+++ b/src/MNH/write_les_budgetn.f90
@@ -44,7 +44,7 @@ subroutine  Write_les_budget_n( tpdiafile )
 !!      Original   07/02/00
 !!                 06/11/02 (V. Masson) new LES budgets
 !  P. Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!  P. Wautelet 15/10/2020: restructure Les_diachro calls to use tfield_metadata_base type
+!  P. Wautelet 15/10/2020: restructure Les_diachro calls to use tfieldmetadata_base type
 !  JL Redelsperger 03/21 modif buoyancy flix for OCEAN LES case  
 ! --------------------------------------------------------------------------
 !
@@ -56,7 +56,7 @@ use modd_cst,         only: xg, xalphaoc
 use modd_dyn_n,       only: locean
 use modd_field,       only: NMNHDIM_BUDGET_LES_LEVEL, NMNHDIM_BUDGET_LES_TIME, &
                             NMNHDIM_BUDGET_TERM, NMNHDIM_UNUSED,               &
-                            tfield_metadata_base, TYPEREAL
+                            tfieldmetadata_base, TYPEREAL
 use modd_io,          only: tfiledata
 use modd_les,         only: cles_norm_type, nles_k, xles_temp_mean_start, xles_temp_mean_end, xles_temp_sampling
 use modd_les_n,       only: nles_times,                                                                                   &
@@ -105,9 +105,9 @@ character(len=:), allocatable          :: ygroupcomment
 !
 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLES_BUDGET
 !
-logical                    :: gdoavg  ! Compute and store time average
-logical                    :: gdonorm ! Compute and store normalized field
-type(tfield_metadata_base) :: tzfield
+logical                   :: gdoavg  ! Compute and store time average
+logical                   :: gdonorm ! Compute and store normalized field
+type(tfieldmetadata_base) :: tzfield
 !-------------------------------------------------------------------------------
 !
 !*          Initializations
diff --git a/src/MNH/write_les_rt_budgetn.f90 b/src/MNH/write_les_rt_budgetn.f90
index 114d39cda70bc47d713bcfbddc3f550c9a27d491..66df13adebabdf556d771123572774257abae163 100644
--- a/src/MNH/write_les_rt_budgetn.f90
+++ b/src/MNH/write_les_rt_budgetn.f90
@@ -43,7 +43,7 @@ subroutine  Write_les_rt_budget_n( tpdiafile )
 !!    -------------
 !!      Original         06/11/02
 !  P. Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!  P. Wautelet 15/10/2020: restructure Les_diachro calls to use tfield_metadata_base type
+!  P. Wautelet 15/10/2020: restructure Les_diachro calls to use tfieldmetadata_base type
 ! --------------------------------------------------------------------------
 !
 !*      0. DECLARATIONS
@@ -52,7 +52,7 @@ subroutine  Write_les_rt_budget_n( tpdiafile )
 use modd_cst,         only: xg
 use modd_field,       only: NMNHDIM_BUDGET_LES_LEVEL, NMNHDIM_BUDGET_LES_TIME, &
                             NMNHDIM_BUDGET_TERM, NMNHDIM_UNUSED,               &
-                            tfield_metadata_base, TYPEREAL
+                            tfieldmetadata_base, TYPEREAL
 use modd_io,          only: tfiledata
 use modd_les,         only: cles_norm_type, nles_k, xles_temp_mean_start, xles_temp_mean_end, xles_temp_sampling
 use modd_les_n,       only: nles_times,                                                                                   &
@@ -98,9 +98,9 @@ character(len=:),   allocatable          :: ygroupcomment
 !
 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLES_BUDGET
 !
-logical                    :: gdoavg  ! Compute and store time average
-logical                    :: gdonorm ! Compute and store normalized field
-type(tfield_metadata_base) :: tzfield
+logical                   :: gdoavg  ! Compute and store time average
+logical                   :: gdonorm ! Compute and store normalized field
+type(tfieldmetadata_base) :: tzfield
 !-------------------------------------------------------------------------------
 !
 !*          Initializations
diff --git a/src/MNH/write_les_sv_budgetn.f90 b/src/MNH/write_les_sv_budgetn.f90
index 6a3997964fff08e950d3de7c18fa1603f5e392ad..8a412845f16ad91b5122ef961529ff316a551f09 100644
--- a/src/MNH/write_les_sv_budgetn.f90
+++ b/src/MNH/write_les_sv_budgetn.f90
@@ -43,7 +43,7 @@ subroutine Write_les_sv_budget_n( tpdiafile )
 !!    -------------
 !!      Original         06/11/02
 !  P. Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!  P. Wautelet 14/10/2020: restructure Les_diachro calls to use tfield_metadata_base type
+!  P. Wautelet 14/10/2020: restructure Les_diachro calls to use tfieldmetadata_base type
 ! --------------------------------------------------------------------------
 !
 !*      0. DECLARATIONS
@@ -53,7 +53,7 @@ use modd_conf_n,      only: luserv
 use modd_cst,         only: xg
 use modd_field,       only: NMNHDIM_BUDGET_LES_LEVEL, NMNHDIM_BUDGET_LES_TIME, NMNHDIM_BUDGET_LES_SV, &
                             NMNHDIM_BUDGET_TERM, NMNHDIM_UNUSED,                                      &
-                            tfield_metadata_base, TYPEREAL
+                            tfieldmetadata_base, TYPEREAL
 use modd_io,          only: tfiledata
 use modd_les,         only: cles_norm_type, nles_k, xles_temp_mean_start, xles_temp_mean_end, xles_temp_sampling
 use modd_les_n,       only: nles_times,                                                                     &
@@ -99,9 +99,9 @@ character(len=:),   allocatable          :: ygroupcomment
 !
 REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZLES_BUDGET
 !
-logical                    :: gdoavg  ! Compute and store time average
-logical                    :: gdonorm ! Compute and store normalized field
-type(tfield_metadata_base) :: tzfield
+logical                   :: gdoavg  ! Compute and store time average
+logical                   :: gdonorm ! Compute and store normalized field
+type(tfieldmetadata_base) :: tzfield
 !-------------------------------------------------------------------------------
 !
 !*          Initializations
diff --git a/src/MNH/write_lesn.f90 b/src/MNH/write_lesn.f90
index e4adb2045bd0fc24bbcf5f685c34fd7051a53ba7..b090d3312e04e059ebd40c692c36595caa2f7144 100644
--- a/src/MNH/write_lesn.f90
+++ b/src/MNH/write_lesn.f90
@@ -7,7 +7,7 @@
 module mode_write_les_n
 !######################
 
-use modd_field, only: tfield_metadata_base
+use modd_field, only: tfieldmetadata_base
 
 implicit none
 
@@ -22,9 +22,9 @@ character(len=:), allocatable :: cgroupcomment
 logical :: ldoavg    ! Compute and store time average
 logical :: ldonorm   ! Compute and store normalized field
 
-type(tfield_metadata_base) :: tfield
-type(tfield_metadata_base) :: tfieldx
-type(tfield_metadata_base) :: tfieldy
+type(tfieldmetadata_base) :: tfield
+type(tfieldmetadata_base) :: tfieldx
+type(tfieldmetadata_base) :: tfieldy
 
 interface Les_diachro_write
   module procedure Les_diachro_write_1D, Les_diachro_write_2D, Les_diachro_write_3D, Les_diachro_write_4D
@@ -71,7 +71,7 @@ subroutine  Write_les_n( tpdiafile )
 !  P. Wautelet 12/10/2020: remove HLES_AVG dummy argument and group all 4 calls
 !  P. Wautelet 13/10/2020: bugfix: correct some names for LES_DIACHRO_2PT diagnostics (Ri)
 !  P. Wautelet 26/10/2020: bugfix: correct some comments and conditions + add missing RES_RTPZ
-!  P. Wautelet 26/10/2020: restructure subroutines to use tfield_metadata_base type
+!  P. Wautelet 26/10/2020: restructure subroutines to use tfieldmetadata_base type
 ! --------------------------------------------------------------------------
 !
 !*      0. DECLARATIONS
diff --git a/src/MNH/write_profilern.f90 b/src/MNH/write_profilern.f90
index 486978e1c2accda7b8125d056c48166d2a5f201c..13d9e1a8e69c53c793ad68cb07f01c1c795a2189 100644
--- a/src/MNH/write_profilern.f90
+++ b/src/MNH/write_profilern.f90
@@ -86,7 +86,7 @@ USE MODD_CH_M9_n,         ONLY: CNAMES
 USE MODD_CST,             ONLY: XRV
 USE MODD_ELEC_DESCR,      ONLY: CELECNAMES
 use modd_field,           only: NMNHDIM_LEVEL, NMNHDIM_PROFILER_TIME, NMNHDIM_PROFILER_PROC, NMNHDIM_UNUSED, &
-                                tfield_metadata_base, TYPEREAL
+                                tfieldmetadata_base, TYPEREAL
 USE MODD_ICE_C1R3_DESCR,  ONLY: C1R3NAMES
 USE MODD_IO,              ONLY: TFILEDATA
 USE MODD_LG,              ONLY: CLGNAMES
@@ -111,21 +111,21 @@ INTEGER,          INTENT(IN) :: KI
 !
 !*      0.2  declaration of local variables for diachro
 !
-character(len=2)                                      :: yidx
-character(len=100)                                    :: ycomment
-character(len=100)                                    :: yname
-CHARACTER(LEN=:),                         allocatable :: YGROUP   ! group title
-INTEGER                                               :: IKU
-INTEGER                                               :: IPROC    ! number of variables records
-INTEGER                                               :: JPROC
-INTEGER                                               :: JRR      ! loop counter
-INTEGER                                               :: JSV      ! loop counter
-integer                                               :: ji
-integer                                               :: irr !Number of moist variables
-REAL, DIMENSION(:,:,:),                   ALLOCATABLE :: ZRHO
-REAL, DIMENSION(:,:,:,:),                 ALLOCATABLE :: ZSV, ZN0, ZSIG, ZRG
-type(tbudiachrometadata)                              :: tzbudiachro
-type(tfield_metadata_base), dimension(:), allocatable :: tzfields
+character(len=2)                                     :: yidx
+character(len=100)                                   :: ycomment
+character(len=100)                                   :: yname
+CHARACTER(LEN=:),                        allocatable :: YGROUP   ! group title
+INTEGER                                              :: IKU
+INTEGER                                              :: IPROC    ! number of variables records
+INTEGER                                              :: JPROC
+INTEGER                                              :: JRR      ! loop counter
+INTEGER                                              :: JSV      ! loop counter
+integer                                              :: ji
+integer                                              :: irr !Number of moist variables
+REAL, DIMENSION(:,:,:),                  ALLOCATABLE :: ZRHO
+REAL, DIMENSION(:,:,:,:),                ALLOCATABLE :: ZSV, ZN0, ZSIG, ZRG
+type(tbudiachrometadata)                             :: tzbudiachro
+type(tfieldmetadata_base), dimension(:), allocatable :: tzfields
 !
 !----------------------------------------------------------------------------
 !
diff --git a/src/MNH/write_seriesn.f90 b/src/MNH/write_seriesn.f90
index 54ed6c7c8cc5667860dc1c0bc285787c09f76772..62999fff5f6b00cc7cc4939150669c14894f29a3 100644
--- a/src/MNH/write_seriesn.f90
+++ b/src/MNH/write_seriesn.f90
@@ -74,7 +74,7 @@ use modd_budget,        only: NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_
 use modd_field,         only: NMNHDIM_NI, NMNHDIM_NI_U,                                                               &
                               NMNHDIM_SERIES_LEVEL, NMNHDIM_SERIES_LEVEL_W, NMNHDIM_SERIES_TIME, NMNHDIM_SERIES_PROC, &
                               NMNHDIM_UNUSED,                                                                         &
-                              tfield_metadata_base, TYPEREAL
+                              tfieldmetadata_base, TYPEREAL
 USE MODD_IO,            ONLY: NGEN_VERB, TFILEDATA
 USE MODD_LUNIT_n,       ONLY: TLUOUT
 USE MODD_PARAMETERS
@@ -117,9 +117,9 @@ INTEGER  :: INFO_ll   ! Return code of FM-routines
 INTEGER :: ISER,INAV
 REAL :: ZSIZEHB
 CHARACTER(LEN=100) :: YMSG
-type(tbudiachrometadata)                              :: tzbudiachro
-type(tfield_metadata_base), dimension(:), allocatable :: tzfields
-type(tfiledata)                                       :: tzfile
+type(tbudiachrometadata)                             :: tzbudiachro
+type(tfieldmetadata_base), dimension(:), allocatable :: tzfields
+type(tfiledata)                                      :: tzfile
 !----------------------------------------------------------------------------
 !
 !*    1.     INITIALIZATION
diff --git a/src/MNH/write_stationn.f90 b/src/MNH/write_stationn.f90
index 7efb9adaa863a844ec485d803cec0a409b8b69e6..972805565d248f7aa0d309cb3ed69d0aa07431c7 100644
--- a/src/MNH/write_stationn.f90
+++ b/src/MNH/write_stationn.f90
@@ -126,7 +126,7 @@ SUBROUTINE STATION_DIACHRO_n(TSTATION,II)
 
 use modd_budget, only: NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK
 use modd_field,  only: NMNHDIM_STATION_TIME, NMNHDIM_STATION_PROC, NMNHDIM_UNUSED, &
-                       tfield_metadata_base, TYPEREAL
+                       tfieldmetadata_base, TYPEREAL
 
 TYPE(STATION),        INTENT(IN)       :: TSTATION
 INTEGER,              INTENT(IN)       :: II
@@ -151,8 +151,8 @@ INTEGER :: IPROC    ! number of variables records
 INTEGER :: JPROC    ! loop counter
 INTEGER :: JRR      ! loop counter
 INTEGER :: JSV      ! loop counter
-type(tbudiachrometadata)                              :: tzbudiachro
-type(tfield_metadata_base), dimension(:), allocatable :: tzfields
+type(tbudiachrometadata)                             :: tzbudiachro
+type(tfieldmetadata_base), dimension(:), allocatable :: tzfields
 !
 !----------------------------------------------------------------------------
 IF (TSTATION%X(II)==XUNDEF) RETURN