diff --git a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
index 10ced03147ebf0d9bb2732f10b50a360e404a136..b48a37b2649d4d8ae06964e24a736db43439cbaf 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
@@ -397,7 +397,7 @@ subroutine IO_Field_create( tpfile, tpfield )
 #endif
 
       case ( 4 ) NDIMS
-        if ( tzfield%ntype /= TYPEREAL ) then
+        if ( All( tzfield%ntype /= [ TYPEINT, TYPEREAL ] ) ) then
           call Print_msg( NVERB_ERROR, 'IO', 'IO_Field_create', Trim( tpfile%cname ) // ': ' &
                           // Trim( tzfield%cmnhname ) // ': invalid ntype for 4D field' )
           return
diff --git a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
index f6d21f935b2095cfd24eed2a48e0a08a71839510..9804348f8da7ba0f62912a75ce4861e77c93b6b6 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
@@ -17,6 +17,8 @@
 !  P. Wautelet 26/11/2020: IO_Vdims_fill_nc4: support for empty kshape
 !  P. Wautelet 08/12/2020: add nbutotwrite
 !  P. Wautelet 18/03/2021: workaround for an intel compiler bug
+!  P. Wautelet 04/05/2021: improve IO_Vdims_fill_nc4 if l2d and lpack
+!  P. Wautelet 27/05/2021: improve IO_Mnhname_clean to autocorrect names to be CF compliant
 !-----------------------------------------------------------------
 #ifdef MNH_IOCDF4
 module mode_io_tools_nc4
@@ -437,26 +439,29 @@ integer,          intent(in)    :: kidx     !Position of the dimension in the li
 character(len=*), intent(in)    :: hdimname !Name of the dimension
 integer,          intent(in)    :: klen     !Length of the dimension
 
+character(len=Len(hdimname))  :: ydimname_clean
 integer(kind=CDFINT)          :: istatus
 
 
+call IO_Mnhname_clean( hdimname, ydimname_clean )
+
 if ( .not.Associated( tpfile%tncdims ) ) &
   call Print_msg( NVERB_FATAL, 'IO', 'IO_Add_dim_nc4', 'tncdims not associated for ' // Trim( tpfile%cname ) )
 
 if ( kidx < 1 .or. kidx > Size( tpfile%tncdims%tdims ) )                                                      &
-  call Print_msg( NVERB_FATAL, 'IO', 'IO_Add_dim_nc4', 'index out of range for dimension ' // Trim( hdimname ) // &
+  call Print_msg( NVERB_FATAL, 'IO', 'IO_Add_dim_nc4', 'index out of range for dimension ' // Trim( ydimname_clean ) // &
                   ' of file ' //Trim( tpfile%cname ) )
 
 if ( tpfile%tncdims%tdims(kidx)%nlen /= -1 .or. tpfile%tncdims%tdims(kidx)%nid /= -1 ) &
-  call Print_msg( NVERB_WARNING, 'IO', 'IO_Add_dim_nc4', 'dimension ' // Trim( hdimname ) //   &
+  call Print_msg( NVERB_WARNING, 'IO', 'IO_Add_dim_nc4', 'dimension ' // Trim( ydimname_clean ) //   &
                   ' already defined for file ' //Trim( tpfile%cname ) )
 
-tpfile%tncdims%tdims(kidx)%cname = hdimname
+tpfile%tncdims%tdims(kidx)%cname = ydimname_clean
 tpfile%tncdims%tdims(kidx)%nlen  = Int( klen, kind = CDFINT )
 
-istatus = NF90_DEF_DIM( tpfile%nncid, Trim( hdimname ), Int( klen, kind = CDFINT ), tpfile%tncdims%tdims(kidx)%nid )
+istatus = NF90_DEF_DIM( tpfile%nncid, Trim( ydimname_clean ), Int( klen, kind = CDFINT ), tpfile%tncdims%tdims(kidx)%nid )
 if ( istatus /= NF90_NOERR ) &
-  call IO_Err_handle_nc4( istatus, 'IO_Add_dim_nc4', 'NF90_DEF_DIM', Trim( hdimname ) )
+  call IO_Err_handle_nc4( istatus, 'IO_Add_dim_nc4', 'NF90_DEF_DIM', Trim( ydimname_clean ) )
 
 end subroutine IO_Add_dim_nc4
 
@@ -479,6 +484,7 @@ SUBROUTINE IO_Vdims_fill_nc4(TPFILE, TPFIELD, KSHAPE, KVDIMS)
 
 use NETCDF, only: NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION
 
+use modd_conf,   only: l2d, lpack
 use modd_field,  only: NMNHDIM_UNKNOWN, NMNHDIM_ONE, NMNHDIM_COMPLEX,                                   &
                        NMNHDIM_NI, NMNHDIM_NJ, NMNHDIM_NI_U, NMNHDIM_NJ_U, NMNHDIM_NI_V, NMNHDIM_NJ_V,  &
                        NMNHDIM_LEVEL, NMNHDIM_LEVEL_W, NMNHDIM_TIME,                                    &
@@ -505,6 +511,7 @@ INTEGER(KIND=CDFINT),DIMENSION(:),ALLOCATABLE,INTENT(OUT) :: KVDIMS
 CHARACTER(LEN=32)             :: YINT
 CHARACTER(LEN=2)              :: YDIR
 character(len=:), allocatable :: ydimname
+integer                       :: idimn
 INTEGER                       :: IGRID
 integer                       :: iidx
 integer                       :: iresp
@@ -607,8 +614,15 @@ else !ndimlist not provided
           kvdims(1) = tpfile%tncdims%tdims(iidx)%nid
         end if
       else if ( ji == 2 ) then
-        if ( ydir == 'XY' .and. kshape(2) == tpfile%tncdims%tdims( NMNHDIM_ARAKAWA(igrid,2) )%nlen ) then
-          kvdims(2) = tpfile%tncdims%tdims( NMNHDIM_ARAKAWA(igrid,2) )%nid
+        !If lpack and l2d, the J dimension is not used.
+        !Therefore, in that case, the second dimension for a 'XY' field corresponds to the K dimension.
+        if ( lpack .and. l2d ) then
+          idimn = 3
+        else
+          idimn = 2
+        end if
+        if ( ydir == 'XY' .and. kshape(2) == tpfile%tncdims%tdims( NMNHDIM_ARAKAWA(igrid,idimn) )%nlen ) then
+          kvdims(2) = tpfile%tncdims%tdims( NMNHDIM_ARAKAWA(igrid,idimn) )%nid
         else
           call IO_Dim_find_create_nc4( tpfile, kshape(2), iidx )
           kvdims(2) = tpfile%tncdims%tdims(iidx)%nid
@@ -642,7 +656,8 @@ integer(kind=CDFINT),       intent(in) :: klen
 CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: HDIMNAME
 integer, intent(out) :: kidx !Position of the dimension in the dimension array
 
-character(len=16)     :: ysuffix
+character(len=:), allocatable :: ydimname_clean
+character(len=16)             :: ysuffix
 integer :: inewsize
 integer :: ji
 integer(kind=CDFINT)  :: istatus
@@ -651,10 +666,12 @@ type(tdimnc), dimension(:), allocatable :: tzncdims
 
 kidx = -1
 
+if ( Present( hdimname ) ) call IO_Mnhname_clean( hdimname, ydimname_clean )
+
 do ji = 1, Size( tpfile%tncdims%tdims )
   if ( tpfile%tncdims%tdims(ji)%nlen == klen ) then
     if ( Present( hdimname ) ) then
-      if ( hdimname == Trim( tpfile%tncdims%tdims(ji)%cname ) ) then
+      if ( ydimname_clean == Trim( tpfile%tncdims%tdims(ji)%cname ) ) then
         kidx = ji
         exit
       end if
@@ -669,9 +686,9 @@ if ( kidx == - 1 ) then
   !Check if already exist with the provided name (if so => error)
   if ( Present( hdimname ) ) then
     do ji = 1, Size( tpfile%tncdims%tdims )
-      if ( hdimname == Trim( tpfile%tncdims%tdims(ji)%cname ) )                             &
+      if ( ydimname_clean == Trim( tpfile%tncdims%tdims(ji)%cname ) )                             &
         call Print_msg( NVERB_ERROR, 'IO', 'IO_Dim_find_create_nc4', 'dimension '          &
-                        // Trim( hdimname ) // ' already exist but with a different size' )
+                        // Trim( ydimname_clean ) // ' already exist but with a different size' )
     end do
   end if
 
@@ -681,7 +698,7 @@ if ( kidx == - 1 ) then
   tzncdims(1 : inewsize - 1) = tpfile%tncdims%tdims(:)
 
   if ( Present( hdimname ) ) then
-    tzncdims(inewsize)%cname = Trim( hdimname )
+    tzncdims(inewsize)%cname = Trim( ydimname_clean )
   else
     Write( ysuffix, '( i0 )' ) klen
     tzncdims(inewsize)%cname = 'size' // Trim( ysuffix )
@@ -822,31 +839,75 @@ end if
 end subroutine IO_Err_handle_nc4
 
 
-SUBROUTINE IO_Mnhname_clean(HINNAME,HOUTNAME)
-  CHARACTER(LEN=*),INTENT(IN)  :: HINNAME
-  CHARACTER(LEN=*),INTENT(OUT) :: HOUTNAME
-
+subroutine IO_Mnhname_clean( hinname, houtname )
+  ! Try to autocorrect hinname to be CF compliant
   ! NetCDF var names can't contain '%' nor '.'
-  ! CF convention allows only letters, digits and underscores
-  HOUTNAME = str_replace(HINNAME,  '%', '__')
-  HOUTNAME = str_replace(HOUTNAME, '.', '___')
-END SUBROUTINE
+  ! CF convention allows only letters, digits and underscores for variable, dimension, attribute and group names
+  ! and they should begin with a letter
+  character(len=*), intent(in)  :: hinname
+  character(len=*), intent(out) :: houtname
 
+  character(len=:), allocatable :: yresult
+  integer :: ipos
 
-FUNCTION str_replace(hstr, hold, hnew)
-CHARACTER(LEN=*) :: hstr, hold, hnew
-CHARACTER(LEN=LEN_TRIM(hstr)+MAX(0,LEN(hnew)-LEN(hold))) :: str_replace
+  if ( Len_trim( hinname ) == 0 ) then
+    houtname = ''
+    return
+  end if
 
-INTEGER :: pos
+  ipos = Scan( Trim( hinname), 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz' )
+  if ( ipos == 0 ) then
+    call Print_msg( NVERB_WARNING, 'IO', 'IO_Mnhname_clean', 'name (' // Trim( hinname) // &
+                    ') must begin with a letter to conform to CF convention' )
+  end if
 
-pos = INDEX(hstr,hold)
-IF (pos /= 0) THEN
-   str_replace = hstr(1:pos-1)//hnew//hstr(pos+LEN(hold):)
-ELSE
-   str_replace = hstr
-END IF
+  ipos = Verify( Trim( hinname), 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789_' )
+  if ( ipos > 0 ) then
+    yresult = Str_replace( hinname,  '%', '__' )
+    yresult = Str_replace( yresult, '.', '___' )
+    yresult = Str_replace( yresult, '-', '_' )
+    yresult = Str_replace( yresult, '*', 'star' )
+    yresult = Str_replace( Trim( yresult ), ' ', '_' ) !Trim to prevent problem with spaces at the end of the string
+
+    !Chek corrected name
+    ipos = Verify( Trim( yresult ), 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789_' )
+
+    if ( ipos == 0 ) then
+      call Print_msg( NVERB_INFO, 'IO', 'IO_Mnhname_clean', "Renaming to comply with CF convention: '" &
+                      // Trim( hinname ) // "' -> '" // Trim( yresult ) // "'" )
+    else
+      call Print_msg( NVERB_WARNING, 'IO', 'IO_Mnhname_clean', "Renaming to comply with CF convention FAILED: '" &
+                      // Trim( hinname ) // "' -> '" // Trim( yresult ) // "'" )
+    end if
+  else
+    yresult = Trim( hinname )
+  end if
+
+  houtname = Trim( yresult )
+
+  if ( Len_trim( yresult ) > Len( houtname ) ) &
+    call Print_msg( NVERB_WARNING, 'IO', 'IO_Mnhname_clean', &
+                    'houtname has been truncated (' // Trim( houtname) // '->' // Trim( yresult ) // ')' )
+
+end subroutine
+
+
+recursive function Str_replace( hstr, hold, hnew ) result( hout )
+character(len=*), intent(in) :: hstr, hold, hnew
+
+character(len=:), allocatable :: hout
+
+integer :: ipos
+
+ipos = Index( hstr, hold )
+if ( ipos > 0 ) then
+   hout = hstr(1 : ipos - 1) // hnew // hstr( ipos + Len( hold ) : )
+   if ( ipos < Len_trim( hstr ) ) hout = Str_replace( hout, hold, hnew )
+else
+   hout = hstr
+end if
 
-END FUNCTION str_replace
+end function Str_replace
 
 
 end module mode_io_tools_nc4
diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
index a52005298762aa03c0acdd382f424a9a9d0b7a37..cc24abb6fb9727634dcf7b04dfc413c34ba28049 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
@@ -296,7 +296,7 @@ IF (.NOT.GISCOORD) THEN
         IF (istatus /= NF90_NOERR) CALL IO_Err_handle_nc4(istatus,'IO_Field_attr_write_nc4','NF90_PUT_ATT','coordinates')
         DEALLOCATE(YCOORDS)
       ELSE
-        CALL PRINT_MSG(NVERB_WARNING,'IO','IO_Field_attr_write_nc4','coordinates not implemented for variable ' &
+        CALL PRINT_MSG(NVERB_DEBUG,'IO','IO_Field_attr_write_nc4','coordinates not implemented for variable ' &
                                                                     //TRIM(TPFIELD%CMNHNAME))
       END IF
     ELSE
@@ -2279,11 +2279,19 @@ subroutine Write_flyer_time_coord( tpflyer )
   use NETCDF
 
   use modd_aircraft_balloon
-  use modd_parameters,       only: XUNDEF
+  use modd_parameters,       only: NBUNAMELGTMAX, XUNDEF
+
+  use mode_io_tools_nc4,     only: IO_Mnhname_clean
+
+  use modi_aircraft_balloon, only: Aircraft_balloon_longtype_get
 
   type(flyer), intent(in) :: tpflyer
 
+  character(len=NBUNAMELGTMAX) :: ytype
+  character(len=NBUNAMELGTMAX) :: ytype_clean
   integer                      :: istatus
+  integer(kind=CDFINT)         :: icatid
+  integer(kind=CDFINT)         :: isubcatid
   integer(kind=CDFINT)         :: idimid
   type(tdimnc),        pointer :: tzdim
 
@@ -2291,39 +2299,30 @@ subroutine Write_flyer_time_coord( tpflyer )
   if ( tpflyer%nmodel == imi .and. Count( tpflyer%x /= XUNDEF) > 1 ) then
     Allocate( tzdim )
 
-
-    !Group with flyer title
-    istatus = NF90_INQ_NCID( tpfile%nncid, Trim( tpflyer%title ), incid )
+    istatus = NF90_INQ_NCID( tpfile%nncid, 'Flyers', icatid )
     if ( istatus /= NF90_NOERR ) then
       call Print_msg( NVERB_ERROR, 'IO', 'Write_flyer_time_coord', &
-                      Trim( tpfile%cname ) // ': group '// Trim( tpflyer%title ) // ' not found' )
+                      Trim( tpfile%cname ) // ': group Flyers not found' )
     end if
 
-    istatus = NF90_INQ_DIMID( incid, 'time_flyer', idimid )
+    call Aircraft_balloon_longtype_get( tpflyer, ytype )
+    call IO_Mnhname_clean( ytype, ytype_clean )
+    istatus = NF90_INQ_NCID( icatid, Trim( ytype_clean ), isubcatid )
     if ( istatus /= NF90_NOERR ) then
       call Print_msg( NVERB_ERROR, 'IO', 'Write_flyer_time_coord', &
-                      Trim( tpfile%cname ) // ': group ' // Trim( tpflyer%title ) // ' time_flyer dimension not found' )
+                      Trim( tpfile%cname ) // ': group ' // Trim( ytype_clean ) // ' not found' )
     end if
 
-    tzdim%cname = 'time_flyer'
-    istatus = NF90_INQUIRE_DIMENSION( incid, idimid, len = tzdim%nlen )
-    tzdim%nid = idimid
-
-    !Remark: incid is used in Write_time_coord
-    call Write_time_coord( tzdim, 'time axis for flyer', tpflyer%tpdates )
-
-
-    !Group with flyer title suffixed by Z
-    istatus = NF90_INQ_NCID( tpfile%nncid, Trim( tpflyer%title ) // 'Z' , incid )
+    istatus = NF90_INQ_NCID( isubcatid, Trim( tpflyer%title ), incid )
     if ( istatus /= NF90_NOERR ) then
       call Print_msg( NVERB_ERROR, 'IO', 'Write_flyer_time_coord', &
-                      Trim( tpfile%cname ) // ': group '// Trim( tpflyer%title ) // 'z not found' )
+                      Trim( tpfile%cname ) // ': group '// Trim( tpflyer%title ) // ' not found' )
     end if
 
     istatus = NF90_INQ_DIMID( incid, 'time_flyer', idimid )
     if ( istatus /= NF90_NOERR ) then
       call Print_msg( NVERB_ERROR, 'IO', 'Write_flyer_time_coord', &
-                      Trim( tpfile%cname ) // ': group ' // Trim( tpflyer%title ) // 'Z time_flyer dimension not found' )
+                      Trim( tpfile%cname ) // ': group ' // Trim( tpflyer%title ) // ' time_flyer dimension not found' )
     end if
 
     tzdim%cname = 'time_flyer'
@@ -2331,8 +2330,7 @@ subroutine Write_flyer_time_coord( tpflyer )
     tzdim%nid = idimid
 
     !Remark: incid is used in Write_time_coord
-    call Write_time_coord( tzdim, 'time axis for flyer', tpflyer  %tpdates )
-
+    call Write_time_coord( tzdim, 'time axis for flyer', tpflyer%tpdates )
 
     Deallocate( tzdim )
 
diff --git a/src/MNH/aircraft_balloon.f90 b/src/MNH/aircraft_balloon.f90
index 5e48b0481a0bdb7d3aea970c82dd1e593c45cde3..153d76fe61b3174ea15d8e7546a8acf6cc4ddc74 100644
--- a/src/MNH/aircraft_balloon.f90
+++ b/src/MNH/aircraft_balloon.f90
@@ -1,6 +1,6 @@
-!MNH_LIC Copyright 1994-2018 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
 !      #####################
@@ -41,6 +41,13 @@ REAL, DIMENSION(:,:),INTENT(IN) :: PSEA
 !
 END SUBROUTINE AIRCRAFT_BALLOON
 !
+SUBROUTINE AIRCRAFT_BALLOON_LONGTYPE_GET( TPFLYER, HLONGTYPE )
+  USE MODD_AIRCRAFT_BALLOON, ONLY: FLYER
+
+  TYPE(FLYER),      INTENT(IN)  :: TPFLYER
+  CHARACTER(LEN=*), INTENT(OUT) :: HLONGTYPE
+END SUBROUTINE AIRCRAFT_BALLOON_LONGTYPE_GET
+
 END INTERFACE
 !
 END MODULE MODI_AIRCRAFT_BALLOON
@@ -337,3 +344,34 @@ ENDIF
 !----------------------------------------------------------------------------
 !
 END SUBROUTINE AIRCRAFT_BALLOON
+
+
+SUBROUTINE AIRCRAFT_BALLOON_LONGTYPE_GET( TPFLYER, HLONGTYPE )
+USE MODD_AIRCRAFT_BALLOON, ONLY: FLYER
+
+USE MODE_MSG
+
+TYPE(FLYER),      INTENT(IN)  :: TPFLYER
+CHARACTER(LEN=*), INTENT(OUT) :: HLONGTYPE
+
+character(len=:), allocatable :: ytype
+
+if ( Trim( TPFLYER%TYPE ) == 'AIRCRA' ) then
+  ytype = 'Aircrafts'
+else if ( Trim( TPFLYER%TYPE ) == 'RADIOS' ) then
+  ytype = 'Radiosonde_balloons'
+else if ( Trim( TPFLYER%TYPE ) == 'ISODEN' ) then
+  ytype = 'Isodensity_balloons'
+else if ( Trim( TPFLYER%TYPE ) == 'CVBALL' ) then
+  ytype = 'Constant_volume_balloons'
+else
+  call Print_msg( NVERB_ERROR, 'GEN', 'AIRCRAFT_BALLOON_LONGTYPE_GET', 'unknown category for flyer ' // Trim( tpflyer%title ) )
+  ytype = 'Unknown'
+end if
+
+if ( Len_trim( ytype ) > Len( HLONGTYPE ) ) &
+  call Print_msg( NVERB_WARNING, 'GEN', 'AIRCRAFT_BALLOON_LONGTYPE_GET', &
+                  'HLONGTYPE truncated for flyer ' // Trim( tpflyer%title ) )
+HLONGTYPE = Trim( ytype )
+
+END SUBROUTINE AIRCRAFT_BALLOON_LONGTYPE_GET
diff --git a/src/MNH/budget_flags.f90 b/src/MNH/budget_flags.f90
index 1d14d21ad01763042a9bb54f29f9d1fa6722ffca..ba8cdde35ed366b879cf9eaa0b87b721d7e84bca 100644
--- a/src/MNH/budget_flags.f90
+++ b/src/MNH/budget_flags.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2002-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2002-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.
@@ -96,7 +96,7 @@ LBUDGET_U  =   (LBU_ENABLE .AND. LBU_RU  ) .OR.  (LLES_CALL .OR. LCHECK )
 LBUDGET_V  =   (LBU_ENABLE .AND. LBU_RV  ) .OR.  (LLES_CALL .OR. LCHECK )
 LBUDGET_W  =   (LBU_ENABLE .AND. LBU_RW  ) .OR.  (LLES_CALL .OR. LCHECK )
 LBUDGET_TH =   (LBU_ENABLE .AND. LBU_RTH ) .OR.  (LLES_CALL .OR. LCHECK )
-LBUDGET_TKE= ( (LBU_ENABLE .AND. LBU_RTKE) .OR.  (LLES_CALL .OR. LCHECK )              ) .AND. CTURB /= 'NONE'
+LBUDGET_TKE= ( (LBU_ENABLE .AND. LBU_RTKE) .OR.  (LLES_CALL .OR. LCHECK )              ) .AND. CTURB == 'TKEL'
 LBUDGET_RV = ( (LBU_ENABLE .AND. LBU_RRV ) .OR. ((LLES_CALL .OR. LCHECK ).AND. OUSERV) ) .AND. NRR >= 1
 LBUDGET_RC = ( (LBU_ENABLE .AND. LBU_RRC ) .OR. ((LLES_CALL .OR. LCHECK ).AND. OUSERC) ) .AND. NRR >= 2
 LBUDGET_RR = ( (LBU_ENABLE .AND. LBU_RRR ) .OR. ((LLES_CALL .OR. LCHECK ).AND. OUSERR) ) .AND. NRR >= 3
diff --git a/src/MNH/ini_budget.f90 b/src/MNH/ini_budget.f90
index 4651b859967f4e5329292351ffca204a8d132dd0..3152cb6e5e17022fc128393ad806dff7b7a08fa6 100644
--- a/src/MNH/ini_budget.f90
+++ b/src/MNH/ini_budget.f90
@@ -41,51 +41,51 @@ end if
 nbudgets = NBUDGET_SV1 - 1 + nsv
 allocate( tbudgets( nbudgets ) )
 
-tbudgets(NBUDGET_U)%cname    = "BU_RU"
+tbudgets(NBUDGET_U)%cname    = "UU"
 tbudgets(NBUDGET_U)%ccomment = "Budget for U"
 tbudgets(NBUDGET_U)%nid      = NBUDGET_U
 
-tbudgets(NBUDGET_V)%cname    = "BU_RV"
+tbudgets(NBUDGET_V)%cname    = "VV"
 tbudgets(NBUDGET_V)%ccomment = "Budget for V"
 tbudgets(NBUDGET_V)%nid      = NBUDGET_V
 
-tbudgets(NBUDGET_W)%cname    = "BU_RW"
+tbudgets(NBUDGET_W)%cname    = "WW"
 tbudgets(NBUDGET_W)%ccomment = "Budget for W"
 tbudgets(NBUDGET_W)%nid      = NBUDGET_W
 
-tbudgets(NBUDGET_TH)%cname    = "BU_RTH"
+tbudgets(NBUDGET_TH)%cname    = "TH"
 tbudgets(NBUDGET_TH)%ccomment = "Budget for potential temperature"
 tbudgets(NBUDGET_TH)%nid      = NBUDGET_TH
 
-tbudgets(NBUDGET_TKE)%cname    = "BU_RTKE"
+tbudgets(NBUDGET_TKE)%cname    = "TK"
 tbudgets(NBUDGET_TKE)%ccomment = "Budget for turbulent kinetic energy"
 tbudgets(NBUDGET_TKE)%nid      = NBUDGET_TKE
 
-tbudgets(NBUDGET_RV)%cname    = "BU_RRV"
+tbudgets(NBUDGET_RV)%cname    = "RV"
 tbudgets(NBUDGET_RV)%ccomment = "Budget for water vapor mixing ratio"
 tbudgets(NBUDGET_RV)%nid      = NBUDGET_RV
 
-tbudgets(NBUDGET_RC)%cname    = "BU_RRC"
+tbudgets(NBUDGET_RC)%cname    = "RC"
 tbudgets(NBUDGET_RC)%ccomment = "Budget for cloud water mixing ratio"
 tbudgets(NBUDGET_RC)%nid      = NBUDGET_RC
 
-tbudgets(NBUDGET_RR)%cname    = "BU_RRR"
+tbudgets(NBUDGET_RR)%cname    = "RR"
 tbudgets(NBUDGET_RR)%ccomment = "Budget for rain water mixing ratio"
 tbudgets(NBUDGET_RR)%nid      = NBUDGET_RR
 
-tbudgets(NBUDGET_RI)%cname    = "BU_RRI"
+tbudgets(NBUDGET_RI)%cname    = "RI"
 tbudgets(NBUDGET_RI)%ccomment = "Budget for cloud ice mixing ratio"
 tbudgets(NBUDGET_RI)%nid      = NBUDGET_RI
 
-tbudgets(NBUDGET_RS)%cname    = "BU_RRS"
+tbudgets(NBUDGET_RS)%cname    = "RS"
 tbudgets(NBUDGET_RS)%ccomment = "Budget for snow/aggregate mixing ratio"
 tbudgets(NBUDGET_RS)%nid      = NBUDGET_RS
 
-tbudgets(NBUDGET_RG)%cname    = "BU_RRG"
+tbudgets(NBUDGET_RG)%cname    = "RG"
 tbudgets(NBUDGET_RG)%ccomment = "Budget for graupel mixing ratio"
 tbudgets(NBUDGET_RG)%nid      = NBUDGET_RG
 
-tbudgets(NBUDGET_RH)%cname    = "BU_RRH"
+tbudgets(NBUDGET_RH)%cname    = "RH"
 tbudgets(NBUDGET_RH)%ccomment = "Budget for hail mixing ratio"
 tbudgets(NBUDGET_RH)%nid      = NBUDGET_RH
 
@@ -175,7 +175,7 @@ end subroutine Budget_preallocate
 !!      C.Lac           01/07/11  Add vegetation drag        
 !!      P. Peyrille, M. Tomasini : include in the forcing term the 2D forcing
 !!                                terms in term 2DFRC search for modif PP . but Not very clean! 
-!!      C .Lac          27/05/14    add negative corrections for chemical species
+!!      C .Lac          27/05/14    add negativity corrections for chemical species
 !!      C.Lac           29/01/15  Correction for NSV_USER
 !!      J.Escobar       02/10/2015 modif for JPHEXT(JPVEXT) variable  
 !!      C.Lac           04/12/15  Correction for LSUPSAT 
@@ -818,7 +818,7 @@ if ( lbu_rw ) then
   tbudgets(NBUDGET_W)%trhodj%cstdname  = ''
   tbudgets(NBUDGET_W)%trhodj%clongname = 'RhodJZ'
   tbudgets(NBUDGET_W)%trhodj%cunits    = 'kg'
-  tbudgets(NBUDGET_W)%trhodj%ccomment  = 'RhodJ for momentum along Y axis'
+  tbudgets(NBUDGET_W)%trhodj%ccomment  = 'RhodJ for momentum along Z axis'
   tbudgets(NBUDGET_W)%trhodj%ngrid     = 4
   tbudgets(NBUDGET_W)%trhodj%ntype     = TYPEREAL
   tbudgets(NBUDGET_W)%trhodj%ndims     = 3
@@ -1045,7 +1045,7 @@ if ( lbu_rth ) then
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'NETUR'
-  tzsource%clongname  = 'negative correction induced by turbulence'
+  tzsource%clongname  = 'negativity correction induced by turbulence'
   tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                                                 .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
@@ -1076,13 +1076,13 @@ if ( lbu_rth ) then
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
+  tzsource%clongname  = 'negativity correction induced by advection'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
+  tzsource%clongname  = 'negativity correction'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
@@ -1158,7 +1158,7 @@ if ( lbu_rth ) then
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'IMLT'
-  tzsource%clongname  = 'ice melting'
+  tzsource%clongname  = 'melting of ice'
   tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE'
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
@@ -1168,13 +1168,13 @@ if ( lbu_rth ) then
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'RIM'
-  tzsource%clongname  = 'riming of cloud droplets'
+  tzsource%clongname  = 'riming of cloud water'
   tzsource%lavailable =    ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) &
                         .or. hcloud(1:3) == 'ICE'
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'ACC'
-  tzsource%clongname  = 'accretion of rain'
+  tzsource%clongname  = 'accretion of rain on aggregates'
   tzsource%lavailable =      ( hcloud == 'LIMA' .and. (        lptsplit                                                            &
                                                         .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima .and. lrain_lima ) ) ) &
                         .or.   hcloud(1:3) == 'ICE'
@@ -1234,7 +1234,7 @@ if ( lbu_rth ) then
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'ADJU'
-  tzsource%clongname  = 'adjustment before'
+  tzsource%clongname  = 'adjustment to saturation'
   tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE'
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
@@ -1250,7 +1250,7 @@ if ( lbu_rth ) then
   call Budget_source_add( tbudgets(NBUDGET_TH), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
+  tzsource%clongname  = 'negativity correction induced by condensation'
   tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
                           .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
                         .and. celec == 'NONE'
@@ -1331,27 +1331,27 @@ if ( lbu_rtke ) then
 
   tzsource%cmnhname   = 'DP'
   tzsource%clongname  = 'dynamic production'
-  tzsource%lavailable = hturb == 'TKEL'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource )
 
   tzsource%cmnhname   = 'TP'
   tzsource%clongname  = 'thermal production'
-  tzsource%lavailable = hturb == 'TKEL'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource )
 
   tzsource%cmnhname   = 'DISS'
   tzsource%clongname  = 'dissipation of TKE'
-  tzsource%lavailable = hturb == 'TKEL'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource )
 
   tzsource%cmnhname   = 'TR'
   tzsource%clongname  = 'turbulent transport'
-  tzsource%lavailable = hturb == 'TKEL'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource )
 
   tzsource%cmnhname   = 'ADV'
   tzsource%clongname  = 'total advection'
-  tzsource%lavailable = hturb == 'TKEL'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource )
 
 
@@ -1434,7 +1434,7 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then
 
   tzsource%cmnhname   = 'REL'
   tzsource%clongname  = 'relaxation'
-  tzsource%lavailable = ohorelax_rv .or. ove_relax
+  tzsource%lavailable = ohorelax_rv
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
   tzsource%cmnhname   = 'DCONV'
@@ -1453,7 +1453,7 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
   tzsource%cmnhname   = 'NETUR'
-  tzsource%clongname  = 'negative correction induced by turbulence'
+  tzsource%clongname  = 'negativity correction induced by turbulence'
   tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                                                 .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
@@ -1479,13 +1479,13 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
+  tzsource%clongname  = 'negativity correction induced by advection'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
+  tzsource%clongname  = 'negativity correction'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
@@ -1537,7 +1537,7 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
   tzsource%cmnhname   = 'ADJU'
-  tzsource%clongname  = 'adjustment before'
+  tzsource%clongname  = 'adjustment to saturation'
   tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE'
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
@@ -1563,7 +1563,7 @@ if ( tbudgets(NBUDGET_RV)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RV), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
+  tzsource%clongname  = 'negativity correction induced by condensation'
   tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
                           .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
                         .and. celec == 'NONE'
@@ -1662,7 +1662,7 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
   tzsource%cmnhname   = 'NETUR'
-  tzsource%clongname  = 'negative correction induced by turbulence'
+  tzsource%clongname  = 'negativity correction induced by turbulence'
   tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                                                 .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
@@ -1678,13 +1678,13 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
+  tzsource%clongname  = 'negativity correction induced by advection'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
+  tzsource%clongname  = 'negativity correction'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
@@ -1751,7 +1751,7 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
   tzsource%cmnhname   = 'ACCR'
-  tzsource%clongname  = 'accretion'
+  tzsource%clongname  = 'accretion of cloud droplets'
   tzsource%lavailable =       ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) &
                          .or.   hcloud      == 'KESS'                                                      &
                          .or. ( hcloud(1:3) == 'ICE'  .and. lwarm_ice )                                    &
@@ -1770,7 +1770,7 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
   tzsource%cmnhname   = 'IMLT'
-  tzsource%clongname  = 'ice melting'
+  tzsource%clongname  = 'melting of ice'
   tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE'
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
@@ -1840,7 +1840,7 @@ if ( tbudgets(NBUDGET_RC)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RC), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
+  tzsource%clongname  = 'negativity correction induced by condensation'
   tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
                           .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
                         .and. celec == 'NONE'
@@ -1915,7 +1915,7 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'NETUR'
-  tzsource%clongname  = 'negative correction induced by turbulence'
+  tzsource%clongname  = 'negativity correction induced by turbulence'
   tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
@@ -1930,13 +1930,13 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
+  tzsource%clongname  = 'negativity correction induced by advection'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
+  tzsource%clongname  = 'negativity correction'
   tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
@@ -1958,12 +1958,12 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'R2C1'
-  tzsource%clongname  = 'rain to cloud after sedimentation'
+  tzsource%clongname  = 'rain to cloud change after sedimentation'
   tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit .and. lwarm_lima .and. lrain_lima
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'AUTO'
-  tzsource%clongname  = 'autoconversion into rain drops'
+  tzsource%clongname  = 'autoconversion into rain'
   tzsource%lavailable =       ( hcloud      == 'LIMA' .and. ( lptsplit .or. ( lwarm_lima .and. lrain_lima ) ) ) &
                          .or.   hcloud      == 'KESS'                                                           &
                          .or. ( hcloud(1:3) == 'ICE'  .and. lwarm_ice )                                         &
@@ -1996,7 +1996,7 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then
 
 
   tzsource%cmnhname   = 'ACC'
-  tzsource%clongname  = 'accretion of rain water on aggregates'
+  tzsource%clongname  = 'accretion of rain on aggregates'
   tzsource%lavailable =      ( hcloud == 'LIMA' .and. ( lptsplit .or. (       lcold_lima .and. lwarm_lima      &
                                                                         .and. lsnow_lima .and. lrain_lima) ) ) &
                         .or.   hcloud(1:3) == 'ICE'
@@ -2008,7 +2008,7 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'CFRZ'
-  tzsource%clongname  = 'conversion freezing of rain drops'
+  tzsource%clongname  = 'conversion freezing of rain'
   tzsource%lavailable =    ( hcloud == 'LIMA' .and. ( lptsplit .or. (lcold_lima .and. lwarm_lima .and. lsnow_lima) ) ) &
                         .or. hcloud(1:3) == 'ICE'
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
@@ -2067,7 +2067,7 @@ if ( tbudgets(NBUDGET_RR)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RR), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
+  tzsource%clongname  = 'negativity correction induced by condensation'
   tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
                           .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
                         .and. celec == 'NONE'
@@ -2157,8 +2157,8 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'NETUR'
-  tzsource%clongname  = 'negative correction induced by turbulence'
-  tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'ICE3' .or. hcloud == 'ICE4' .or. hcloud == 'LIMA' )
+  tzsource%clongname  = 'negativity correction induced by turbulence'
+  tzsource%lavailable = hturb == 'TKEL' .and. ( hcloud == 'ICE3' .or. hcloud == 'ICE4' .or. hcloud == 'LIMA' )
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'VISC'
@@ -2172,15 +2172,13 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction induced by advection'
+  tzsource%lavailable =  .true.
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction'
+  tzsource%lavailable =  .true.
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'CORR'
@@ -2191,7 +2189,7 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'ADJU'
-  tzsource%clongname  = 'adjustment before on ice'
+  tzsource%clongname  = 'adjustment to saturation'
   tzsource%lavailable = hcloud(1:3) == 'ICE' .and. lred .and. ladj_before .and. celec == 'NONE'
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
@@ -2227,7 +2225,7 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'HONC'
-  tzsource%clongname  = 'droplet homogeneous nucleation'
+  tzsource%clongname  = 'droplet homogeneous freezing'
   tzsource%lavailable = hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lnucl_lima ) )
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
@@ -2252,7 +2250,7 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'IMLT'
-  tzsource%clongname  = 'ice melting'
+  tzsource%clongname  = 'melting of ice'
   tzsource%lavailable = ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima ) ) ) .or. hcloud(1:3) == 'ICE'
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
@@ -2267,7 +2265,7 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'CFRZ'
-  tzsource%clongname  = 'conversion freezing of rain drops'
+  tzsource%clongname  = 'conversion freezing of rain'
   tzsource%lavailable =    ( hcloud == 'LIMA' .and. ( lptsplit .or. ( lcold_lima .and. lwarm_lima .and. lsnow_lima ) ) ) &
                         .or. hcloud(1:3) == 'ICE'
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
@@ -2318,10 +2316,8 @@ if ( tbudgets(NBUDGET_RI)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
-  tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
-                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
-                        .and. celec == 'NONE'
+  tzsource%clongname  = 'negativity correction induced by condensation'
+  tzsource%lavailable = celec == 'NONE'
   call Budget_source_add( tbudgets(NBUDGET_RI), tzsource )
 
 
@@ -2393,7 +2389,7 @@ if ( tbudgets(NBUDGET_RS)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
 !   tzsource%cmnhname   = 'NETUR'
-!   tzsource%clongname  = 'negative correction induced by turbulence'
+!   tzsource%clongname  = 'negativity correction induced by turbulence'
 !   tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'ICE3' .or. hcloud == 'ICE4' &
 !                                   .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
 !   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource nneturrs )
@@ -2409,15 +2405,13 @@ if ( tbudgets(NBUDGET_RS)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction induced by advection'
+  tzsource%lavailable =  .true.
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
   tzsource%cmnhname   = 'CORR'
@@ -2470,7 +2464,7 @@ if ( tbudgets(NBUDGET_RS)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
   tzsource%cmnhname   = 'ACC'
-  tzsource%clongname  = 'accretion of rain water'
+  tzsource%clongname  = 'accretion of rain on snow'
   tzsource%lavailable =       ( hcloud == 'LIMA' .and. ( lptsplit .or. (       lcold_lima .and. lwarm_lima      &
                                                                          .and. lsnow_lima .and. lrain_lima) ) ) &
                          .or.   hcloud(1:3) == 'ICE'
@@ -2507,10 +2501,8 @@ if ( tbudgets(NBUDGET_RS)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
-  tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
-                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
-                        .and. celec == 'NONE'
+  tzsource%clongname  = 'negativity correction induced by condensation'
+  tzsource%lavailable = celec == 'NONE'
   call Budget_source_add( tbudgets(NBUDGET_RS), tzsource )
 
 
@@ -2582,7 +2574,7 @@ if ( tbudgets(NBUDGET_RG)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource )
 
 !   tzsource%cmnhname   = 'NETUR'
-!   tzsource%clongname  = 'negative correction induced by turbulence'
+!   tzsource%clongname  = 'negativity correction induced by turbulence'
 !   tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'ICE3' .or. hcloud == 'ICE4' &
 !                                   .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
 !   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource nneturrg )
@@ -2598,15 +2590,13 @@ if ( tbudgets(NBUDGET_RG)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction induced by advection'
+  tzsource%lavailable =  hcloud == 'ICE3' .or. hcloud == 'ICE4' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction'
+  tzsource%lavailable =  hcloud == 'ICE3' .or. hcloud == 'ICE4' .or. hcloud == 'LIMA'
   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource )
 
   tzsource%cmnhname   = 'CORR'
@@ -2643,7 +2633,7 @@ if ( tbudgets(NBUDGET_RG)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource )
 
   tzsource%cmnhname   = 'ACC'
-  tzsource%clongname  = 'rain accretion on graupel'
+  tzsource%clongname  = 'accretion of rain on graupel'
   tzsource%lavailable =      ( hcloud == 'LIMA' .and. ( lptsplit .or. (       lcold_lima .and. lwarm_lima      &
                                                                         .and. lsnow_lima .and. lrain_lima) ) ) &
                         .or.   hcloud(1:3) == 'ICE'
@@ -2712,7 +2702,7 @@ if ( tbudgets(NBUDGET_RG)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RG), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
+  tzsource%clongname  = 'negativity correction induced by condensation'
   tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
                           .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
                         .and. celec == 'NONE'
@@ -2739,7 +2729,7 @@ if ( tbudgets(NBUDGET_RH)%lenabled ) then
 
   tbudgets(NBUDGET_RH)%tsources(:)%ngroup = 0
 
-  tzsource%ccomment = 'Budget of graupel mixing ratio'
+  tzsource%ccomment = 'Budget of hail mixing ratio'
   tzsource%ngrid    = 1
 
   tzsource%cunits   = 'kg kg-1'
@@ -2787,7 +2777,7 @@ if ( tbudgets(NBUDGET_RH)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource )
 
 !   tzsource%cmnhname   = 'NETUR'
-!   tzsource%clongname  = 'negative correction induced by turbulence'
+!   tzsource%clongname  = 'negativity correction induced by turbulence'
 !   tzsource%lavailable = hturb == 'TKEL' .and. (      hcloud == 'ICE3' .or. hcloud == 'ICE4' &
 !                                   .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' )
 !   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource nneturrh )
@@ -2803,15 +2793,13 @@ if ( tbudgets(NBUDGET_RH)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource )
 
   tzsource%cmnhname   = 'NEADV'
-  tzsource%clongname  = 'negative correction induced by advection'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction induced by advection'
+  tzsource%lavailable = .true.
   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource )
 
   tzsource%cmnhname   = 'NEGA'
-  tzsource%clongname  = 'negative correction'
-  tzsource%lavailable =       hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4' &
-                         .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA'
+  tzsource%clongname  = 'negativity correction'
+  tzsource%lavailable =  .true.
   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource )
 
   tzsource%cmnhname   = 'SEDI'
@@ -2868,10 +2856,8 @@ if ( tbudgets(NBUDGET_RH)%lenabled ) then
   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource )
 
   tzsource%cmnhname   = 'NECON'
-  tzsource%clongname  = 'negative correction induced by condensation'
-  tzsource%lavailable = (      hcloud == 'KESS' .or. hcloud == 'ICE3' .or. hcloud == 'ICE4'   &
-                          .or. hcloud == 'KHKO' .or. hcloud == 'C2R2' .or. hcloud == 'LIMA' ) &
-                        .and. celec == 'NONE'
+  tzsource%clongname  = 'negativity correction induced by condensation'
+  tzsource%lavailable = celec == 'NONE'
   call Budget_source_add( tbudgets(NBUDGET_RH), tzsource )
 
 
@@ -2980,7 +2966,7 @@ SV_BUDGETS: do jsv = 1, ksv
     call Budget_source_add( tbudgets(ibudget), tzsource )
 
     tzsource%cmnhname   = 'NEGA2'
-    tzsource%clongname  = 'negative correction'
+    tzsource%clongname  = 'negativity correction'
     tzsource%lavailable = .true.
     call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -2994,22 +2980,22 @@ SV_BUDGETS: do jsv = 1, ksv
 
       ! Source terms in common for all C2R2/KHKO budgets
       tzsource%cmnhname   = 'NETUR'
-      tzsource%clongname  = 'negative correction induced by turbulence'
+      tzsource%clongname  = 'negativity correction induced by turbulence'
       tzsource%lavailable = hturb == 'TKEL'
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
       tzsource%cmnhname   = 'NEADV'
-      tzsource%clongname  = 'negative correction induced by advection'
+      tzsource%clongname  = 'negativity correction induced by advection'
       tzsource%lavailable = .true.
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
       tzsource%cmnhname   = 'NEGA'
-      tzsource%clongname  = 'negative correction'
+      tzsource%clongname  = 'negativity correction'
       tzsource%lavailable = .true.
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
       tzsource%cmnhname   = 'NECON'
-      tzsource%clongname  = 'negative correction induced by condensation'
+      tzsource%clongname  = 'negativity correction induced by condensation'
       tzsource%lavailable = .true.
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3048,7 +3034,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'ACCR'
-          tzsource%clongname  = 'accretion'
+          tzsource%clongname  = 'accretion of cloud droplets'
           tzsource%lavailable = lrain_c2r2
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3112,22 +3098,22 @@ SV_BUDGETS: do jsv = 1, ksv
       ! Source terms in common for all LIMA budgets (except supersaturation)
       if ( jsv /= nsv_lima_spro ) then
         tzsource%cmnhname   = 'NETUR'
-        tzsource%clongname  = 'negative correction induced by turbulence'
+        tzsource%clongname  = 'negativity correction induced by turbulence'
         tzsource%lavailable = hturb == 'TKEL'
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'NEADV'
-        tzsource%clongname  = 'negative correction induced by advection'
+        tzsource%clongname  = 'negativity correction induced by advection'
         tzsource%lavailable = .true.
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'NEGA'
-        tzsource%clongname  = 'negative correction'
+        tzsource%clongname  = 'negativity correction'
         tzsource%lavailable = .true.
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'NECON'
-        tzsource%clongname  = 'negative correction induced by condensation'
+        tzsource%clongname  = 'negativity correction induced by condensation'
         tzsource%lavailable = .true.
         call Budget_source_add( tbudgets(ibudget), tzsource )
       end if
@@ -3136,10 +3122,10 @@ SV_BUDGETS: do jsv = 1, ksv
       ! Source terms specific to each budget
       SV_LIMA: if ( jsv == nsv_lima_nc ) then
         ! Cloud droplets concentration
-          tzsource%cmnhname   = 'DEPOTR'
-          tzsource%clongname  = 'tree droplet deposition'
-          tzsource%lavailable = odragtree .and. odepotree
-          call Budget_source_add( tbudgets(ibudget), tzsource )
+        tzsource%cmnhname   = 'DEPOTR'
+        tzsource%clongname  = 'tree droplet deposition'
+        tzsource%lavailable = odragtree .and. odepotree
+        call Budget_source_add( tbudgets(ibudget), tzsource )
 
 !         tzsource%cmnhname   = 'CORR'
 !         tzsource%clongname  = 'correction'
@@ -3182,7 +3168,7 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'ACCR'
-        tzsource%clongname  = 'accretion'
+        tzsource%clongname  = 'accretion of cloud droplets'
         tzsource%lavailable = lptsplit .or. ( lwarm_lima  .and. lrain_lima )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3192,12 +3178,12 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'HONC'
-        tzsource%clongname  = 'droplet homogeneous nucleation'
+        tzsource%clongname  = 'droplet homogeneous freezing'
         tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima  .and. lnucl_lima )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'IMLT'
-        tzsource%clongname  = 'ice melting'
+        tzsource%clongname  = 'melting of ice'
         tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima  )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3228,7 +3214,7 @@ SV_BUDGETS: do jsv = 1, ksv
 
         tzsource%cmnhname   = 'CORR2'
         tzsource%clongname  = 'supplementary correction inside LIMA splitting'
-        tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit
+        tzsource%lavailable = lptsplit
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'CEDS'
@@ -3280,7 +3266,7 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'ACC'
-        tzsource%clongname  = 'accretion of rain water'
+        tzsource%clongname  = 'accretion of rain  on aggregates'
         tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima  .and. lsnow_lima .and. lrain_lima )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3315,13 +3301,13 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'HMLT'
-        tzsource%clongname  = 'hail melting'
+        tzsource%clongname  = 'melting of hail'
         tzsource%lavailable = .not.lptsplit .and. lhail_lima .and. lcold_lima .and. lwarm_lima  .and. lsnow_lima
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'CORR2'
         tzsource%clongname  = 'supplementary correction inside LIMA splitting'
-        tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit
+        tzsource%lavailable = lptsplit
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
 
@@ -3407,7 +3393,7 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'HONC'
-        tzsource%clongname  = 'droplet homogeneous nucleation'
+        tzsource%clongname  = 'droplet homogeneous freezing'
         tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima  .and. lnucl_lima )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3427,7 +3413,7 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'IMLT'
-        tzsource%clongname  = 'ice melting'
+        tzsource%clongname  = 'melting of ice'
         tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima  )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3468,7 +3454,7 @@ SV_BUDGETS: do jsv = 1, ksv
 
         tzsource%cmnhname   = 'CORR2'
         tzsource%clongname  = 'supplementary correction inside LIMA splitting'
-        tzsource%lavailable = hcloud == 'LIMA' .and. lptsplit
+        tzsource%lavailable = lptsplit
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
 
@@ -3504,7 +3490,7 @@ SV_BUDGETS: do jsv = 1, ksv
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
         tzsource%cmnhname   = 'IMLT'
-        tzsource%clongname  = 'ice melting'
+        tzsource%clongname  = 'melting of ice'
         tzsource%lavailable = lptsplit .or. ( lcold_lima .and. lwarm_lima )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3531,9 +3517,8 @@ SV_BUDGETS: do jsv = 1, ksv
         ! Homogeneous freezing of CCN
         tzsource%cmnhname   = 'HONH'
         tzsource%clongname  = 'haze homogeneous nucleation'
-        tzsource%lavailable = lcold_lima .and. lnucl_lima  .and.                                                     &
-                              (      ( .not.lptsplit .and. ( ( lhhoni_lima .and. nmod_ccn >= 1 ) .or. lwarm_lima ) ) &
-                                .or. (      lptsplit .and.   ( lhhoni_lima .and. nmod_ccn >= 1 )                 ) )
+        tzsource%lavailable = lcold_lima .and. lnucl_lima .and.                                             &
+                              ( ( lhhoni_lima .and. nmod_ccn >= 1 ) .or. ( .not.lptsplit .and. lwarm_lima ) )
         call Budget_source_add( tbudgets(ibudget), tzsource )
 
 
@@ -3550,7 +3535,7 @@ SV_BUDGETS: do jsv = 1, ksv
     else if ( jsv >= nsv_elecbeg .and. jsv <= nsv_elecend ) then SV_VAR
       ! Electricity case
       tzsource%cmnhname   = 'NEGA'
-      tzsource%clongname  = 'negative correction'
+      tzsource%clongname  = 'negativity correction'
       tzsource%lavailable = .true.
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3588,7 +3573,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'NEUT'
-          tzsource%clongname  = 'NEUT'
+          tzsource%clongname  = 'neutralization'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3606,7 +3591,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'ACCR'
-          tzsource%clongname  = 'accretion'
+          tzsource%clongname  = 'accretion of cloud droplets'
           tzsource%lavailable = lwarm_ice
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3636,7 +3621,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'IMLT'
-          tzsource%clongname  = 'ice melting'
+          tzsource%clongname  = 'melting of ice'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3656,7 +3641,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'NEUT'
-          tzsource%clongname  = 'NEUT'
+          tzsource%clongname  = 'neutralization'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3674,7 +3659,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'ACCR'
-          tzsource%clongname  = 'accretion'
+          tzsource%clongname  = 'accretion of cloud droplets'
           tzsource%lavailable = lwarm_ice
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3684,7 +3669,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'ACC'
-          tzsource%clongname  = 'accretion of rain water'
+          tzsource%clongname  = 'accretion of rain  on aggregates'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3724,7 +3709,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'NEUT'
-          tzsource%clongname  = 'NEUT'
+          tzsource%clongname  = 'neutralization'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3766,7 +3751,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'IMLT'
-          tzsource%clongname  = 'ice melting'
+          tzsource%clongname  = 'melting of ice'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3791,7 +3776,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'NEUT'
-          tzsource%clongname  = 'NEUT'
+          tzsource%clongname  = 'neutralization'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3819,7 +3804,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'ACC'
-          tzsource%clongname  = 'accretion of rain water'
+          tzsource%clongname  = 'accretion of rain on snow'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3854,7 +3839,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'NEUT'
-          tzsource%clongname  = 'NEUT'
+          tzsource%clongname  = 'neutralization'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3877,7 +3862,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'ACC'
-          tzsource%clongname  = 'accretion of rain water'
+          tzsource%clongname  = 'accretion of rain  on graupel'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3922,7 +3907,7 @@ SV_BUDGETS: do jsv = 1, ksv
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
           tzsource%cmnhname   = 'NEUT'
-          tzsource%clongname  = 'NEUT'
+          tzsource%clongname  = 'neutralization'
           tzsource%lavailable = .true.
           call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3951,7 +3936,7 @@ SV_BUDGETS: do jsv = 1, ksv
             call Budget_source_add( tbudgets(ibudget), tzsource )
 
             tzsource%cmnhname   = 'NEUT'
-            tzsource%clongname  = 'NEUT'
+            tzsource%clongname  = 'neutralization'
             tzsource%lavailable = .true.
             call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -3989,7 +3974,7 @@ SV_BUDGETS: do jsv = 1, ksv
             call Budget_source_add( tbudgets(ibudget), tzsource )
 
             tzsource%cmnhname   = 'NEUT'
-            tzsource%clongname  = 'NEUT'
+            tzsource%clongname  = 'neutralization'
             tzsource%lavailable = .true.
             call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -4025,7 +4010,7 @@ SV_BUDGETS: do jsv = 1, ksv
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
       tzsource%cmnhname   = 'NEGA'
-      tzsource%clongname  = 'negative correction'
+      tzsource%clongname  = 'negativity correction'
       tzsource%lavailable = .true.
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
@@ -4037,7 +4022,7 @@ SV_BUDGETS: do jsv = 1, ksv
     else if ( jsv >= nsv_aerbeg .and. jsv <= nsv_aerend ) then SV_VAR
       !Chemical aerosol case
       tzsource%cmnhname   = 'NEGA'
-      tzsource%clongname  = 'negative correction'
+      tzsource%clongname  = 'negativity correction'
       tzsource%lavailable = lorilam
       call Budget_source_add( tbudgets(ibudget), tzsource )
 
diff --git a/src/MNH/ini_seriesn.f90 b/src/MNH/ini_seriesn.f90
index dbb0030186716cf329c841a8027b1773de9dfe54..45bdbdcca4945fcc696de676559089056cc5ec4c 100644
--- a/src/MNH/ini_seriesn.f90
+++ b/src/MNH/ini_seriesn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2002-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2002-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.
@@ -43,7 +43,7 @@
 !  P. Wautelet 10/04/2019: replace ABORT and STOP calls by Print_msg
 !  P. Wautelet 12/04/2019: use standard measurement units
 !  P. Wautelet 13/09/2019: budget: simplify and modernize date/time management
-!
+!  P. Wautelet 05/05/2021: add CSMASK1/2/3 variables
 !-------------------------------------------------------------------------------
 !
 !*    0. Declaration
@@ -88,6 +88,7 @@ INTEGER :: IIDIM1 ! I size of the slice
 INTEGER :: JJ,JI ! loop indices
 INTEGER :: ISB1,ISB2,ISB3
 INTEGER :: ISER
+CHARACTER (LEN=4), DIMENSION(3) :: YMASK
 CHARACTER (LEN=5), DIMENSION(3) :: YSUF
 INTEGER  :: ILUOUT ! Logical unit number for output-listing
 INTEGER  :: IRESP   ! Return code of FM-routines
@@ -258,6 +259,9 @@ ALLOCATE( CSTITLE3   (NSTEMP_SERIE3) )
 ALLOCATE( CSUNIT1    (NSTEMP_SERIE1) )
 ALLOCATE( CSUNIT2    (NSTEMP_SERIE2) )
 ALLOCATE( CSUNIT3    (NSTEMP_SERIE3) )
+ALLOCATE( CSMASK1    (NSTEMP_SERIE1) )
+ALLOCATE( CSMASK2    (NSTEMP_SERIE2) )
+! ALLOCATE( CSMASK3    (NSTEMP_SERIE3) )
 ALLOCATE( NSGRIDD1   (NSTEMP_SERIE1) )
 ALLOCATE( NSGRIDD2   (NSTEMP_SERIE2) )
 ALLOCATE( NSGRIDD3   (NSTEMP_SERIE3) )
@@ -304,6 +308,10 @@ IF (LMASKLANDSEA) ISER=3
 YSUF(1)='-GLOB'
 YSUF(2)='-LAND'
 YSUF(3)='-SEA '
+
+YMASK(1) = 'GLOB'
+YMASK(2) = 'LAND'
+YMASK(3) = 'SEA'
 !
 !*       2.1   Temporal series t
 !              -----------------
@@ -319,38 +327,38 @@ ISB1=0
 DO JI=1,ISER
   ! total surface explicit precipitations
   IF (SIZE(XINPRR)/=0) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='INPRT'//YSUF(JI) ; CSUNIT1(ISB1)='mm day-1'
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='ACPRT'//YSUF(JI) ; CSUNIT1(ISB1)='mm'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='INPRT'//YSUF(JI) ; CSUNIT1(ISB1)='mm day-1' ; CSMASK1(ISB1) = YMASK(JI)
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='ACPRT'//YSUF(JI) ; CSUNIT1(ISB1)='mm'       ; CSMASK1(ISB1) = YMASK(JI)
   END IF
   ! Mixing ratios
   IF (LUSERV) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RVT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RVT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   END IF
   IF (LUSERC) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RCT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RCT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   END IF
   IF (LUSERR) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RRT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RRT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   ENDIF
   IF (LUSERI) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RIT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RIT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   END IF
   IF (LUSERS) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RST'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RST'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   END IF
   IF (LUSERG) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RGT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RGT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   END IF
   IF (LUSERH) THEN
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RHT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='RHT'//YSUF(JI) ; CSUNIT1(ISB1)='kg m-2'     ; CSMASK1(ISB1) = YMASK(JI)
   END IF
 ! SURFACE FIELDS
   IF (LSURF) THEN
-     ISB1=ISB1+1 ; CSTITLE1(ISB1)='TS_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='K'
-     ISB1=ISB1+1 ; CSTITLE1(ISB1)='T_MNW_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='K'
-     ISB1=ISB1+1 ; CSTITLE1(ISB1)='T_BOT_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='K'
-     ISB1=ISB1+1 ; CSTITLE1(ISB1)='CT_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='1'
-     ISB1=ISB1+1 ; CSTITLE1(ISB1)='HML_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='m'
+     ISB1=ISB1+1 ; CSTITLE1(ISB1)='TS_WATER'//YSUF(JI) ;    CSUNIT1(ISB1)='K' ; CSMASK1(ISB1) = YMASK(JI)
+     ISB1=ISB1+1 ; CSTITLE1(ISB1)='T_MNW_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='K' ; CSMASK1(ISB1) = YMASK(JI)
+     ISB1=ISB1+1 ; CSTITLE1(ISB1)='T_BOT_WATER'//YSUF(JI) ; CSUNIT1(ISB1)='K' ; CSMASK1(ISB1) = YMASK(JI)
+     ISB1=ISB1+1 ; CSTITLE1(ISB1)='CT_WATER'//YSUF(JI) ;    CSUNIT1(ISB1)='1' ; CSMASK1(ISB1) = YMASK(JI)
+     ISB1=ISB1+1 ; CSTITLE1(ISB1)='HML_WATER'//YSUF(JI) ;   CSUNIT1(ISB1)='m' ; CSMASK1(ISB1) = YMASK(JI)
   ENDIF
   ! end SURFACE FIELDS
 END DO
@@ -358,9 +366,9 @@ END DO
 IF (LWMINMAX) THEN
     DO JI=1,ISER
     ! Max of vertical speed
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='WMAX'//YSUF(JI) ; CSUNIT1(ISB1)='m s-1' ; NSGRIDD1(ISB1)=4
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='WMAX'//YSUF(JI) ; CSUNIT1(ISB1)='m s-1' ; NSGRIDD1(ISB1)=4 ; CSMASK1(ISB1) = YMASK(JI)
     ! Min of vertical speed
-    ISB1=ISB1+1 ; CSTITLE1(ISB1)='WMIN'//YSUF(JI) ; CSUNIT1(ISB1)='m s-1' ; NSGRIDD1(ISB1)=4
+    ISB1=ISB1+1 ; CSTITLE1(ISB1)='WMIN'//YSUF(JI) ; CSUNIT1(ISB1)='m s-1' ; NSGRIDD1(ISB1)=4 ; CSMASK1(ISB1) = YMASK(JI)
   END DO
 END IF
 !
@@ -384,29 +392,29 @@ NSGRIDD2(:)=1
 ISB2=0
 DO JI=1,ISER
   ! Vertical velocity
-  ISB2=ISB2+1 ; CSTITLE2(ISB2)='WT'//YSUF(JI) ; CSUNIT2(ISB2)='m s-1' ; NSGRIDD2(ISB2)=4
+  ISB2=ISB2+1 ; CSTITLE2(ISB2)='WT'//YSUF(JI) ; CSUNIT2(ISB2)='m s-1'      ; CSMASK2(ISB2) = YMASK(JI) ; NSGRIDD2(ISB2)=4
   ! Potential temperature
-  ISB2=ISB2+1 ; CSTITLE2(ISB2)='THT'//YSUF(JI) ; CSUNIT2(ISB2)='K'
+  ISB2=ISB2+1 ; CSTITLE2(ISB2)='THT'//YSUF(JI) ; CSUNIT2(ISB2)='K'         ; CSMASK2(ISB2) = YMASK(JI)
   ! Pressure
-  ISB2=ISB2+1 ; CSTITLE2(ISB2)='PABST'//YSUF(JI) ; CSUNIT2(ISB2)='Pa'
+  ISB2=ISB2+1 ; CSTITLE2(ISB2)='PABST'//YSUF(JI) ; CSUNIT2(ISB2)='Pa'      ; CSMASK2(ISB2) = YMASK(JI)
   ! Mixing ratios
   IF (LUSERV) THEN
-    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RVT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1'
+    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RVT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1' ; CSMASK2(ISB2) = YMASK(JI)
   END IF
   IF (LUSERC) THEN
-    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RCT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1'
+    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RCT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1' ; CSMASK2(ISB2) = YMASK(JI)
   END IF
   IF (LUSERR) THEN
-    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RRT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1'
+    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RRT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1' ; CSMASK2(ISB2) = YMASK(JI)
   END IF
   IF (LUSERI) THEN
-    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RIT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1'
+    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RIT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1' ; CSMASK2(ISB2) = YMASK(JI)
   END IF
   IF (LUSERS) THEN
-    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RST'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1'
+    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RST'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1' ; CSMASK2(ISB2) = YMASK(JI)
   END IF
   IF (LUSERG) THEN
-    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RGT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1'
+    ISB2=ISB2+1 ; CSTITLE2(ISB2)='RGT'//YSUF(JI) ; CSUNIT2(ISB2)='kg kg-1' ; CSMASK2(ISB2) = YMASK(JI)
   END IF
 END DO
 !
diff --git a/src/MNH/lesn.f90 b/src/MNH/lesn.f90
index aca09170f137177acc0c2a77d5394c067a7f302d..129929246495bee84d57526e482a17fc9b4e52b7 100644
--- a/src/MNH/lesn.f90
+++ b/src/MNH/lesn.f90
@@ -1,4 +1,4 @@
-!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.
@@ -1250,6 +1250,7 @@ LOGICAL, DIMENSION(:,:,:),   INTENT(IN) :: OMASK     ! 2D mask for computations
 !       0.2  declaration of local variables
 !
 INTEGER :: JSV      ! scalar variables counter
+INTEGER :: JI
 INTEGER :: JK       ! vertical loop counter
 INTEGER :: JPDF     ! pdf counter
 !
diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90
index 44a3cfff0e0cdd4c5a930be3631aadba593c9ef9..7442dfd3e0184598cd4ee7687456a5e31b900e5b 100644
--- a/src/MNH/modd_budget.f90
+++ b/src/MNH/modd_budget.f90
@@ -78,6 +78,27 @@ integer, parameter :: NBUDGET_RG  = 11 ! Reference number for budget of RhoJrg a
 integer, parameter :: NBUDGET_RH  = 12 ! Reference number for budget of RhoJrh and/or LES budgets with rh
 integer, parameter :: NBUDGET_SV1 = 13 ! Reference number for 1st budget of RhoJsv and/or LES budgets with sv
 
+integer, parameter :: NMAXLEVELS       = 7
+integer, parameter :: NLVL_ROOT        = 0
+integer, parameter :: NLVL_CATEGORY    = 1
+integer, parameter :: NLVL_SUBCATEGORY = 2
+integer, parameter :: NLVL_GROUP       = 3
+integer, parameter :: NLVL_SHAPE       = 4
+integer, parameter :: NLVL_TIMEAVG     = 5
+integer, parameter :: NLVL_NORM        = 6
+integer, parameter :: NLVL_MASK        = 7
+
+#ifdef MNH_IOCDF4
+character(len=*), dimension(NMAXLEVELS), parameter :: CNCGROUPNAMES = [ &
+                                         'category   ', &  !Name of the different type of groups/levels in the netCDF file
+                                         'subcategory', &
+                                         'group      ', &
+                                         'shape      ', &
+                                         'timeavg    ', &
+                                         'norm       ', &
+                                         'mask       '  ]
+#endif
+
 integer :: nbudgets ! Number of budget categories
 
 
@@ -104,16 +125,16 @@ type, extends( tfield_metadata_base ) :: tburhodata
 end type tburhodata
 
 type :: tbudiachrometadata
-  character(len=NBUNAMELGTMAX)  :: cgroupname  = 'not set'
-  character(len=NBUNAMELGTMAX)  :: cname       = 'not set'
-  character(len=NCOMMENTLGTMAX) :: ccomment    = 'not set'
-  character(len=NBUNAMELGTMAX)  :: ctype       = 'not set'
-  character(len=NBUNAMELGTMAX)  :: ccategory   = 'not set' !budget, LES, aircraft, balloon, series, station, profiler
-  character(len=NBUNAMELGTMAX)  :: cshape      = 'not set' !Shape of the domain (mask, cartesian, vertical profile, point)
-  logical :: lmobile    = .false.                          !Is the domain moving? (ie for aircrafts and balloons)
+  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
+  character(len=1)              :: cdirection   = ''                    !Used for 2pt correlation and spectrum
+  logical :: lmobile    = .false.                                       !Is the domain moving? (ie for aircrafts and balloons)
   logical :: licompress = .false.
   logical :: ljcompress = .false.
   logical :: lkcompress = .false.
+  logical :: ltcompress = .false. ! true if values are time averaged (can be on multiple time periods)
+  logical :: lnorm      = .false. ! true if values are normalized
+  logical, dimension(NMAXLEVELS) :: lleveluse = .false.
   integer :: nil = -1 !Cartesian box boundaries in physical domain coordinates
   integer :: nih = -1
   integer :: njl = -1
diff --git a/src/MNH/modd_seriesn.f90 b/src/MNH/modd_seriesn.f90
index 03ab9f206df8701771193cbe8960cec8394ee320..b407ae675e0c28458fbc50ca03bcce61e273d138 100644
--- a/src/MNH/modd_seriesn.f90
+++ b/src/MNH/modd_seriesn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1998-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1998-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.
@@ -33,6 +33,7 @@
 !!                Oct. 10,1998 (Lafore) adaptation of Diagnostics 
 !!                                      to the sequential nesting version
 !  P. Wautelet 13/09/2019: budget: simplify and modernize date/time management
+!  P. Wautelet 05/05/2021: add CSMASK1/2/3 variables
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
@@ -79,6 +80,9 @@ TYPE SERIES_t
 !     associated with the 1st group
   CHARACTER(LEN=100),DIMENSION(:),POINTER :: CSUNIT2=>NULL() ! with the 2nd
   CHARACTER(LEN=100),DIMENSION(:),POINTER :: CSUNIT3=>NULL() ! with the 3rd
+  CHARACTER(LEN=4),  DIMENSION(:),POINTER :: CSMASK1=>NULL()
+  CHARACTER(LEN=4),  DIMENSION(:),POINTER :: CSMASK2=>NULL()
+!   CHARACTER(LEN=4),  DIMENSION(:),POINTER :: CSMASK3=>NULL()
   INTEGER       , DIMENSION(:)  ,POINTER :: NSGRIDD1=>NULL() !grid indicator for the 1st serie
   INTEGER       , DIMENSION(:)  ,POINTER :: NSGRIDD2=>NULL() ! for the  2nd 
   INTEGER       , DIMENSION(:)  ,POINTER :: NSGRIDD3=>NULL() ! for the 3rd 
@@ -135,6 +139,9 @@ CHARACTER(LEN=100),DIMENSION(:),POINTER :: CSTITLE3=>NULL()
 CHARACTER(LEN=100),DIMENSION(:),POINTER :: CSUNIT1=>NULL()
 CHARACTER(LEN=100),DIMENSION(:),POINTER :: CSUNIT2=>NULL()
 CHARACTER(LEN=100),DIMENSION(:),POINTER :: CSUNIT3=>NULL()
+CHARACTER(LEN=4),  DIMENSION(:),POINTER :: CSMASK1=>NULL()
+CHARACTER(LEN=4),  DIMENSION(:),POINTER :: CSMASK2=>NULL()
+! CHARACTER(LEN=4),  DIMENSION(:),POINTER :: CSMASK3=>NULL()
 INTEGER       , DIMENSION(:)  ,POINTER :: NSGRIDD1=>NULL()
 INTEGER       , DIMENSION(:)  ,POINTER :: NSGRIDD2=>NULL()
 INTEGER       , DIMENSION(:)  ,POINTER :: NSGRIDD3=>NULL()
@@ -181,6 +188,9 @@ SERIES_MODEL(KFROM)%CSTITLE3=>CSTITLE3
 SERIES_MODEL(KFROM)%CSUNIT1=>CSUNIT1
 SERIES_MODEL(KFROM)%CSUNIT2=>CSUNIT2
 SERIES_MODEL(KFROM)%CSUNIT3=>CSUNIT3
+SERIES_MODEL(KFROM)%CSMASK1=>CSMASK1
+SERIES_MODEL(KFROM)%CSMASK2=>CSMASK2
+! SERIES_MODEL(KFROM)%CSMASK3=>CSMASK3
 SERIES_MODEL(KFROM)%NSGRIDD1=>NSGRIDD1
 SERIES_MODEL(KFROM)%NSGRIDD2=>NSGRIDD2
 SERIES_MODEL(KFROM)%NSGRIDD3=>NSGRIDD3
@@ -220,6 +230,9 @@ CSTITLE3=>SERIES_MODEL(KTO)%CSTITLE3
 CSUNIT1=>SERIES_MODEL(KTO)%CSUNIT1
 CSUNIT2=>SERIES_MODEL(KTO)%CSUNIT2
 CSUNIT3=>SERIES_MODEL(KTO)%CSUNIT3
+CSMASK1=>SERIES_MODEL(KTO)%CSMASK1
+CSMASK2=>SERIES_MODEL(KTO)%CSMASK2
+! CSMASK3=>SERIES_MODEL(KTO)%CSMASK3
 NSGRIDD1=>SERIES_MODEL(KTO)%NSGRIDD1
 NSGRIDD2=>SERIES_MODEL(KTO)%NSGRIDD2
 NSGRIDD3=>SERIES_MODEL(KTO)%NSGRIDD3
diff --git a/src/MNH/mode_les_diachro.f90 b/src/MNH/mode_les_diachro.f90
index 27764a382b7ad500d65dfde90516e50bcbb897df..1aeec63c152b37e0cd52545de59ca5bbbccd8b5a 100644
--- a/src/MNH/mode_les_diachro.f90
+++ b/src/MNH/mode_les_diachro.f90
@@ -17,7 +17,8 @@
 MODULE MODE_LES_DIACHRO
 !#######################
 
-use modd_budget, only: tbudiachrometadata
+use modd_budget, only: NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK, &
+                       tbudiachrometadata
 use modd_les_n,  only: tles_dates, xles_times
 use modd_lunit
 
@@ -748,9 +749,9 @@ end if
 
 end subroutine Les_diachro_2D
 
-!##################################################################################
-subroutine Les_diachro_3D( tpdiafile, tpfield, odoavg, odonorm, pfield, hsuffixes )
-!##################################################################################
+!##########################################################################################
+subroutine Les_diachro_3D( tpdiafile, tpfield, odoavg, odonorm, pfield, hsuffixes, hmasks )
+!##########################################################################################
 
 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,        &
@@ -763,6 +764,7 @@ logical,                                   intent(in) :: odoavg     ! Compute an
 logical,                                   intent(in) :: odonorm    ! Compute and store normalized field
 real,                    dimension(:,:,:), intent(in) :: pfield     ! Data array
 character(len=*),        dimension(:),     optional, intent(in) :: hsuffixes
+character(len=*),        dimension(:),     optional, intent(in) :: hmasks
 
 type(tfield_metadata_base) :: tzfield
 
@@ -779,9 +781,23 @@ if ( Any( tzfield%ndimlist(4:) /= NMNHDIM_UNUSED ) ) then
   tzfield%ndimlist(4:) = NMNHDIM_UNUSED
 end if
 
-if (         tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL                                                 &
-     .and.   tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME                                                  &
-     .and. ( tzfield%ndimlist(3) == NMNHDIM_BUDGET_LES_MASK .or.tzfield%ndimlist(3) == NMNHDIM_BUDGET_TERM ) ) then
+if (       tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL &
+     .and. tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME  &
+     .and. tzfield%ndimlist(3) == NMNHDIM_BUDGET_LES_MASK  ) then
+  if ( .not. Present( hmasks ) ) &
+    call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_3D', &
+                    'optional dummy argument hmasks is needed for tpfield (' // Trim( tzfield%cmnhname ) // ')' )
+
+  if ( Size( hmasks ) /= Size( pfield, 3) ) &
+    call Print_msg( NVERB_FATAL, 'IO', 'Les_diachro_3D', 'wrong size for hmasks (' // Trim( tzfield%cmnhname ) // ')' )
+
+  tzfield%ndimlist(4) = NMNHDIM_UNUSED
+  call Les_diachro_common( tpdiafile, tzfield,                                                                &
+                           reshape( pfield, [ size( pfield, 1 ), size( pfield, 2 ), size( pfield, 3 ), 1 ] ), &
+                           odoavg, odonorm, hmasks = hmasks )
+else if (       tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL &
+          .and. tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME  &
+          .and. tzfield%ndimlist(3) == NMNHDIM_BUDGET_TERM      ) then
   if ( .not. Present( hsuffixes ) ) &
     call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_3D', &
                     'optional dummy argument hsuffixes is needed for tpfield (' // Trim( tzfield%cmnhname ) // ')' )
@@ -792,7 +808,7 @@ if (         tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL
   tzfield%ndimlist(4) = NMNHDIM_UNUSED
   call Les_diachro_common( tpdiafile, tzfield,                                                                &
                            reshape( pfield, [ size( pfield, 1 ), size( pfield, 2 ), size( pfield, 3 ), 1 ] ), &
-                           odoavg, odonorm, hsuffixes )
+                           odoavg, odonorm, hsuffixes = hsuffixes )
 else if (       tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL &
           .and. tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME  &
           .and. tzfield%ndimlist(3) == NMNHDIM_BUDGET_LES_SV    ) then
@@ -800,6 +816,10 @@ else if (       tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL &
     call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_3D', &
                     'optional dummy argument hsuffixes is not needed for tpfield (' // Trim( tzfield%cmnhname ) // ')' )
 
+  if ( Present( hmasks ) ) &
+    call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_3D', &
+                    'optional dummy argument hmasks is not needed for tpfield (' // Trim( tzfield%cmnhname ) // ')' )
+
   tzfield%ndimlist(4) = tzfield%ndimlist(3)
   tzfield%ndimlist(3) = NMNHDIM_UNUSED
   call Les_diachro_common( tpdiafile, tzfield,                                                                &
@@ -812,9 +832,9 @@ end if
 
 end subroutine Les_diachro_3D
 
-!##################################################################################
-subroutine Les_diachro_4D( tpdiafile, tpfield, odoavg, odonorm, pfield, hsuffixes )
-!##################################################################################
+!##########################################################################################
+subroutine Les_diachro_4D( tpdiafile, tpfield, odoavg, odonorm, pfield, hsuffixes, hmasks )
+!##########################################################################################
 
 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,        &
@@ -827,6 +847,7 @@ logical,                                     intent(in) :: odoavg     ! Compute
 logical,                                     intent(in) :: odonorm    ! Compute and store normalized field
 real,                    dimension(:,:,:,:), intent(in) :: pfield     ! Data array
 character(len=*),        dimension(:),     optional, intent(in) :: hsuffixes
+character(len=*),        dimension(:),     optional, intent(in) :: hmasks
 
 type(tfield_metadata_base) :: tzfield
 
@@ -843,10 +864,22 @@ if ( Any( tzfield%ndimlist(5:) /= NMNHDIM_UNUSED ) ) then
   tzfield%ndimlist(5:) = NMNHDIM_UNUSED
 end if
 
-if (         tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL                                                 &
-     .and.   tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME                                                  &
-     .and. ( tzfield%ndimlist(3) == NMNHDIM_BUDGET_LES_MASK .or.tzfield%ndimlist(3) == NMNHDIM_BUDGET_TERM ) &
-     .and.   tzfield%ndimlist(4) == NMNHDIM_BUDGET_LES_SV                                                    ) then
+if (       tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL&
+     .and. tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME &
+     .and. tzfield%ndimlist(3) == NMNHDIM_BUDGET_LES_MASK &
+     .and. tzfield%ndimlist(4) == NMNHDIM_BUDGET_LES_SV   ) then
+  if ( .not. Present( hmasks ) ) &
+    call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_4D', &
+                    'optional dummy argument hmasks is needed for tpfield (' // Trim( tzfield%cmnhname ) // ')' )
+
+  if ( Size( hmasks ) /= Size( pfield, 3) ) &
+    call Print_msg( NVERB_FATAL, 'IO', 'Les_diachro_4D', 'wrong size for hmasks (' // Trim( tzfield%cmnhname ) // ')' )
+
+  call Les_diachro_common( tpdiafile, tzfield, pfield, odoavg, odonorm, hmasks = hmasks )
+else if (       tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL &
+          .and. tzfield%ndimlist(2) == NMNHDIM_BUDGET_LES_TIME  &
+          .and. tzfield%ndimlist(3) == NMNHDIM_BUDGET_TERM      &
+          .and. tzfield%ndimlist(4) == NMNHDIM_BUDGET_LES_SV    ) then
   if ( .not. Present( hsuffixes ) ) &
     call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_4D', &
                     'optional dummy argument hsuffixes is needed for tpfield (' // Trim( tzfield%cmnhname ) // ')' )
@@ -854,7 +887,7 @@ if (         tzfield%ndimlist(1) == NMNHDIM_BUDGET_LES_LEVEL
   if ( Size( hsuffixes ) /= Size( pfield, 3) ) &
     call Print_msg( NVERB_FATAL, 'IO', 'Les_diachro_4D', 'wrong size for hsuffixes (' // Trim( tzfield%cmnhname ) // ')' )
 
-  call Les_diachro_common( tpdiafile, tzfield, pfield, odoavg, odonorm, hsuffixes )
+  call Les_diachro_common( tpdiafile, tzfield, pfield, odoavg, odonorm, hsuffixes= hsuffixes )
 else
   call Print_msg( NVERB_ERROR, 'IO', 'Les_diachro_4D', &
                   'ndimlist configuration not yet implemented for ' // Trim( tzfield%cmnhname ) )
@@ -862,9 +895,9 @@ end if
 
 end subroutine Les_diachro_4D
 
-!#######################################################################################
-subroutine Les_diachro_common( tpdiafile, tpfield, pfield, odoavg, odonorm, hsuffixes )
-!#######################################################################################
+!##############################################################################################
+subroutine Les_diachro_common( tpdiafile, tpfield, pfield, odoavg, odonorm, hsuffixes, hmasks )
+!##############################################################################################
 
 use modd_field,         only: tfield_metadata_base
 use modd_io,            only: tfiledata
@@ -881,14 +914,14 @@ real,                       dimension(:,:,:,:),           intent(in) :: pfield
 logical,                                                  intent(in) :: odoavg    ! Compute and store time average
 logical,                                                  intent(in) :: odonorm   ! Compute and store normalized field
 character(len=*),           dimension(:),       optional, intent(in) :: hsuffixes
+character(len=*),           dimension(:),       optional, intent(in) :: hmasks
 
 character(len=100),         dimension(:),     allocatable :: ycomment                      ! Comment string
 character(len=100),         dimension(:),     allocatable :: ytitle                        ! Title
-integer                                                   :: iavg
 integer                                                   :: iles_k                        ! Number of vertical levels
 integer                                                   :: iil, iih, ijl, ijh, ikl, ikh  ! Cartesian area relatively to the
                                                                                            ! entire domain
-integer                                                   :: jk                            ! Vertical loop counter
+integer                                                   :: jp                            ! Process loop counter
 real,                       dimension(:,:,:), allocatable :: ztrajz                        ! x and y are not used for LES
 type(tfield_metadata_base), dimension(:),     allocatable :: tzfields
 !------------------------------------------------------------------------------
@@ -909,9 +942,18 @@ ikl = nles_levels(1)
 ikh = nles_levels(iles_k)
 
 if ( Present( hsuffixes ) ) then
+  if ( Present( hmasks ) ) &
+    call Print_msg( NVERB_FATAL, 'IO', 'Les_diachro_common', 'hsuffixes and hmasks optional arguments may not be present ' // &
+                    'at the same time (' // Trim( tpfield%cmnhname ) // ')' )
   if ( Size( hsuffixes ) /= Size( pfield, 3) ) &
     call Print_msg( NVERB_FATAL, 'IO', 'Les_diachro_common', 'wrong size for hsuffixes (' // Trim( tpfield%cmnhname ) // ')' )
-  ycomment(:) = Trim( tpfield%ccomment(:) ) // hsuffixes(:)
+  ycomment(:) = Trim( tpfield%ccomment(:) ) // ' ' // hsuffixes(:)
+else if ( Present( hmasks ) ) then
+  if ( Size( hmasks ) /= Size( pfield, 3) ) &
+    call Print_msg( NVERB_FATAL, 'IO', 'Les_diachro_common', 'wrong size for hmasks (' // Trim( tpfield%cmnhname ) // ')' )
+  do jp = 1, Size( ycomment )
+    ycomment(jp) = Trim( tpfield%ccomment(:) ) // ' (' // Trim( hmasks(jp) ) // ')'
+  end do
 else
   ycomment(:) = tpfield%ccomment(:)
 end if
@@ -927,7 +969,8 @@ contains
 subroutine Les_diachro_common_intern( oavg, onorm )
 !#######################################################################################
 
-use modd_field,         only: NMNHDIM_BUDGET_LES_TIME, NMNHDIM_BUDGET_LES_AVG_TIME, NMNHDIM_BUDGET_LES_SV, NMNHDIM_UNUSED
+use modd_field,         only: NMNHDIM_BUDGET_LES_TIME, NMNHDIM_BUDGET_LES_AVG_TIME, NMNHDIM_BUDGET_LES_MASK, &
+                              NMNHDIM_BUDGET_LES_SV, NMNHDIM_UNUSED
 use modd_les,           only: nles_current_times
 
 use mode_write_diachro, only: Write_diachro
@@ -935,9 +978,9 @@ use mode_write_diachro, only: Write_diachro
 logical, intent(in) :: oavg
 logical, intent(in) :: onorm
 
-character(len=10)                                    :: ygroup  ! Group title
 integer                                              :: iresp   ! Return code
 integer                                              :: ji
+integer                                              :: jk      ! Vertical loop counter
 integer                                              :: jp      ! Process loop counter
 integer                                              :: jsv     ! Scalar loop counter
 logical                                              :: gsv
@@ -970,32 +1013,14 @@ else
   zfield(:, :, :, :) = pfield(:, :, :, :)
 end if
 
-! Time average
+! Time average (physical units remain unchanged)
 iresp = 0
 if ( oavg ) call Les_time_avg_4d( zfield, tzdates, iresp )
 
-if ( oavg ) then
-  if ( onorm ) then
-    ygroup = 'H_' // tpfield%cmnhname
-    tzbudiachro%ccomment = Trim( tpfield%ccomment ) // ' (normalized and time averaged)'
-  else
-    ygroup = 'A_' // tpfield%cmnhname
-    tzbudiachro%ccomment = Trim( tpfield%ccomment ) // ' (time averaged)'
-  end if
-else
-  if ( onorm ) then
-    ygroup = 'E_' // tpfield%cmnhname
-    tzbudiachro%ccomment = Trim( tpfield%ccomment ) // ' (normalized)'
-  else
-    ygroup = tpfield%cmnhname
-    tzbudiachro%ccomment = Trim( tpfield%ccomment )
-  end if
-endif
-
 if ( Present( hsuffixes ) ) then
-  ytitle(:) = ygroup // hsuffixes(:)
+  ytitle(:) = Trim( tpfield%cmnhname ) // '_' // hsuffixes(:)
 else
-  ytitle(:) = ygroup
+  ytitle(:) = tpfield%cmnhname
 endif
 
 ! Write the profile
@@ -1024,25 +1049,91 @@ if ( iresp == 0 .and. any( zfield /= XUNDEF ) ) then
   tzfields(:)%clongname = ytitle(:)
   tzfields(:)%ccomment  = ycomment(:)
 
-  tzbudiachro%cgroupname = ygroup
-  tzbudiachro%cname      = ygroup
-  !tzbudiachro%ccomment   = DONE BEFORE
-!   tzbudiachro%ctype      = 'SSOL'
-  tzbudiachro%ctype      = 'TLES' !T for trajectory (used in Write_diachro_lfi to add trajectory terms)
-  tzbudiachro%ccategory  = 'LES'
-  tzbudiachro%cshape     = 'cartesian'
+  tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+  tzbudiachro%clevels  (NLVL_CATEGORY)    = 'LES_budgets'
+  tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different LES budgets'
+
+  tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+  tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+  tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+  tzbudiachro%lleveluse(NLVL_GROUP)       = .false.
+  tzbudiachro%clevels  (NLVL_GROUP)       = ''
+  tzbudiachro%ccomments(NLVL_GROUP)       = ''
+
+  tzbudiachro%lleveluse(NLVL_SHAPE)       = .true.
+  tzbudiachro%clevels  (NLVL_SHAPE)       = 'Cartesian'
+  tzbudiachro%ccomments(NLVL_SHAPE)       = 'Cartesian domain'
+
+  tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .true.
+  if ( oavg ) then
+    tzbudiachro%clevels  (NLVL_TIMEAVG)   = 'Time_averaged'
+    tzbudiachro%ccomments(NLVL_TIMEAVG)   = 'Values are time averaged'
+  else
+    tzbudiachro%clevels  (NLVL_TIMEAVG)   = 'Not_time_averaged'
+    tzbudiachro%ccomments(NLVL_TIMEAVG)   = 'Values are not time averaged'
+  end if
+
+  tzbudiachro%lleveluse(NLVL_NORM)        = .true.
+  if ( onorm ) then
+    tzbudiachro%clevels  (NLVL_NORM)      = 'Normalized'
+    !Type of normalization is stored in the attribute "normalization" in Write_diachro
+    tzbudiachro%ccomments(NLVL_NORM)      = 'Values are normalized'
+  else
+    tzbudiachro%clevels  (NLVL_NORM)      = 'Not_normalized'
+    tzbudiachro%ccomments(NLVL_NORM)      = 'Values are not normalized'
+  end if
+
+  !lleveluse true also if no mask dimension to allow all fields to be in the same level/place in the file
+  !(especially if the 2 situation arise in the run)
+  tzbudiachro%lleveluse(NLVL_MASK)        = .true.
+  if ( tzfields(1)%ndimlist(6) == NMNHDIM_BUDGET_LES_MASK ) then
+!     tzbudiachro%clevels  (NLVL_MASK)        = DONE AFTER
+!     tzbudiachro%ccomments(NLVL_MASK)        = DONE AFTER
+  else
+    tzbudiachro%clevels  (NLVL_MASK)        = ''
+    tzbudiachro%ccomments(NLVL_MASK)        = ''
+  end if
+
   tzbudiachro%lmobile    = .false.
-  tzbudiachro%licompress = .false.
-  tzbudiachro%ljcompress = .false.
+  tzbudiachro%licompress = .true.
+  tzbudiachro%ljcompress = .true.
   tzbudiachro%lkcompress = .false.
+  tzbudiachro%ltcompress = oavg
+  tzbudiachro%lnorm      = onorm
   tzbudiachro%nil        = iil
   tzbudiachro%nih        = iih
   tzbudiachro%njl        = ijl
   tzbudiachro%njh        = ijh
+  !nkl and nkh values have no real meaning here except if all levels from ikl to ikh are used (and are correctly ordered)
+  !and if xles_altitudes is not used
+  !These values are not written in the netCDF files
+  !These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
   tzbudiachro%nkl        = ikl
   tzbudiachro%nkh        = ikh
 
-  call Write_diachro( tpdiafile, tzbudiachro, tzfields, tzdates, zwork6 )
+  if ( tzfields(1)%ndimlist(6) == NMNHDIM_BUDGET_LES_MASK ) then
+    tzfields(:)%ndimlist(6) = NMNHDIM_UNUSED
+
+    ! Loop on the different masks
+    ! Do not provide all tzfields once because they can be stored in different HDF groups (based on masks)
+    do jp = 1, Size( hmasks )
+      tzfields(jp)%clongname = Trim( ytitle(jp) ) // ' (' // Trim( hmasks(jp) ) // ')'
+      tzfields(jp)%ndims     = tzfields(jp)%ndims - 1
+
+      tzbudiachro%clevels(NLVL_MASK) = hmasks(jp)
+      tzbudiachro%ccomments(NLVL_MASK) = ''
+
+      call Write_diachro( tpdiafile, tzbudiachro, [ tzfields(jp) ], tzdates, zwork6(:,:,:,:,:,jp:jp) )
+    end do
+  else
+    !Set to the same value ('cart') than for the fields with no mask in Write_les_n
+    !to put the fields in the same position of the netCDF file
+    tzbudiachro%clevels(NLVL_MASK) = 'cart'
+
+    call Write_diachro( tpdiafile, tzbudiachro, tzfields, tzdates, zwork6 )
+  end if
+
 end if
 
 !-------------------------------------------------------------------------------
@@ -1128,6 +1219,11 @@ type(tfield_metadata_base)                           :: tzfield
 allocate( tzdates( NLES_CURRENT_TIMES ) )
 tzdates(:) = tles_dates(:)
 
+iil = nles_current_iinf
+iih = nles_current_isup
+ijl = nles_current_jinf
+ijh = nles_current_jsup
+
 ikl = 1
 ikh = nspectra_k
 
@@ -1137,11 +1233,6 @@ tzfield = tpfield
 if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NI ) then
   Allocate( zwork6(Size( pfield, 1 ), 1, nspectra_k, nles_current_times, 1, 1) )
 
-  iil = nles_current_iinf
-  iih = nles_current_isup
-  ijl = 1
-  ijh = 1
-
   do jt = 1, Size( pfield,  3 )
     do jk = 1, Size( pfield, 2 )
       zwork6(:, 1, jk, jt, 1, 1) = pfield (:, jk, jt)
@@ -1161,11 +1252,6 @@ if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NI ) then
 else if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NJ ) then
   Allocate( zwork6(1, Size( pfield, 1 ), nspectra_k, nles_current_times, 1, 1) )
 
-  iil = 1
-  iih = 1
-  ijl = nles_current_jinf
-  ijh = nles_current_jsup
-
   do jt = 1, Size( pfield, 3 )
     do jk = 1, Size( pfield, 2 )
       zwork6(1, :, jk, jt, 1, 1) = pfield (:, jk, jt)
@@ -1191,7 +1277,7 @@ tzfield%cmnhname  = ygroup
 tzfield%clongname = ygroup
 tzfield%ccomment  = ycomment(:)
 
-!* time average
+!* time average (physical units remain unchanged)
 iresp = 0
 if ( gavg ) then
   call Les_time_avg( zwork6, tzdates, iresp )
@@ -1202,24 +1288,60 @@ if ( gavg ) then
   end do
 end if
 
-tzbudiachro%cgroupname = ygroup
-tzbudiachro%cname      = ygroup
-if ( .not. gavg ) then
-  tzbudiachro%ccomment = tzfield%ccomment
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'LES_budgets'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different LES budgets'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .false.
+tzbudiachro%clevels  (NLVL_GROUP)       = ''
+tzbudiachro%ccomments(NLVL_GROUP)       = ''
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .true.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Two_point_correlation'
+tzbudiachro%ccomments(NLVL_SHAPE)       = ''
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .true.
+if ( gavg ) then
+  tzbudiachro%clevels  (NLVL_TIMEAVG)   = 'Time_averaged'
+  tzbudiachro%ccomments(NLVL_TIMEAVG)   = 'Values are time averaged'
+else
+  tzbudiachro%clevels  (NLVL_TIMEAVG)   = 'Not_time_averaged'
+  tzbudiachro%ccomments(NLVL_TIMEAVG)   = 'Values are not time averaged'
+end if
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .true.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
+if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NI ) then
+  tzbudiachro%cdirection = 'I'
 else
-  tzbudiachro%ccomment = Trim( tzfield%ccomment ) // ' (time averaged)'
+  tzbudiachro%cdirection = 'J'
 end if
-tzbudiachro%ctype      = 'SPXY'
-tzbudiachro%ccategory  = 'LES'
-tzbudiachro%cshape     = 'spectrum'
 tzbudiachro%lmobile    = .false.
+!i/j/k compression has no meaning here as it is 2-point correlations
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility with these values
 tzbudiachro%licompress = .false.
 tzbudiachro%ljcompress = .false.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = gavg
+tzbudiachro%lnorm      = .false.
 tzbudiachro%nil        = iil
 tzbudiachro%nih        = iih
 tzbudiachro%njl        = ijl
 tzbudiachro%njh        = ijh
+!nkl and nkh values have no real meaning here
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nkl        = ikl
 tzbudiachro%nkh        = ikh
 
@@ -1295,6 +1417,11 @@ type(tfield_metadata_base)                           :: tzfield
 allocate( tzdates( nles_current_times ) )
 tzdates(:) = tles_dates(:)
 
+iil = nles_current_iinf
+iih = nles_current_isup
+ijl = nles_current_jinf
+ijh = nles_current_jsup
+
 ikl = 1
 ikh = nspectra_k
 
@@ -1307,11 +1434,6 @@ tzfield = tpfield
 if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NI ) then
   Allocate( zwork6(Size( pspectra, 1 ), 1, nspectra_k, nles_current_times, 2, 1) )
 
-  iil = nles_current_iinf
-  iih = nles_current_isup
-  ijl = 1
-  ijh = 1
-
   do jt = 1, Size( pspectra, 4 )
     do jk = 1, Size( pspectra, 3 )
       zwork6(:, 1, jk, jt, 1, 1) = pspectra (:, 1, jk, jt)
@@ -1332,11 +1454,6 @@ if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NI ) then
 else if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NJ ) then
   Allocate( zwork6( 1, Size( pspectra, 1 ), nspectra_k, nles_current_times, 2, 1 ) )
 
-  iil = 1
-  iih = 1
-  ijl = nles_current_jinf
-  ijh = nles_current_jsup
-
   do jt = 1, Size( pspectra, 4 )
     do jk = 1, Size( pspectra, 3 )
       zwork6(1, :, jk, jt, 1, 1) = pspectra (:, 1, jk, jt)
@@ -1362,48 +1479,117 @@ tzfield%cmnhname  = ygroup
 tzfield%clongname = ygroup
 tzfield%ccomment  = ycomment(:)
 
-tzbudiachro%cgroupname = ygroup
-tzbudiachro%cname      = ygroup
-tzbudiachro%ccomment   = tzfield%ccomment
-tzbudiachro%ctype      = 'SPXY'
-tzbudiachro%ccategory  = 'LES'
-tzbudiachro%cshape     = 'spectrum'
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'LES_budgets'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different LES budgets'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .false.
+tzbudiachro%clevels  (NLVL_GROUP)       = ''
+tzbudiachro%ccomments(NLVL_GROUP)       = ''
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .true.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Spectrum'
+tzbudiachro%ccomments(NLVL_SHAPE)       = ''
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .true.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .true.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
+if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NI ) then
+  tzbudiachro%cdirection = 'I'
+else
+  tzbudiachro%cdirection = 'J'
+end if
 tzbudiachro%lmobile    = .false.
+!i/j/k compression has no meaning here as it is spectrum
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility with these values
 tzbudiachro%licompress = .false.
 tzbudiachro%ljcompress = .false.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
 tzbudiachro%nil        = iil
 tzbudiachro%nih        = iih
 tzbudiachro%njl        = ijl
 tzbudiachro%njh        = ijh
+!nkl and nkh values have no real meaning here
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nkl        = ikl
 tzbudiachro%nkh        = ikh
 
 call Write_diachro( tpdiafile, tzbudiachro, [ tzfield ], tzdates, zwork6 )
 !
-!* time average
+!* time average (physical units remain unchanged)
 !
 iresp = 0
 call Les_time_avg( zwork6, tzdates, iresp )
-ygroup = 'T_' // ygroup
 do ji = 1, NMNHMAXDIMS
   if ( tzfield%ndimlist(ji) == NMNHDIM_BUDGET_LES_TIME ) tzfield%ndimlist(ji) = NMNHDIM_BUDGET_LES_AVG_TIME
 end do
 
-tzbudiachro%cgroupname = ygroup
-tzbudiachro%cname      = ygroup
-tzbudiachro%ccomment   = Trim( tzfield%ccomment ) // ' (time averaged)'
-tzbudiachro%ctype      = 'SPXY'
-tzbudiachro%ccategory  = 'LES'
-tzbudiachro%cshape     = 'spectrum'
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'LES_budgets'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different LES budgets'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .false.
+tzbudiachro%clevels  (NLVL_GROUP)       = ''
+tzbudiachro%ccomments(NLVL_GROUP)       = ''
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .true.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Spectrum'
+tzbudiachro%ccomments(NLVL_SHAPE)       = ''
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .true.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .true.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
+if ( tzfield%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NI ) then
+  tzbudiachro%cdirection = 'I'
+else
+  tzbudiachro%cdirection = 'J'
+end if
 tzbudiachro%lmobile    = .false.
+!i/j/k compression has no meaning here as it is spectrum
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility with these values
 tzbudiachro%licompress = .false.
 tzbudiachro%ljcompress = .false.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = .true.
+tzbudiachro%lnorm      = .false.
 tzbudiachro%nil        = iil
 tzbudiachro%nih        = iih
 tzbudiachro%njl        = ijl
 tzbudiachro%njh        = ijh
+!nkl and nkh values have no real meaning here
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nkl        = ikl
 tzbudiachro%nkh        = ikh
 
diff --git a/src/MNH/write_aircraft_balloon.f90 b/src/MNH/write_aircraft_balloon.f90
index f375e6beb766dcc9d865f44a2882bb5a22dd58cb..a48117c835fa54237c162f999914b7f6f33ea319 100644
--- a/src/MNH/write_aircraft_balloon.f90
+++ b/src/MNH/write_aircraft_balloon.f90
@@ -176,10 +176,13 @@ CONTAINS
 !
 SUBROUTINE FLYER_DIACHRO(TPFLYER)
 
-use modd_budget, only: tbudiachrometadata
+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
 
+use modi_aircraft_balloon, only: Aircraft_balloon_longtype_get
+
 TYPE(FLYER),        INTENT(IN)       :: TPFLYER
 !
 !*      0.2  declaration of local variables for diachro
@@ -253,7 +256,7 @@ ALLOCATE (IGRIDZ  (IPROCZ))
 IGRID  = 1
 YGROUP = TPFLYER%TITLE
 IGRIDZ = 1
-YGROUPZ = TRIM(TPFLYER%TITLE)//"Z"
+YGROUPZ = TPFLYER%TITLE
 !
 !----------------------------------------------------------------------------
 JPROC = 0
@@ -853,27 +856,44 @@ tzfields(:)%ndimlist(4) = NMNHDIM_FLYER_TIME
 tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(6) = NMNHDIM_FLYER_PROC
 
-tzbudiachro%cgroupname = ygroup
-tzbudiachro%cname      = ygroup
-tzbudiachro%ccomment   = 'Values at position of flyer ' // Trim( tpflyer%title )
-tzbudiachro%ctype      = 'RSPL'
-if ( Trim( tpflyer%type ) == 'AIRCRA' ) then
-  tzbudiachro%ccategory  = 'aircraft'
-else if ( Trim( tpflyer%type ) == 'RADIOS' ) then
-  tzbudiachro%ccategory  = 'radiosonde balloon'
-else if ( Trim( tpflyer%type ) == 'ISODEN' ) then
-  tzbudiachro%ccategory  = 'iso-density balloon'
-else if ( Trim( tpflyer%type ) == 'CVBALL' ) then
-  tzbudiachro%ccategory  = 'constant volume balloon'
-else
-  call Print_msg( NVERB_ERROR, 'IO', 'WRITE_AIRCRAFT_BALLOON', 'unknown category for flyer ' // Trim( tpflyer%title ) )
-  tzbudiachro%ccategory  = 'unknown'
-end if
-tzbudiachro%cshape     = 'point'
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Flyers'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different flyers (aircrafts and balloons)'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .true.
+call Aircraft_balloon_longtype_get( tpflyer, tzbudiachro%clevels(NLVL_SUBCATEGORY) )
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = 'Level for the flyers of type: ' // Trim( tzbudiachro%clevels(NLVL_SUBCATEGORY) )
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+tzbudiachro%clevels  (NLVL_GROUP)       = Trim( ygroup )
+tzbudiachro%ccomments(NLVL_GROUP)       = 'Values for flyer ' // Trim( tpflyer%title )
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .true.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Point'
+tzbudiachro%ccomments(NLVL_SHAPE)       = 'Values at position of flyer ' // Trim( tpflyer%title )
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = ''
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = ''
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+tzbudiachro%clevels  (NLVL_NORM)        = ''
+tzbudiachro%ccomments(NLVL_NORM)        = ''
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
 tzbudiachro%lmobile    = .true.
+!Compression does not make sense here
 ! tzbudiachro%licompress = NOT SET (default values)
 ! tzbudiachro%ljcompress = NOT SET (default values)
 ! tzbudiachro%lkcompress = NOT SET (default values)
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
+!Boundaries in physical domain does not make sense here (but flyer position does)
+!These values are not written in the netCDF files
+!These values are written in the LFI files
 ! tzbudiachro%nil        = NOT SET (default values)
 ! tzbudiachro%nih        = NOT SET (default values)
 ! tzbudiachro%njl        = NOT SET (default values)
@@ -903,20 +923,53 @@ tzfields(:)%ndimlist(4) = NMNHDIM_FLYER_TIME
 tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(6) = NMNHDIM_FLYER_PROC
 
-tzbudiachro%cgroupname = ygroupz
-tzbudiachro%cname      = ygroupz
-tzbudiachro%ccomment   = 'Vertical profiles at position of flyer ' // Trim( tpflyer%title )
-tzbudiachro%ctype      = 'CART'
-! tzbudiachro%ccategory  =  !unchanged
-tzbudiachro%cshape     = 'vertical profile'
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Flyers'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different flyers (aircrafts and balloons)'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .true.
+call Aircraft_balloon_longtype_get( tpflyer, tzbudiachro%clevels(NLVL_SUBCATEGORY) )
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = 'Level for the flyers of type: ' // Trim( tzbudiachro%clevels(NLVL_SUBCATEGORY) )
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+tzbudiachro%clevels  (NLVL_GROUP)       = Trim( ygroupz )
+tzbudiachro%ccomments(NLVL_GROUP)       = 'Values for flyer ' // Trim( tpflyer%title )
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .true.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Vertical_profile'
+tzbudiachro%ccomments(NLVL_SHAPE)       = 'Vertical profiles at position of flyer ' // Trim( tpflyer%title )
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
 tzbudiachro%lmobile    = .true.
+!Compression does not make sense here
+!Keep these values for backward compatibility of LFI files
 tzbudiachro%licompress = .true.
 tzbudiachro%ljcompress = .true.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
+!Horizontal boundaries in physical domain does not make sense here (but flyer position does)
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nil        = 1
 tzbudiachro%nih        = 1
 tzbudiachro%njl        = 1
 tzbudiachro%njh        = 1
+!1->iku includes non-physical levels (IKU=NKMAX+2*JPVEXT)
+!This does not conform to documentation (limits are in the physical domain)
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nkl        = 1
 tzbudiachro%nkh        = iku
 
diff --git a/src/MNH/write_budget.f90 b/src/MNH/write_budget.f90
index be4f2d5a2d56ce97923cd3cf146b6b3a04ba3816..767541ad935a58606ffd9de97aaddc47c1fe836c 100644
--- a/src/MNH/write_budget.f90
+++ b/src/MNH/write_budget.f90
@@ -46,6 +46,8 @@ private
 
 public :: Write_budget
 
+character(len=*), parameter :: CMASK_VARNAME = 'MASKS'
+
 contains
 
 !#########################################################
@@ -103,7 +105,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
                                  tbudgets, tburhodj
   use modd_field,          only: NMNHDIM_ONE, NMNHDIM_NI, NMNHDIM_NJ,                              &
                                  NMNHDIM_BUDGET_TIME, NMNHDIM_BUDGET_MASK_NBUMASK, NMNHDIM_UNUSED, &
-                                 tfielddata, TYPEREAL
+                                 tfielddata, TYPEINT, TYPEREAL
   use modd_io,             only: tfiledata
   use modd_lunit_n,        only: tluout
   use modd_parameters,     only: NMNHNAMELGTMAX
@@ -272,14 +274,14 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
         tzfile = tpdiafile
         tzfile%cformat = 'NETCDF4'
 
-        tzfield%cmnhname   = 'MASKS'
+        tzfield%cmnhname   = CMASK_VARNAME
         tzfield%cstdname   = ''
         tzfield%clongname  = Trim( tzfield%cmnhname )
         tzfield%cunits     = '1'
         tzfield%cdir       = 'XY'
         tzfield%ccomment   = 'Masks for budget areas'
         tzfield%ngrid      = 1
-        tzfield%ntype      = TYPEREAL
+        tzfield%ntype      = TYPEINT
         tzfield%ndims      = 4
         tzfield%ltimedep   = .false. !The time dependance is in the NMNHDIM_BUDGET_TIME dimension
         tzfield%ndimlist(1)  = NMNHDIM_NI
@@ -294,7 +296,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
         !Write the data (partial write of the field with the given offset)
         call IO_Field_write( tzfile, tzfield, nbusurf(:,:,:,:), koffset= [ 0, 0, 0, ( nbutshift - 1 ) * nbusubwrite ] )
 
-        if ( nbutshift == 1 ) call Menu_diachro( tzfile, 'MASKS' )
+        if ( nbutshift == 1 ) call Menu_diachro( tzfile, CMASK_VARNAME )
       end if
   !
   END SELECT
@@ -306,22 +308,22 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
   !* RU budgets
   !
     IF (LBU_RU) THEN
-      call Store_one_budget_rho( tpdiafile, tzdates, tbudgets(NBUDGET_U)%trhodj,   NBUDGET_U, gnocompress, zrhodjn )
-      call Store_one_budget    ( tpdiafile, tzdates, tbudgets(NBUDGET_U), zrhodjn,            gnocompress, ptstep  )
+      call Store_one_budget_rho( tpdiafile, tzdates, tbudgets(NBUDGET_U)%trhodj,   gnocompress, zrhodjn )
+      call Store_one_budget    ( tpdiafile, tzdates, tbudgets(NBUDGET_U), zrhodjn, gnocompress, ptstep  )
     END IF
   !
   !* RV budgets
   !
     IF (LBU_RV) THEN
-      call Store_one_budget_rho( tpdiafile, tzdates, tbudgets(NBUDGET_V)%trhodj,   NBUDGET_V, gnocompress, zrhodjn )
-      call Store_one_budget    ( tpdiafile, tzdates, tbudgets(NBUDGET_V), zrhodjn,            gnocompress, ptstep  )
+      call Store_one_budget_rho( tpdiafile, tzdates, tbudgets(NBUDGET_V)%trhodj,   gnocompress, zrhodjn )
+      call Store_one_budget    ( tpdiafile, tzdates, tbudgets(NBUDGET_V), zrhodjn, gnocompress, ptstep  )
     END IF
   !
   !* RW budgets
   !
     IF (LBU_RW) THEN
-      call Store_one_budget_rho( tpdiafile, tzdates, tbudgets(NBUDGET_W)%trhodj,   NBUDGET_W, gnocompress, zrhodjn )
-      call Store_one_budget    ( tpdiafile, tzdates, tbudgets(NBUDGET_W), zrhodjn,            gnocompress, ptstep  )
+      call Store_one_budget_rho( tpdiafile, tzdates, tbudgets(NBUDGET_W)%trhodj,   gnocompress, zrhodjn )
+      call Store_one_budget    ( tpdiafile, tzdates, tbudgets(NBUDGET_W), zrhodjn, gnocompress, ptstep  )
     END IF
   !
   !* RHODJ storage for Scalars
@@ -329,7 +331,7 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
     IF (LBU_RTH .OR. LBU_RTKE .OR. LBU_RRV .OR. LBU_RRC .OR. LBU_RRR .OR. &
         LBU_RRI .OR. LBU_RRS  .OR. LBU_RRG .OR. LBU_RRH .OR. LBU_RSV      ) THEN
       if ( .not. associated( tburhodj ) ) call Print_msg( NVERB_FATAL, 'BUD', 'Write_budget', 'tburhodj not associated' )
-      call Store_one_budget_rho( tpdiafile, tzdates, tburhodj, NBUDGET_RHO, gnocompress, zrhodjn )
+      call Store_one_budget_rho( tpdiafile, tzdates, tburhodj, gnocompress, zrhodjn )
     ENDIF
   !
   !* RTH budget
@@ -398,14 +400,14 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
 end subroutine Write_budget
 
 
-subroutine Store_one_budget_rho( tpdiafile, tpdates, tprhodj, kp, knocompress, prhodjn )
-  use modd_budget,            only: cbutype,                                                      &
-                                    lbu_icp, lbu_jcp, lbu_kcp,                                    &
-                                    nbuil, nbuih, nbujl, nbujh, nbukl, nbukh,                     &
-                                    nbuimax, nbuimax_ll, nbujmax, nbujmax_ll, nbukmax, nbutshift, &
-                                    nbumask, nbusubwrite,                                         &
-                                    tbudiachrometadata, tburhodata,                               &
-                                    NBUDGET_RHO, NBUDGET_U, NBUDGET_V, NBUDGET_W
+subroutine Store_one_budget_rho( tpdiafile, tpdates, tprhodj, knocompress, prhodjn )
+  use modd_budget,            only: cbutype,                                                                                     &
+                                    lbu_icp, lbu_jcp, lbu_kcp,                                                                   &
+                                    nbuil, nbuih, nbujl, nbujh, nbukl, nbukh,                                                    &
+                                    nbuimax, nbuimax_ll, nbujmax, nbujmax_ll, nbukmax, nbutshift,                                &
+                                    nbumask, nbusubwrite,                                                                        &
+                                    NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK, &
+                                    tbudiachrometadata, tburhodata
   use modd_field,             only: NMNHDIM_BUDGET_CART_NI,    NMNHDIM_BUDGET_CART_NJ,   NMNHDIM_BUDGET_CART_NI_U, &
                                     NMNHDIM_BUDGET_CART_NJ_U,  NMNHDIM_BUDGET_CART_NI_V, NMNHDIM_BUDGET_CART_NJ_V, &
                                     NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W,                        &
@@ -428,12 +430,10 @@ subroutine Store_one_budget_rho( tpdiafile, tpdates, tprhodj, kp, knocompress, p
   type(tfiledata),                                      intent(in)  :: tpdiafile   ! file to write
   type(date_time), dimension(:),                        intent(in)  :: tpdates
   type(tburhodata),                                     intent(in)  :: tprhodj     ! rhodj datastructure
-  integer,                                              intent(in)  :: kp          ! reference number of budget
   logical,                                              intent(in)  :: knocompress ! compression for the cart option
   real,            dimension(:,:,:,:,:,:), allocatable, intent(out) :: prhodjn
 
   character(len=4)              :: ybutype
-  character(len=:), allocatable :: ygroup_name
   type(tbudiachrometadata)      :: tzbudiachro
   type(tburhodata)              :: tzfield
 
@@ -466,23 +466,6 @@ subroutine Store_one_budget_rho( tpdiafile, tpdates, tprhodj, kp, knocompress, p
       call Print_msg( NVERB_ERROR, 'BUD', 'Store_one_budget_rho', 'unknown CBUTYPE' )
   end select
 
-  select case( kp )
-    case( NBUDGET_RHO )
-      ygroup_name = 'RJS'
-
-    case( NBUDGET_U )
-      ygroup_name = 'RJX'
-
-    case( NBUDGET_V )
-      ygroup_name = 'RJY'
-
-    case( NBUDGET_W )
-      ygroup_name = 'RJZ'
-
-    case default
-      call Print_msg( NVERB_ERROR, 'BUD', 'Store_one_budget_rho', 'unknown budget type' )
-  end select
-
   !Copy all fields from tprhodj
   tzfield = tprhodj
 
@@ -555,20 +538,58 @@ subroutine Store_one_budget_rho( tpdiafile, tpdates, tprhodj, kp, knocompress, p
     tzfield%ndimlist(:) = NMNHDIM_UNKNOWN
   end if
 
-  tzbudiachro%cgroupname = ygroup_name
-  tzbudiachro%cname      = tprhodj%cmnhname
-  tzbudiachro%ccomment   = tprhodj%ccomment
-  tzbudiachro%ctype      = ybutype
-  tzbudiachro%ccategory  = 'budget'
+  tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+  tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Budgets'
+  tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different budgets'
+
+  tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+  tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+  tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+  tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+  tzbudiachro%clevels  (NLVL_GROUP)       = 'RhodJ'
+  tzbudiachro%ccomments(NLVL_GROUP)       = 'mass of dry air contained in the mesh cells'
+
+  tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+  if ( ybutype == 'CART' ) then
+    tzbudiachro%clevels  (NLVL_SHAPE)     = 'Cartesian'
+    tzbudiachro%ccomments(NLVL_SHAPE)     = 'cartesian domain'
+  else
+    tzbudiachro%clevels  (NLVL_SHAPE)     = 'Mask'
+    tzbudiachro%ccomments(NLVL_SHAPE)     = 'masked domain'
+  end if
+
+  tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+  tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Time_averaged'
+  tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are time averaged'
+
+  tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+  tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+  tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+  tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+  if ( ybutype == 'MASK' ) then
+    tzbudiachro%clevels  (NLVL_MASK)      = CMASK_VARNAME
+    tzbudiachro%ccomments(NLVL_MASK)      = ''
+  else
+    tzbudiachro%clevels  (NLVL_MASK)      = ''
+    tzbudiachro%ccomments(NLVL_MASK)      = ''
+  end if
+
   if ( ybutype == 'CART' ) then
-    tzbudiachro%cshape   = 'cartesian'
+    tzbudiachro%lmobile  = .false.
   else
-    tzbudiachro%cshape   = 'mask'
+    !Masks are updated at each timestep (therefore the studied domains change during execution)
+    tzbudiachro%lmobile  = .true.
   end if
-  tzbudiachro%lmobile    = .false.
   tzbudiachro%licompress = lbu_icp
   tzbudiachro%ljcompress = lbu_jcp
   tzbudiachro%lkcompress = lbu_kcp
+  tzbudiachro%ltcompress = .true. !Data is temporally averaged
+  tzbudiachro%lnorm      = .false.
+  !Boundaries in physical domain does not make sense here if 'MASK'
+  !In that case, these values are not written in the netCDF files
+  !But they are always written in the LFI files. They are kept (in the MASK case) for backward compatibility.
   tzbudiachro%nil        = nbuil
   tzbudiachro%nih        = nbuih
   tzbudiachro%njl        = nbujl
@@ -589,6 +610,7 @@ subroutine Store_one_budget( tpdiafile, tpdates, tpbudget, prhodjn, knocompress,
                                     nbumask, nbusubwrite,                                                                         &
                                     NBUDGET_U, NBUDGET_V, NBUDGET_W, NBUDGET_TH, NBUDGET_TKE, NBUDGET_RV, NBUDGET_RC, NBUDGET_RR, &
                                     NBUDGET_RI, NBUDGET_RS, NBUDGET_RG, NBUDGET_RH, NBUDGET_SV1,                                  &
+                                    NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK,  &
                                     tbudgetdata, tbudiachrometadata, tbugroupdata
   use modd_field,             only: NMNHDIM_BUDGET_CART_NI,    NMNHDIM_BUDGET_CART_NJ,   NMNHDIM_BUDGET_CART_NI_U, &
                                     NMNHDIM_BUDGET_CART_NJ_U,  NMNHDIM_BUDGET_CART_NI_V, NMNHDIM_BUDGET_CART_NJ_V, &
@@ -619,7 +641,6 @@ subroutine Store_one_budget( tpdiafile, tpdates, tpbudget, prhodjn, knocompress,
   real,                                                 intent(in) :: ptstep      ! time step
 
   character(len=4)                                        :: ybutype
-  character(len=:),                           allocatable :: ygroup_name
   integer                                                 :: igroups
   integer                                                 :: jproc
   integer                                                 :: jsv
@@ -682,52 +703,6 @@ subroutine Store_one_budget( tpdiafile, tpdates, tpbudget, prhodjn, knocompress,
 
   deallocate(zconvert)
 
-  jsv = -1
-  select case( tpbudget%nid )
-    case ( NBUDGET_U )
-      ygroup_name = 'UU'
-
-    case ( NBUDGET_V )
-      ygroup_name = 'VV'
-
-    case ( NBUDGET_W )
-      ygroup_name = 'WW'
-
-    case ( NBUDGET_TH )
-      ygroup_name = 'TH'
-
-    case ( NBUDGET_TKE )
-      ygroup_name = 'TK'
-
-    case ( NBUDGET_RV )
-      ygroup_name = 'RV'
-
-    case ( NBUDGET_RC )
-      ygroup_name = 'RC'
-
-    case ( NBUDGET_RR )
-      ygroup_name = 'RR'
-
-    case ( NBUDGET_RI )
-      ygroup_name = 'RI'
-
-    case ( NBUDGET_RS )
-      ygroup_name = 'RS'
-
-    case ( NBUDGET_RG )
-      ygroup_name = 'RG'
-
-    case ( NBUDGET_RH )
-      ygroup_name = 'RH'
-
-    case ( NBUDGET_SV1 : )
-      jsv = tpbudget%nid - NBUDGET_SV1 + 1
-      ygroup_name = csvnames(jsv)
-
-    case default
-      call Print_msg( NVERB_ERROR, 'BUD', 'Store_one_budget', 'unknown budget type' )
-  end select
-
   allocate( tzfields( igroups ) )
 
   !Copy all fields from tpbudget%tgroups
@@ -808,26 +783,71 @@ subroutine Store_one_budget( tpdiafile, tpdates, tpbudget, prhodjn, knocompress,
     end if
   end do
 
-  tzbudiachro%cgroupname = ygroup_name
-  tzbudiachro%cname      = tpbudget%cname
-  tzbudiachro%ccomment   = tpbudget%ccomment
-  tzbudiachro%ctype      = ybutype
-  tzbudiachro%ccategory  = 'budget'
+  tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+  tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Budgets'
+  tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different budgets'
+
+  tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+  tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+  tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+  tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+  tzbudiachro%clevels  (NLVL_GROUP)       = Trim( tpbudget%cname )
+  tzbudiachro%ccomments(NLVL_GROUP)       = Trim( tpbudget%ccomment )
+
+  tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+  if ( ybutype == 'CART' ) then
+    tzbudiachro%clevels  (NLVL_SHAPE)     = 'Cartesian'
+    tzbudiachro%ccomments(NLVL_SHAPE)     = 'Cartesian domain'
+  else
+    tzbudiachro%clevels  (NLVL_SHAPE)     = 'Mask'
+    tzbudiachro%ccomments(NLVL_SHAPE)     = 'Masked domain'
+  end if
+
+  tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+  tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Time_averaged'
+  tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are time averaged'
+
+  tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+  tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+  tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+  tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+  if ( ybutype == 'MASK' ) then
+    tzbudiachro%clevels  (NLVL_MASK)      = CMASK_VARNAME
+    tzbudiachro%ccomments(NLVL_MASK)      = ''
+  else
+    tzbudiachro%clevels  (NLVL_MASK)      = ''
+    tzbudiachro%ccomments(NLVL_MASK)      = ''
+  end if
+
   if ( ybutype == 'CART' ) then
-    tzbudiachro%cshape   = 'cartesian'
+    tzbudiachro%lmobile  = .false.
   else
-    tzbudiachro%cshape   = 'mask'
+    !Masks are updated at each timestep (therefore the studied domains change during execution)
+    tzbudiachro%lmobile  = .true.
   end if
-  tzbudiachro%lmobile    = .false.
   tzbudiachro%licompress = lbu_icp
   tzbudiachro%ljcompress = lbu_jcp
   tzbudiachro%lkcompress = lbu_kcp
+  !Remark: ltcompress should be false for INIF and ENDF fields
+  !        but if set to false these fields should be separated and stored somewhere else
+  tzbudiachro%ltcompress = .true. !Data is temporally averaged
+  tzbudiachro%lnorm      = .false.
+  !Boundaries in physical domain does not make sense here if 'MASK'
+  !In that case, these values are not written in the netCDF files
+  !But they are always written in the LFI files. They are kept (in the MASK case) for backward compatibility.
   tzbudiachro%nil        = nbuil
   tzbudiachro%nih        = nbuih
   tzbudiachro%njl        = nbujl
   tzbudiachro%njh        = nbujh
   tzbudiachro%nkl        = nbukl
   tzbudiachro%nkh        = nbukh
+  if ( tpbudget%nid > NBUDGET_SV1 ) then
+    jsv = tpbudget%nid - NBUDGET_SV1 + 1
+  else
+    jsv = -1
+  end if
   tzbudiachro%nsv        = jsv
 
   call Write_diachro( tpdiafile, tzbudiachro, tzfields, tpdates, zworkt, osplit = .true. )
diff --git a/src/MNH/write_diachro.f90 b/src/MNH/write_diachro.f90
index 485909a62c4103ad9b3ada8e0f027453d1e58e45..cfb648886b09bc7999acbc1cecb7467442c568e0 100644
--- a/src/MNH/write_diachro.f90
+++ b/src/MNH/write_diachro.f90
@@ -13,6 +13,9 @@ private
 
 public :: Write_diachro
 
+interface Att_write
+   procedure Att_write_c0, Att_write_i0, Att_write_x0
+end interface
 contains
 
 ! #################################################################
@@ -139,7 +142,7 @@ end subroutine Write_diachro
 subroutine Write_diachro_lfi( tpdiafile, tpbudiachro, tpfields, tpdates, pvar, tpflyer )
 
 use modd_aircraft_balloon, only: flyer
-use modd_budget,         only: nbumask, nbutshift, nbusubwrite, tbudiachrometadata
+use modd_budget,         only: NLVL_CATEGORY, NLVL_GROUP, NLVL_SHAPE, nbumask, nbutshift, nbusubwrite, tbudiachrometadata
 use modd_field,          only: NMNHDIM_ONE, NMNHDIM_UNKNOWN, NMNHDIM_FLYER_TIME, NMNHDIM_NOTLISTED, NMNHDIM_UNUSED, &
                                TYPECHAR, TYPEINT, TYPEREAL,                                                         &
                                tfield_metadata_base, tfielddata
@@ -168,6 +171,8 @@ integer, parameter :: LFITITLELGT = 100
 integer, parameter :: LFIUNITLGT = 100
 integer, parameter :: LFICOMMENTLGT = 100
 
+character(len=:), allocatable :: ycategory
+character(len=:), allocatable :: yshape
 character(len=:), allocatable :: ytype
 CHARACTER(LEN=20) :: YCOMMENT
 CHARACTER(LEN=3)  :: YJ
@@ -185,6 +190,7 @@ INTEGER   ::   IIMASK, IJMASK, IKMASK, ITMASK, INMASK, IPMASK
 INTEGER   ::   IIMAX_ll, IJMAX_ll ! size of the physical global domain
 integer   ::   ji
 INTEGER,DIMENSION(:),ALLOCATABLE :: ITABCHAR
+logical   :: gdistributed
 real, dimension(:,:), allocatable :: ztimes
 real, dimension(:,:), allocatable :: zdatime
 real, dimension(:,:,:), allocatable :: ztrajz
@@ -202,37 +208,135 @@ ijh = tpbudiachro%njh
 ikl = tpbudiachro%nkl
 ikh = tpbudiachro%nkh
 
+ycategory = Trim( tpbudiachro%clevels(NLVL_CATEGORY) )
+yshape    = Trim( tpbudiachro%clevels(NLVL_SHAPE) )
+
+!For backward compatibility of LFI files
+if ( tpbudiachro%cdirection == 'I' ) then
+  ijl = 1
+  ijh = 1
+else if ( tpbudiachro%cdirection == 'J' ) then
+  iil = 1
+  iih = 1
+end if
+
 !Write only in LFI files
 tzfile%cformat = 'LFI'
 
 YCOMMENT='NOTHING'
 
 !Set ygroup to preserve backward compatibility of LFI files
-if (      Any( tpbudiachro%cgroupname == [ 'RJS', 'RJX', 'RJY', 'RJZ'] )                                              &
-     .or. Any( tpbudiachro%cgroupname == [ 'UU', 'VV', 'WW', 'TH', 'TK', 'RV', 'RC', 'RR', 'RI', 'RS', 'RG', 'RH' ] ) &
-     .or.    ( tpbudiachro%cgroupname(1:2) == 'SV' .and. Len_trim( tpbudiachro%cgroupname ) == 5 )                    ) then
+if (      Any( tpbudiachro%clevels(NLVL_GROUP) == [ 'UU', 'VV', 'WW', 'TH', 'TK', 'RV', 'RC', 'RR', 'RI', 'RS', 'RG', 'RH' ] ) &
+     .or.    ( tpbudiachro%clevels(NLVL_GROUP)(1:2) == 'SV' .and. Len_trim( tpbudiachro%clevels(NLVL_GROUP) ) == 5 )         ) then
   Allocate( character(len=9) :: ygroup )
-  ygroup(:) = Trim( tpbudiachro%cgroupname )
-  do ji = Len_trim( tpbudiachro%cgroupname ) + 1, 5
+  ygroup(:) = Trim( tpbudiachro%clevels(NLVL_GROUP) )
+  do ji = Len_trim( tpbudiachro%clevels(NLVL_GROUP) ) + 1, 5
     ygroup(ji : ji) = '_'
   end do
   Write( ygroup(6:9), '( i4.4 )' ) nbutshift
+else if ( tpbudiachro%clevels(NLVL_GROUP) == 'RhodJ' ) then
+  Allocate( character(len=9) :: ygroup )
+
+  if ( tpfields(1)%cmnhname == 'RhodJX' ) then
+    ygroup(1:3) = 'RJX'
+  else if ( tpfields(1)%cmnhname == 'RhodJY' ) then
+    ygroup(1:3) = 'RJY'
+  else if ( tpfields(1)%cmnhname == 'RhodJZ' ) then
+    ygroup(1:3) = 'RJZ'
+  else if ( tpfields(1)%cmnhname == 'RhodJS' ) then
+    ygroup(1:3) = 'RJS'
+  else
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', 'unknown variable ' // Trim( tpfields(1)%cmnhname ) // &
+                    ' for group ' // Trim( tpbudiachro%clevels(NLVL_GROUP) ) )
+  end if
+
+  ygroup(4:5) = '__'
+  Write( ygroup(6:9), '( i4.4 )' ) nbutshift
 else if ( tpbudiachro%nsv > 0 ) then
   Allocate( character(len=9) :: ygroup )
   Write( ygroup, '( "SV", i3.3, i4.4 )' ) tpbudiachro%nsv, nbutshift
 else
-  ygroup = Trim( tpbudiachro%cgroupname )
+  ygroup = Trim( tpbudiachro%clevels(NLVL_GROUP) )
 end if
 
-ytype = Trim( tpbudiachro%ctype )
+!For backward compatibility
+if (       Trim( tpbudiachro%clevels(NLVL_CATEGORY) ) == 'Flyers'           &
+     .and. Trim( tpbudiachro%clevels(NLVL_SHAPE) )    == 'Vertical_profile' ) then
+  ygroup = Trim( ygroup ) // 'Z'
+end if
+
+if (       Trim( tpbudiachro%clevels(NLVL_CATEGORY) ) == 'LES_budgets' &
+     .and. Trim( tpbudiachro%clevels(NLVL_SHAPE) )    == 'Cartesian'   ) then
+  if ( tpbudiachro%ltcompress ) then
+    if ( tpbudiachro%lnorm ) then
+      ygroup = 'H_' // Trim( ygroup )
+    else
+      ygroup = 'A_' // Trim( ygroup )
+    end if
+  else
+    if ( tpbudiachro%lnorm ) then
+      ygroup = 'E_' // Trim( ygroup )
+    else
+      !Nothing to do
+    end if
+  end if
+  !Limit to 10 characters (backward compatibility again...)
+  if ( Len_trim( ygroup )  > 10 ) ygroup = ygroup(1:10)
+end if
+
+if (       Trim( tpbudiachro%clevels(NLVL_CATEGORY) ) == 'LES_budgets' &
+     .and. Trim( tpbudiachro%clevels(NLVL_SHAPE) )    == 'Spectrum'    ) then
+  if ( tpbudiachro%ltcompress ) then
+    ygroup = 'T_' // Trim( ygroup )
+    !Limit to 10 characters (backward compatibility again...)
+    if ( Len_trim( ygroup )  > 10 ) ygroup = ygroup(1:10)
+  end if
+end if
+
+!Recompute old TYPE for backward compatibility
+if ( ycategory == 'Budgets' ) then
+  if ( yshape == 'Cartesian' ) then
+    ytype = 'CART'
+  else
+    ytype = 'MASK'
+  end if
+else if ( ycategory == 'LES_budgets' ) then
+  if ( yshape == 'Cartesian' ) then
+    ytype = 'SSOL'
+  else
+    ytype = 'SPXY'
+  end if
+else if ( ycategory == 'Flyers' ) then
+  if ( yshape == 'Point' ) then
+    ytype = 'RSPL'
+  else
+    ytype = 'CART'
+  end if
+else if ( ycategory == 'Profilers' .or. ycategory == 'Stations' ) then
+  ytype = 'CART'
+else if ( ycategory == 'Time series'  ) then
+  if ( tpbudiachro%licompress ) then
+    ytype = 'CART'
+  else
+    ytype = 'SSOL'
+  end if
+else
+  call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', &
+                  'unknown classification for type of variable '//trim(tpfields(1)%cmnhname) )
+  ytype = 'UNKN'
+end if
 
 II = SIZE(PVAR,1)
 IJ = SIZE(PVAR,2)
-IF(YTYPE == 'CART' .AND. .NOT. tpbudiachro%licompress .AND. .NOT. tpbudiachro%ljcompress) THEN
-                              !for parallel execution, PVAR is distributed on several proc
+if ( ycategory == 'Budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' &
+     .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress       ) then
   II=iih-iil+1
   IJ=ijh-ijl+1
-ENDIF
+  gdistributed = .true.
+else
+  !By default data is already collected on the write process for budgets
+  gdistributed = .false.
+end if
 IK = SIZE(PVAR,3)
 IT = SIZE(PVAR,4)
 IN = SIZE(PVAR,5)
@@ -247,7 +351,7 @@ IF ( PRESENT( tpflyer ) ) THEN
   IKTRAJX = 1
   ITTRAJX = SIZE( tpflyer%x )
   INTRAJX = 1
-ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
+ELSE IF ( ycategory == 'LES_budgets' .and.  tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN
   IKTRAJX = 1
   ITTRAJX = 1
   INTRAJX = IN
@@ -256,7 +360,7 @@ IF ( PRESENT( tpflyer ) ) THEN
   IKTRAJY = 1
   ITTRAJY = SIZE( tpflyer%y )
   INTRAJY = 1
-ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
+ELSE IF ( ycategory == 'LES_budgets' .and.  tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN
   IKTRAJY = 1
   ITTRAJY = 1
   INTRAJY = IN
@@ -265,14 +369,14 @@ IF ( PRESENT( tpflyer ) ) THEN
   IKTRAJZ = 1
   ITTRAJZ = SIZE( tpflyer%z )
   INTRAJZ = 1
-ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
+ELSE IF ( ycategory == 'LES_budgets' .and.  tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN
   IKTRAJZ = IK
   ITTRAJZ = 1
   INTRAJZ = IN
 ENDIF
 
 IIMASK=0; IJMASK=0; IKMASK=0; ITMASK=0; INMASK=0; IPMASK=0
-IF(YTYPE == 'MASK')THEN
+IF ( tpbudiachro%clevels(NLVL_SHAPE) == 'Mask' ) THEN
 !     MASK is written outside this routine but the dimensions must be initialized
 !     the mask is defined on the extended domain
   CALL GET_GLOBALDIMS_ll (IIMAX_ll,IJMAX_ll)
@@ -333,7 +437,7 @@ SELECT CASE(YTYPE)
     ITABCHAR(16)=Merge( 1, 0, tpbudiachro%licompress )
     ITABCHAR(17)=Merge( 1, 0, tpbudiachro%ljcompress )
     ITABCHAR(18)=Merge( 1, 0, tpbudiachro%lkcompress )
-    IF(YTYPE == 'MASK')THEN
+    IF( tpbudiachro%clevels(NLVL_SHAPE) == 'Mask' )THEN
 !     ITABCHAR(10)=1; ITABCHAR(11)=1
 !     ITABCHAR(13)=1; ITABCHAR(14)=1
       ITABCHAR(16)=1; ITABCHAR(17)=1
@@ -445,7 +549,7 @@ DO J = 1,IP
   ELSE IF(J >= 100 .AND. J < 1000) THEN
           WRITE(YJ,'(I3)')J
   ENDIF
-  IF(YTYPE == 'CART' .AND. .NOT. tpbudiachro%licompress .AND. .NOT. tpbudiachro%ljcompress) THEN
+  IF ( gdistributed ) THEN
     TZFIELD%CMNHNAME   = TRIM(ygroup)//'.PROC'//YJ
     TZFIELD%CSTDNAME   = ''
     TZFIELD%CLONGNAME  = TRIM(TZFIELD%CMNHNAME)
@@ -528,7 +632,7 @@ IF(PRESENT(tpflyer))THEN
   TZFIELD%NDIMS      = 3
   TZFIELD%LTIMEDEP   = .FALSE.
   CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%x, [1, Size( tpflyer%x), 1] ) )
-ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
+ELSE IF ( ycategory == 'LES_budgets' .and.  tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN
   TZFIELD%CMNHNAME   = TRIM(ygroup)//'.TRAJX'
   TZFIELD%CSTDNAME   = ''
   TZFIELD%CLONGNAME  = TRIM(ygroup)//'.TRAJX'
@@ -540,9 +644,9 @@ ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
   TZFIELD%NDIMS      = 3
   TZFIELD%LTIMEDEP   = .FALSE.
   !TRAJX is given in extended domain coordinates (=> +jphext) for backward compatibility
-  CALL IO_Field_write(tzfile,TZFIELD, Reshape( &
+  CALL IO_Field_write(tzfile,TZFIELD, Real( Reshape( &
                        Spread( source = ( nles_current_iinf + nles_current_isup) / 2 + jphext, dim = 1, ncopies = IN ), &
-                       [1, 1, IN] ) )
+                       [1, 1, IN] ) ) )
 ENDIF
 !
 ! 9eme enregistrement TRAJY
@@ -559,7 +663,7 @@ IF(PRESENT(tpflyer))THEN
   TZFIELD%NDIMS      = 3
   TZFIELD%LTIMEDEP   = .FALSE.
   CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%y, [1, Size( tpflyer%y), 1] ) )
-ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
+ELSE IF ( ycategory == 'LES_budgets' .and.  tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN
   TZFIELD%CMNHNAME   = TRIM(ygroup)//'.TRAJY'
   TZFIELD%CSTDNAME   = ''
   TZFIELD%CLONGNAME  = TRIM(ygroup)//'.TRAJY'
@@ -571,9 +675,9 @@ ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
   TZFIELD%NDIMS      = 3
   TZFIELD%LTIMEDEP   = .FALSE.
   !TRAJY is given in extended domain coordinates (=> +jphext) for backward compatibility
-  CALL IO_Field_write(tzfile,TZFIELD, Reshape( &
+  CALL IO_Field_write(tzfile,TZFIELD, Real( Reshape( &
                        Spread( source = ( nles_current_jinf + nles_current_jsup) / 2 + jphext, dim = 1, ncopies = IN ), &
-                       [1, 1, IN] ) )
+                       [1, 1, IN] ) ) )
 ENDIF
 !
 ! 10eme enregistrement TRAJZ
@@ -590,7 +694,7 @@ IF(PRESENT(tpflyer))THEN
   TZFIELD%NDIMS      = 3
   TZFIELD%LTIMEDEP   = .FALSE.
   CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%z, [1, Size( tpflyer%z), 1] ) )
-ELSE IF ( tpbudiachro%ctype == 'TLES' ) THEN
+ELSE IF ( ycategory == 'LES_budgets' .and.  tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN
   TZFIELD%CMNHNAME   = TRIM(ygroup)//'.TRAJZ'
   TZFIELD%CSTDNAME   = ''
   TZFIELD%CLONGNAME  = TRIM(ygroup)//'.TRAJZ'
@@ -656,16 +760,18 @@ end subroutine Write_diachro_lfi
 !-----------------------------------------------------------------------------
 subroutine Write_diachro_nc4( tpdiafile, tpbudiachro, tpfields, pvar, osplit, tpflyer )
 
-use NETCDF,                only: NF90_DEF_DIM, NF90_DEF_GRP, NF90_DEF_VAR, NF90_INQ_NCID, NF90_PUT_ATT, NF90_PUT_VAR, &
-                                 NF90_GLOBAL, NF90_NOERR, NF90_STRERROR
+use NETCDF,                only: NF90_DEF_DIM, NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION, NF90_NOERR
 
 use modd_aircraft_balloon, only: flyer
-use modd_budget,           only: nbutshift, nbusubwrite, tbudiachrometadata
+use modd_budget,           only: CNCGROUPNAMES,                                                      &
+                                 NMAXLEVELS, NLVL_ROOT, NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, &
+                                 NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK,                     &
+                                 nbutshift, nbusubwrite, tbudiachrometadata
 use modd_conf,             only: lcartesian
 use modd_field
 use modd_io,               only: isp, tfiledata
-use modd_les,              only: nles_masks
-use modd_parameters,       only: jphext
+use modd_les,              only: cbl_height_def, cles_norm_type, nles_masks, xles_temp_sampling
+use modd_parameters,       only: jphext, NBUNAMELGTMAX, NCOMMENTLGTMAX
 use modd_precision,        only: CDFINT, MNHREAL_NF90
 use modd_type_date,        only: date_time
 
@@ -679,33 +785,38 @@ real,                        dimension(:,:,:,:,:,:), intent(in)           :: pva
 logical,                                             intent(in), optional :: osplit
 type(flyer),                                         intent(in), optional :: tpflyer
 
-character(len=:), allocatable :: ygroup
-character(len=:), allocatable :: ytype
+character(len=:), allocatable :: ycategory
+character(len=:), allocatable :: ylevelname
+character(len=:), allocatable :: ylevels
+character(len=:), allocatable :: yshape
 character(len=:), allocatable :: ystdnameprefix
-integer              :: iil, iih, ijl, ijh, ikl, ikh
-integer              :: idims
-integer              :: icount
-integer              :: icorr
-integer              :: ji
-integer              :: jp
-integer(kind=CDFINT) :: isavencid
-integer(kind=CDFINT) :: idimid
-integer(kind=CDFINT) :: igrpid
-integer(kind=CDFINT) :: istatus
-logical              :: gdistributed
-logical              :: ggroupdefined
-logical              :: gsplit
-type(tfielddata)     :: tzfield
-type(tfiledata)      :: tzfile
-
-ytype = Trim( tpbudiachro%ctype )
+integer                                       :: iil, iih, ijl, ijh, ikl, ikh
+integer                                       :: idims
+integer                                       :: icount
+integer                                       :: icorr
+integer                                       :: ji
+integer                                       :: jl
+integer                                       :: jp
+integer(kind=CDFINT)                          :: idimid
+integer(kind=CDFINT)                          :: ilen
+integer(kind=CDFINT)                          :: istatus
+integer(kind=CDFINT)                          :: ilevelid
+integer(kind=CDFINT), dimension(0:NMAXLEVELS) :: ilevelids ! ids of the different groups/levels in the netCDF file
+logical                                       :: gdistributed
+logical                                       :: gsplit
+logical(kind=CDFINT), dimension(0:NMAXLEVELS) :: gleveldefined ! Are the different groups/levels already defined in the netCDF file
+type(tfielddata)                              :: tzfield
+type(tfiledata)                               :: tzfile
+
+call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro_nc4', 'called' )
 
 tzfile = tpdiafile
 
 !Write only in netCDF files
 tzfile%cformat = 'NETCDF4'
 
-ygroup = tpbudiachro%cgroupname
+ycategory = Trim( tpbudiachro%clevels(NLVL_CATEGORY)  )
+yshape    = Trim( tpbudiachro%clevels(NLVL_SHAPE) )
 
 iil = tpbudiachro%nil
 iih = tpbudiachro%nih
@@ -714,14 +825,8 @@ ijh = tpbudiachro%njh
 ikl = tpbudiachro%nkl
 ikh = tpbudiachro%nkh
 
-if ( trim ( ytype ) == 'CART' .or. trim ( ytype ) == 'MASK' .or. trim ( ytype ) == 'SPXY') then
-    if ( iil < 0 .or. iih < 0 .or. ijl < 0 .or. ijh < 0 .or. ikl < 0 .or. ikh < 0 ) then
-      call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
-                      'nil, nih, njl, njh, nkl or nkh not set in tpbudiachro for variable ' // Trim( tpfields(1)%cmnhname ) )
-    end if
-end if
-
-if ( Trim( ytype ) == 'CART' .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then
+if ( ycategory == 'Budgets' .and. yshape == 'Cartesian' &
+     .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then
   gdistributed = .true.
 else
   !By default data is already collected on the write process for budgets
@@ -735,82 +840,159 @@ else
 end if
 
 MASTER: if ( isp == tzfile%nmaster_rank) then
-  ggroupdefined = .false.
+  ilevelids(NLVL_ROOT) = tzfile%nncid
 
-  istatus = NF90_INQ_NCID( tzfile%nncid, trim( ygroup ), igrpid )
-  if ( istatus == NF90_NOERR ) then
-    ggroupdefined = .true.
-    if ( .not. gsplit ) then
-      call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', trim(tzfile%cname)//': group '//trim(ygroup)//' already defined' )
-    end if
-  else
-    istatus = NF90_DEF_GRP( tzfile%nncid, trim( ygroup ), igrpid )
-    if ( istatus /= NF90_NOERR ) &
-      call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_GRP', 'for '//trim(ygroup)//' group' )
-  end if
+  gleveldefined(:) = .false.
+
+  do jl = 1, NMAXLEVELS
+    call Move_to_next_level( ilevelids(jl-1), gleveldefined(jl-1), tpbudiachro%lleveluse(jl), &
+                           tpbudiachro%clevels(jl), gleveldefined(jl), ilevelids(jl) )
+  end do
+
+  tzfile%nncid = ilevelids(NLVL_MASK)
+
+  ylevels = ''
 
-  !Save id of the file root group ('/' group)
-  isavencid = tzfile%nncid
-  tzfile%nncid = igrpid
+  do jl = NMAXLEVELS, 1, -1
+    ylevels = Trim( CNCGROUPNAMES(jl) ) // ' ' // ylevels
+    if ( tpbudiachro%lleveluse(jl) ) then
+      call Att_write( tpbudiachro%clevels(jl), ilevelids(jl), 'levels', Trim( ylevels ) )
+      ylevels = ''
+    end if
+  end do
 
-  if ( .not. ggroupdefined ) then
-    istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'name', Trim( tpbudiachro%cname ) )
-    if (istatus /= NF90_NOERR ) &
-      call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'name for '//trim(ygroup)//' group' )
+  if ( .not. gleveldefined(NLVL_CATEGORY) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_CATEGORY)
+    ilevelid   = ilevelids  (NLVL_CATEGORY)
 
-    istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'comment', Trim( tpbudiachro%ccomment ) )
-    if (istatus /= NF90_NOERR ) &
-      call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'comment for '//trim(ygroup)//' group' )
+    call Att_write( ylevelname, ilevelid, 'category', ylevelname )
+    if ( tpbudiachro%lleveluse(NLVL_CATEGORY) .and. Len_trim( tpbudiachro%ccomments(NLVL_CATEGORY) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment',  tpbudiachro%ccomments(NLVL_CATEGORY) )
 
-    istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'type', trim( ytype ) )
-    if (istatus /= NF90_NOERR ) &
-      call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'type for '//trim(ygroup)//' group' )
+    if ( ycategory == 'LES_budgets' ) &
+    call Att_write( ylevelname, ilevelid, 'temporal_sampling_frequency', xles_temp_sampling )
+  end if
 
-    if ( trim ( ytype ) == 'CART' .or. trim ( ytype ) == 'MASK' .or. trim ( ytype ) == 'SPXY') then
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'min x index in physical domain', iil )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'min x index for '//trim(ygroup)//' group' )
+  if ( .not. gleveldefined(NLVL_SUBCATEGORY) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_SUBCATEGORY)
+    ilevelid   = ilevelids  (NLVL_SUBCATEGORY)
 
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'max x index in physical domain', iih )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'max x index for '//trim(ygroup)//' group' )
+    call Att_write( ylevelname, ilevelid, 'subcategory', ylevelname )
+    if ( tpbudiachro%lleveluse(NLVL_SUBCATEGORY) .and. Len_trim( tpbudiachro%ccomments(NLVL_SUBCATEGORY) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment',     tpbudiachro%ccomments(NLVL_SUBCATEGORY) )
+  end if
 
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'min y index in physical domain', ijl )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'min y index for '//trim(ygroup)//' group' )
+  if ( .not. gleveldefined(NLVL_GROUP) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_GROUP)
+    ilevelid   = ilevelids  (NLVL_GROUP)
 
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'max y index in physical domain', ijh )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'max y index for '//trim(ygroup)//' group' )
+    call Att_write( ylevelname, ilevelid, 'group',   ylevelname )
+    if ( tpbudiachro%lleveluse(NLVL_GROUP) .and. Len_trim( tpbudiachro%ccomments(NLVL_GROUP) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_GROUP) )
+  end if
 
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'min z index in physical domain', ikl )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'min z index for '//trim(ygroup)//' group' )
+  if ( .not. gleveldefined(NLVL_SHAPE) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_SHAPE)
+    ilevelid   = ilevelids  (NLVL_SHAPE)
+
+    call Att_write( ylevelname, ilevelid, 'shape',   ylevelname )
+    if ( tpbudiachro%lleveluse(NLVL_SHAPE) .and. Len_trim( tpbudiachro%ccomments(NLVL_SHAPE) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_SHAPE) )
+
+    call Att_write( ylevelname, ilevelid, 'moving', Merge( 'yes', 'no ', tpbudiachro%lmobile ) )
+
+    if (      ( ycategory == 'Budgets' .and. yshape == 'Cartesian' )             &
+         .or. ycategory == 'LES_budgets'                                         &
+         .or. tpbudiachro%clevels(NLVL_GROUP)      == 'TSERIES'                  &
+         .or. tpbudiachro%clevels(NLVL_GROUP)      == 'ZTSERIES'                 &
+         .or. tpbudiachro%clevels(NLVL_GROUP)(1:8) == 'XTSERIES'                 ) then
+      call Att_write( ylevelname, ilevelid, 'min_I_index_in_physical_domain', iil )
+      call Att_write( ylevelname, ilevelid, 'max_I_index_in_physical_domain', iih )
+      call Att_write( ylevelname, ilevelid, 'min_J_index_in_physical_domain', ijl )
+      call Att_write( ylevelname, ilevelid, 'max_J_index_in_physical_domain', ijh )
+    end if
 
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'max z index in physical domain', ikh )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'max z index for '//trim(ygroup)//' group' )
+    if (      ( ycategory == 'Budgets' .and. yshape == 'Cartesian' )           &
+         .or. tpbudiachro%clevels(NLVL_GROUP)      == 'TSERIES'                &
+         .or. tpbudiachro%clevels(NLVL_GROUP)      == 'ZTSERIES'               &
+         .or. tpbudiachro%clevels(NLVL_GROUP)(1:8) == 'XTSERIES'               ) then
+      !Disabled for LES_budgets because no real meaning on that case (vertical levels are stored in the level_les variable)
+      call Att_write( ylevelname, ilevelid, 'min_K_index_in_physical_domain', ikl )
+      call Att_write( ylevelname, ilevelid, 'max_K_index_in_physical_domain', ikh )
     end if
 
-    if ( trim ( ytype ) == 'CART' ) then
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'averaged on x dimension', Merge( 1, 0, tpbudiachro%licompress ) )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'averaged on x dimension '//trim(ygroup)//' group' )
 
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'averaged on y dimension', Merge( 1, 0, tpbudiachro%ljcompress ) )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'averaged on y dimension '//trim(ygroup)//' group' )
+    if (      ( ycategory == 'Budgets' .and. yshape == 'Cartesian' )           &
+         .or. ( ycategory == 'LES_budgets'    .and. yshape == 'Cartesian' )    &
+         .or. tpbudiachro%clevels(NLVL_GROUP)      == 'TSERIES'                &
+         .or. tpbudiachro%clevels(NLVL_GROUP)      == 'ZTSERIES'               &
+         .or. tpbudiachro%clevels(NLVL_GROUP)(1:8) == 'XTSERIES'               ) then
+      call Att_write( ylevelname, ilevelid, &
+                      'averaged_in_the_I_direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )
+      call Att_write( ylevelname, ilevelid, &
+                      'averaged_in_the_J_direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )
+      call Att_write( ylevelname, ilevelid, &
+                      'averaged_in_the_K_direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )
     end if
+  end if
+
+  if ( .not. gleveldefined(NLVL_TIMEAVG) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_TIMEAVG)
+    ilevelid   = ilevelids  (NLVL_TIMEAVG)
+
+    if ( tpbudiachro%lleveluse(NLVL_TIMEAVG) .and. Len_trim( tpbudiachro%ccomments(NLVL_TIMEAVG) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment',        tpbudiachro%ccomments(NLVL_TIMEAVG) )
+
+    call Att_write( ylevelname, ilevelid, 'time_averaged', Merge( 'yes', 'no ', tpbudiachro%ltcompress ) )
+  end if
 
-    if ( trim ( ytype ) == 'CART' .or. trim ( ytype ) == 'MASK' .or. trim ( ytype ) == 'SPXY') then
-      istatus = NF90_PUT_ATT( igrpid, NF90_GLOBAL, 'averaged on z dimension', Merge( 1, 0, tpbudiachro%lkcompress ) )
-      if (istatus /= NF90_NOERR ) &
-        call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', 'averaged on z dimension '//trim(ygroup)//' group' )
+  if ( .not. gleveldefined(NLVL_NORM) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_NORM)
+    ilevelid   = ilevelids  (NLVL_NORM)
+
+    if ( tpbudiachro%lleveluse(NLVL_NORM) .and. Len_trim( tpbudiachro%ccomments(NLVL_NORM) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment',   tpbudiachro%ccomments(NLVL_NORM) )
+
+    call Att_write( ylevelname, ilevelid, 'normalized', Merge( 'yes', 'no ', tpbudiachro%lnorm ) )
+
+    if ( ycategory == 'LES_budgets' .and. yshape == 'Cartesian' ) then
+      if ( tpbudiachro%lnorm ) then
+        if ( cles_norm_type == 'NONE' ) then
+          call Att_write( ylevelname, ilevelid, 'normalization', 'none' )
+        else if ( cles_norm_type == 'CONV' ) then
+          call Att_write( ylevelname, ilevelid, 'normalization', 'convective' )
+          ! cbl_height_def determines how the boundary layer height is computed, which is used in this normalization
+          call Att_write( ylevelname, ilevelid, 'definition_of_boundary_layer_height', cbl_height_def )
+        else if ( cles_norm_type == 'EKMA' ) then
+          call Att_write( ylevelname, ilevelid, 'normalization', 'Ekman' )
+          ! cbl_height_def determines how the boundary layer height is computed, which is used in this normalization
+          call Att_write( ylevelname, ilevelid, 'definition_of_boundary_layer_height', cbl_height_def )
+        else if ( cles_norm_type == 'MOBU' ) then
+          call Att_write( ylevelname, ilevelid, 'normalization', 'Monin-Obukhov' )
+        else
+          call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &
+                          ': group ' // Trim( tpbudiachro%clevels(NLVL_GROUP) ) // ': unknown normalization' )
+          call Att_write( ylevelname, ilevelid, 'normalization', 'unknown' )
+        end if
+      else
+      call Att_write( ylevelname, ilevelid, 'normalization', 'none' )
+      end if
     end if
   end if
 
-end if MASTER
+  if ( .not. gleveldefined(NLVL_MASK) ) then
+    ylevelname = tpbudiachro%clevels(NLVL_MASK)
+    ilevelid   = ilevelids  (NLVL_MASK)
 
+    call Att_write( ylevelname, ilevelid, 'mask',    ylevelname )
+    if ( tpbudiachro%lleveluse(NLVL_MASK) .and. Len_trim( tpbudiachro%ccomments(NLVL_MASK) ) > 0 ) &
+    call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_MASK) )
+
+    if ( ycategory == 'Budgets' .and. yshape == 'Mask' ) &
+    call Att_write( ylevelname, ilevelid, 'masks_are_stored_in_variable', tpbudiachro%clevels(NLVL_MASK) )
+  end if
+
+end if MASTER
 
 !Determine the number of dimensions and do some verifications
 do jp = 1, Size( tpfields )
@@ -848,12 +1030,12 @@ do jp = 2, Size( tpfields )
   end do
 end do
 
-!Check that if 'CART' and no horizontal compression, parameters are as expected
-if ( ytype == 'CART' .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then
+!Check that if cartesian and no horizontal compression, parameters are as expected
+if ( yshape == 'Cartesian' .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then
   icorr = Merge( 1, 0, tpbudiachro%lkcompress )
   if ( ( idims + icorr ) /= 3 .and. ( idims + icorr ) /= 4 ) then
-    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4',                                                 &
-                    'unexpected number of dimensions for CART without horizontal compression for variable ' &
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4',                                                            &
+                    'unexpected number of dimensions for cartesian shape without horizontal compression for variable ' &
                     // Trim( tpfields(1)%cmnhname ) )
   end if
 
@@ -866,7 +1048,7 @@ if ( ytype == 'CART' .and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%
        .or. (       .not. tpbudiachro%lkcompress                                                     &
               .and. tpfields(1)%ndimlist(3) /= NMNHDIM_BUDGET_CART_LEVEL           &
               .and. tpfields(1)%ndimlist(3) /= NMNHDIM_BUDGET_CART_LEVEL_W       ) &
-       .or. ( idims == 4 .and. tpfields(1)%ndimlist(6) /= NMNHDIM_BUDGET_NGROUPS ) ) then
+       .or. ( ( idims + icorr ) == 4 .and. tpfields(1)%ndimlist(6) /= NMNHDIM_BUDGET_NGROUPS ) ) then
     call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4',                                       &
                     'unexpected dimensions for CART without horizontal compression for variable ' &
                     // Trim( tpfields(1)%cmnhname ) )
@@ -877,40 +1059,41 @@ end if
 select case ( idims )
   case (0)
      !Remark: [ integer:: ] is a constructor for a zero-size array of integers, [] is not allowed (type can not be determined)
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ integer:: ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ integer:: ], gsplit, gdistributed )
 
   case (1)
 
-    if ( tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) then
+    if ( Any ( tpfields(1)%ndimlist(4) == [ NMNHDIM_BUDGET_LES_TIME, NMNHDIM_BUDGET_LES_AVG_TIME, NMNHDIM_SERIES_TIME ] ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
 
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 4 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 4 ], gsplit, gdistributed )
     else if ( Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI,     &
                                                 NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V              ] ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
 
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1 ], gsplit, gdistributed )
 
     else if ( Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_NJ, NMNHDIM_NJ_U, NMNHDIM_NJ_V, NMNHDIM_BUDGET_CART_NJ,     &
                                                 NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V              ] ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 2 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2 ], gsplit, gdistributed )
     else if ( Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_LEVEL, NMNHDIM_LEVEL_W,                            &
                                                 NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 3 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3 ], gsplit, gdistributed )
     else if ( tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
       do ji = 1, Size( pvar, 6 )
         !Remark: [ integer:: ] is a constructor for a zero-size array of integers, [] is not allowed (type can not be determined)
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ integer:: ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ integer:: ], &
+                                          gsplit, gdistributed )
       end do
     else
       call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
-                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )
+                      'case not yet implemented (1D variable '//trim(tpfields(1)%cmnhname)//')' )
     end if
 
 
@@ -922,7 +1105,7 @@ select case ( idims )
                                                  NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] )          ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1, 2 ], gsplit, gdistributed, &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 2 ], gsplit, gdistributed, &
                                         iil, iih, ijl, ijh, ikl, ikh )
     else if (       Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_NI, NMNHDIM_NI_U, NMNHDIM_NI_V, NMNHDIM_BUDGET_CART_NI, &
                                                       NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] )          &
@@ -930,72 +1113,94 @@ select case ( idims )
                                                       NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] )      ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1, 3 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 3 ], gsplit, gdistributed )
     else if (       Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_NJ, NMNHDIM_NJ_U, NMNHDIM_NJ_V, NMNHDIM_BUDGET_CART_NJ, &
                                                       NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] )          &
               .and. Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_LEVEL, NMNHDIM_LEVEL_W,                                 &
                                                       NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] )      ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 2, 3 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2, 3 ], gsplit, gdistributed )
     else if (  Any( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ] ) &
               .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 1 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1 ], gsplit, gdistributed )
       end do
     else if (  Any( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ] ) &
               .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 2 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 2 ], gsplit, gdistributed )
       end do
     else if (       tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL     &
        .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
                .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 3, 4 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4 ], gsplit, gdistributed )
     else if ( Any( tpfields(1)%ndimlist(3) == [ NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] ) &
               .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3 ], gsplit, gdistributed )
       end do
     else if (  tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 4, 5 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 4, 5 ], gsplit, gdistributed )
     else if (  (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
                  .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) &
          .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV       ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 4, 5 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 4, 5 ], gsplit, gdistributed )
     else if (  tpfields(1)%ndimlist(4) == NMNHDIM_FLYER_TIME &
          .and. tpfields(1)%ndimlist(6) == NMNHDIM_FLYER_PROC ) then
       !Correspond to FLYER_DIACHRO
       !Create local time dimension
       if ( isp == tzfile%nmaster_rank) then
-        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
-        if ( istatus /= NF90_NOERR ) &
-          call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
+        istatus = NF90_INQ_DIMID( ilevelids(NLVL_GROUP), 'time_flyer', idimid )
+        if ( istatus == NF90_NOERR ) then
+          !Dimension already exists, check that it is not changed
+          istatus = NF90_INQUIRE_DIMENSION( ilevelids(NLVL_GROUP), idimid, len = ilen )
+          if ( ilen /= Int( Size( pvar, 4), kind = CDFINT ) ) &
+            call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', 'time_flyer dimension has changed' )
+        else
+          !Dimension does not exist yet, create it
+          istatus = NF90_DEF_DIM( ilevelids(NLVL_GROUP), 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
+          if ( istatus /= NF90_NOERR ) &
+            call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
+        end if
       end if
 
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
       end do
     else if (  tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
          .and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
       !Correspond to WRITE_SERIES_n
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
+      end do
+    else if (  ( tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL_W ) &
+         .and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME ) then
+      !Correspond to WRITE_SERIES_n
+      if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
+                                                   'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar(:,:,:,:,:,:), [ 3, 4 ], gsplit, gdistributed )
+    else if (  tpfields(1)%ndimlist(4) == NMNHDIM_STATION_TIME &
+         .and. tpfields(1)%ndimlist(6) == NMNHDIM_STATION_PROC ) then
+      !Correspond to WRITE_STATION_n
+      ! Loop on the processes
+      do ji = 1, Size( pvar, 6 )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4 ], gsplit, gdistributed )
       end do
     else
       call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
-                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )
+                      'case not yet implemented (2D variable '//trim(tpfields(1)%cmnhname)//')' )
     end if
 
 
@@ -1009,15 +1214,15 @@ select case ( idims )
                                                  NMNHDIM_BUDGET_CART_LEVEL, NMNHDIM_BUDGET_CART_LEVEL_W ] )      ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1, 2, 3 ], gsplit, gdistributed, &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 2, 3 ], gsplit, gdistributed, &
                                         iil, iih, ijl, ijh, ikl, ikh )
     else if (       Any(tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U, NMNHDIM_BUDGET_CART_NI_V ]) &
               .and. Any(tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U, NMNHDIM_BUDGET_CART_NJ_V ]) &
               .and.     tpfields(1)%ndimlist(6) ==   NMNHDIM_BUDGET_NGROUPS                                                   ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 1, 2 ], gsplit, gdistributed, &
-                                          iil, iih, ijl, ijh, ikl, ikh )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 2 ], &
+                                          gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )
       end do
     else if (       Any ( tpfields(1)%ndimlist(1) == [ NMNHDIM_BUDGET_CART_NI, NMNHDIM_BUDGET_CART_NI_U,          &
                                                        NMNHDIM_BUDGET_CART_NI_V ] )                               &
@@ -1025,7 +1230,7 @@ select case ( idims )
               .and.       tpfields(1)%ndimlist(6) ==   NMNHDIM_BUDGET_NGROUPS                                     ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 1, 3 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 3 ], gsplit, gdistributed )
       end do
     else if (       Any ( tpfields(1)%ndimlist(2) == [ NMNHDIM_BUDGET_CART_NJ, NMNHDIM_BUDGET_CART_NJ_U,          &
                                                        NMNHDIM_BUDGET_CART_NJ_V ] )                               &
@@ -1033,7 +1238,7 @@ select case ( idims )
               .and.       tpfields(1)%ndimlist(6) ==   NMNHDIM_BUDGET_NGROUPS                                     ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 2, 3 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 2, 3 ], gsplit, gdistributed )
       end do
     else if (         (      tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL     &
                         .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL_W ) &
@@ -1042,7 +1247,7 @@ select case ( idims )
       !Correspond to Store_one_budget_rho (MASK)
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 3, 4, 5 ], gsplit, gdistributed, &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4, 5 ], gsplit, gdistributed, &
                                         iil, iih, ijl, ijh, ikl, ikh )
     else if (              tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL      &
               .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
@@ -1055,7 +1260,7 @@ select case ( idims )
 
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
       end do
     else if (       tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL     &
        .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME &
@@ -1063,7 +1268,7 @@ select case ( idims )
        .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_TERM      ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
       end do
     else if (              tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL      &
               .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
@@ -1071,7 +1276,7 @@ select case ( idims )
               .and.        tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_LES_SV         ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 3, 4, 5 ], gsplit, gdistributed, &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 3, 4, 5 ], gsplit, gdistributed, &
                                         iil, iih, ijl, ijh, ikl, ikh )
     else if (              tpfields(1)%ndimlist(1) == NMNHDIM_SPECTRA_2PTS_NI       &
               .and.        tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL         &
@@ -1079,7 +1284,7 @@ select case ( idims )
                       .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1, 3, 4 ], gsplit, gdistributed, &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 3, 4 ], gsplit, gdistributed, &
                                         iil, iih, ijl, ijh, ikl, ikh )
     else if (       tpfields(1)%ndimlist(2) == NMNHDIM_SPECTRA_2PTS_NJ                   &
               .and. tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL                &
@@ -1087,7 +1292,7 @@ select case ( idims )
                       .or. tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_AVG_TIME ) ) then
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 2, 3, 4 ], gsplit, gdistributed, &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2, 3, 4 ], gsplit, gdistributed, &
                                         iil, iih, ijl, ijh, ikl, ikh )
     else if ( ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W ) &
          .and. tpfields(1)%ndimlist(4) == NMNHDIM_FLYER_TIME &
@@ -1095,14 +1300,23 @@ select case ( idims )
       !Correspond to FLYER_DIACHRO
       !Create local time dimension
       if ( isp == tzfile%nmaster_rank) then
-        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
-        if ( istatus /= NF90_NOERR ) &
-          call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
+        istatus = NF90_INQ_DIMID( ilevelids(NLVL_GROUP), 'time_flyer', idimid )
+        if ( istatus == NF90_NOERR ) then
+          !Dimension already exists, check that it is not changed
+          istatus = NF90_INQUIRE_DIMENSION( ilevelids(NLVL_GROUP), idimid, len = ilen )
+          if ( ilen /= Int( Size( pvar, 4), kind = CDFINT ) ) &
+            call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', 'time_flyer dimension has changed' )
+        else
+          !Dimension does not exist yet, create it
+          istatus = NF90_DEF_DIM( ilevelids(NLVL_GROUP), 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
+          if ( istatus /= NF90_NOERR ) &
+            call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
+        end if
       end if
 
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
       end do
     else if (  ( tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_LEVEL_W ) &
          .and. tpfields(1)%ndimlist(4) == NMNHDIM_PROFILER_TIME &
@@ -1110,7 +1324,7 @@ select case ( idims )
       !Correspond to PROFILER_DIACHRO_n
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
       end do
     else if (  ( tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL .or. tpfields(1)%ndimlist(3) == NMNHDIM_SERIES_LEVEL_W ) &
          .and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
@@ -1118,7 +1332,7 @@ select case ( idims )
       !Correspond to PROFILER_DIACHRO_n
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4 ], gsplit, gdistributed )
       end do
     else if (  ( tpfields(1)%ndimlist(1) == NMNHDIM_NI .or. tpfields(1)%ndimlist(1) == NMNHDIM_NI_U )      &
          .and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
@@ -1126,25 +1340,25 @@ select case ( idims )
       !Correspond to PROFILER_DIACHRO_n
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 1, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 4 ], gsplit, gdistributed )
       end do
     else if (  ( tpfields(1)%ndimlist(2) == NMNHDIM_NJ .or. tpfields(1)%ndimlist(2) == NMNHDIM_NJ_U )      &
          .and. tpfields(1)%ndimlist(4) == NMNHDIM_SERIES_TIME &
          .and. tpfields(1)%ndimlist(6) == NMNHDIM_SERIES_PROC ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 2, 4 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 2, 4 ], gsplit, gdistributed )
       end do
     else if (       tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_TIME         &
               .and. tpfields(1)%ndimlist(5) == NMNHDIM_BUDGET_MASK_NBUMASK &
               .and. tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_NGROUPS      ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 4, 5 ], gsplit, gdistributed )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 4, 5 ], gsplit, gdistributed )
       end do
     else
       call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
-                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )
+                      'case not yet implemented (3D variable '//trim(tpfields(1)%cmnhname)//')' )
     end if
 
   case (4)
@@ -1156,8 +1370,8 @@ select case ( idims )
       !Correspond to Store_one_budget (CART)
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 1, 2, 3 ], gsplit, gdistributed, &
-                                          iil, iih, ijl, ijh, ikl, ikh )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 2, 3 ], &
+                                          gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )
       end do
     elseif (  (        tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL     &
                   .or. tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_MASK_LEVEL_W ) &
@@ -1167,8 +1381,8 @@ select case ( idims )
       !Correspond to Store_one_budget (MASK)
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], gsplit, gdistributed, &
-                                          iil, iih, ijl, ijh, ikl, ikh )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], &
+                                          gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )
       end do
     else if (              tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL      &
               .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
@@ -1182,8 +1396,8 @@ select case ( idims )
 
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], gsplit, gdistributed, &
-                                          iil, iih, ijl, ijh, ikl, ikh )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], &
+                                          gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )
       end do
     else if (              tpfields(1)%ndimlist(3) == NMNHDIM_BUDGET_LES_LEVEL      &
               .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
@@ -1192,8 +1406,8 @@ select case ( idims )
        .and.               tpfields(1)%ndimlist(6) == NMNHDIM_BUDGET_TERM           ) then
       ! Loop on the processes
       do ji = 1, Size( pvar, 6 )
-        call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], gsplit, gdistributed, &
-                                          iil, iih, ijl, ijh, ikl, ikh )
+        call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 3, 4, 5 ], &
+                                          gsplit, gdistributed, iil, iih, ijl, ijh, ikl, ikh )
       end do
     else if (             tpfields(1)%ndimlist(1) == NMNHDIM_SPECTRA_SPEC_NI       &
              .and.        tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL         &
@@ -1203,7 +1417,7 @@ select case ( idims )
       !Correspond to LES_DIACHRO_SPEC
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 1, 3, 4, 5 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 1, 3, 4, 5 ], gsplit, gdistributed )
     else if (              tpfields(1)%ndimlist(2) == NMNHDIM_SPECTRA_SPEC_NJ       &
               .and.        tpfields(1)%ndimlist(3) == NMNHDIM_SPECTRA_LEVEL         &
               .and. (      tpfields(1)%ndimlist(4) == NMNHDIM_BUDGET_LES_TIME       &
@@ -1212,10 +1426,10 @@ select case ( idims )
       !Correspond to LES_DIACHRO_SPEC
       if ( Size( tpfields ) /= 1 ) call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
                                                    'wrong size of tpfields (variable '//trim(tpfields(1)%cmnhname)//')' )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(1), ytype, pvar, [ 2, 3, 4, 5 ], gsplit, gdistributed )
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(1), pvar, [ 2, 3, 4, 5 ], gsplit, gdistributed )
     else
       call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_nc4', &
-                      'case not yet implemented (variable '//trim(tpfields(1)%cmnhname)//')' )
+                      'case not yet implemented (4D variable '//trim(tpfields(1)%cmnhname)//')' )
     end if
 
 !   case (5)
@@ -1224,7 +1438,7 @@ select case ( idims )
 
   case default
     do ji = 1, Size( pvar, 6 )
-      call Diachro_one_field_write_nc4( tzfile, tpfields(ji), ytype, pvar(:,:,:,:,:,ji:ji), [ 1, 2, 3, 4, 5 ], &
+      call Diachro_one_field_write_nc4( tzfile, tpbudiachro, tpfields(ji), pvar(:,:,:,:,:,ji:ji), [ 1, 2, 3, 4, 5 ], &
                                         gsplit, gdistributed )
     end do
 
@@ -1260,19 +1474,12 @@ if ( Present( tpflyer ) ) then
   call IO_Field_write( tzfile, tzfield, tpflyer%y )
 end if
 
-
-
-
-
-!
-
-!Restore id of the file root group ('/' group)
-tzfile%nncid = isavencid
-
 end  subroutine Write_diachro_nc4
 
-subroutine Diachro_one_field_write_nc4( tpfile, tpfield, htype, pvar, kdims, osplit, odistributed, kil, kih, kjl, kjh, kkl, kkh )
-use modd_budget,      only: nbutshift, nbusubwrite
+
+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_io,          only: isp, tfiledata
 use modd_parameters,  only: jphext
@@ -1280,8 +1487,8 @@ 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
-character(len=*),                                    intent(in)  :: htype
 real,                        dimension(:,:,:,:,:,:), intent(in)  :: pvar
 integer, dimension(:),                               intent(in)  :: kdims        !List of indices of dimensions to use
 logical,                                             intent(in)  :: osplit
@@ -1307,13 +1514,13 @@ type(tfielddata)                                           :: tzfield
 idims = Size( kdims )
 
 if ( odistributed ) then
-  if ( idims /= 2 .and. idims /= 3 )                                                                                  &
+  if ( idims /= 2 .and. idims /= 3 )                                                                 &
     call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4',                                &
                    'odistributed=.true. not allowed for dims/=3, field: ' //Trim( tzfield%cmnhname ) )
 
-  if ( htype /= 'CART' )                                                                                 &
-    call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4',                                    &
-                   'odistributed=.true. not allowed for htype/=CART, field: ' //Trim( tzfield%cmnhname ) )
+  if ( tpbudiachro%clevels(NLVL_SHAPE) /= 'Cartesian' )                                                                    &
+    call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4',                                         &
+                   'odistributed=.true. not allowed for shape/=cartesian, field: ' //Trim( tzfield%cmnhname ) )
 end if
 
 if ( osplit ) then
@@ -1321,9 +1528,9 @@ if ( osplit ) then
     call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4',                                       &
                                  'osplit=.true. not allowed for dims>3, field: ' //Trim( tzfield%cmnhname ) )
 
-  if ( htype /= 'CART' .and. htype /= 'MASK' )                                                                 &
-    call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4',                                          &
-                    'osplit=.true. not allowed for htype/=CART and /=MASK, field: ' //Trim( tzfield%cmnhname ) )
+  if ( tpbudiachro%clevels(NLVL_CATEGORY) /= 'Budgets' )                                                  &
+    call Print_msg( NVERB_FATAL, 'IO', 'Diachro_one_field_write_nc4',                                    &
+                    'osplit=.true. not allowed for category/=budget, field: ' //Trim( tzfield%cmnhname ) )
 end if
 
 Allocate( isizes(idims) )
@@ -1581,6 +1788,207 @@ if ( osplit ) then
 end if
 
 end subroutine Prepare_diachro_write
+
+
+subroutine Att_write_c0( hlevel, kgrpid, hattname, hdata )
+use NETCDF,            only: NF90_GET_ATT, NF90_INQUIRE_ATTRIBUTE, NF90_PUT_ATT, NF90_CHAR, NF90_GLOBAL, NF90_NOERR
+
+use modd_precision,    only: CDFINT
+
+use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean
+
+character(len=*),     intent(in) :: hlevel
+integer(kind=CDFINT), intent(in) :: kgrpid
+character(len=*),     intent(in) :: hattname
+character(len=*),     intent(in) :: hdata
+
+character(len=Len(hattname))  :: yattname
+character(len=:), allocatable :: yatt
+integer(kind=CDFINT)          :: ilen
+integer(kind=CDFINT)          :: istatus
+integer(kind=CDFINT)          :: itype
+
+call IO_Mnhname_clean( hattname, yattname )
+
+istatus = NF90_INQUIRE_ATTRIBUTE( kgrpid, NF90_GLOBAL, yattname, xtype = itype, len = ilen )
+if (istatus == NF90_NOERR ) then
+  call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' already exists for ' // Trim( hlevel ) )
+
+  if ( itype /= NF90_CHAR ) then
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'type for attribute ' // yattname // &
+                    ' has changed for ' // Trim( hlevel ) )
+    return
+  end if
+
+  Allocate( character(len=ilen) :: yatt )
+  istatus = NF90_GET_ATT( kgrpid, NF90_GLOBAL, yattname, yatt )
+  if ( yatt == Trim( hdata ) ) then
+    call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' is unchanged for ' // Trim( hlevel ) )
+    !If unchanged, no need to write it again => return
+    return
+  else
+    cmnhmsg(1) = 'attribute ' // yattname // ' has changed for ' // Trim( hlevel )
+    cmnhmsg(2) = yatt // ' -> ' // Trim( hdata )
+    call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4' )
+  end if
+
+end if
+
+istatus = NF90_PUT_ATT( kgrpid, NF90_GLOBAL, yattname, Trim( hdata ) )
+if (istatus /= NF90_NOERR ) &
+ call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', Trim( yattname ) // ' for '// Trim( hlevel ) // ' group' )
+
+end subroutine Att_write_c0
+
+
+subroutine Att_write_i0( hlevel, kgrpid, hattname, kdata )
+use NETCDF,            only: NF90_GET_ATT, NF90_INQUIRE_ATTRIBUTE, NF90_PUT_ATT, NF90_GLOBAL, NF90_NOERR
+
+use modd_precision,    only: CDFINT, MNHINT_NF90
+
+use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean
+
+character(len=*),     intent(in) :: hlevel
+integer(kind=CDFINT), intent(in) :: kgrpid
+character(len=*),     intent(in) :: hattname
+integer,              intent(in) :: kdata
+
+character(len=Len(hattname)) :: yattname
+integer              :: iatt
+integer(kind=CDFINT) :: ilen
+integer(kind=CDFINT) :: istatus
+integer(kind=CDFINT) :: itype
+
+call IO_Mnhname_clean( hattname, yattname )
+
+istatus = NF90_INQUIRE_ATTRIBUTE( kgrpid, NF90_GLOBAL, yattname, xtype = itype, len = ilen )
+if (istatus == NF90_NOERR ) then
+  call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' already exists for ' // Trim( hlevel ) )
+
+  if ( itype /= MNHINT_NF90 ) then
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'type for attribute ' // yattname // &
+                    ' has changed for ' // Trim( hlevel ) )
+    return
+  end if
+
+  if ( ilen /= 1 ) then
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'size of attribute ' // yattname // &
+                    ' has changed for ' // Trim( hlevel ) )
+    return
+  end if
+
+  istatus = NF90_GET_ATT( kgrpid, NF90_GLOBAL, yattname, iatt )
+  if ( iatt == kdata ) then
+    call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' is unchanged for ' // Trim( hlevel ) )
+    !If unchanged, no need to write it again => return
+    return
+  else
+    cmnhmsg(1) = 'attribute ' // yattname // ' has changed for ' // Trim( hlevel )
+    Write( cmnhmsg(2), '( I0, " -> ", I0 )' ) iatt, kdata
+    call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4' )
+  end if
+
+end if
+
+istatus = NF90_PUT_ATT( kgrpid, NF90_GLOBAL, yattname, kdata )
+if (istatus /= NF90_NOERR ) &
+ call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', Trim( yattname ) // ' for '// Trim( hlevel ) // ' group' )
+
+end subroutine Att_write_i0
+
+
+subroutine Att_write_x0( hlevel, kgrpid, hattname, pdata )
+use NETCDF,            only: NF90_GET_ATT, NF90_INQUIRE_ATTRIBUTE, NF90_PUT_ATT, NF90_GLOBAL, NF90_NOERR
+
+use modd_precision,    only: CDFINT, MNHREAL_NF90
+
+use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean
+
+character(len=*),     intent(in) :: hlevel
+integer(kind=CDFINT), intent(in) :: kgrpid
+character(len=*),     intent(in) :: hattname
+real,                 intent(in) :: pdata
+
+character(len=Len(hattname)) :: yattname
+integer(kind=CDFINT) :: ilen
+integer(kind=CDFINT) :: istatus
+integer(kind=CDFINT) :: itype
+real                 :: zatt
+
+call IO_Mnhname_clean( hattname, yattname )
+
+istatus = NF90_INQUIRE_ATTRIBUTE( kgrpid, NF90_GLOBAL, yattname, xtype = itype, len = ilen )
+if (istatus == NF90_NOERR ) then
+  call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' already exists for ' // Trim( hlevel ) )
+
+  if ( itype /= MNHREAL_NF90 ) then
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'type for attribute ' // yattname // &
+                    ' has changed for ' // Trim( hlevel ) )
+    return
+  end if
+
+  if ( ilen /= 1 ) then
+    call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_nc4', 'size of attribute ' // yattname // &
+                    ' has changed for ' // Trim( hlevel ) )
+    return
+  end if
+
+  istatus = NF90_GET_ATT( kgrpid, NF90_GLOBAL, yattname, zatt )
+  if ( zatt == pdata ) then
+    call Print_msg( NVERB_DEBUG, 'IO', 'Write_diachro_nc4', 'attribute ' // yattname // ' is unchanged for ' // Trim( hlevel ) )
+    !If unchanged, no need to write it again => return
+    return
+  else
+    cmnhmsg(1) = 'attribute ' // yattname // ' has changed for ' // Trim( hlevel )
+    Write( cmnhmsg(2), '( F15.7, " -> ", F15.7 )' ) zatt, pdata
+    call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4' )
+  end if
+
+end if
+
+istatus = NF90_PUT_ATT( kgrpid, NF90_GLOBAL, yattname, pdata )
+if (istatus /= NF90_NOERR ) &
+ call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_PUT_ATT', Trim( yattname ) // ' for '// Trim( hlevel ) // ' group' )
+
+end subroutine Att_write_x0
+
+
+subroutine Move_to_next_level( kpreviouslevelid, gpreviousleveldefined, oleveluse, hlevelname, gleveldefined, klevelid )
+use NETCDF,            only: NF90_DEF_GRP, NF90_INQ_NCID, NF90_NOERR
+
+use modd_precision,    only: CDFINT
+
+use mode_io_tools_nc4, only: IO_Err_handle_nc4, IO_Mnhname_clean
+
+integer(kind=CDFINT), intent(in)    :: kpreviouslevelid
+logical,              intent(in)    :: gpreviousleveldefined
+logical,              intent(in)    :: oleveluse
+! character(len=*),     intent(inout) :: hlevelname
+character(len=*),     intent(in)    :: hlevelname
+logical,              intent(out)   :: gleveldefined
+integer(kind=CDFINT), intent(out)   :: klevelid
+
+character(len=Len(hlevelname)) :: ylevelname
+integer(kind=CDFINT) :: istatus
+
+call IO_Mnhname_clean( hlevelname, ylevelname )
+
+if ( oleveluse ) then
+  istatus = NF90_INQ_NCID( kpreviouslevelid, Trim( ylevelname ), klevelid )
+  if ( istatus == NF90_NOERR ) then
+    gleveldefined = .true.
+  else
+    gleveldefined = .false.
+    istatus = NF90_DEF_GRP( kpreviouslevelid, Trim( ylevelname ), klevelid )
+    if ( istatus /= NF90_NOERR ) &
+      call IO_Err_handle_nc4( istatus, 'Move_to_next_level', 'NF90_DEF_GRP', 'for ' // Trim( ylevelname ) )
+  end if
+else
+  gleveldefined = gpreviousleveldefined
+  klevelid = kpreviouslevelid
+end if
+
+end subroutine Move_to_next_level
 #endif
 
 end module mode_write_diachro
diff --git a/src/MNH/write_les_budgetn.f90 b/src/MNH/write_les_budgetn.f90
index 3e54c2e3a8d46ea7dbabe980e0315fdb2b2cac9e..fec25b5ea6ee41a77ebf0b8f659e8b47d5c3154b 100644
--- a/src/MNH/write_les_budgetn.f90
+++ b/src/MNH/write_les_budgetn.f90
@@ -131,7 +131,7 @@ gdonorm = Trim( cles_norm_type ) /= 'NONE'
 !*      1.  total (resolved+subgrid) kinetic energy budget
 !            ------------------------------------
 !
-YGROUP= 'BU_KE   '
+YGROUP= 'BU_KE'
 ILES=0
 ILES_STA=ILES
 !
@@ -139,7 +139,7 @@ ILES_STA=ILES
 !     --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TEND'
+YSUBTITLE(ILES) = 'SBG_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_TEND)
 !
@@ -148,7 +148,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_TEND)
 !     ---------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 !
 ZLES_BUDGET(:,:,ILES)= - XLES_SUBGRID_WU (:,:,1) * XLES_MEAN_DUDZ(:,:,1)  &
                        - XLES_SUBGRID_WV (:,:,1) * XLES_MEAN_DVDZ(:,:,1)  &
@@ -158,7 +158,7 @@ ZLES_BUDGET(:,:,ILES)= - XLES_SUBGRID_WU (:,:,1) * XLES_MEAN_DUDZ(:,:,1)  &
 !     ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_DP) - ZLES_BUDGET(:,:,2)
 !
@@ -169,7 +169,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_DP) - ZLES_BUDGET(:,:,2)
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG ADVM'
+YSUBTITLE(ILES) = 'SBG_ADVM'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_ADVM)
 END IF
@@ -180,7 +180,7 @@ END IF
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG FORC'
+YSUBTITLE(ILES) = 'SBG_FORC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_FORC)
 END IF
@@ -190,7 +190,7 @@ END IF
 !      -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_TR)
 !
@@ -199,7 +199,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_TR)
 !      -----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG ADVR'
+YSUBTITLE(ILES) = 'SBG_ADVR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_ADVR)
 !
@@ -209,7 +209,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_ADVR)
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_PRES)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG PRES'
+YSUBTITLE(ILES) = 'SBG_PRES'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_PRES)
 END IF
@@ -219,7 +219,7 @@ END IF
 !      ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TP'
+YSUBTITLE(ILES) = 'SBG_TP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_TP)
 !
@@ -228,7 +228,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_TP)
 !       -----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS'
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_DISS)
 !
@@ -238,7 +238,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_DISS)
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG NUMD'
+YSUBTITLE(ILES) = 'SBG_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_DIFF)
 END IF
@@ -248,7 +248,7 @@ END IF
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RELA'
+YSUBTITLE(ILES) = 'SBG_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_RELA)
 END IF
@@ -258,7 +258,7 @@ END IF
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG NEST'
+YSUBTITLE(ILES) = 'SBG_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_NEST)
 END IF
@@ -269,7 +269,7 @@ END IF
 !
 IF ( ANY(XLES_BU_SBG_TKE(:,:,NLES_MISC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG MISC'
+YSUBTITLE(ILES) = 'SBG_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_SBG_TKE(:,:,NLES_MISC)
 END IF
@@ -279,7 +279,7 @@ END IF
 !       --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -292,7 +292,7 @@ ILES_STA=ILES
 !       --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_TEND)
 !
@@ -302,7 +302,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_TEND)
 !
 IF ( ANY(XLES_BU_RES_KE(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES ADV '
+YSUBTITLE(ILES) = 'RES_ADV'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_Ke(:,:,NLES_ADVM)
 END IF
@@ -313,7 +313,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_KE(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES FORC'
+YSUBTITLE(ILES) = 'RES_FORC'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_Ke(:,:,NLES_FORC)
 END IF
@@ -323,7 +323,7 @@ END IF
 !       --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Ke(:,:,NLES_DP)
 !
@@ -332,7 +332,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Ke(:,:,NLES_DP)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_TR)
 !
@@ -342,7 +342,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_TR)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES PRES'
+YSUBTITLE(ILES) = 'RES_PRES'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_PRES)
 !
@@ -351,7 +351,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_PRES)
 !       ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TP  '
+YSUBTITLE(ILES) = 'RES_TP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_GRAV)
 !
@@ -360,7 +360,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_GRAV)
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_VTURB) + XLES_BU_RES_KE(:,:,NLES_HTURB)
 !
@@ -369,7 +369,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_VTURB) + XLES_BU_RES_KE(:,:,NLES
 !
 IF ( ANY(XLES_BU_RES_KE(:,:,NLES_COR)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES CORI'
+YSUBTITLE(ILES) = 'RES_CORI'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_COR)
 END IF
@@ -379,7 +379,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_KE(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NUMD'
+YSUBTITLE(ILES) = 'RES_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_DIFF)
 END IF
@@ -389,7 +389,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_KE(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RELA'
+YSUBTITLE(ILES) = 'RES_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_RELA)
 END IF
@@ -399,7 +399,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_KE(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NEST'
+YSUBTITLE(ILES) = 'RES_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_NEST)
 END IF
@@ -411,7 +411,7 @@ END IF
 IF ( ANY( XLES_BU_RES_KE(:,:,NLES_MISC) &
          +XLES_BU_RES_KE(:,:,NLES_CURV) /= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES MISC'
+YSUBTITLE(ILES) = 'RES_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_KE(:,:,NLES_MISC)  &
                       + XLES_BU_RES_KE(:,:,NLES_CURV)
@@ -421,7 +421,7 @@ END IF
 !       ------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -438,7 +438,7 @@ tzfield%clongname = ygroup
 tzfield%ccomment  = 'resolved KE budget'
 tzfield%cunits    = 'm2 s-3'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
@@ -446,7 +446,7 @@ call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles),
 !*      2.  temperature variance budget
 !           ---------------------------
 !
-YGROUP= 'BU_THL2 '
+YGROUP= 'BU_THL2'
 ILES=0
 !
 ILES_STA=ILES
@@ -455,7 +455,7 @@ ILES_STA=ILES
 !      ----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 ZLES_BUDGET(:,:,ILES)= - 2. * XLES_SUBGRID_WThl(:,:,1) * XLES_MEAN_dThldz(:,:,1)
@@ -466,7 +466,7 @@ ZLES_BUDGET(:,:,ILES)= - 2. * XLES_SUBGRID_WThl(:,:,1) * XLES_MEAN_dThldz(:,:,1)
 !
 IF ( ANY(XLES_SUBGRID_WThl2(:,:,1)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES) = - ( XLES_SUBGRID_WThl2 (JK+1,:,1)      &
@@ -483,7 +483,7 @@ END IF
 !      --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 ILES_P2=ILES
 !
 ZLES_BUDGET(:,:,ILES)= - 2. * XLES_RES_ddxa_Thl_SBG_UaThl(:,:,1)  &
@@ -494,7 +494,7 @@ ZLES_BUDGET(:,:,ILES)= - 2. * XLES_RES_ddxa_Thl_SBG_UaThl(:,:,1)  &
 !      -----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS    '
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_DISS_Thl2(:,:,1)
 !
@@ -503,7 +503,7 @@ ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_DISS_Thl2(:,:,1)
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -516,7 +516,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_TEND)
 !
@@ -526,7 +526,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_TEND)
 !
 IF ( ANY(XLES_BU_RES_Thl2(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES ADV '
+YSUBTITLE(ILES) = 'RES_ADV'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_ADVM)
 END IF
@@ -537,7 +537,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Thl2(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES FORC'
+YSUBTITLE(ILES) = 'RES_FORC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_FORC)
 END IF
@@ -547,7 +547,7 @@ END IF
 !      ----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_DP)
 
@@ -556,7 +556,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_DP)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_TR)
 !
@@ -565,7 +565,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_TR)
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_VTURB) + XLES_BU_RES_Thl2(:,:,NLES_HTURB)
 !
@@ -574,7 +574,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_VTURB) + XLES_BU_RES_Thl2(:,:,
 !
 IF ( ANY(XLES_BU_RES_Thl2(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NUMD'
+YSUBTITLE(ILES) = 'RES_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_DIFF)
 END IF
@@ -584,7 +584,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Thl2(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RELA'
+YSUBTITLE(ILES) = 'RES_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_RELA)
 END IF
@@ -594,7 +594,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Thl2(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NEST'
+YSUBTITLE(ILES) = 'RES_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_NEST)
 END IF
@@ -607,7 +607,7 @@ IF ( ANY( XLES_BU_RES_Thl2(:,:,NLES_MISC) &
          +XLES_BU_RES_Thl2(:,:,NLES_MICR) &
          + XLES_BU_RES_Thl2(:,:,NLES_PREF) /= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES MISC'
+YSUBTITLE(ILES) = 'RES_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Thl2(:,:,NLES_MISC) &
                       + XLES_BU_RES_Thl2(:,:,NLES_RAD ) &
@@ -620,7 +620,7 @@ END IF
 !       ---------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -631,7 +631,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG TEND'
+YSUBTITLE(ILES) = 'NSG_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 IF (NLES_TIMES>2) THEN
@@ -650,7 +650,7 @@ END IF
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)=  -XLES_MEAN_W(JK,:,1)                 &
@@ -667,7 +667,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - ( XLES_RES_W_SBG_Thl2   (JK+1,:,1)    &
@@ -690,14 +690,14 @@ tzfield%clongname = ygroup
 tzfield%ccomment  = 'thetal variance budget'
 tzfield%cunits    = 'K2 s-1'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
 !*      3.  temperature flux budget
 !            ---------------------
 !
-YGROUP= 'BU_WTHL '
+YGROUP= 'BU_WTHL'
 ILES=0
 !
 ILES_STA=ILES
@@ -706,7 +706,7 @@ ILES_STA=ILES
 !     -----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 ZLES_BUDGET(:,:,ILES) =  - XLES_SUBGRID_W2(:,:,1) * XLES_MEAN_dThldz(:,:,1)
@@ -716,7 +716,7 @@ ZLES_BUDGET(:,:,ILES) =  - XLES_SUBGRID_W2(:,:,1) * XLES_MEAN_dThldz(:,:,1)
 !     -------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 !
 ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddz_Thl_SBG_W2(:,:,1) &
                       - ZLES_BUDGET(:,:,ILES_P1)
@@ -727,7 +727,7 @@ ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddz_Thl_SBG_W2(:,:,1) &
 !
 IF ( ANY(XLES_SUBGRID_W2Thl(:,:,1)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES) = - ( XLES_SUBGRID_W2Thl (JK+1,:,1)       &
@@ -746,7 +746,7 @@ END IF
 !
 IF ( ANY(XLES_SUBGRID_ThlPz(:,:,1)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG PRES'
+YSUBTITLE(ILES) = 'SBG_PRES'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_ThlPz(:,:,1)
 END IF
@@ -756,7 +756,7 @@ END IF
 !      ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TP  '
+YSUBTITLE(ILES) = 'SBG_TP'
 !
 IF (LUSERV) THEN
   ZLES_BUDGET(:,:,ILEs) =  XG * XLES_SUBGRID_ThlThv(:,:,1)   &
@@ -773,7 +773,7 @@ END IF
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -786,7 +786,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_TEND)
 !
@@ -795,7 +795,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_TEND)
 !
 IF ( ANY(XLES_BU_RES_WThl(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES ADV '
+YSUBTITLE(ILES) = 'RES_ADV'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_WThl(:,:,NLES_ADVM)
 END IF
@@ -805,7 +805,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WThl(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES FORC'
+YSUBTITLE(ILES) = 'RES_FORC'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_WThl(:,:,NLES_FORC)
 END IF
@@ -815,7 +815,7 @@ END IF
 !       ----------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_WThl(:,:,NLES_DP)
 !
@@ -823,7 +823,7 @@ ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_WThl(:,:,NLES_DP)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_WThl(:,:,NLES_TR)
 !
@@ -832,7 +832,7 @@ ZLES_BUDGET(:,:,ILES) =  XLES_BU_RES_WThl(:,:,NLES_TR)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES PRES'
+YSUBTITLE(ILES) = 'RES_PRES'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_PRES)
 !
@@ -841,7 +841,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_PRES)
 !       ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TP  '
+YSUBTITLE(ILES) = 'RES_TP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_GRAV)
 !
@@ -850,7 +850,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_GRAV)
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_VTURB) + XLES_BU_RES_WThl(:,:,NLES_HTURB)
 !
@@ -859,7 +859,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_VTURB) + XLES_BU_RES_WThl(:,:,
 !
 IF ( ANY(XLES_BU_RES_WThl(:,:,NLES_COR)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES CORI'
+YSUBTITLE(ILES) = 'RES_CORI'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_COR)
 END IF
@@ -869,7 +869,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WThl(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NUMD'
+YSUBTITLE(ILES) = 'RES_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_DIFF)
 END IF
@@ -879,7 +879,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WThl(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RELA'
+YSUBTITLE(ILES) = 'RES_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_RELA)
 END IF
@@ -889,7 +889,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WThl(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NEST'
+YSUBTITLE(ILES) = 'RES_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_NEST)
 END IF
@@ -903,7 +903,7 @@ IF ( ANY( XLES_BU_RES_WThl(:,:,NLES_MISC) &
          +XLES_BU_RES_WThl(:,:,NLES_PREF) &
          +XLES_BU_RES_WThl(:,:,NLES_CURV) /= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES MISC'
+YSUBTITLE(ILES) = 'RES_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WThl(:,:,NLES_MISC) &
                       + XLES_BU_RES_WThl(:,:,NLES_RAD ) &
@@ -917,7 +917,7 @@ END IF
 !       --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -928,7 +928,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG TEND'
+YSUBTITLE(ILES) = 'NSG_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 IF (NLES_TIMES>2) THEN
@@ -949,7 +949,7 @@ END IF
 !       ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - XLES_MEAN_W(JK,:,1)                               &
@@ -966,7 +966,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - ( XLES_RES_W_SBG_WThl(JK+1,:,1)   &
@@ -982,7 +982,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ----------------------------------------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG DPGW'
+YSUBTITLE(ILES) = 'NSG_DPGW'
 !
 ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddxa_W_SBG_UaThl(:,:,1)
 !
@@ -991,7 +991,7 @@ ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddxa_W_SBG_UaThl(:,:,1)
 !       -------------------------------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG DPGT'
+YSUBTITLE(ILES) = 'NSG_DPGT'
 !
 ZLES_BUDGET(:,:,ILES)=-XLES_RES_ddxa_Thl_SBG_UaW(:,:,1)       &
                       -ZLES_BUDGET(:,:,ILES_P1) -ZLES_BUDGET(:,:,ILES_P2)
@@ -1008,7 +1008,7 @@ tzfield%clongname = ygroup
 tzfield%ccomment  = 'thetal flux budget'
 tzfield%cunits    = 'm K s-2'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
diff --git a/src/MNH/write_les_rt_budgetn.f90 b/src/MNH/write_les_rt_budgetn.f90
index 595556a566827243497e934ab67194aeaf397065..e2cb0096113e8b44e841339a15fc495dd93453bd 100644
--- a/src/MNH/write_les_rt_budgetn.f90
+++ b/src/MNH/write_les_rt_budgetn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2002-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2002-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.
@@ -125,7 +125,7 @@ gdonorm = Trim( cles_norm_type ) /= 'NONE'
 !           ---------------------------
 !
 !
-YGROUP= 'BU_RT2  '
+YGROUP= 'BU_RT2'
 ILES=0
 ILES_STA=ILES
 !
@@ -134,7 +134,7 @@ ILES_STA=ILES
 !      ----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 ZLES_BUDGET(:,:,ILES)= - 2. * XLES_SUBGRID_WRt(:,:,1) * XLES_MEAN_dRtdz(:,:,1)
@@ -144,7 +144,7 @@ ZLES_BUDGET(:,:,ILES)= - 2. * XLES_SUBGRID_WRt(:,:,1) * XLES_MEAN_dRtdz(:,:,1)
 !      --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 !
 ZLES_BUDGET(:,:,ILES)= - 2. * XLES_RES_ddxa_Rt_SBG_UaRt(:,:,1)  &
                           - ZLES_BUDGET(:,:,ILES_P1)
@@ -155,7 +155,7 @@ ZLES_BUDGET(:,:,ILES)= - 2. * XLES_RES_ddxa_Rt_SBG_UaRt(:,:,1)  &
 !
 IF ( ANY(XLES_SUBGRID_WRt2(:,:,1)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES) = - ( XLES_SUBGRID_WRt2 (JK+1,:,1)      &
@@ -172,7 +172,7 @@ END IF
 !      -----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS    '
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_DISS_Rt2(:,:,1)
 !
@@ -181,7 +181,7 @@ ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_DISS_Rt2(:,:,1)
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -194,7 +194,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_TEND)
 !
@@ -204,7 +204,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_TEND)
 !
 IF ( ANY(XLES_BU_RES_Rt2(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES ADV '
+YSUBTITLE(ILES) = 'RES_ADV'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_ADVM)
 END IF
@@ -214,7 +214,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Rt2(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES FORC'
+YSUBTITLE(ILES) = 'RES_FORC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_FORC)
 END IF
@@ -224,7 +224,7 @@ END IF
 !      ----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_DP)
 
@@ -233,7 +233,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_DP)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_TR)
 !
@@ -242,7 +242,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_TR)
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_VTURB) + XLES_BU_RES_Rt2(:,:,NLES_HTURB)
 !
@@ -252,7 +252,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_VTURB) + XLES_BU_RES_Rt2(:,:,NL
 !
 IF ( ANY(XLES_BU_RES_Rt2(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NUMD'
+YSUBTITLE(ILES) = 'RES_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_DIFF)
 END IF
@@ -262,7 +262,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Rt2(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RELA'
+YSUBTITLE(ILES) = 'RES_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_RELA)
 END IF
@@ -272,7 +272,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Rt2(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NEST'
+YSUBTITLE(ILES) = 'RES_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_NEST)
 END IF
@@ -283,7 +283,7 @@ END IF
 IF ( ANY( XLES_BU_RES_Rt2(:,:,NLES_MISC) &
          +XLES_BU_RES_Rt2(:,:,NLES_MICR)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES MISC'
+YSUBTITLE(ILES) = 'RES_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_Rt2(:,:,NLES_MISC) &
                       + XLES_BU_RES_Rt2(:,:,NLES_MICR)
@@ -294,7 +294,7 @@ END IF
 !       ---------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -305,7 +305,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG TEND'
+YSUBTITLE(ILES) = 'NSG_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 IF (NLES_TIMES>2) THEN
@@ -324,7 +324,7 @@ END IF
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)=  -XLES_MEAN_W(JK,:,1)                &
@@ -341,7 +341,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - ( XLES_RES_W_SBG_Rt2   (JK+1,:,1)    &
@@ -363,7 +363,7 @@ tzfield%clongname = ygroup
 tzfield%ccomment  = 'Rt variance budget'
 tzfield%cunits    = 'kg2 kg-2 s-1'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
@@ -371,7 +371,7 @@ call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles),
 !           -----------------------
 !
 !
-YGROUP= 'BU_WRT  '
+YGROUP= 'BU_WRT'
 ILES=0
 ILES_STA=ILES
 !
@@ -379,7 +379,7 @@ ILES_STA=ILES
 !     -----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 ZLES_BUDGET(:,:,ILES) =  - XLES_SUBGRID_W2(:,:,1) * XLES_MEAN_dRtdz(:,:,1)
@@ -389,7 +389,7 @@ ZLES_BUDGET(:,:,ILES) =  - XLES_SUBGRID_W2(:,:,1) * XLES_MEAN_dRtdz(:,:,1)
 !     -------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(2) = ' SBG DP R'
+YSUBTITLE(2) = 'SBG_DP_R'
 ILES_P2=ILES
 !
 ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddz_Rt_SBG_W2(:,:,1) &
@@ -402,7 +402,7 @@ ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddz_Rt_SBG_W2(:,:,1) &
 !
 IF ( ANY(XLES_SUBGRID_W2Rt(:,:,1)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES) = - ( XLES_SUBGRID_W2Rt (JK+1,:,1)       &
@@ -420,7 +420,7 @@ END IF
 !      -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG PRES'
+YSUBTITLE(ILES) = 'SBG_PRES'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_RtPz(:,:,1)
 !
@@ -429,7 +429,7 @@ ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_RtPz(:,:,1)
 !      ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TP  '
+YSUBTITLE(ILES) = 'SBG_TP'
 !
 ZLES_BUDGET(:,:,ILES) =  XG * XLES_SUBGRID_RtThv(:,:,1)   &
                             / XLES_MEAN_Thv     (:,:,1)
@@ -438,8 +438,9 @@ ZLES_BUDGET(:,:,ILES) =  XG * XLES_SUBGRID_RtThv(:,:,1)   &
 !* 3.6 dissipation
 !      -----------
 !
+!PW: not in the documentation, but set to 0 anyway
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS    '
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 !
@@ -448,7 +449,7 @@ ZLES_BUDGET(:,:,ILES) = 0.
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -461,7 +462,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_TEND)
 !
@@ -470,7 +471,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_TEND)
 !
 IF ( ANY(XLES_BU_RES_WRt(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES ADV '
+YSUBTITLE(ILES) = 'RES_ADV'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_ADVM)
 END IF
@@ -480,7 +481,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WRt(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES FORC'
+YSUBTITLE(ILES) = 'RES_FORC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_FORC)
 END IF
@@ -489,7 +490,7 @@ END IF
 !       ----------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_DP)
 !
@@ -497,7 +498,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_DP)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_TR)
 !
@@ -506,7 +507,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_TR)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES PRES'
+YSUBTITLE(ILES) = 'RES_PRES'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_PRES)
 !
@@ -515,7 +516,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_PRES)
 !       ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TP  '
+YSUBTITLE(ILES) = 'RES_TP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_GRAV)
 !
@@ -524,7 +525,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_GRAV)
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_VTURB) + XLES_BU_RES_WRt(:,:,NLES_HTURB)
 !
@@ -533,7 +534,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_VTURB) + XLES_BU_RES_WRt(:,:,NL
 !
 IF ( ANY(XLES_BU_RES_WRt(:,:,NLES_COR)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES CORI'
+YSUBTITLE(ILES) = 'RES_CORI'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_COR)
 END IF
@@ -543,7 +544,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WRt(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NUMD'
+YSUBTITLE(ILES) = 'RES_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_DIFF)
 END IF
@@ -553,7 +554,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WRt(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RELA'
+YSUBTITLE(ILES) = 'RES_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_RELA)
 END IF
@@ -563,7 +564,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WRt(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NEST'
+YSUBTITLE(ILES) = 'RES_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_NEST)
 END IF
@@ -574,7 +575,7 @@ END IF
 IF ( ANY( XLES_BU_RES_WRt(:,:,NLES_MISC) &
          +XLES_BU_RES_WRt(:,:,NLES_MICR) /= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES MISC'
+YSUBTITLE(ILES) = 'RES_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_WRt(:,:,NLES_MISC) &
                       + XLES_BU_RES_WRt(:,:,NLES_MICR)
@@ -584,7 +585,7 @@ END IF
 !       --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -595,7 +596,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TEND'
+YSUBTITLE(ILES) = 'SBG_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 IF (NLES_TIMES>2) THEN
@@ -616,7 +617,7 @@ END IF
 !       ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - XLES_MEAN_W(JK,:,1)                              &
@@ -633,7 +634,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - ( XLES_RES_W_SBG_WRt(JK+1,:,1)   &
@@ -649,7 +650,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ----------------------------------------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG DPGW'
+YSUBTITLE(ILES) = 'NSG_DPGW'
 !
 ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddxa_W_SBG_UaRt(:,:,1)
 !
@@ -658,7 +659,7 @@ ZLES_BUDGET(:,:,ILES)=- XLES_RES_ddxa_W_SBG_UaRt(:,:,1)
 !       -------------------------------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG DPGT'
+YSUBTITLE(ILES) = 'NSG_DPGT'
 !
 ZLES_BUDGET(:,:,ILES)=-XLES_RES_ddxa_Rt_SBG_UaW(:,:,1)       &
                       -ZLES_BUDGET(:,:,ILES_P1) -ZLES_BUDGET(:,:,ILES_P2)
@@ -673,7 +674,7 @@ tzfield%clongname = ygroup
 tzfield%ccomment  = 'Rt flux budget'
 tzfield%cunits    = 'm kg kg-1 s-2'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
@@ -681,7 +682,7 @@ call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles),
 !           ------------------------------------------------------------
 !
 !
-YGROUP= 'BU_THLR '
+YGROUP= 'BU_THLR'
 ILES=0
 ILES_STA=ILES
 !
@@ -690,7 +691,7 @@ ILES_STA=ILES
 !      ----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 ZLES_BUDGET(:,:,ILES)=-XLES_SUBGRID_WRt (:,:,1) * XLES_MEAN_dThldz(:,:,1) &
@@ -701,7 +702,7 @@ ZLES_BUDGET(:,:,ILES)=-XLES_SUBGRID_WRt (:,:,1) * XLES_MEAN_dThldz(:,:,1) &
 !      --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 !
 ZLES_BUDGET(:,:,ILES)= - XLES_RES_ddxa_Rt_SBG_UaThl(:,:,1)  &
                        - XLES_RES_ddxa_Thl_SBG_UaRt(:,:,1)  &
@@ -713,7 +714,7 @@ ZLES_BUDGET(:,:,ILES)= - XLES_RES_ddxa_Rt_SBG_UaThl(:,:,1)  &
 !
 IF ( ANY(XLES_SUBGRID_WThlRt(:,:,1)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES) = - ( XLES_SUBGRID_WThlRt (JK+1,:,1)      &
@@ -730,7 +731,7 @@ END IF
 !      -----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS    '
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_DISS_ThlRt(:,:,1)
 !
@@ -739,7 +740,7 @@ ZLES_BUDGET(:,:,ILES) =  XLES_SUBGRID_DISS_ThlRt(:,:,1)
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -752,7 +753,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_TEND)
 !
@@ -762,7 +763,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_TEND)
 !
 IF ( ANY(XLES_BU_RES_ThlRt(:,:,NLES_ADVM)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(7) = ' RES ADV '
+YSUBTITLE(7) = 'RES_ADV'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_ADVM)
 END IF
@@ -772,7 +773,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_ThlRt(:,:,NLES_FORC)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES FORC'
+YSUBTITLE(ILES) = 'RES_FORC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_FORC)
 END IF
@@ -781,7 +782,7 @@ END IF
 !      ----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_DP)
 !
@@ -789,7 +790,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_DP)
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_TR)
 !
@@ -798,7 +799,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_TR)
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_VTURB) + XLES_BU_RES_ThlRt(:,:,NLES_HTURB)
 !
@@ -808,7 +809,7 @@ ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_VTURB) + XLES_BU_RES_ThlRt(:,
 !
 IF ( ANY(XLES_BU_RES_ThlRt(:,:,NLES_DIFF)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NUMD'
+YSUBTITLE(ILES) = 'RES_NUMD'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_DIFF)
 END IF
@@ -818,7 +819,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_ThlRt(:,:,NLES_RELA)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RELA'
+YSUBTITLE(ILES) = 'RES_RELA'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_RELA)
 END IF
@@ -828,7 +829,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_ThlRt(:,:,NLES_NEST)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES NEST'
+YSUBTITLE(ILES) = 'RES_NEST'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_NEST)
 END IF
@@ -841,7 +842,7 @@ IF ( ANY( XLES_BU_RES_ThlRt(:,:,NLES_MISC) &
          +XLES_BU_RES_ThlRt(:,:,NLES_RAD ) &
          +XLES_BU_RES_ThlRt(:,:,NLES_MICR) /= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES MISC'
+YSUBTITLE(ILES) = 'RES_MISC'
 !
 ZLES_BUDGET(:,:,ILES) = XLES_BU_RES_ThlRt(:,:,NLES_MISC) &
                       + XLES_BU_RES_ThlRt(:,:,NLES_PREF) &
@@ -854,7 +855,7 @@ END IF
 !       ---------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 DO JLES=ILES_STA+1,ILES-1
@@ -865,7 +866,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG TEND'
+YSUBTITLE(ILES) = 'NSG_TEND'
 !
 ZLES_BUDGET(:,:,ILES) = 0.
 IF (NLES_TIMES>2) THEN
@@ -884,7 +885,7 @@ END IF
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)=  -XLES_MEAN_W(JK,:,1)                &
@@ -901,7 +902,7 @@ ZLES_BUDGET(NLES_K,:,ILES) = ZLES_BUDGET(NLES_K-1,:,ILES)
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JK=2,NLES_K-1
   ZLES_BUDGET(JK,:,ILES)= - ( XLES_RES_W_SBG_ThlRt (JK+1,:,1)    &
@@ -923,7 +924,7 @@ tzfield%clongname = ygroup
 tzfield%ccomment  = 'Thl-Rt covariance budget'
 tzfield%cunits    = 'K kg kg-1 s-1'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
diff --git a/src/MNH/write_les_sv_budgetn.f90 b/src/MNH/write_les_sv_budgetn.f90
index e2434073f1033beb19654ff6f11380b5cb3b02fc..4bed642c49d6f57d932b4a8e5771b2bf9045b0fe 100644
--- a/src/MNH/write_les_sv_budgetn.f90
+++ b/src/MNH/write_les_sv_budgetn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2002-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2002-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.
@@ -115,7 +115,7 @@ ZLES_BUDGET(:,:,:,:) = XUNDEF
 !           ----------------------------
 !
 !
-YGROUP='BU_SV2  '
+YGROUP='BU_SV2'
 !
 ILES=0
 ILES_STA=ILES
@@ -124,7 +124,7 @@ ILES_STA=ILES
 !      ----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 DO JSV=1,NSV
@@ -136,7 +136,7 @@ END DO
 !      --------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV)= - 2. * XLES_RES_ddxa_Sv_SBG_UaSv(:,:,1,JSV)  &
@@ -149,7 +149,7 @@ END DO
 !
 IF ( ANY(XLES_SUBGRID_WSv2(:,:,1,:)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JSV=1,NSV
   DO JK=2,NLES_K-1
@@ -168,7 +168,7 @@ END IF
 !      -----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS    '
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) =  XLES_SUBGRID_DISS_Sv2(:,:,1,JSV)
@@ -179,7 +179,7 @@ END DO
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = 0.
@@ -194,7 +194,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_TEND,JSV)
@@ -205,7 +205,7 @@ END DO
 !
 IF ( ANY(XLES_BU_RES_Sv2(:,:,NLES_ADVM,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES ADV '
+  YSUBTITLE(ILES) = 'RES_ADV'
 !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_ADVM,JSV)
@@ -217,7 +217,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Sv2(:,:,NLES_FORC,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES FORC'
+  YSUBTITLE(ILES) = 'RES_FORC'
 !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_FORC,JSV)
@@ -229,7 +229,7 @@ END IF
 !      ----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_DP,JSV)
@@ -239,7 +239,7 @@ END DO
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_TR,JSV)
@@ -250,7 +250,7 @@ END DO
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_VTURB,JSV) &
@@ -262,7 +262,7 @@ END DO
 !
 IF ( ANY(XLES_BU_RES_Sv2(:,:,NLES_DIFF,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES NUMD'
+  YSUBTITLE(ILES) = 'RES_NUMD'
 !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_DIFF,JSV)
@@ -274,7 +274,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Sv2(:,:,NLES_RELA,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES RELA'
+  YSUBTITLE(ILES) = 'RES_RELA'
 !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_RELA,JSV)
@@ -286,7 +286,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Sv2(:,:,NLES_NEST,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES NEST'
+  YSUBTITLE(ILES) = 'RES_NEST'
 !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_NEST,JSV)
@@ -298,7 +298,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_Sv2(:,:,NLES_MISC,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES MISC'
+  YSUBTITLE(ILES) = 'RES_MISC'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_Sv2(:,:,NLES_MISC,JSV)
@@ -309,7 +309,7 @@ END IF
 !       ---------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = 0.
@@ -322,7 +322,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG TEND'
+YSUBTITLE(ILES) = 'NSG_TEND'
 !
 IF (NLES_TIMES>2) THEN
   DO JSV=1,NSV
@@ -343,7 +343,7 @@ END IF
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JSV=1,NSV
   DO JK=2,NLES_K-1
@@ -361,7 +361,7 @@ END DO
 !       ----------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JSV=1,NSV
   DO JK=2,NLES_K-1
@@ -399,7 +399,7 @@ tzfield%ndimlist(5:) = NMNHDIM_UNUSED
 gdoavg  = xles_temp_mean_start /= XUNDEF .and. xles_temp_mean_end /= XUNDEF
 gdonorm = trim(cles_norm_type) /= 'NONE'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles, :), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles, :), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
@@ -407,7 +407,7 @@ call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles,
 !           -----------------------
 !
 !
-YGROUP = 'BU_WSV  '
+YGROUP = 'BU_WSV'
 !
 !
 ILES=0
@@ -417,7 +417,7 @@ ILES_STA=ILES
 !     -----------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP M'
+YSUBTITLE(ILES) = 'SBG_DP_M'
 ILES_P1=ILES
 !
 DO JSV=1,NSV
@@ -430,7 +430,7 @@ END DO
 !     -------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG DP R'
+YSUBTITLE(ILES) = 'SBG_DP_R'
 ILES_P2=ILES
 !
 DO JSV=1,NSV
@@ -445,7 +445,7 @@ END DO
 !
 IF ( ANY(XLES_SUBGRID_W2Sv(:,:,1,:)/= 0.) ) THEN
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TR  '
+YSUBTITLE(ILES) = 'SBG_TR'
 !
 DO JSV=1,NSV
   DO JK=2,NLES_K-1
@@ -464,7 +464,7 @@ END IF
 !      -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG PRES'
+YSUBTITLE(ILES) = 'SBG_PRES'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) =  XLES_SUBGRID_SvPz(:,:,1,JSV)
@@ -475,7 +475,7 @@ END DO
 !      ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG TP  '
+YSUBTITLE(ILES) = 'SBG_TP'
 !
 IF (LUSERV) THEN
   DO JSV=1,NSV
@@ -494,7 +494,7 @@ END IF
 !      -----------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' DISS    '
+YSUBTITLE(ILES) = 'SBG_DISS'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = 0.
@@ -505,7 +505,7 @@ END DO
 !      --------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' SBG RESI'
+YSUBTITLE(ILES) = 'SBG_RESI'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = 0.
@@ -520,7 +520,7 @@ ILES_STA=ILES
 !      --------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TEND'
+YSUBTITLE(ILES) = 'RES_TEND'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_TEND,JSV)
@@ -531,7 +531,7 @@ END DO
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_ADVM,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES ADV '
+  YSUBTITLE(ILES) = 'RES_ADV'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_ADVM,JSV)
@@ -543,7 +543,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_FORC,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES FORC'
+  YSUBTITLE(ILES) = 'RES_FORC'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_FORC,JSV)
@@ -554,7 +554,7 @@ END IF
 !       ----------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES DP  '
+YSUBTITLE(ILES) = 'RES_DP'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_DP,JSV)
@@ -564,7 +564,7 @@ END DO
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TR  '
+YSUBTITLE(ILES) = 'RES_TR'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_TR,JSV)
@@ -575,7 +575,7 @@ END DO
 !       -------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES PRES'
+YSUBTITLE(ILES) = 'RES_PRES'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_PRES,JSV)
@@ -586,7 +586,7 @@ END DO
 !       ------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES TP  '
+YSUBTITLE(ILES) = 'RES_TP'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_GRAV,JSV)
@@ -597,7 +597,7 @@ END DO
 !       ----------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES SBGT'
+YSUBTITLE(ILES) = 'RES_SBGT'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_VTURB,JSV) + XLES_BU_RES_WSv(:,:,NLES_HTURB,JSV)
@@ -608,7 +608,7 @@ END DO
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_COR,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES CORI'
+  YSUBTITLE(ILES) = 'RES_CORI'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_COR,JSV)
@@ -620,7 +620,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_DIFF,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES NUMD'
+  YSUBTITLE(ILES) = 'RES_NUMD'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_DIFF,JSV)
@@ -632,7 +632,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_RELA,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES RELA'
+  YSUBTITLE(ILES) = 'RES_RELA'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_RELA,JSV)
@@ -644,7 +644,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_NEST,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES NEST'
+  YSUBTITLE(ILES) = 'RES_NEST'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_NEST,JSV)
@@ -656,7 +656,7 @@ END IF
 !
 IF ( ANY(XLES_BU_RES_WSv(:,:,NLES_MISC,:)/= 0.) ) THEN
   ILES=ILES+1
-  YSUBTITLE(ILES) = ' RES MISC'
+  YSUBTITLE(ILES) = 'RES_MISC'
   !
   DO JSV=1,NSV
     ZLES_BUDGET(:,:,ILES,JSV) = XLES_BU_RES_WSv(:,:,NLES_MISC,JSV)
@@ -667,7 +667,7 @@ END IF
 !       -------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' RES RESI'
+YSUBTITLE(ILES) = 'RES_RESI'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = 0.
@@ -680,7 +680,7 @@ END DO
 !       ------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG TEND'
+YSUBTITLE(ILES) = 'NSG_TEND'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV) = 0.
@@ -703,7 +703,7 @@ END DO
 !       ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVM'
+YSUBTITLE(ILES) = 'NSG_ADVM'
 !
 DO JSV=1,NSV
   DO JK=2,NLES_K-1
@@ -721,7 +721,7 @@ END DO
 !       ------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG ADVR'
+YSUBTITLE(ILES) = 'NSG_ADVR'
 !
 DO JSV=1,NSV
   DO JK=2,NLES_K-1
@@ -738,7 +738,7 @@ END DO
 !       ----------------------------------------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG DPGW'
+YSUBTITLE(ILES) = 'NSG_DPGW'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV)=- XLES_RES_ddxa_W_SBG_UaSv(:,:,1,JSV)
@@ -749,7 +749,7 @@ END DO
 !       -------------------------------------------------------------------------
 !
 ILES=ILES+1
-YSUBTITLE(ILES) = ' NSG DPGT'
+YSUBTITLE(ILES) = 'NSG_DPGT'
 !
 DO JSV=1,NSV
   ZLES_BUDGET(:,:,ILES,JSV)=-XLES_RES_ddxa_Sv_SBG_UaW(:,:,1,JSV)       &
@@ -781,7 +781,7 @@ tzfield%ndimlist(5:) = NMNHDIM_UNUSED
 gdoavg  = xles_temp_mean_start /= XUNDEF .and. xles_temp_mean_end /= XUNDEF
 gdonorm = trim(cles_norm_type) /= 'NONE'
 
-call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles, :), ysubtitle(:iles) )
+call Les_diachro( tpdiafile, tzfield, gdoavg, gdonorm, zles_budget(:, :, :iles, :), hsuffixes = ysubtitle(:iles) )
 
 !-------------------------------------------------------------------------------
 !
diff --git a/src/MNH/write_lesn.f90 b/src/MNH/write_lesn.f90
index 09724ca6a50988a652edf5f748576c19a04c3c99..e971d432cbfe94e4be5c582197476ede4ad2507a 100644
--- a/src/MNH/write_lesn.f90
+++ b/src/MNH/write_lesn.f90
@@ -1,4 +1,4 @@
-!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.
@@ -107,8 +107,9 @@ INTEGER :: IMASK
 INTEGER :: JSV       ! scalar loop counter
 INTEGER :: JI        ! loop counter
 !
-CHARACTER(len=9), DIMENSION(NLES_MASKS) :: YSUBTITLE
+character(len=3)                        :: ynum
 CHARACTER(len=5)                        :: YGROUP
+character(len=7), dimension(nles_masks) :: ymasks
 !
 logical :: gdoavg    ! Compute and store time average
 logical :: gdonorm   ! Compute and store normalized field
@@ -234,32 +235,33 @@ tfield%ntype = TYPEREAL
 !*      2.   (z,t) profiles (all masks)
 !            --------------
 IMASK = 1
-YSUBTITLE(IMASK) = " (cart)"
+ymasks(imask) = 'cart'
 IF (LLES_NEB_MASK) THEN
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (neb)"
+  ymasks(imask) = 'neb'
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (clear)"
+  ymasks(imask) = 'clear'
 END IF
 IF (LLES_CORE_MASK) THEN
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (core)"
+  ymasks(imask) = 'core'
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (env)"
+  ymasks(imask) = 'env'
 END IF
 IF (LLES_MY_MASK) THEN
    DO JI=1,NLES_MASKS_USER
         IMASK=IMASK+1
-        YSUBTITLE(IMASK) = " (user)"
+        Write( ynum, '( i3.3 )' ) ji
+        ymasks(imask) = 'user' // ynum
    END DO
 END IF
 IF (LLES_CS_MASK) THEN
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (cs1)"
+  ymasks(imask) = 'cs1'
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (cs2)"
+  ymasks(imask) = 'cs2'
   IMASK=IMASK+1
-  YSUBTITLE(IMASK) = " (cs3)"
+  ymasks(imask) = 'cs3'
 END IF
 !
 !*      2.0  averaging diagnostics
@@ -281,10 +283,10 @@ tfield%ndimlist(4:) = NMNHDIM_UNUSED
 ldoavg  = xles_temp_mean_start /= XUNDEF .and. xles_temp_mean_end /= XUNDEF
 ldonorm = .false.
 
-call Les_diachro_write( tpdiafile, zavg_pts_ll,                'AVG_PTS',  'number of points used for averaging',   '1', ysubtitle)
-call Les_diachro_write( tpdiafile, zavg_pts_ll / zcart_pts_ll, 'AVG_PTSF', 'fraction of points used for averaging', '1', ysubtitle)
-call Les_diachro_write( tpdiafile, zund_pts_ll,                'UND_PTS',  'number of points below orography',      '1', ysubtitle)
-call Les_diachro_write( tpdiafile, zund_pts_ll / zcart_pts_ll, 'UND_PTSF', 'fraction of points below orography',    '1', ysubtitle)
+call Les_diachro_write( tpdiafile, zavg_pts_ll,                'AVG_PTS',  'number of points used for averaging',   '1', ymasks )
+call Les_diachro_write( tpdiafile, zavg_pts_ll / zcart_pts_ll, 'AVG_PTSF', 'fraction of points used for averaging', '1', ymasks )
+call Les_diachro_write( tpdiafile, zund_pts_ll,                'UND_PTS',  'number of points below orography',      '1', ymasks )
+call Les_diachro_write( tpdiafile, zund_pts_ll / zcart_pts_ll, 'UND_PTSF', 'fraction of points below orography',    '1', ymasks )
 
 DEALLOCATE(ZAVG_PTS_ll)
 DEALLOCATE(ZUND_PTS_ll)
@@ -301,54 +303,54 @@ tfield%ndimlist(4:) = NMNHDIM_UNUSED
 ldoavg  = xles_temp_mean_start /= XUNDEF .and. xles_temp_mean_end /= XUNDEF
 ldonorm = trim(cles_norm_type) /= 'NONE'
 
-call Les_diachro_write( tpdiafile, XLES_MEAN_U,      'MEAN_U',      'Mean U Profile',                        'm s-1',  ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_V,      'MEAN_V',      'Mean V Profile',                        'm s-1',  ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_W,      'MEAN_W',      'Mean W Profile',                        'm s-1',  ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_P,      'MEAN_PRE',    'Mean pressure Profile',                 'Pa',     ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_DP,     'MEAN_DP',     'Mean Dyn production TKE Profile',       'm2 s-3', ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_TP,     'MEAN_TP',     'Mean Thermal production TKE Profile',   'm2 s-3', ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_TR,     'MEAN_TR',     'Mean transport production TKE Profile', 'm2 s-3', ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_DISS,   'MEAN_DISS',   'Mean Dissipation TKE Profile',          'm2 s-3', ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_LM,     'MEAN_LM',     'Mean mixing length Profile',            'm',      ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_RHO,    'MEAN_RHO',    'Mean density Profile',                  'kg m-3', ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_Th,     'MEAN_TH',     'Mean potential temperature Profile',    'K',      ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_MEAN_Mf,     'MEAN_MF',     'Mass-flux Profile',                     'm s-1',  ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_U,      'MEAN_U',      'Mean U Profile',                        'm s-1',  ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_V,      'MEAN_V',      'Mean V Profile',                        'm s-1',  ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_W,      'MEAN_W',      'Mean W Profile',                        'm s-1',  ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_P,      'MEAN_PRE',    'Mean pressure Profile',                 'Pa',     ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_DP,     'MEAN_DP',     'Mean Dyn production TKE Profile',       'm2 s-3', ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_TP,     'MEAN_TP',     'Mean Thermal production TKE Profile',   'm2 s-3', ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_TR,     'MEAN_TR',     'Mean transport production TKE Profile', 'm2 s-3', ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_DISS,   'MEAN_DISS',   'Mean Dissipation TKE Profile',          'm2 s-3', ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_LM,     'MEAN_LM',     'Mean mixing length Profile',            'm',      ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_RHO,    'MEAN_RHO',    'Mean density Profile',                  'kg m-3', ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Th,     'MEAN_TH',     'Mean potential temperature Profile',    'K',      ymasks )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Mf,     'MEAN_MF',     'Mass-flux Profile',                     'm s-1',  ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Thl,    'MEAN_THL',    'Mean liquid potential temperature Profile',  'K', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Thl,    'MEAN_THL',    'Mean liquid potential temperature Profile',  'K', ymasks )
 if ( luserv ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Thv,    'MEAN_THV',    'Mean virtual potential temperature Profile', 'K', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Thv,    'MEAN_THV',    'Mean virtual potential temperature Profile', 'K', ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rt,     'MEAN_RT',     'Mean Rt Profile', 'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rt,     'MEAN_RT',     'Mean Rt Profile', 'kg kg-1', ymasks )
 if ( luserv ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rv,     'MEAN_RV',     'Mean Rv Profile', 'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rv,     'MEAN_RV',     'Mean Rv Profile', 'kg kg-1', ymasks )
 if ( luserv ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rehu,   'MEAN_REHU',   'Mean Rh Profile', 'percent', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rehu,   'MEAN_REHU',   'Mean Rh Profile', 'percent', ymasks )
 if ( luserv ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Qs,     'MEAN_QS',     'Mean Qs Profile', 'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Qs,     'MEAN_QS',     'Mean Qs Profile', 'kg kg-1', ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_KHt,    'MEAN_KHT',    'Eddy-diffusivity (temperature) Profile', 'm2 s-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_KHt,    'MEAN_KHT',    'Eddy-diffusivity (temperature) Profile', 'm2 s-1', ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_KHr,    'MEAN_KHR',    'Eddy-diffusivity (wvapor) Profile',      'm2 s-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_KHr,    'MEAN_KHR',    'Eddy-diffusivity (vapor) Profile',      'm2 s-1', ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rc,     'MEAN_RC',     'Mean Rc Profile', 'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rc,     'MEAN_RC',     'Mean Rc Profile',              'kg kg-1', ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Cf,     'MEAN_CF',     'Mean Cf Profile',              '1',       ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Cf,     'MEAN_CF',     'Mean Cf Profile',              '1',       ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_INDCf,  'MEAN_INDCF',  'Mean Cf>1-6 Profile (0 or 1)', '1',       ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_INDCf,  'MEAN_INDCF',  'Mean Cf>1-6 Profile (0 or 1)', '1',       ymasks )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_INDCf2, 'MEAN_INDCF2', 'Mean Cf>1-5 Profile (0 or 1)', '1',       ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_INDCf2, 'MEAN_INDCF2', 'Mean Cf>1-5 Profile (0 or 1)', '1',       ymasks )
 if ( luserr ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rr,     'MEAN_RR',     'Mean Rr Profile',              'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rr,     'MEAN_RR',     'Mean Rr Profile',              'kg kg-1', ymasks )
 if ( luserr ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_RF,     'MEAN_RF',     'Mean RF Profile',              '1',       ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_RF,     'MEAN_RF',     'Mean RF Profile',              '1',       ymasks )
 if ( luseri ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Ri,     'MEAN_RI',     'Mean Ri Profile',              'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Ri,     'MEAN_RI',     'Mean Ri Profile',              'kg kg-1', ymasks )
 if ( lusers ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rs,     'MEAN_RS',     'Mean Rs Profile',              'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rs,     'MEAN_RS',     'Mean Rs Profile',              'kg kg-1', ymasks )
 if ( luserg ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rg,     'MEAN_RG',     'Mean Rg Profile',              'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rg,     'MEAN_RG',     'Mean Rg Profile',              'kg kg-1', ymasks )
 if ( luserh ) &
-call Les_diachro_write( tpdiafile, XLES_MEAN_Rh,     'MEAN_RH',     'Mean Rh Profile',              'kg kg-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_Rh,     'MEAN_RH',     'Mean Rh Profile',              'kg kg-1', ymasks )
 
 if ( nsv > 0 ) then
   tfield%ndims = 4
@@ -358,7 +360,7 @@ if ( nsv > 0 ) then
   tfield%ndimlist(4)  = NMNHDIM_BUDGET_LES_SV
   tfield%ndimlist(5:) = NMNHDIM_UNUSED
 
-  call Les_diachro_write( tpdiafile, XLES_MEAN_Sv, 'MEAN_SV', 'Mean Sv Profiles', 'kg kg-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_MEAN_Sv, 'MEAN_SV', 'Mean Sv Profiles', 'kg kg-1', ymasks )
 
   tfield%ndims = 3
   !tfield%ndimlist(1)  = NMNHDIM_BUDGET_LES_LEVEL
@@ -368,28 +370,28 @@ if ( nsv > 0 ) then
   !tfield%ndimlist(5:) = NMNHDIM_UNUSED
 end if
 
-call Les_diachro_write( tpdiafile, XLES_MEAN_WIND, 'MEANWIND',       'Profile of Mean Modulus of Wind', 'm s-1',      ysubtitle )
-call Les_diachro_write( tpdiafile, XLES_RESOLVED_MASSFX, 'MEANMSFX', 'Total updraft mass flux',         'kg m-2 s-1', ysubtitle )
+call Les_diachro_write( tpdiafile, XLES_MEAN_WIND, 'MEANWIND',       'Profile of Mean Modulus of Wind', 'm s-1',      ymasks )
+call Les_diachro_write( tpdiafile, XLES_RESOLVED_MASSFX, 'MEANMSFX', 'Total updraft mass flux',         'kg m-2 s-1', ymasks )
 
 if ( lles_pdf ) then
-  call Les_diachro_write( tpdiafile,   XLES_PDF_TH,  'PDF_TH',  'Pdf potential temperature Profiles', '1', ysubtitle )
-  call Les_diachro_write( tpdiafile,   XLES_PDF_W,   'PDF_W',   'Pdf vertical velocity Profiles',     '1', ysubtitle )
-  call Les_diachro_write( tpdiafile,   XLES_PDF_THV, 'PDF_THV', 'Pdf virtual pot. temp. Profiles',    '1', ysubtitle )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_TH,  'PDF_TH',  'Pdf potential temperature Profiles', '1', ymasks )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_W,   'PDF_W',   'Pdf vertical velocity Profiles',     '1', ymasks )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_THV, 'PDF_THV', 'Pdf virtual pot. temp. Profiles',    '1', ymasks )
   if ( luserv ) &
-  call Les_diachro_write( tpdiafile,   XLES_PDF_RV,  'PDF_RV',  'Pdf Rv Profiles',                    '1', ysubtitle )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_RV,  'PDF_RV',  'Pdf Rv Profiles',                    '1', ymasks )
   if ( luserc ) then
-    call Les_diachro_write( tpdiafile, XLES_PDF_RC,  'PDF_RC',  'Pdf Rc Profiles',                    '1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_PDF_RT,  'PDF_RT',  'Pdf Rt Profiles',                    '1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_PDF_THL, 'PDF_THL', 'Pdf Thl Profiles',                   '1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_PDF_RC,  'PDF_RC',  'Pdf Rc Profiles',                    '1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_PDF_RT,  'PDF_RT',  'Pdf Rt Profiles',                    '1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_PDF_THL, 'PDF_THL', 'Pdf Thl Profiles',                   '1', ymasks )
   end if
   if ( luserr ) &
-  call Les_diachro_write( tpdiafile,   XLES_PDF_RR,  'PDF_RR',  'Pdf Rr Profiles',                    '1', ysubtitle )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_RR,  'PDF_RR',  'Pdf Rr Profiles',                    '1', ymasks )
   if ( luseri ) &
-  call Les_diachro_write( tpdiafile,   XLES_PDF_RI,  'PDF_RI',  'Pdf Ri Profiles',                    '1', ysubtitle )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_RI,  'PDF_RI',  'Pdf Ri Profiles',                    '1', ymasks )
   if ( lusers ) &
-  call Les_diachro_write( tpdiafile,   XLES_PDF_RS,  'PDF_RS',  'Pdf Rs Profiles',                    '1', ysubtitle )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_RS,  'PDF_RS',  'Pdf Rs Profiles',                    '1', ymasks )
   if ( luserg ) &
-  call Les_diachro_write( tpdiafile,   XLES_PDF_RG,  'PDF_RG',  'Pdf Rg Profiles',                    '1', ysubtitle )
+  call Les_diachro_write( tpdiafile,   XLES_PDF_RG,  'PDF_RG',  'Pdf Rg Profiles',                    '1', ymasks )
 end if
 !
 !*      2.2  resolved quantities
@@ -406,89 +408,79 @@ if ( lles_resolved ) then
   tfield%ndimlist(3)  = NMNHDIM_BUDGET_LES_MASK
   tfield%ndimlist(4:) = NMNHDIM_UNUSED
 
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_U2, 'RES_U2',  'Resolved <u2> variance',        'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_V2, 'RES_V2',  'Resolved <v2> variance',        'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2, 'RES_W2',  'Resolved <w2> variance',        'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UV, 'RES_UV',  'Resolved <uv> Flux',            'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WU, 'RES_WU',  'Resolved <wu> Flux',            'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WV, 'RES_WV',  'Resolved <wv> Flux',            'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_Ke, 'RES_KE',  'Resolved TKE Profile',          'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_P2, 'RES_P2',  'Resolved pressure variance',    'Pa2',    ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UP, 'RES_UPZ', 'Resolved <up> horizontal Flux', 'Pa s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_VP, 'RES_VPZ', 'Resolved <vp> horizontal Flux', 'Pa s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WP, 'RES_WPZ', 'Resolved <wp> vertical Flux',   'Pa s-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_U2, 'RES_U2',  'Resolved <u2> variance',        'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_V2, 'RES_V2',  'Resolved <v2> variance',        'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2, 'RES_W2',  'Resolved <w2> variance',        'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UV, 'RES_UV',  'Resolved <uv> Flux',            'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WU, 'RES_WU',  'Resolved <wu> Flux',            'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WV, 'RES_WV',  'Resolved <wv> Flux',            'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_Ke, 'RES_KE',  'Resolved TKE Profile',          'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_P2, 'RES_P2',  'Resolved pressure variance',    'Pa2',    ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UP, 'RES_UPZ', 'Resolved <up> horizontal Flux', 'Pa s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_VP, 'RES_VPZ', 'Resolved <vp> horizontal Flux', 'Pa s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WP, 'RES_WPZ', 'Resolved <wp> vertical Flux',   'Pa s-1', ymasks )
 
   if ( luserv ) &
   call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThThv, 'RES_THTV', &
-                          'Resolved potential temperature - virtual potential temperature covariance',        'K2', ysubtitle )
+                          'Resolved potential temperature - virtual potential temperature covariance',        'K2', ymasks )
   if ( luserc ) &
   call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlThv, 'RES_TLTV', &
-                          'Resolved liquid potential temperature - virtual potential temperature covariance', 'K2',  ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_Th2, 'RES_TH2', 'Resolved potential temperature variance', 'K2', ysubtitle )
+                          'Resolved liquid potential temperature - virtual potential temperature covariance', 'K2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_Th2, 'RES_TH2', 'Resolved potential temperature variance', 'K2', ymasks )
   if ( luserc ) &
   call Les_diachro_write( tpdiafile, XLES_RESOLVED_Thl2, 'RES_THL2', 'Resolved liquid potential temperature variance', 'K2',&
-                          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UTh, 'RES_UTH', 'Resolved <uth> horizontal Flux', 'm K s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_VTh, 'RES_VTH', 'Resolved <vth> horizontal Flux', 'm K s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WTh, 'RES_WTH', 'Resolved <wth> vertical Flux',   'm K s-1', ysubtitle )
+                          ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UTh, 'RES_UTH', 'Resolved <uth> horizontal Flux', 'm K s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_VTh, 'RES_VTH', 'Resolved <vth> horizontal Flux', 'm K s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WTh, 'RES_WTH', 'Resolved <wth> vertical Flux',   'm K s-1', ymasks )
 
   if ( luserc ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_UThl, 'RES_UTHL', 'Resolved <uthl> horizontal Flux', 'm K s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VThl, 'RES_VTHL', 'Resolved <vthl> horizontal Flux', 'm K s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThl, 'RES_WTHL', 'Resolved <wthl> vertical Flux',   'm K s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Rt2, 'RES_RT2',  'Resolved total water variance',    'kg2 kg-2', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRt, 'RES_WRT',  'Resolved <wrt> vertical Flux', 'm kg kg-1 s-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_UThl, 'RES_UTHL', 'Resolved <uthl> horizontal Flux', 'm K s-1',       ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VThl, 'RES_VTHL', 'Resolved <vthl> horizontal Flux', 'm K s-1',       ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThl, 'RES_WTHL', 'Resolved <wthl> vertical Flux',   'm K s-1',       ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Rt2,  'RES_RT2',  'Resolved total water variance',   'kg2 kg-2',      ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRt,  'RES_WRT',  'Resolved <wrt> vertical Flux',    'm kg kg-1 s-1', ymasks )
   end if
 
   if ( luserv ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_UThv,  'RES_UTHV', 'Resolved <uthv> horizontal Flux', 'm K s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VThv,  'RES_VTHV', 'Resolved <vthv> horizontal Flux', 'm K s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThv,  'RES_WTHV', 'Resolved <wthv> vertical Flux',   'm K s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Rv2,   'RES_RV2',  'Resolved water vapor variance',   'kg2 kg-2', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThRv,  'RES_THRV', 'Resolved <thrv> covariance',      'K kg kg-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_UThv,  'RES_UTHV', 'Resolved <uthv> horizontal Flux', 'm K s-1',       ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VThv,  'RES_VTHV', 'Resolved <vthv> horizontal Flux', 'm K s-1',       ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThv,  'RES_WTHV', 'Resolved <wthv> vertical Flux',   'm K s-1',       ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Rv2,   'RES_RV2',  'Resolved water vapor variance',   'kg2 kg-2',      ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThRv,  'RES_THRV', 'Resolved <thrv> covariance',      'K kg kg-1',     ymasks )
     if ( luserc ) &
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlRv, 'RES_TLRV', 'Resolved <thlrv> covariance',     'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvRv, 'RES_TVRV', 'Resolved <thvrv> covariance',     'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_URv,   'RES_URV',  'Resolved <urv> horizontal flux',  'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VRv,   'RES_VRV',  'Resolved <vrv> horizontal flux',  'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRv,   'RES_WRV',  'Resolved <wrv> vertical flux',    'm kg kg-1 s-1', &
-                            ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlRv, 'RES_TLRV', 'Resolved <thlrv> covariance',     'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvRv, 'RES_TVRV', 'Resolved <thvrv> covariance',     'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_URv,   'RES_URV',  'Resolved <urv> horizontal flux',  'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VRv,   'RES_VRV',  'Resolved <vrv> horizontal flux',  'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRv,   'RES_WRV',  'Resolved <wrv> vertical flux',    'm kg kg-1 s-1', ymasks )
   end if
 
   if ( luserc ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Rc2,   'RES_RC2',  'Resolved cloud water variance',   'kg2 kg-2', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThRc,  'RES_THRC', 'Resolved <thrc> covariance',      'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlRc, 'RES_TLRC', 'Resolved <thlrc> covariance',     'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvRc, 'RES_TVRC', 'Resolved <thvrc> covariance',     'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_URc,   'RES_URC',  'Resolved <urc> horizontal flux',  'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VRc,   'RES_VRC',  'Resolved <vrc> horizontal flux',  'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRc,   'RES_WRC',  'Resolved <wrc> vertical flux',    'm kg kg-1 s-1', &
-                            ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Rc2,   'RES_RC2',  'Resolved cloud water variance',  'kg2 kg-2',      ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThRc,  'RES_THRC', 'Resolved <thrc> covariance',     'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlRc, 'RES_TLRC', 'Resolved <thlrc> covariance',    'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvRc, 'RES_TVRC', 'Resolved <thvrc> covariance',    'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_URc,   'RES_URC',  'Resolved <urc> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VRc,   'RES_VRC',  'Resolved <vrc> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRc,   'RES_WRC',  'Resolved <wrc> vertical flux',   'm kg kg-1 s-1', ymasks )
   end if
 
   if ( luseri ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Ri2,   'RES_RI2',  'Resolved cloud ice variance',     'kg2 kg-2', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThRi,  'RES_THRI', 'Resolved <thri> covariance',      'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlRi, 'RES_TLRI', 'Resolved <thlri> covariance',     'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvRi, 'RES_TVRI', 'Resolved <thvri> covariance',     'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_URi,   'RES_URI',  'Resolved <uri> horizontal flux',  'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VRi,   'RES_VRI',  'Resolved <vri> horizontal flux',  'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRi,   'RES_WRI',  'Resolved <wri> vertical flux',    'm kg kg-1 s-1', &
-                            ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Ri2,   'RES_RI2',  'Resolved cloud ice variance',    'kg2 kg-2',      ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThRi,  'RES_THRI', 'Resolved <thri> covariance',     'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlRi, 'RES_TLRI', 'Resolved <thlri> covariance',    'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvRi, 'RES_TVRI', 'Resolved <thvri> covariance',    'K kg kg-1',     ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_URi,   'RES_URI',  'Resolved <uri> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VRi,   'RES_VRI',  'Resolved <vri> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRi,   'RES_WRI',  'Resolved <wri> vertical flux',   'm kg kg-1 s-1', ymasks )
   end if
 
   if ( luserr ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRr,   'RES_WRR',  'Resolved <wrr> vertical flux',    'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_INPRR3D,     'INPRR3D',   'Precipitation flux',  'm s-1',       ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_MAX_INPRR3D, 'MAXINPR3D', 'Max Precip flux',     'm s-1',       ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_EVAP3D,      'EVAP3D',    'Evaporation profile', 'kg kg-1 s-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRr,   'RES_WRR',   'Resolved <wrr> vertical flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_INPRR3D,        'INPRR3D',   'Precipitation flux',           'm s-1',         ymasks )
+    call Les_diachro_write( tpdiafile, XLES_MAX_INPRR3D,    'MAXINPR3D', 'Max Precip flux',              'm s-1',         ymasks )
+    call Les_diachro_write( tpdiafile, XLES_EVAP3D,         'EVAP3D',    'Evaporation profile',          'kg kg-1 s-1',   ymasks )
   end if
 
   if ( nsv > 0 ) then
@@ -499,19 +491,15 @@ if ( lles_resolved ) then
     tfield%ndimlist(4)  = NMNHDIM_BUDGET_LES_SV
     tfield%ndimlist(5:) = NMNHDIM_UNUSED
 
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Sv2,   'RES_SV2',  'Resolved scalar variables variances', 'kg2 kg-2', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThSv,  'RES_THSV', 'Resolved <ThSv> variance',  'K kg kg-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_Sv2,   'RES_SV2',  'Resolved scalar variables variances', 'kg2 kg-2', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThSv,  'RES_THSV', 'Resolved <ThSv> variance',  'K kg kg-1',          ymasks )
     if ( luserc ) &
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlSv, 'RES_TLSV', 'Resolved <ThlSv> variance', 'K kg kg-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlSv, 'RES_TLSV', 'Resolved <ThlSv> variance', 'K kg kg-1',          ymasks )
     if ( luserv ) &
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvSv, 'RES_TVSV', 'Resolved <ThvSv> variance', 'K kg kg-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_USv,   'RES_USV',  'Resolved <uSv> horizontal flux', 'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VSv,   'RES_VSV',  'Resolved <vSv> horizontal flux', 'm kg kg-1 s-1', &
-                            ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WSv,   'RES_WSV',  'Resolved <wSv> vertical flux', 'm kg kg-1 s-1',   &
-                            ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThvSv, 'RES_TVSV', 'Resolved <ThvSv> variance', 'K kg kg-1',          ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_USv,   'RES_USV',  'Resolved <uSv> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_VSv,   'RES_VSV',  'Resolved <vSv> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WSv,   'RES_WSV',  'Resolved <wSv> vertical flux', 'm kg kg-1 s-1',   ymasks )
 
     tfield%ndims = 3
     !tfield%ndimlist(1)  = NMNHDIM_BUDGET_LES_LEVEL
@@ -521,37 +509,37 @@ if ( lles_resolved ) then
     !tfield%ndimlist(5:) = NMNHDIM_UNUSED
   end if
 
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_U3, 'RES_U3', 'Resolved <u3>', 'm3 s-3', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_V3, 'RES_V3', 'Resolved <v3>', 'm3 s-3', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W3, 'RES_W3', 'Resolved <w3>', 'm3 s-3', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_U4, 'RES_U4', 'Resolved <u4>', 'm4 s-4', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_V4, 'RES_V4', 'Resolved <v4>', 'm4 s-4', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W4, 'RES_W4', 'Resolved <>w4', 'm4 s-4', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_U3, 'RES_U3', 'Resolved <u3>', 'm3 s-3', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_V3, 'RES_V3', 'Resolved <v3>', 'm3 s-3', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W3, 'RES_W3', 'Resolved <w3>', 'm3 s-3', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_U4, 'RES_U4', 'Resolved <u4>', 'm4 s-4', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_V4, 'RES_V4', 'Resolved <v4>', 'm4 s-4', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W4, 'RES_W4', 'Resolved <w4>', 'm4 s-4', ymasks )
 
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThl2, 'RES_WTL2', 'Resolved <wThl2',  'm K2 s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Thl, 'RES_W2TL', 'Resolved <w2Thl>', 'm2 K s-2', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThl2, 'RES_WTL2', 'Resolved <wThl2>', 'm K2 s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Thl, 'RES_W2TL', 'Resolved <w2Thl>', 'm2 K s-2', ymasks )
 
   if ( luserv ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRv2,   'RES_WRV2', 'Resolved <wRv2>',   'm kg2 kg-2 s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Rv,   'RES_W2RV', 'Resolved <w2Rv>',   'm2 kg kg-1 s-2',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRt2,   'RES_WRT2', 'Resolved <wRt2>',   'm kg2 kg-2 s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Rt,   'RES_W2RT', 'Resolved <w2Rt>',   'm2 kg kg-1 s-2',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRv, 'RE_WTLRV', 'Resolved <wThlRv>', 'm K kg kg-1 s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRt, 'RE_WTLRT', 'Resolved <wThlRt>', 'm K kg kg-1 s-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRv2,   'RES_WRV2', 'Resolved <wRv2>',   'm kg2 kg-2 s-1',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Rv,   'RES_W2RV', 'Resolved <w2Rv>',   'm2 kg kg-1 s-2',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRt2,   'RES_WRT2', 'Resolved <wRt2>',   'm kg2 kg-2 s-1',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Rt,   'RES_W2RT', 'Resolved <w2Rt>',   'm2 kg kg-1 s-2',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRv, 'RE_WTLRV', 'Resolved <wThlRv>', 'm K kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRt, 'RE_WTLRT', 'Resolved <wThlRt>', 'm K kg kg-1 s-1', ymasks )
   end if
 
   if ( luserc ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRc2,   'RES_WRC2', 'Resolved <wRc2>',   'm kg2 kg-2 s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Rc,   'RES_W2RC', 'Resolved <w2Rc>',   'm2 kg kg-1 s-2',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRc, 'RE_WTLRC', 'Resolved <wThlRc>', 'm K kg kg-1 s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRvRc,  'RE_WRVRC', 'Resolved <wRvRc>',  'm kg2 kg-2 s-1',  ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRc2,   'RES_WRC2', 'Resolved <wRc2>',   'm kg2 kg-2 s-1',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Rc,   'RES_W2RC', 'Resolved <w2Rc>',   'm2 kg kg-1 s-2',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRc, 'RE_WTLRC', 'Resolved <wThlRc>', 'm K kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRvRc,  'RE_WRVRC', 'Resolved <wRvRc>',  'm kg2 kg-2 s-1',  ymasks )
   end if
 
   if ( luseri ) then
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRi2,   'RES_WRI2', 'Resolved <wRi2>',   'm kg2 kg-2 s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Ri,   'RES_W2RI', 'Resolved <w2Ri>',   'm2 kg kg-1 s-2',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRi, 'RE_WTLRI', 'Resolved <wThlRi>', 'm K kg kg-1 s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRvRi,  'RE_WRVRI', 'Resolved <wRvRi>',  'm kg2 kg-2 s-1',  ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRi2,   'RES_WRI2', 'Resolved <wRi2>',   'm kg2 kg-2 s-1',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Ri,   'RES_W2RI', 'Resolved <w2Ri>',   'm2 kg kg-1 s-2',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlRi, 'RE_WTLRI', 'Resolved <wThlRi>', 'm K kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRvRi,  'RE_WRVRI', 'Resolved <wRvRi>',  'm kg2 kg-2 s-1',  ymasks )
   end if
 
   if ( nsv > 0 ) then
@@ -562,11 +550,11 @@ if ( lles_resolved ) then
     tfield%ndimlist(4)  = NMNHDIM_BUDGET_LES_SV
     tfield%ndimlist(5:) = NMNHDIM_UNUSED
 
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WSv2,   'RES_WSV2', 'Resolved <wSv2>',   'm kg2 kg-2 s-1',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Sv,   'RES_W2SV', 'Resolved <w2Sv>',   'm2 kg kg-1 s-2',  ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlSv, 'RE_WTLSV', 'Resolved <wThlSv>', 'm K kg kg-1 s-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WSv2,   'RES_WSV2', 'Resolved <wSv2>',   'm kg2 kg-2 s-1',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_W2Sv,   'RES_W2SV', 'Resolved <w2Sv>',   'm2 kg kg-1 s-2',  ymasks )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WThlSv, 'RE_WTLSV', 'Resolved <wThlSv>', 'm K kg kg-1 s-1', ymasks )
     if ( luserv ) &
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRvSv,  'RE_WRVSV', 'Resolved <wRvSv>',  'm kg2 kg-2 s-1',  ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_WRvSv,  'RE_WRVSV', 'Resolved <wRvSv>',  'm kg2 kg-2 s-1',  ymasks )
 
     tfield%ndims = 3
     !tfield%ndimlist(1)  = NMNHDIM_BUDGET_LES_LEVEL
@@ -576,15 +564,15 @@ if ( lles_resolved ) then
     !tfield%ndimlist(5:) = NMNHDIM_UNUSED
   end if
 
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlPz, 'RES_TLPZ', 'Resolved <Thldp/dz>', 'K Pa m-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_ThlPz, 'RES_TLPZ', 'Resolved <Thldp/dz>', 'K Pa m-1',        ymasks )
   if ( luserc ) &
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RtPz, 'RES_RTPZ', 'Resolved <Rtdp/dz>', 'kg2 kg-2 Pa m-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RtPz,  'RES_RTPZ', 'Resolved <Rtdp/dz>',  'kg2 kg-2 Pa m-1', ymasks )
   if ( luserv ) &
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RvPz, 'RES_RVPZ', 'Resolved <Rvdp/dz>', 'kg2 kg-2 Pa m-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RvPz,  'RES_RVPZ', 'Resolved <Rvdp/dz>',  'kg2 kg-2 Pa m-1', ymasks )
   if ( luserc ) &
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RcPz, 'RES_RCPZ', 'Resolved <Rcdp/dz>', 'kg2 kg-2 Pa m-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RcPz,  'RES_RCPZ', 'Resolved <Rcdp/dz>',  'kg2 kg-2 Pa m-1', ymasks )
   if ( luseri ) &
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RiPz, 'RES_RIPZ', 'Resolved <Ridp/dz>', 'kg2 kg-2 Pa m-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_RiPz,  'RES_RIPZ', 'Resolved <Ridp/dz>',  'kg2 kg-2 Pa m-1', ymasks )
 
   if ( nsv > 0 ) then
     tfield%ndims = 4
@@ -594,7 +582,7 @@ if ( lles_resolved ) then
     tfield%ndimlist(4)  = NMNHDIM_BUDGET_LES_SV
     tfield%ndimlist(5:) = NMNHDIM_UNUSED
 
-    call Les_diachro_write( tpdiafile, XLES_RESOLVED_SvPz, 'RES_SVPZ', 'Resolved <Svdp/dz>', 'kg2 kg-2 Pa m-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_RESOLVED_SvPz, 'RES_SVPZ', 'Resolved <Svdp/dz>', 'kg2 kg-2 Pa m-1', ymasks )
 
     tfield%ndims = 3
     !tfield%ndimlist(1)  = NMNHDIM_BUDGET_LES_LEVEL
@@ -604,9 +592,9 @@ if ( lles_resolved ) then
     !tfield%ndimlist(5:) = NMNHDIM_UNUSED
   end if
 
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UKe, 'RES_UKE', 'Resolved flux of resolved kinetic energy', 'm3 s-3', ysubtitle)
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_VKe, 'RES_VKE', 'Resolved flux of resolved kinetic energy', 'm3 s-3', ysubtitle)
-  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WKe, 'RES_WKE', 'Resolved flux of resolved kinetic energy', 'm3 s-3', ysubtitle)
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_UKe, 'RES_UKE', 'Resolved flux of resolved kinetic energy', 'm3 s-3', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_VKe, 'RES_VKE', 'Resolved flux of resolved kinetic energy', 'm3 s-3', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_RESOLVED_WKe, 'RES_WKE', 'Resolved flux of resolved kinetic energy', 'm3 s-3', ymasks )
 end if
 !
 !
@@ -624,73 +612,73 @@ if ( lles_subgrid ) then
   tfield%ndimlist(3)  = NMNHDIM_BUDGET_LES_MASK
   tfield%ndimlist(4:) = NMNHDIM_UNUSED
 
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_Tke,  'SBG_TKE',  'Subgrid TKE',           'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_U2,   'SBG_U2',   'Subgrid <u2> variance', 'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_V2,   'SBG_V2',   'Subgrid <v2> variance', 'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_W2,   'SBG_W2',   'Subgrid <w2> variance', 'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_UV,   'SBG_UV',   'Subgrid <uv> flux',     'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WU,   'SBG_WU',   'Subgrid <wu> flux',     'm2 s-2', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WV,   'SBG_WV',   'Subgrid <wv> flux',     'm2 s-2', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_Tke,  'SBG_TKE',  'Subgrid TKE',           'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_U2,   'SBG_U2',   'Subgrid <u2> variance', 'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_V2,   'SBG_V2',   'Subgrid <v2> variance', 'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_W2,   'SBG_W2',   'Subgrid <w2> variance', 'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_UV,   'SBG_UV',   'Subgrid <uv> flux',     'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WU,   'SBG_WU',   'Subgrid <wu> flux',     'm2 s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WV,   'SBG_WV',   'Subgrid <wv> flux',     'm2 s-2', ymasks )
   call Les_diachro_write( tpdiafile, XLES_SUBGRID_Thl2, 'SBG_THL2', 'Subgrid liquid potential temperature variance', &
-                          'K2', ysubtITLE )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_UThl, 'SBG_UTHL', 'Subgrid hor. flux of liquid potential temperature',  &
-                          'm K s-1', YSUBTITLE )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_VThl, 'SBG_VTHL', 'Subgrid hor. flux of liquid potential temperature',  &
-                          'm K s-1', YSUBTITLE )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WThl, 'SBG_WTHL', 'Subgrid vert. flux of liquid potential temperature', &
-                          'm K s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WP,   'SBG_WP',   'Subgrid <wp> vertical Flux', 'm Pa s-1', ysubtitle )
-
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_THLUP_MF, 'THLUP_MF', 'Subgrid <thl> of updraft',    'K',          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RTUP_MF,  'RTUP_MF',  'Subgrid <rt> of updraft',     'kg kg-1',    ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RVUP_MF,  'RVUP_MF',  'Subgrid <rv> of updraft',     'kg kg-1',    ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RCUP_MF,  'RCUP_MF',  'Subgrid <rc> of updraft',     'kg kg-1',    ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RIUP_MF,  'RIUP_MF',  'Subgrid <ri> of updraft',     'kg kg-1',    ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WUP_MF,   'WUP_MF',   'Subgrid <w> of updraft',      'm s-1',      ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_MASSFLUX, 'MAFLX_MF', 'Subgrid <MF> of updraft',     'kg m-2 s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_DETR,     'DETR_MF',  'Subgrid <detr> of updraft',   'kg m-3 s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_ENTR,     'ENTR_MF',  'Subgrid <entr> of updraft',   'kg m-3 s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_FRACUP,   'FRCUP_MF', 'Subgrid <FracUp> of updraft', '1',          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_THVUP_MF, 'THVUP_MF', 'Subgrid <thv> of updraft',    'K',          ysubtitle )
+                          'K2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_UThl, 'SBG_UTHL', 'Subgrid horizontal flux of liquid potential temperature',  &
+                          'm K s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_VThl, 'SBG_VTHL', 'Subgrid horizontal flux of liquid potential temperature',  &
+                          'm K s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WThl, 'SBG_WTHL', 'Subgrid vertical flux of liquid potential temperature', &
+                          'm K s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WP,   'SBG_WP',   'Subgrid <wp> vertical Flux', 'm Pa s-1', ymasks )
+
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_THLUP_MF, 'THLUP_MF', 'Subgrid <thl> of updraft',    'K',          ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RTUP_MF,  'RTUP_MF',  'Subgrid <rt> of updraft',     'kg kg-1',    ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RVUP_MF,  'RVUP_MF',  'Subgrid <rv> of updraft',     'kg kg-1',    ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RCUP_MF,  'RCUP_MF',  'Subgrid <rc> of updraft',     'kg kg-1',    ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_RIUP_MF,  'RIUP_MF',  'Subgrid <ri> of updraft',     'kg kg-1',    ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WUP_MF,   'WUP_MF',   'Subgrid <w> of updraft',      'm s-1',      ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_MASSFLUX, 'MAFLX_MF', 'Subgrid <MF> of updraft',     'kg m-2 s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_DETR,     'DETR_MF',  'Subgrid <detr> of updraft',   'kg m-3 s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_ENTR,     'ENTR_MF',  'Subgrid <entr> of updraft',   'kg m-3 s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_FRACUP,   'FRCUP_MF', 'Subgrid <FracUp> of updraft', '1',          ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_THVUP_MF, 'THVUP_MF', 'Subgrid <thv> of updraft',    'K',          ymasks )
   call Les_diachro_write( tpdiafile, XLES_SUBGRID_WTHLMF,   'WTHL_MF',  'Subgrid <wthl> of mass flux convection scheme', &
-                          'm K s-1', ysubtitle )
+                          'm K s-1', ymasks )
   call Les_diachro_write( tpdiafile, XLES_SUBGRID_WRTMF,    'WRT_MF',   'Subgrid <wrt> of mass flux convection scheme',  &
-                          'm kg kg-1 s-1', ysubtitle )
+                          'm kg kg-1 s-1', ymasks )
   call Les_diachro_write( tpdiafile, XLES_SUBGRID_WTHVMF,   'WTHV_MF',  'Subgrid <wthv> of mass flux convection scheme', &
-                          'm K s-1', ysubtitle )
+                          'm K s-1', ymasks )
   call Les_diachro_write( tpdiafile, XLES_SUBGRID_WUMF,     'WU_MF',    'Subgrid <wu> of mass flux convection scheme',   &
-                          'm2 s-2', ysubtitle )
+                          'm2 s-2', ymasks )
   call Les_diachro_write( tpdiafile, XLES_SUBGRID_WVMF,     'WV_MF',    'Subgrid <wv> of mass flux convection scheme',   &
-                          'm2 s-2', ysubtitle )
+                          'm2 s-2', ymasks )
 
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_PHI3,  'SBG_PHI3', 'Subgrid Phi3 function',         '1',      ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_LMix,  'SBG_LMIX', 'Subgrid Mixing Length',         '1',      ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_LDiss, 'SBG_LDIS', 'Subgrid Dissipation Length',    '1',      ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_Km,    'SBG_KM',   'Eddy diffusivity for momentum', 'm2 s-1', ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_Kh,    'SBG_KH',   'Eddy diffusivity for heat',     'm2 s-1', ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_PHI3,  'SBG_PHI3', 'Subgrid Phi3 function',         '1',      ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_LMix,  'SBG_LMIX', 'Subgrid Mixing Length',         '1',      ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_LDiss, 'SBG_LDIS', 'Subgrid Dissipation Length',    '1',      ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_Km,    'SBG_KM',   'Eddy diffusivity for momentum', 'm2 s-1', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_Kh,    'SBG_KH',   'Eddy diffusivity for heat',     'm2 s-1', ymasks )
 
   if ( luserv ) then
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_WThv,  'SBG_WTHV', 'Subgrid vert. flux of liquid potential temperature', &
-                            'm K s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_Rt2,   'SBG_RT2',  'Subgrid total water variance', 'kg2 kg-2', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_ThlRt, 'SBG_TLRT', 'Subgrid <thlrt> covariance',  'K kg kg-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_WThv,  'SBG_WTHV', 'Subgrid vertical flux of liquid potential temperature', &
+                            'm K s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_Rt2,   'SBG_RT2',  'Subgrid total water variance', 'kg2 kg-2', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_ThlRt, 'SBG_TLRT', 'Subgrid <thlrt> covariance',  'K kg kg-1', ymasks )
     call Les_diachro_write( tpdiafile, XLES_SUBGRID_URt,   'SBG_URT',  'Subgrid total water horizontal flux', &
-                            'm kg kg-1 s-1', ysubtitle )
+                            'm kg kg-1 s-1', ymasks )
     call Les_diachro_write( tpdiafile, XLES_SUBGRID_VRt,   'SBG_VRT',  'Subgrid total water horizontal flux', &
-                            'm kg kg-1 s-1', ysubtitle )
+                            'm kg kg-1 s-1', ymasks )
     call Les_diachro_write( tpdiafile, XLES_SUBGRID_WRt,   'SBG_WRT',  'Subgrid total water vertical flux',   &
-                            'm kg kg-1 s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_PSI3,  'SBG_PSI3', 'Subgrid Psi3 function', '1', ysubtitle )
+                            'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_PSI3,  'SBG_PSI3', 'Subgrid Psi3 function', '1', ymasks )
   end if
 
   if ( luserc ) then
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_Rc2, 'SBG_RC2', 'Subgrid cloud water variance',        'kg2 kg-2', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_Rc2, 'SBG_RC2', 'Subgrid cloud water variance',        'kg2 kg-2', ymasks )
     call Les_diachro_write( tpdiafile, XLES_SUBGRID_URc, 'SBG_URC', 'Subgrid cloud water horizontal flux', 'm kg kg-1 s-1', &
-                            ysubtitle )
+                            ymasks )
     call Les_diachro_write( tpdiafile, XLES_SUBGRID_VRc, 'SBG_VRC', 'Subgrid cloud water horizontal flux', 'm kg kg-1 s-1', &
-                            ysubtitle )
+                            ymasks )
     call Les_diachro_write( tpdiafile, XLES_SUBGRID_WRc, 'SBG_WRC', 'Subgrid cloud water vertical flux',   'm kg kg-1 s-1', &
-                            ysubtitle )
+                            ymasks )
   end if
 
   if ( nsv > 0 ) then
@@ -701,9 +689,9 @@ if ( lles_subgrid ) then
     tfield%ndimlist(4)  = NMNHDIM_BUDGET_LES_SV
     tfield%ndimlist(5:) = NMNHDIM_UNUSED
 
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_USv, 'SBG_USV', 'Subgrid <uSv> horizontal flux', 'm kg kg-1 s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_VSv, 'SBG_VSV', 'Subgrid <vSv> horizontal flux', 'm kg kg-1 s-1', ysubtitle )
-    call Les_diachro_write( tpdiafile, XLES_SUBGRID_WSv, 'SBG_WSV', 'Subgrid <wSv> vertical flux',   'm kg kg-1 s-1', ysubtitle )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_USv, 'SBG_USV', 'Subgrid <uSv> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_VSv, 'SBG_VSV', 'Subgrid <vSv> horizontal flux', 'm kg kg-1 s-1', ymasks )
+    call Les_diachro_write( tpdiafile, XLES_SUBGRID_WSv, 'SBG_WSV', 'Subgrid <wSv> vertical flux',   'm kg kg-1 s-1', ymasks )
 
     tfield%ndims = 3
     !tfield%ndimlist(1)  = NMNHDIM_BUDGET_LES_LEVEL
@@ -715,16 +703,11 @@ if ( lles_subgrid ) then
 
   end if
 
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_UTke,  'SBG_UTKE', 'Subgrid flux of subgrid kinetic energy', 'm3 s-3',   &
-                          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_VTke,  'SBG_VTKE', 'Subgrid flux of subgrid kinetic energy', 'm3 s-3',   &
-                          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WTke,  'SBG_WTKE', 'Subgrid flux of subgrid kinetic energy', 'm3 s-3',   &
-                          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_W2Thl, 'SBG_W2TL', 'Subgrid flux of subgrid kinetic energy', 'm2 K s-2', &
-                          ysubtitle )
-  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WThl2, 'SBG_WTL2', 'Subgrid flux of subgrid kinetic energy', 'm K2 s-1', &
-                          ysubtitle )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_UTke,  'SBG_UTKE', 'Subgrid flux of subgrid kinetic energy', 'm3 s-3',   ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_VTke,  'SBG_VTKE', 'Subgrid flux of subgrid kinetic energy', 'm3 s-3',   ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WTke,  'SBG_WTKE', 'Subgrid flux of subgrid kinetic energy', 'm3 s-3',   ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_W2Thl, 'SBG_W2TL', 'Subgrid flux of subgrid kinetic energy', 'm2 K s-2', ymasks )
+  call Les_diachro_write( tpdiafile, XLES_SUBGRID_WThl2, 'SBG_WTL2', 'Subgrid flux of subgrid kinetic energy', 'm K2 s-1', ymasks )
 end if
 
 
@@ -972,14 +955,14 @@ tfield%ndimlist(3:) = NMNHDIM_UNUSED
 ldoavg  = xles_temp_mean_start /= XUNDEF .and. xles_temp_mean_end /= XUNDEF
 ldonorm = .false.
 
-call Les_diachro_write( tpdiafile, XLES_SWU,      'SWU',      'sw_up',     'W m-2' )
-call Les_diachro_write( tpdiafile, XLES_SWD,      'SWD',      'sw_down',   'W m-2' )
-call Les_diachro_write( tpdiafile, XLES_LWU,      'LWU',      'lw_up',     'W m-2' )
-call Les_diachro_write( tpdiafile, XLES_LWD,      'LWD',      'lw_down',   'W m-2' )
-call Les_diachro_write( tpdiafile, XLES_DTHRADSW, 'DTHRADSW', 'dthrad_sw', 'K s-1' )
-call Les_diachro_write( tpdiafile, XLES_DTHRADLW, 'DTHRADLW', 'dthrad_lw', 'K s-1' )
+call Les_diachro_write( tpdiafile, XLES_SWU,      'SWU',      'SW upward radiative flux',          'W m-2' )
+call Les_diachro_write( tpdiafile, XLES_SWD,      'SWD',      'SW downward radiative flux',        'W m-2' )
+call Les_diachro_write( tpdiafile, XLES_LWU,      'LWU',      'LW upward radiative flux',          'W m-2' )
+call Les_diachro_write( tpdiafile, XLES_LWD,      'LWD',      'LW downward radiative flux',        'W m-2' )
+call Les_diachro_write( tpdiafile, XLES_DTHRADSW, 'DTHRADSW', 'SW radiative temperature tendency', 'K s-1' )
+call Les_diachro_write( tpdiafile, XLES_DTHRADLW, 'DTHRADLW', 'LW radiative temperature tendency', 'K s-1' )
 !writes mean_effective radius at all levels
-call Les_diachro_write( tpdiafile, XLES_RADEFF,   'RADEFF',   'mean effective radius', 'micron' )
+call Les_diachro_write( tpdiafile, XLES_RADEFF,   'RADEFF',   'Mean effective radius',             'micron' )
 
 
 ! !Prepare metadate (used in Les_diachro_write calls)
@@ -1005,17 +988,17 @@ if ( nsv > 0 ) then
   !tfield%ndimlist(3:) = NMNHDIM_UNUSED
 end if
 
-call Les_diachro_write( tpdiafile, XLES_USTAR,      'U*',         'Friction velocity',                   'm s-1' )
-call Les_diachro_write( tpdiafile, XLES_WSTAR,      'W*',         'Convective velocity',                 'm s-1' )
+call Les_diachro_write( tpdiafile, XLES_USTAR,      'Ustar',      'Friction velocity',                   'm s-1' )
+call Les_diachro_write( tpdiafile, XLES_WSTAR,      'Wstar',      'Convective velocity',                 'm s-1' )
 call Les_diachro_write( tpdiafile, XLES_BL_HEIGHT,  'BL_H',       'Boundary Layer Height',               'm' )
 call Les_diachro_write( tpdiafile, XLES_MO_LENGTH,  'L_MO',       'Monin-Obukhov length',                'm' )
-call Les_diachro_write( tpdiafile, XLES_INT_TKE,    'INT_TKE',    'Vertical integrated tke',             'm2 s-2' )
+call Les_diachro_write( tpdiafile, XLES_INT_TKE,    'INT_TKE',    'Vertical integrated TKE',             'm2 s-2' )
 if ( luserc ) &
 call Les_diachro_write( tpdiafile, XLES_ZCB,        'ZCB',        'Cloud base Height',                   'm' )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_CFtot,      'ZCFTOT',     'Total Cloud cover',                   '1' )
+call Les_diachro_write( tpdiafile, XLES_CFtot,      'ZCFTOT',     'Total cloud cover (rc>1e-6)',         '1' )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_CF2tot,     'ZCF2TOT',    'Total Cloud cove 2r',                 '1' )
+call Les_diachro_write( tpdiafile, XLES_CF2tot,     'ZCF2TOT',    'Total cloud cover (rc>1e-5)',         '1' )
 if ( luserc ) &
 call Les_diachro_write( tpdiafile, XLES_LWP,        'LWP',        'Liquid Water path',                   'kg m-2' )
 if ( luserc ) &
@@ -1031,21 +1014,22 @@ call Les_diachro_write( tpdiafile, XLES_GWP,        'GWP',        'Graupel Water
 if ( luserh ) &
 call Les_diachro_write( tpdiafile, XLES_HWP,        'HWP',        'Hail Water path',                     'kg m-2' )
 if ( luserr ) &
-call Les_diachro_write( tpdiafile, XLES_PRECFR,     'PREC_FRAC',  'Fract of col where rain at surface',  '1' )
+call Les_diachro_write( tpdiafile, XLES_PRECFR,     'PREC_FRAC',  'Fraction of columns where rain at surface',  '1' )
 if ( luserr ) &
-call Les_diachro_write( tpdiafile, XLES_INPRR,      'INST_PREC',  'Inst precip rate',                    'mm day-1' )
+call Les_diachro_write( tpdiafile, XLES_INPRR,      'INST_PREC',  'Instantaneous precipitation rate',       'mm day-1' )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_INPRC,      'INST_SEDIM', 'Inst cloud precip rate',              'mm day-1' )
+call Les_diachro_write( tpdiafile, XLES_INPRC,      'INST_SEDIM', 'Instantaneous cloud precipitation rate', 'mm day-1' )
 if ( luserc .and. ( ldeposc .or. ldepoc ) ) &
-call Les_diachro_write( tpdiafile, XLES_INDEP,      'INST_DEPOS', 'Inst cloud deposi rate',              'mm day-1' )
+call Les_diachro_write( tpdiafile, XLES_INDEP,      'INST_DEPOS', 'Instantaneous cloud deposition rate',    'mm day-1' )
 if ( luserr ) &
-call Les_diachro_write( tpdiafile, XLES_RAIN_INPRR, 'RAIN_PREC',  'Inst pr. rate over rainy grid cells', 'mm day-1' )
+call Les_diachro_write( tpdiafile, XLES_RAIN_INPRR, 'RAIN_PREC',  'Instantaneous precipitation rate over rainy grid cells', &
+                        'mm day-1' )
 if ( luserr ) &
-call Les_diachro_write( tpdiafile, XLES_ACPRR,      'ACCU_PREC',  'Accu precip rate',                    'mm' )
+call Les_diachro_write( tpdiafile, XLES_ACPRR,      'ACCU_PREC',  'Accumulated precipitation rate',             'mm' )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_ZMAXCF,     'ZMAXCF',     'Height of Cloud fraction max',        'm' )
+call Les_diachro_write( tpdiafile, XLES_ZMAXCF,     'ZMAXCF',     'Height of Cloud fraction maximum (rc>1e-6)', 'm' )
 if ( luserc ) &
-call Les_diachro_write( tpdiafile, XLES_ZMAXCF2,    'ZMAXCF2',    'Height of Cloud fraction2max',        'm' )
+call Les_diachro_write( tpdiafile, XLES_ZMAXCF2,    'ZMAXCF2',    'Height of Cloud fraction maximum (rc>1e-5)', 'm' )
 
 !-------------------------------------------------------------------------------
 !
@@ -1118,12 +1102,14 @@ if ( nspectra_k > 0 ) then
     call Les_diachro_2pt_write( tpdiafile, XCORRi_WRi,   XCORRj_WRi,   'WRI',  'W*ri    2 points correlations', 'm kg s-1 kg-1' )
   end if
 
+!PW: TODO: ameliorer le ygroup (tenir compte de ce qu'est la variable scalaire et pas juste son jsv!)
   do jsv = 1, nsv
     Write( ygroup, fmt = "( a2, i3.3 )" ) "SS", jsv
     call Les_diachro_2pt_write( tpdiafile, XCORRi_SvSv(:,:,:,JSV), XCORRj_SvSv(:,:,:,JSV), ygroup, &
                                 'Sv*Sv   2 points correlations','kg2 kg-2' )
   end do
 
+!PW: TODO: ameliorer le ygroup (tenir compte de ce qu'est la variable scalaire et pas juste son jsv!)
   do jsv = 1, nsv
     Write( ygroup, fmt = "( a2, i3.3 )" ) "WS", jsv
     call Les_diachro_2pt_write( tpdiafile, XCORRi_WSv(:,:,:,JSV), XCORRj_WSv(:,:,:,JSV), ygroup, &
@@ -1205,7 +1191,7 @@ end subroutine Les_diachro_write_2D
 
 !------------------------------------------------------------------------------
 
-subroutine Les_diachro_write_3D( tpdiafile, pdata, hmnhname, hcomment, hunits, hsuffixes )
+subroutine Les_diachro_write_3D( tpdiafile, pdata, hmnhname, hcomment, hunits, hmasks )
 
 use modd_io,          only: tfiledata
 
@@ -1216,20 +1202,20 @@ real,             dimension(:,:,:),       intent(in) :: pdata
 character(len=*),                         intent(in) :: hmnhname
 character(len=*),                         intent(in) :: hcomment
 character(len=*),                         intent(in) :: hunits
-character(len=*), dimension(:), optional, intent(in) :: hsuffixes
+character(len=*), dimension(:), optional, intent(in) :: hmasks
 
 tfield%cmnhname  = hmnhname
 tfield%clongname = hmnhname
 tfield%ccomment  = hcomment
 tfield%cunits    = hunits
 
-call Les_diachro( tpdiafile, tfield, ldoavg, ldonorm, pdata, hsuffixes )
+call Les_diachro( tpdiafile, tfield, ldoavg, ldonorm, pdata, hmasks = hmasks )
 
 end subroutine Les_diachro_write_3D
 
 !------------------------------------------------------------------------------
 
-subroutine Les_diachro_write_4D( tpdiafile, pdata, hmnhname, hcomment, hunits, hsuffixes )
+subroutine Les_diachro_write_4D( tpdiafile, pdata, hmnhname, hcomment, hunits, hmasks )
 
 use modd_io,          only: tfiledata
 
@@ -1240,14 +1226,14 @@ real,             dimension(:,:,:,:),       intent(in) :: pdata
 character(len=*),                           intent(in) :: hmnhname
 character(len=*),                           intent(in) :: hcomment
 character(len=*),                           intent(in) :: hunits
-character(len=*), dimension(:),   optional, intent(in) :: hsuffixes
+character(len=*), dimension(:),   optional, intent(in) :: hmasks
 
 tfield%cmnhname  = hmnhname
 tfield%clongname = hmnhname
 tfield%ccomment  = hcomment
 tfield%cunits    = hunits
 
-call Les_diachro( tpdiafile, tfield, ldoavg, ldonorm, pdata, hsuffixes )
+call Les_diachro( tpdiafile, tfield, ldoavg, ldonorm, pdata, hmasks = hmasks )
 
 end subroutine Les_diachro_write_4D
 
diff --git a/src/MNH/write_profilern.f90 b/src/MNH/write_profilern.f90
index 45771c76007a73d4431544caa77a48ff7c103f21..16a433d17e545a4c0d6d1ca3489ccdd040eecbf2 100644
--- a/src/MNH/write_profilern.f90
+++ b/src/MNH/write_profilern.f90
@@ -127,7 +127,8 @@ CONTAINS
 !----------------------------------------------------------------------------
 SUBROUTINE PROFILER_DIACHRO_n(TPROFILER,II)
 
-use modd_budget, only: tbudiachrometadata
+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_PROFILER_TIME, NMNHDIM_PROFILER_PROC, NMNHDIM_UNUSED, &
                        tfield_metadata_base, TYPEREAL
 
@@ -651,20 +652,53 @@ tzfields(:)%ndimlist(4) = NMNHDIM_PROFILER_TIME
 tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(6) = NMNHDIM_PROFILER_PROC
 
-tzbudiachro%cgroupname = ygroup
-tzbudiachro%cname      = ygroup
-tzbudiachro%ccomment   = 'Vertical profiles at position of profiler ' // Trim( ygroup )
-tzbudiachro%ctype      = 'CART'
-tzbudiachro%ccategory  = 'profiler'
-tzbudiachro%cshape     = 'vertical profile'
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Profilers'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different vertical profilers'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+tzbudiachro%clevels  (NLVL_GROUP)       = ygroup
+tzbudiachro%ccomments(NLVL_GROUP)       = 'Vertical profiles at position of profiler ' // Trim( ygroup )
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Vertical_profile'
+tzbudiachro%ccomments(NLVL_SHAPE)       = ''
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
 tzbudiachro%lmobile    = .false.
+!Compression does not make sense here
+!Keep these values for backward compatibility of LFI files
 tzbudiachro%licompress = .true.
 tzbudiachro%ljcompress = .true.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
+!Horizontal boundaries in physical domain does not make sense here (but flyer position does)
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nil        = 1
 tzbudiachro%nih        = 1
 tzbudiachro%njl        = 1
 tzbudiachro%njh        = 1
+!1->iku includes non-physical levels (IKU=NKMAX+2*JPVEXT)
+!This does not conform to documentation (limits are in the physical domain)
+!These values are not written in the netCDF files
+!These values are written in the LFI files. They are kept for backward compatibility (and not set to default values)
 tzbudiachro%nkl        = 1
 tzbudiachro%nkh        = iku
 
diff --git a/src/MNH/write_seriesn.f90 b/src/MNH/write_seriesn.f90
index e0aa67be2a6e3884202bd00288f5cbff50d3594c..a1e425f39842f5fb842e9b524db845929f6549e2 100644
--- a/src/MNH/write_seriesn.f90
+++ b/src/MNH/write_seriesn.f90
@@ -69,7 +69,8 @@ END MODULE MODI_WRITE_SERIES_n
 !*    0. Declaration
 !     --------------
 !
-use modd_budget,        only: tbudiachrometadata
+use modd_budget,        only: NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK, &
+                              tbudiachrometadata
 use modd_field,         only: NMNHDIM_NI, NMNHDIM_NI_U,                                                               &
                               NMNHDIM_SERIES_LEVEL, NMNHDIM_SERIES_LEVEL_W, NMNHDIM_SERIES_TIME, NMNHDIM_SERIES_PROC, &
                               NMNHDIM_UNUSED,                                                                         &
@@ -95,7 +96,7 @@ TYPE(TFILEDATA),    INTENT(IN) :: TPDIAFILE    ! file to write
 !
 INTEGER                              :: IIB,IJB,IKB     ! Begin of physical dimensions
 INTEGER                              :: IIE,IJE,IKE     ! End   of physical dimensions
-INTEGER                              :: JS,JT,JJ,JI      ! Loop indices 
+INTEGER                              :: JS, JT, JJ, JI, JP ! Loop indices
 INTEGER                              :: ISB1,ISB2
 CHARACTER (LEN=2)                    :: YS             ! String for y-slice
 CHARACTER (LEN=3)                    :: YSL,YSH        ! Strings for y-slice
@@ -251,24 +252,50 @@ tzfields(:)%cunits    = csunit1(:)
 tzfields(:)%ccomment  = cscomment1(:)
 tzfields(:)%ngrid     = nsgridd1(:)
 tzfields(:)%ntype     = TYPEREAL
-tzfields(:)%ndims     = 2
+! tzfields(:)%ndims     = 2
+tzfields(:)%ndims     = 1 !Set to 1 because write are done in a loop (1 write per "process")
 tzfields(:)%ndimlist(1) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(2) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(3) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(4) = NMNHDIM_SERIES_TIME
 tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
-tzfields(:)%ndimlist(6) = NMNHDIM_SERIES_PROC
-
-tzbudiachro%cgroupname = 'TSERIES'
-tzbudiachro%cname      = 'TSERIES'
-tzbudiachro%ccomment   = 'Time series of horizontally and vertically averaged fields'
-tzbudiachro%ctype      = 'CART'
-tzbudiachro%ccategory  = 'time series'
-tzbudiachro%cshape     = 'cartesian' !It is based on a cartesian domain (with compression in all directions)
+! tzfields(:)%ndimlist(6) = NMNHDIM_SERIES_PROC
+tzfields(:)%ndimlist(6) = NMNHDIM_UNUSED !Set to unused because write are done in a loop (1 write per "process")
+
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Time_series'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different time series'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+tzbudiachro%clevels  (NLVL_GROUP)       = 'TSERIES'
+tzbudiachro%ccomments(NLVL_GROUP)       = 'Time series of horizontally and vertically averaged fields'
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Cartesian' !It is based on a cartesian domain (with compression in all directions)
+tzbudiachro%ccomments(NLVL_SHAPE)       = 'Cartesian domain'
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .true.
+! tzbudiachro%clevels  (NLVL_MASK)        = DONE LATER
+! tzbudiachro%ccomments(NLVL_MASK)        = DONE LATER
+
 tzbudiachro%lmobile    = .false.
 tzbudiachro%licompress = .true.
 tzbudiachro%ljcompress = .true.
 tzbudiachro%lkcompress = .true.
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
 tzbudiachro%nil        = niboxl
 tzbudiachro%nih        = niboxh
 tzbudiachro%njl        = njboxl
@@ -276,8 +303,15 @@ tzbudiachro%njh        = njboxh
 tzbudiachro%nkl        = 1
 tzbudiachro%nkh        = ikmax
 
-call Write_diachro( tpdiafile, tzbudiachro, tzfields, tpsdates(1:nsnbstept), &
-                    xsseries1(1:1,1:1,1:1,1:nsnbstept,1:1,:)                 )
+! Loop on the different masks
+! Do not provide all tzfields once because they can be stored in different HDF groups (based on masks)
+do jp = 1 , nstemp_serie1
+  tzbudiachro%clevels(NLVL_MASK) = Trim( csmask1(jp) )
+  tzbudiachro%ccomments(NLVL_MASK) = ''
+
+  call Write_diachro( tpdiafile, tzbudiachro, [ tzfields(jp) ], tpsdates(1:nsnbstept), &
+                      xsseries1(1:1,1:1,1:1,1:nsnbstept,1:1,jp:jp)                 )
+end do
 
 deallocate( tzfields )
 !
@@ -337,7 +371,8 @@ tzfields(:)%cunits    = csunit2(:)
 tzfields(:)%ccomment  = cscomment2(:)
 tzfields(:)%ngrid     = nsgridd2(:)
 tzfields(:)%ntype     = TYPEREAL
-tzfields(:)%ndims     = 3
+! tzfields(:)%ndims     = 3
+tzfields(:)%ndims     = 2 !Set to 2 because write are done in a loop (1 write per "process")
 tzfields(:)%ndimlist(1) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(2) = NMNHDIM_UNUSED
 do ji = 1, nstemp_serie2
@@ -352,18 +387,43 @@ do ji = 1, nstemp_serie2
 end do
 tzfields(:)%ndimlist(4) = NMNHDIM_SERIES_TIME
 tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
-tzfields(:)%ndimlist(6) = NMNHDIM_SERIES_PROC
-
-tzbudiachro%cgroupname = 'ZTSERIES'
-tzbudiachro%cname      = 'ZTSERIES'
-tzbudiachro%ccomment   = 'Time series of horizontally averaged vertical profile'
-tzbudiachro%ctype      = 'CART'
-tzbudiachro%ccategory  = 'time series'
-tzbudiachro%cshape     = 'cartesian'  !It is based on a cartesian domain (with horizontal compression)
+! tzfields(:)%ndimlist(6) = NMNHDIM_SERIES_PROC
+tzfields(:)%ndimlist(6) = NMNHDIM_UNUSED !Set to unused because write are done in a loop (1 write per "process")
+
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Time_series'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different time series'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+tzbudiachro%clevels  (NLVL_GROUP)       = 'ZTSERIES'
+tzbudiachro%ccomments(NLVL_GROUP)       = 'Time series of horizontally averaged vertical profile'
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Cartesian' !It is based on a cartesian domain (with horizontal compression)
+tzbudiachro%ccomments(NLVL_SHAPE)       = 'Cartesian domain'
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .true.
+! tzbudiachro%clevels  (NLVL_MASK)        = DONE LATER
+! tzbudiachro%ccomments(NLVL_MASK)        = DONE LATER
+
 tzbudiachro%lmobile    = .false.
 tzbudiachro%licompress = .true.
 tzbudiachro%ljcompress = .true.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
 tzbudiachro%nil        = niboxl
 tzbudiachro%nih        = niboxh
 tzbudiachro%njl        = njboxl
@@ -371,8 +431,15 @@ tzbudiachro%njh        = njboxh
 tzbudiachro%nkl        = 1
 tzbudiachro%nkh        = ikmax
 
-call Write_diachro( tpdiafile, tzbudiachro, tzfields, tpsdates(1:nsnbstept), &
-                    xsseries2(1:1,1:1,1:ikmax,1:nsnbstept,1:1,:)             )
+! Loop on the different masks
+! Do not provide all tzfields once because they can be stored in different HDF groups (based on masks)
+do jp = 1 , nstemp_serie2
+  tzbudiachro%clevels(NLVL_MASK) = csmask2(jp)
+  tzbudiachro%ccomments(NLVL_MASK) = ''
+
+  call Write_diachro( tpdiafile, tzbudiachro, [ tzfields(jp) ], tpsdates(1:nsnbstept), &
+                      xsseries2(1:1,1:1,1:ikmax,1:nsnbstept,1:1,jp:jp)                 )
+end do
 
 deallocate( tzfields )
 !
@@ -453,16 +520,41 @@ DO JS=1,NBJSLICE
   tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
   tzfields(:)%ndimlist(6) = NMNHDIM_SERIES_PROC
 
-  tzbudiachro%cgroupname = ygroup
-  tzbudiachro%cname      = ygroup
-  tzbudiachro%ccomment   = 'Time series of y-horizontally averaged fields at one level or vertically averaged between 2 levels'
-  tzbudiachro%ctype      = 'SSOL'
-  tzbudiachro%ccategory  = 'time series'
-  tzbudiachro%cshape     = 'cartesian' !It is based on a cartesian domain (with compression in 1 direction)
+  tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+  tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Time_series'
+  tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different time series'
+
+  tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+  tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+  tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+  tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+  tzbudiachro%clevels  (NLVL_GROUP)       = Trim( ygroup )
+  tzbudiachro%ccomments(NLVL_GROUP)       = 'Time series of y-horizontally averaged fields at one level ' // &
+                                            'or vertically averaged between 2 levels'
+
+  tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+  tzbudiachro%clevels  (NLVL_SHAPE)       = 'Cartesian' !It is based on a cartesian domain (with compression in 1 direction)
+  tzbudiachro%ccomments(NLVL_SHAPE)       = 'Cartesian domain'
+
+  tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+  tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+  tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+  tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+  tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+  tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+  tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+  tzbudiachro%clevels  (NLVL_MASK)        = ''
+  tzbudiachro%ccomments(NLVL_MASK)        = ''
+
   tzbudiachro%lmobile    = .false.
   tzbudiachro%licompress = .false.
   tzbudiachro%ljcompress = .true.
   tzbudiachro%lkcompress = .true.
+  tzbudiachro%ltcompress = .false.
+  tzbudiachro%lnorm      = .false.
   tzbudiachro%nil        = 1
   tzbudiachro%nih        = iiu_ll
   tzbudiachro%njl        = 1
diff --git a/src/MNH/write_stationn.f90 b/src/MNH/write_stationn.f90
index 398d122cab218274a707ce9ffe13318c991c3210..7934d9f400638166ba241ad91dd3e099d1378f54 100644
--- a/src/MNH/write_stationn.f90
+++ b/src/MNH/write_stationn.f90
@@ -123,7 +123,8 @@ CONTAINS
 !----------------------------------------------------------------------------
 SUBROUTINE STATION_DIACHRO_n(TSTATION,II)
 
-use modd_field, only:  NMNHDIM_STATION_TIME, NMNHDIM_STATION_PROC, NMNHDIM_UNUSED, &
+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
 
 TYPE(STATION),        INTENT(IN)       :: TSTATION
@@ -759,16 +760,45 @@ tzfields(:)%ndimlist(4) = NMNHDIM_STATION_TIME
 tzfields(:)%ndimlist(5) = NMNHDIM_UNUSED
 tzfields(:)%ndimlist(6) = NMNHDIM_STATION_PROC
 
-tzbudiachro%cgroupname = ygroup
-tzbudiachro%cname      = ygroup
-tzbudiachro%ccomment   = 'Values at position of station ' // Trim( ygroup )
-tzbudiachro%ctype      = 'CART'
-tzbudiachro%ccategory  = 'station'
-tzbudiachro%cshape     = 'point'
+tzbudiachro%lleveluse(NLVL_CATEGORY)    = .true.
+tzbudiachro%clevels  (NLVL_CATEGORY)    = 'Stations'
+tzbudiachro%ccomments(NLVL_CATEGORY)    = 'Level for the different stations'
+
+tzbudiachro%lleveluse(NLVL_SUBCATEGORY) = .false.
+tzbudiachro%clevels  (NLVL_SUBCATEGORY) = ''
+tzbudiachro%ccomments(NLVL_SUBCATEGORY) = ''
+
+tzbudiachro%lleveluse(NLVL_GROUP)       = .true.
+tzbudiachro%clevels  (NLVL_GROUP)       = ygroup
+tzbudiachro%ccomments(NLVL_GROUP)       = 'Values at position of station ' // Trim( ygroup )
+
+tzbudiachro%lleveluse(NLVL_SHAPE)       = .false.
+tzbudiachro%clevels  (NLVL_SHAPE)       = 'Point'
+tzbudiachro%ccomments(NLVL_SHAPE)       = 'Values at position of station ' // Trim( ygroup )
+
+tzbudiachro%lleveluse(NLVL_TIMEAVG)     = .false.
+tzbudiachro%clevels  (NLVL_TIMEAVG)     = 'Not_time_averaged'
+tzbudiachro%ccomments(NLVL_TIMEAVG)     = 'Values are not time averaged'
+
+tzbudiachro%lleveluse(NLVL_NORM)        = .false.
+tzbudiachro%clevels  (NLVL_NORM)        = 'Not_normalized'
+tzbudiachro%ccomments(NLVL_NORM)        = 'Values are not normalized'
+
+tzbudiachro%lleveluse(NLVL_MASK)        = .false.
+tzbudiachro%clevels  (NLVL_MASK)        = ''
+tzbudiachro%ccomments(NLVL_MASK)        = ''
+
 tzbudiachro%lmobile    = .false.
+!Compression does not make sense here
+!Keep these values for backward compatibility of LFI files
 tzbudiachro%licompress = .true.
 tzbudiachro%ljcompress = .true.
 tzbudiachro%lkcompress = .false.
+tzbudiachro%ltcompress = .false.
+tzbudiachro%lnorm      = .false.
+!Boundaries in physical domain does not make sense here
+!These values are not written in the netCDF files
+!These values are written in the LFI files. Kept for backward compatibility of LFI files
 tzbudiachro%nil        = 1
 tzbudiachro%nih        = 1
 tzbudiachro%njl        = 1