diff --git a/conf/profile_mesonh.ihm b/conf/profile_mesonh.ihm
index 8dc9ea7c4319d051b022a6d958825a61a93507f0..123412edff8769c00cf6ef1ab94bf62da0382d19 100755
--- a/conf/profile_mesonh.ihm
+++ b/conf/profile_mesonh.ihm
@@ -91,6 +91,10 @@ export LFI_INT=${LFI_INT}
 #
 export MNH_REAL=${MNH_REAL}
 #
+#  Len of HREC characters 
+#
+export LEN_HREC=${LEN_HREC}
+#
 #  FOREFIRE
 #
 export MNH_FOREFIRE=${MNH_FOREFIRE}
diff --git a/src/MNH/mode_RBK90_Integrator.f90 b/src/MNH/mode_RBK90_Integrator.f90
index a16d225f9060279ac0dac3a4d73b54c280c11a98..3746e1712af2007c807dc77135d6e7bbda710f55 100644
--- a/src/MNH/mode_RBK90_Integrator.f90
+++ b/src/MNH/mode_RBK90_Integrator.f90
@@ -303,7 +303,7 @@ INTEGER, INTENT(IN) :: KMI      ! model number
    REAL :: ros_A(15), ros_C(15), ros_M(6), ros_E(6), &
                     ros_Alpha(6), ros_Gamma(6), ros_ELO
    LOGICAL :: ros_NewF(6)
-   CHARACTER(LEN=12) :: ros_Name
+   CHARACTER(LEN=LEN_HREC) :: ros_Name
 !~~~>  Local variables
    REAL :: Roundoff, FacMin, FacMax, FacRej, FacSafe
    REAL :: Hmin, Hmax, Hstart
diff --git a/src/MNH/modeln.f90 b/src/MNH/modeln.f90
index b0323f1c0d5e61267078dce9dbeee78433e006e6..09408f9ca0836e7d7e6cc089f498c196a0697a93 100644
--- a/src/MNH/modeln.f90
+++ b/src/MNH/modeln.f90
@@ -445,7 +445,7 @@ REAL*8,DIMENSION(2)         :: ZTIME,ZTIME1,ZTIME2,ZEND,ZTOT,ZALL,ZTOT_PT
 REAL*8,DIMENSION(2)         :: ZTIME_STEP,ZTIME_STEP_PTS
 CHARACTER                 :: YMI
 INTEGER                   :: IPOINTS
-CHARACTER(len=12)         :: YTCOUNT,YPOINTS
+CHARACTER(len=LEN_HREC)         :: YTCOUNT,YPOINTS
 
 REAL         :: ZSTAT_CSTORE,ZSTAT_CBOUND,ZSTAT_CGUESS,ZSTAT_CADV,ZSTAT_CSOURCES
 REAL         :: ZSTAT_CDIFF,ZSTAT_CRELAX,ZSTAT_CPARAM
@@ -519,7 +519,7 @@ LOGICAL :: KHHONI
 REAL :: TEMPS
 INTEGER :: NSV_END
 CHARACTER (LEN=100) :: YCOMMENT   ! Comment string in LFIFM file
-CHARACTER (LEN=16)  :: YRECFM     ! Name of the desired field in LFIFM file
+CHARACTER (LEN=LEN_HREC)  :: YRECFM     ! Name of the desired field in LFIFM file
 !
 INTEGER             :: ILENG      ! Length of comment string in LFIFM file
 INTEGER             :: IGRID      ! C-grid indicator in LFIFM file
diff --git a/src/MNH/read_all_data_grib_case.f90 b/src/MNH/read_all_data_grib_case.f90
index b7c9ac81447cee60a2365fba62a7a1f81b9ce336..68682d9ff69c564e97284c9395c476183958d6dc 100644
--- a/src/MNH/read_all_data_grib_case.f90
+++ b/src/MNH/read_all_data_grib_case.f90
@@ -277,7 +277,7 @@ INTEGER  :: IDATE
 INTEGER  :: ITIMESTEP
 CHARACTER(LEN=10) :: CSTEPUNIT
 !chemistery field
-CHARACTER(LEN=12)                  :: YPRE_MOC="PRE_MOC1.nam"
+CHARACTER(LEN=LEN_HREC)                  :: YPRE_MOC="PRE_MOC1.nam"
 INTEGER, DIMENSION(:), ALLOCATABLE :: INUMGRIB, INUMLEV  ! grib
 INTEGER, DIMENSION(:), ALLOCATABLE :: INUMLEV1, INUMLEV2 !numbers
 INTEGER                            :: IMOC
@@ -286,7 +286,7 @@ INTEGER                            :: ICHANNEL
 INTEGER                            :: INDX
 INTEGER                            :: INACT
 CHARACTER(LEN=40)                  :: YINPLINE        ! input line
-CHARACTER(LEN=16)                  :: YFIELD
+CHARACTER(LEN=LEN_HREC)                  :: YFIELD
 CHARACTER, PARAMETER               :: YPTAB = CHAR(9) ! TAB character is ASCII : 9
 CHARACTER, PARAMETER               :: YPCOM = CHAR(44)! COMma character is ASCII : 44
 CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE :: YMNHNAME ! species names
diff --git a/src/MNH/write_surf_mnh.f90 b/src/MNH/write_surf_mnh.f90
index 073515c71e85bc044222c5aaa3026d037404b5bd..59923d9ccc504a699cc898c760d8a34a08ecb9cb 100644
--- a/src/MNH/write_surf_mnh.f90
+++ b/src/MNH/write_surf_mnh.f90
@@ -65,7 +65,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12), INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC), INTENT(IN)  :: HREC     ! name of the article to be read
 REAL,              INTENT(IN)  :: PFIELD   ! the real scalar to be read
 INTEGER,           INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
 CHARACTER(LEN=100),INTENT(IN)  :: HCOMMENT ! Comment string
@@ -171,7 +171,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),   INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),   INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,             INTENT(IN)  :: KL       ! number of points
 REAL, DIMENSION(KL), INTENT(IN)  :: PFIELD   ! array containing the data field
 INTEGER,             INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
@@ -424,7 +424,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),   INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),   INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,             INTENT(IN)  :: KL1,KL2       ! number of points
 REAL, DIMENSION(KL1,KL2), INTENT(IN)  :: PFIELD   ! array containing the data field
 LOGICAL,DIMENSION(JPCOVER),   INTENT(IN)  ::OFLAG  ! mask for array filling
@@ -452,7 +452,7 @@ REAL, DIMENSION(:),   ALLOCATABLE :: ZW1D   ! 1D work array
 INTEGER           :: IIU, IJU, IIB, IJB, IIE, IJE ! dimensions of horizontal fields
 INTEGER, DIMENSION(:), ALLOCATABLE :: IMASK       ! mask for unpacking
 !
-CHARACTER(LEN=16) :: YREC
+CHARACTER(LEN=LEN_HREC) :: YREC
 CHARACTER(LEN=100):: YCOMMENT
 !JUANZ
 INTEGER           :: NCOVER,ICOVER,IKL2, JL2
@@ -607,7 +607,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),        INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),        INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,                  INTENT(IN)  :: KL1      ! number of points
 INTEGER,                  INTENT(IN)  :: KL2      ! 2nd dimension
 REAL, DIMENSION(KL1,KL2), INTENT(IN)  :: PFIELD   ! array containing the data field
@@ -757,7 +757,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),   INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),   INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,             INTENT(IN)  :: KFIELD   ! the integer to be read
 INTEGER,             INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
 CHARACTER(LEN=100),  INTENT(IN)  :: HCOMMENT ! Comment string
@@ -861,7 +861,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),      INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),      INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,                INTENT(IN)  :: KL       ! number of points
 INTEGER, DIMENSION(KL), INTENT(IN)  :: KFIELD   ! the integer to be read
 INTEGER,                INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
@@ -964,7 +964,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be read
 CHARACTER(LEN=40),  INTENT(IN)  :: HFIELD   ! the integer to be read
 INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
 CHARACTER(LEN=100), INTENT(IN)  :: HCOMMENT ! Comment string
@@ -1056,7 +1056,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),      INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),      INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,                INTENT(IN)  :: KL       ! number of points
 LOGICAL, DIMENSION(KL), INTENT(IN)  :: OFIELD   ! array containing the data field
 INTEGER,                INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
@@ -1186,7 +1186,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be read
 LOGICAL,            INTENT(IN)  :: OFIELD   ! array containing the data field
 INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem appears
 CHARACTER(LEN=100), INTENT(IN)  :: HCOMMENT ! Comment string
@@ -1276,7 +1276,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,            INTENT(IN)  :: KYEAR    ! year
 INTEGER,            INTENT(IN)  :: KMONTH   ! month
 INTEGER,            INTENT(IN)  :: KDAY     ! day
@@ -1287,7 +1287,7 @@ CHARACTER(LEN=100), INTENT(IN)  :: HCOMMENT ! Comment string
 !*      0.2   Declarations of local variables
 !
 !
-CHARACTER(LEN=16)      :: YRECFM    ! Name of the article to be written
+CHARACTER(LEN=LEN_HREC)      :: YRECFM    ! Name of the article to be written
 INTEGER, DIMENSION(3)  :: ITDATE
 !-------------------------------------------------------------------------------
 !
@@ -1395,7 +1395,7 @@ IMPLICIT NONE
 !
 !*      0.1   Declarations of arguments
 !
-CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,            INTENT(IN) :: KL1       ! number of points
 INTEGER, DIMENSION(KL1), INTENT(IN)  :: KYEAR    ! year
 INTEGER, DIMENSION(KL1), INTENT(IN)  :: KMONTH   ! month
@@ -1407,7 +1407,7 @@ CHARACTER(LEN=100), INTENT(IN)  :: HCOMMENT ! Comment string
 !*      0.2   Declarations of local variables
 !
 !
-CHARACTER(LEN=16)      :: YRECFM    ! Name of the article to be written
+CHARACTER(LEN=LEN_HREC)      :: YRECFM    ! Name of the article to be written
 INTEGER, DIMENSION(3,KL1)  :: ITDATE
 !-------------------------------------------------------------------------------
 !
diff --git a/src/Makefile.MESONH.mk b/src/Makefile.MESONH.mk
index b86951ce046e3dd9bc2db9150c86b0eed8aa2ed4..179f53bddb479270c6eaae260344f52202df2319 100644
--- a/src/Makefile.MESONH.mk
+++ b/src/Makefile.MESONH.mk
@@ -53,6 +53,12 @@ ifeq "$(MNH_INT)" "8"
 CPPFLAGS   += -DMNH_INT8
 endif
 
+#
+#  Len of HREC characters 
+#
+CPPFLAGS   += -DLEN_HREC=$(LEN_HREC)
+#
+
 OBJS_NOCB +=  spll_dxf.o spll_dxm.o spll_dyf.o spll_dym.o \
         spll_dzf.o spll_dzm.o spll_mxf.o \
         spll_mxm.o spll_myf.o spll_mym.o spll_mzf.o \
diff --git a/src/SURFEX/alloc_diag_surf_atmn.F90 b/src/SURFEX/alloc_diag_surf_atmn.F90
index 8c0869e13ac057ac1d80516557d6971c9b5a7237..c90e4c49ad2a9abcf5558dc9909bcd37eba4abc6 100644
--- a/src/SURFEX/alloc_diag_surf_atmn.F90
+++ b/src/SURFEX/alloc_diag_surf_atmn.F90
@@ -53,7 +53,7 @@ INTEGER,                 INTENT(IN) :: KSW       ! number of short-wave spectral
 !
 INTEGER           :: IVERSION
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/build_pronoslistn.F90 b/src/SURFEX/build_pronoslistn.F90
index ceb2a5cac9bf7efc2818fbdb142ce840715c038e..ab72d61128fe7cc32e42b64cee95e4f1673b13b9 100644
--- a/src/SURFEX/build_pronoslistn.F90
+++ b/src/SURFEX/build_pronoslistn.F90
@@ -58,7 +58,7 @@ IMPLICIT NONE
 TYPE(SV_t), INTENT(INOUT) :: SV
 !
 INTEGER,                       INTENT(IN)  :: KEMIS_NBR ! number of emitted species
- CHARACTER(LEN=12), DIMENSION(KEMIS_NBR), INTENT(IN) :: HEMIS_NAME ! name of emitted species
+ CHARACTER(LEN=LEN_HREC), DIMENSION(KEMIS_NBR), INTENT(IN) :: HEMIS_NAME ! name of emitted species
 TYPE(PRONOSVAR_T),             POINTER     :: TPPRONOS
 INTEGER,                       INTENT(IN)  :: KCH     ! logical unit of input chemistry file
 INTEGER,                       INTENT(IN)  :: KLUOUT  ! output listing channel
diff --git a/src/SURFEX/ch_init_emissionn.F90 b/src/SURFEX/ch_init_emissionn.F90
index beed2f7666ffea9ab906ba7d9a2187074253d893..fe1a1da8823cc846115dc59554702b57d5d10525 100644
--- a/src/SURFEX/ch_init_emissionn.F90
+++ b/src/SURFEX/ch_init_emissionn.F90
@@ -75,13 +75,13 @@ REAL, DIMENSION(:),INTENT(IN)  :: PRHOA    ! air density
 !
 INTEGER             :: IRESP                 !   File 
 INTEGER             :: ILUOUT                ! output listing logical unit
- CHARACTER (LEN=16)  :: YRECFM                ! management
+ CHARACTER (LEN=LEN_HREC)  :: YRECFM                ! management
  CHARACTER (LEN=100) :: YCOMMENT              ! variables
 INTEGER             :: JSPEC                 ! Loop index for cover data
 INTEGER             :: IIND1,IIND2           ! Indices counter
 !
  CHARACTER(LEN=40)                 :: YSPEC_NAME ! species name
- CHARACTER(LEN=12), DIMENSION(:),ALLOCATABLE :: YEMIS_NAME ! species name
+ CHARACTER(LEN=LEN_HREC), DIMENSION(:),ALLOCATABLE :: YEMIS_NAME ! species name
 INTEGER,DIMENSION(:),ALLOCATABLE  :: INBTIMES! number of emission times array
 INTEGER,DIMENSION(:),ALLOCATABLE  :: ITIMES  ! emission times for a species
 INTEGER,DIMENSION(:),ALLOCATABLE  :: IOFFNDX ! index array of offline emission species
diff --git a/src/SURFEX/default_assim.F90 b/src/SURFEX/default_assim.F90
index c91718000ddbb6ce9dc7760df7b710b9527cbd67..c523b518e3216351bf932d1474bf479e0a0740a6 100644
--- a/src/SURFEX/default_assim.F90
+++ b/src/SURFEX/default_assim.F90
@@ -124,7 +124,7 @@ REAL, DIMENSION(NVARMAX), INTENT(OUT) :: PTPRT_M
 INTEGER, DIMENSION(NVARMAX), INTENT(OUT) :: KNCV
 REAL,                INTENT(OUT) :: PSCALE_Q
 REAL,                INTENT(OUT) :: PSCALE_QLAI
- CHARACTER(LEN=12),   INTENT(OUT) :: HBIO
+ CHARACTER(LEN=LEN_HREC),   INTENT(OUT) :: HBIO
  CHARACTER(LEN=100),  INTENT(OUT) :: HPREFIX_BIO
 REAL, DIMENSION(12), INTENT(OUT) :: PALPH
 !
diff --git a/src/SURFEX/default_diag_surf_atm.F90 b/src/SURFEX/default_diag_surf_atm.F90
index 5a99e0946a6430102d75985e444927e97c427090..bb10c5b2279efcf06fa67110ba0d3dc0a50017ee 100644
--- a/src/SURFEX/default_diag_surf_atm.F90
+++ b/src/SURFEX/default_diag_surf_atm.F90
@@ -69,7 +69,7 @@ LOGICAL,  INTENT(OUT) :: OPROVAR_TO_DIAG    ! switch to write (or not) prognosti
 LOGICAL,  INTENT(OUT) :: ODIAG_GRID    ! flag for mean grid diag
 LOGICAL,  INTENT(OUT) :: OFRAC         ! flag for fractions of tiles
 REAL,     INTENT(OUT) :: PDIAG_TSTEP   ! time-step for writing
- CHARACTER(LEN=12), DIMENSION(200), INTENT(OUT), OPTIONAL :: CSELECT  
+ CHARACTER(LEN=LEN_HREC), DIMENSION(200), INTENT(OUT), OPTIONAL :: CSELECT  
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !*       0.2   Declarations of local variables
diff --git a/src/SURFEX/diag_flake_initn.F90 b/src/SURFEX/diag_flake_initn.F90
index b56c71717fecad58ef47aa64bb5b156e08a8c8ec..1c58fd5ec0e5084b3e854eb27169727b06d6a4e2 100644
--- a/src/SURFEX/diag_flake_initn.F90
+++ b/src/SURFEX/diag_flake_initn.F90
@@ -82,7 +82,7 @@ INTEGER, INTENT(IN) :: KSW   ! number of SW spectral bands
 !
 INTEGER           :: IVERSION
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB)   :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/diag_ideal_initn.F90 b/src/SURFEX/diag_ideal_initn.F90
index 529536c7b54b15f231b3b48371f070b62bd63f95..67412ab4981b375ff1bc5333edd524712fc30358 100644
--- a/src/SURFEX/diag_ideal_initn.F90
+++ b/src/SURFEX/diag_ideal_initn.F90
@@ -68,7 +68,7 @@ INTEGER, INTENT(IN) :: KSW   ! spectral bands
 !
 INTEGER           :: IVERSION
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/diag_isba_initn.F90 b/src/SURFEX/diag_isba_initn.F90
index c114531b9f3b1fa6e329954f48a4cc9cc7dc29d1..8116c2667571e8f050fabcc87ef7c753cbbd62b0 100644
--- a/src/SURFEX/diag_isba_initn.F90
+++ b/src/SURFEX/diag_isba_initn.F90
@@ -115,7 +115,7 @@ INTEGER, INTENT(IN)         :: KSW       ! spectral bands
 INTEGER           :: IVERSION, IBUG
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
 INTEGER           :: ISIZE_LMEB_PATCH   ! Number of patches where multi-energy balance should be applied
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
  CHARACTER(LEN=4) :: YREC2
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/diag_misc_teb_initn.F90 b/src/SURFEX/diag_misc_teb_initn.F90
index 1f5cacb326cfa572f269f530e095d7fc83e6820a..3f897c6bd225a6b46f87c39e8ad582fc7d472888 100644
--- a/src/SURFEX/diag_misc_teb_initn.F90
+++ b/src/SURFEX/diag_misc_teb_initn.F90
@@ -75,7 +75,7 @@ INTEGER, INTENT(IN) :: KSW   ! spectral bands
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/diag_seaflux_initn.F90 b/src/SURFEX/diag_seaflux_initn.F90
index 0292b5e0a8aa96dc7364f8d0af2c573a3a01a952..80141bc001b957bedb7dfd5d40286076963925f5 100644
--- a/src/SURFEX/diag_seaflux_initn.F90
+++ b/src/SURFEX/diag_seaflux_initn.F90
@@ -92,7 +92,7 @@ INTEGER, INTENT(IN) :: KSW   ! number of SW spectral bands
 !
 INTEGER           :: IVERSION
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 !
 REAL(KIND=JPRB)   :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/diag_teb_garden_initn.F90 b/src/SURFEX/diag_teb_garden_initn.F90
index 485b5845470b74cc54b466e5a8112fff0bcfb8c8..b903c518469a522e9ee3fdc0cca07bad796e7839 100644
--- a/src/SURFEX/diag_teb_garden_initn.F90
+++ b/src/SURFEX/diag_teb_garden_initn.F90
@@ -77,7 +77,7 @@ INTEGER, INTENT(IN)         :: KSW       ! spectral bands
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/diag_teb_greenroof_initn.F90 b/src/SURFEX/diag_teb_greenroof_initn.F90
index af81285c9384423e6a655f602382872d87fad165..9300d54c2b2d1e0963fbcd314d98c041611123e6 100644
--- a/src/SURFEX/diag_teb_greenroof_initn.F90
+++ b/src/SURFEX/diag_teb_greenroof_initn.F90
@@ -75,7 +75,7 @@ INTEGER, INTENT(IN)         :: KSW       ! spectral bands
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/diag_teb_initn.F90 b/src/SURFEX/diag_teb_initn.F90
index 8fbd5735cc1f7f7ed10c764327ebdf2394b5905a..b80ee886286f90c6a1bd74881cc8040b6f29b3d4 100644
--- a/src/SURFEX/diag_teb_initn.F90
+++ b/src/SURFEX/diag_teb_initn.F90
@@ -73,7 +73,7 @@ INTEGER, INTENT(IN) :: KSW   ! spectral bands
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/diag_watflux_initn.F90 b/src/SURFEX/diag_watflux_initn.F90
index b824277aa7f84e108d3453cef127101f0c19d5dc..8dd54621e389a079ae6fec32604bffc416feef44 100644
--- a/src/SURFEX/diag_watflux_initn.F90
+++ b/src/SURFEX/diag_watflux_initn.F90
@@ -81,7 +81,7 @@ INTEGER, INTENT(IN) :: KSW   ! number of SW spectral bands
 !
 INTEGER           :: IVERSION
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YREC           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YREC           ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/get_teb_depths.F90 b/src/SURFEX/get_teb_depths.F90
index 82b18d389897d44c451d30ca5958026c81258b29..50f24202a416130f7c7b2a731793798ae65feb25 100644
--- a/src/SURFEX/get_teb_depths.F90
+++ b/src/SURFEX/get_teb_depths.F90
@@ -97,10 +97,10 @@ REAL,    DIMENSION(:,:), ALLOCATABLE :: ZPAR_HC, ZPAR_TC, ZHC, ZTC ! work arrays
 INTEGER           :: IVERSION       ! surface version
 INTEGER           :: IBUGFIX        ! surface bugfix version
  CHARACTER(LEN=5)  :: YSURF          ! Type of surface
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
- CHARACTER(LEN=12) :: YRECFM0        ! Name of the article to be read
- CHARACTER(LEN=12) :: YRECFM1        ! Name of the article to be read
- CHARACTER(LEN=12) :: YRECFM2        ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM0        ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM1        ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM2        ! Name of the article to be read
  CHARACTER(LEN=3)  :: YAREA          ! Area where field is to be averaged
 INTEGER           :: IRESP          ! reading return code
 LOGICAL           :: GDATA          ! T if depth is to be read in the file
diff --git a/src/SURFEX/init_cpl_gcmn.F90 b/src/SURFEX/init_cpl_gcmn.F90
index d3c9c31d7bfce1e31e62c1c00df63d096e94ea9f..91f4c9636ccb430bf79d6b9cdfa4621ea47616b7 100644
--- a/src/SURFEX/init_cpl_gcmn.F90
+++ b/src/SURFEX/init_cpl_gcmn.F90
@@ -80,7 +80,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !
 INTEGER           :: IRESP      ! Error code after redding
 ! 
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 !
 INTEGER           :: IVERSION   ! surface version
 !
diff --git a/src/SURFEX/init_teb_veg_optionsn.F90 b/src/SURFEX/init_teb_veg_optionsn.F90
index f6b449761ecfbe2fee33050a82feafd5fe711c52..22f83d6f5ed1823e7c4408b637974331208aaaa2 100644
--- a/src/SURFEX/init_teb_veg_optionsn.F90
+++ b/src/SURFEX/init_teb_veg_optionsn.F90
@@ -99,7 +99,7 @@ TYPE(TEB_VEG_OPTIONS_t), INTENT(INOUT) :: TVG
 INTEGER           :: IVERSION, IBUGFIX  ! surface version
 INTEGER           :: ILUOUT   ! unit of output listing file
 INTEGER           :: IRESP    ! Error code after redding
- CHARACTER(LEN=12) :: YRECFM   ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM   ! Name of the article to be read
  CHARACTER(LEN=4 ) :: YLVL
 !
 INTEGER :: JLAYER ! loop counter on layers
diff --git a/src/SURFEX/io_buff.F90 b/src/SURFEX/io_buff.F90
index 9194ac2891961336f9130f82b752e71877f53000..866e5707ed789485587a054c11d2d086008b063f 100644
--- a/src/SURFEX/io_buff.F90
+++ b/src/SURFEX/io_buff.F90
@@ -52,7 +52,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! field to read or write
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! field to read or write
  CHARACTER(LEN=1),   INTENT(IN) :: HACTION  ! 'R' : file being read
                                            ! 'W' : file being written
 !
diff --git a/src/SURFEX/modd_assim.F90 b/src/SURFEX/modd_assim.F90
index 9098b3322d777bd6769ef1219cda3e2a97a30506..5b1b19f25c84f3949580ef06240029a07a496da9 100644
--- a/src/SURFEX/modd_assim.F90
+++ b/src/SURFEX/modd_assim.F90
@@ -85,7 +85,7 @@ IMPLICIT NONE
  CHARACTER(LEN=100),DIMENSION(NVARMAX) :: CPREFIX_M            ! The prefix of the control variables (in PREP.txt file) (max dim)      
  CHARACTER(LEN=10),DIMENSION(:), ALLOCATABLE  :: COBS          ! Identifier for simulated observations
  CHARACTER(LEN=3),DIMENSION(:), ALLOCATABLE   :: CVAR          ! Identifier for control variable
- CHARACTER(LEN=12)                     :: CBIO                 ! Name of Biomass variable
+ CHARACTER(LEN=LEN_HREC)                     :: CBIO                 ! Name of Biomass variable
  CHARACTER(LEN=100)                    :: CPREFIX_BIO          ! The prefix of the Biomass variable 
  CHARACTER(LEN=5)                      :: CASSIM_ISBA          ! OI/EKF
  CHARACTER(LEN=5)                      :: CASSIM               ! type of correction
diff --git a/src/SURFEX/modd_ch_snapn.F90 b/src/SURFEX/modd_ch_snapn.F90
index e79fc6b38c8bbc2b95e1bec3ed958903b894f4ad..b6a9c2e0aba9b69041e5273f5f6000186adb9e0a 100644
--- a/src/SURFEX/modd_ch_snapn.F90
+++ b/src/SURFEX/modd_ch_snapn.F90
@@ -56,7 +56,7 @@ TYPE CH_EMIS_SNAP_t
 !                          !  'LEGAL' : LEGAL time
 !                          !
 
-  CHARACTER(LEN=12), DIMENSION(:), POINTER :: CEMIS_NAME
+  CHARACTER(LEN=LEN_HREC), DIMENSION(:), POINTER :: CEMIS_NAME
 !                          ! name of the chemical fields (emitted species)
   CHARACTER(LEN=40), DIMENSION(:), POINTER :: CEMIS_COMMENT
 !                          ! comment on the chemical fields (emitted species)
diff --git a/src/SURFEX/modd_diag_surf_atmn.F90 b/src/SURFEX/modd_diag_surf_atmn.F90
index e2d1581d0a47b3824d39046a05bfb63a3bc6de49..36826fecadc101ac2655337863698ff7e10a2ac9 100644
--- a/src/SURFEX/modd_diag_surf_atmn.F90
+++ b/src/SURFEX/modd_diag_surf_atmn.F90
@@ -66,7 +66,7 @@ TYPE DIAG_SURF_ATM_t
 !  
   TYPE(DATE_TIME):: TIME_BUDGETC
 !                                  
-  CHARACTER(LEN=12), POINTER, DIMENSION(:) :: CSELECT  ! Name of ouput fields if LSELECT=true
+  CHARACTER(LEN=LEN_HREC), POINTER, DIMENSION(:) :: CSELECT  ! Name of ouput fields if LSELECT=true
 !
 !* variables for each tile
 !
diff --git a/src/SURFEX/modd_io_buff.F90 b/src/SURFEX/modd_io_buff.F90
index 95706110565e9ced2d70ed9aec5973de4dd9f4e6..41bc6a8e8015ca27906e227a67dcf7f4175bccd1 100644
--- a/src/SURFEX/modd_io_buff.F90
+++ b/src/SURFEX/modd_io_buff.F90
@@ -32,7 +32,7 @@
 !
 IMPLICIT NONE
 
- CHARACTER(LEN=12), DIMENSION(3000) :: CREC   ! list of records already read/written
+ CHARACTER(LEN=LEN_HREC), DIMENSION(3000) :: CREC   ! list of records already read/written
 INTEGER                            :: NREC   ! number of records read/written
 
 !
diff --git a/src/SURFEX/mode_read_extern.F90 b/src/SURFEX/mode_read_extern.F90
index 8763ce798a308b01b21a045342ce90296735be0a..9b81e89f5344f8cf1d23720e1e76b93671b31f7b 100644
--- a/src/SURFEX/mode_read_extern.F90
+++ b/src/SURFEX/mode_read_extern.F90
@@ -88,8 +88,8 @@ INTEGER, DIMENSION(:,:), INTENT(OUT):: KWG_LAYER
 !  ---------------
 !
  CHARACTER(LEN=4 ) :: YLVL
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
- CHARACTER(LEN=16) :: YRECFM2
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM2
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: JLAYER         ! loop counter
@@ -433,7 +433,7 @@ LOGICAL, OPTIONAL,  INTENT(INOUT) :: OKEY
 !* local variables
 !  ---------------
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=4)  :: YLVL
  CHARACTER(LEN=3)  :: YISBA          ! type of ISBA soil scheme
 #ifdef MNH_PARALLEL
diff --git a/src/SURFEX/mode_write_surf_asc.F90 b/src/SURFEX/mode_write_surf_asc.F90
index f2e264225762c17fc3f1c71e1ec12d12921d0e68..2b5f60056e736c51e2322fdc3e23a0386feb4877 100644
--- a/src/SURFEX/mode_write_surf_asc.F90
+++ b/src/SURFEX/mode_write_surf_asc.F90
@@ -50,7 +50,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 REAL,               INTENT(IN) :: PFIELD   ! the real scalar to be read
 INTEGER,            INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN) :: HCOMMENT ! comment string
@@ -107,7 +107,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,            INTENT(IN) :: KFIELD   ! the integer to be read
 INTEGER,            INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN) :: HCOMMENT ! comment string
@@ -164,7 +164,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 LOGICAL,            INTENT(IN) :: OFIELD   ! array containing the data field
 INTEGER,            INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN) :: HCOMMENT ! comment string
@@ -221,7 +221,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN)  :: HREC      ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC      ! name of the article to be read
  CHARACTER(LEN=40),  INTENT(IN)  :: HFIELD    ! the integer to be read
 INTEGER,            INTENT(OUT) :: KRESP     ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN)  :: HCOMMENT  ! comment string
@@ -285,7 +285,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),   INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),   INTENT(IN) :: HREC     ! name of the article to be read
 REAL, DIMENSION(:),  INTENT(IN) :: PFIELD   ! array containing the data field
 INTEGER,             INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100),  INTENT(IN) :: HCOMMENT ! comment string
@@ -385,7 +385,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),        INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),        INTENT(IN) :: HREC     ! name of the article to be read
 REAL, DIMENSION(:,:),     INTENT(IN) :: PFIELD   ! array containing the data field
 INTEGER,                  INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100),       INTENT(IN) :: HCOMMENT ! comment string
@@ -485,7 +485,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),      INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),      INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER, DIMENSION(:),  INTENT(IN) :: KFIELD   ! the integer to be read
 INTEGER,                INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100),     INTENT(IN) :: HCOMMENT ! comment string
@@ -582,7 +582,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),      INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),      INTENT(IN) :: HREC     ! name of the article to be read
 LOGICAL, DIMENSION(:),  INTENT(IN) :: OFIELD   ! array containing the data field
 INTEGER,                INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100),     INTENT(IN) :: HCOMMENT ! comment string
@@ -663,7 +663,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,            INTENT(IN)  :: KYEAR    ! year
 INTEGER,            INTENT(IN)  :: KMONTH   ! month
 INTEGER,            INTENT(IN)  :: KDAY     ! day
@@ -738,7 +738,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),     INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),     INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER, DIMENSION(:), INTENT(IN) :: KYEAR    ! year
 INTEGER, DIMENSION(:), INTENT(IN) :: KMONTH   ! month
 INTEGER, DIMENSION(:), INTENT(IN) :: KDAY     ! day
@@ -834,7 +834,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),       INTENT(IN)  :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),       INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER, DIMENSION(:,:), INTENT(IN)  :: KYEAR    ! year
 INTEGER, DIMENSION(:,:), INTENT(IN)  :: KMONTH   ! month
 INTEGER, DIMENSION(:,:), INTENT(IN)  :: KDAY     ! day
diff --git a/src/SURFEX/mode_write_surf_cov.F90 b/src/SURFEX/mode_write_surf_cov.F90
index a13901a127306ef29ac96b69c6650ff3afa24291..71166fb00cf9ef236306879b636a522ef93b41eb 100644
--- a/src/SURFEX/mode_write_surf_cov.F90
+++ b/src/SURFEX/mode_write_surf_cov.F90
@@ -51,7 +51,7 @@ INTEGER,              INTENT(OUT) :: KRESP    ! KRESP  : return-code if a proble
 !                                             ! '-' : no horizontal dim.
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
  CHARACTER(LEN=100) :: YCOMMENT
 INTEGER            :: IL1
 INTEGER            :: IL2
diff --git a/src/SURFEX/mode_write_surf_fa.F90 b/src/SURFEX/mode_write_surf_fa.F90
index 8c0dae01c34afdd87cec7f632b9e4c0a063a9f08..8b1386d58471726ecb6ff9b41dac5bc334b4b0c5 100644
--- a/src/SURFEX/mode_write_surf_fa.F90
+++ b/src/SURFEX/mode_write_surf_fa.F90
@@ -51,7 +51,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 REAL,               INTENT(IN) :: PFIELD   ! the real scalar to be read
 INTEGER,            INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN) :: HCOMMENT ! comment string
@@ -120,7 +120,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,            INTENT(IN) :: KFIELD   ! the integer to be read
 INTEGER,            INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN) :: HCOMMENT ! comment string
@@ -189,7 +189,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HREC     ! name of the article to be read
 LOGICAL,            INTENT(IN) :: OFIELD   ! array containing the data field
 INTEGER,            INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN) :: HCOMMENT ! comment string
@@ -258,7 +258,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN)  :: HREC      ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC      ! name of the article to be read
  CHARACTER(LEN=40),  INTENT(IN)  :: HFIELD    ! the integer to be read
 INTEGER,            INTENT(OUT) :: KRESP     ! KRESP  : return-code if a problem appears
  CHARACTER(LEN=100), INTENT(IN)  :: HCOMMENT  ! comment string
@@ -336,7 +336,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),   INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),   INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,             INTENT(IN) :: KL       ! number of points
 REAL, DIMENSION(KL), INTENT(IN) :: PFIELD   ! array containing the data field
 INTEGER,             INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
@@ -454,7 +454,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),        INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),        INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,                  INTENT(IN) :: KL1      ! number of points
 INTEGER,                  INTENT(IN) :: KL2      ! 2nd dimension
 REAL, DIMENSION(KL1,KL2), INTENT(IN) :: PFIELD   ! array containing the data field
@@ -581,7 +581,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),      INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),      INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,                INTENT(IN) :: KL       ! number of points
 INTEGER, DIMENSION(KL), INTENT(IN) :: KFIELD   ! array containing the data field
 INTEGER,                INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
@@ -689,7 +689,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),      INTENT(IN) :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),      INTENT(IN) :: HREC     ! name of the article to be read
 INTEGER,             INTENT(IN) :: KL       ! number of points
 LOGICAL, DIMENSION(KL), INTENT(IN) :: OFIELD   ! array containing the data field
 INTEGER,                INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem appears
@@ -782,7 +782,7 @@ IMPLICIT NONE
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,            INTENT(IN)  :: KYEAR    ! year
 INTEGER,            INTENT(IN)  :: KMONTH   ! month
 INTEGER,            INTENT(IN)  :: KDAY     ! day
@@ -885,7 +885,7 @@ INCLUDE "mpif.h"
 !
 !
 !
- CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be read
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be read
 INTEGER,                      INTENT(IN) :: KL1      ! number of points
 INTEGER,                      INTENT(IN) :: KL2      ! 2nd dimension
 INTEGER, DIMENSION(KL1,KL2), INTENT(IN)  :: KYEAR    ! year
diff --git a/src/SURFEX/modn_surf_atmn.F90 b/src/SURFEX/modn_surf_atmn.F90
index 5d8cd63a2cc43cfa7cb989868124c4b6a8ce9abc..39464032b4e9721b497c3d0fe395f0f28ef36ffe 100644
--- a/src/SURFEX/modn_surf_atmn.F90
+++ b/src/SURFEX/modn_surf_atmn.F90
@@ -59,7 +59,7 @@ LOGICAL  :: LSURF_VARS
 LOGICAL  :: LDIAG_GRID
 LOGICAL  :: LPROVAR_TO_DIAG
 LOGICAL  :: LSELECT
- CHARACTER(LEN=12), DIMENSION(500)    :: CSELECT
+ CHARACTER(LEN=LEN_HREC), DIMENSION(500)    :: CSELECT
 !
 NAMELIST/NAM_CH_CONTROLn/CCHEM_SURF_FILE
 NAMELIST/NAM_CH_SURFn/LCH_SURF_EMIS
diff --git a/src/SURFEX/old_name.F90 b/src/SURFEX/old_name.F90
index ea1d01f0aaa3d65836606e825e7ad1ace408b4ab..d3a92baa5f9e42cb634c0ea52fda91423bbabca0 100644
--- a/src/SURFEX/old_name.F90
+++ b/src/SURFEX/old_name.F90
@@ -56,8 +56,8 @@ IMPLICIT NONE
 !
 !
  CHARACTER(LEN=6),  INTENT(IN)  :: HPROGRAM ! main program
- CHARACTER(LEN=12), INTENT(IN)  :: HRECIN   ! name of field to be read
- CHARACTER(LEN=12), INTENT(OUT) :: HRECOUT  ! name of field to be read is old file
+ CHARACTER(LEN=LEN_HREC), INTENT(IN)  :: HRECIN   ! name of field to be read
+ CHARACTER(LEN=LEN_HREC), INTENT(OUT) :: HRECOUT  ! name of field to be read is old file
 !
 !
 !*       0.2   Declarations of local variables
diff --git a/src/SURFEX/pgd_chemistry_snap.F90 b/src/SURFEX/pgd_chemistry_snap.F90
index 6f2100b611d870a60994882207d22dbcda289a8c..2fed8c2002d5fef13c2fb94697b60a76beb8b9d9 100644
--- a/src/SURFEX/pgd_chemistry_snap.F90
+++ b/src/SURFEX/pgd_chemistry_snap.F90
@@ -99,7 +99,7 @@ INTEGER                           :: JSNAP     ! loop counter on SNAP categories
 !            ------------------------
 !
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
- CHARACTER(LEN=12),  DIMENSION(JPEMISMAX_S):: CEMIS_NAME
+ CHARACTER(LEN=LEN_HREC),  DIMENSION(JPEMISMAX_S):: CEMIS_NAME
  CHARACTER(LEN=40), DIMENSION(JPEMISMAX_S):: CEMIS_COMMENT
  CHARACTER(LEN=28), DIMENSION(JPEMISMAX_S):: CSNAP_MONTHLY_FILE
  CHARACTER(LEN=28), DIMENSION(JPEMISMAX_S):: CSNAP_DAILY_FILE
diff --git a/src/SURFEX/prep_flake_extern.F90 b/src/SURFEX/prep_flake_extern.F90
index 5e02db9b495809293694dfc7f555769ef3a8c5e3..dae0075344a5c7732fcd4251129f9ba821448eb7 100644
--- a/src/SURFEX/prep_flake_extern.F90
+++ b/src/SURFEX/prep_flake_extern.F90
@@ -47,7 +47,7 @@ REAL,DIMENSION(:,:), POINTER    :: PFIELD    ! field to interpolate horizontally
 !
 REAL, DIMENSION(:), ALLOCATABLE :: ZMASK
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: ILUOUT
 !
diff --git a/src/SURFEX/prep_grid_cartesian.F90 b/src/SURFEX/prep_grid_cartesian.F90
index 1bebd59788f0f51d53a0146f5e2d2aa7d2cf2090..edef06fde55b29aaa904aa029feba55c21994bb6 100644
--- a/src/SURFEX/prep_grid_cartesian.F90
+++ b/src/SURFEX/prep_grid_cartesian.F90
@@ -64,7 +64,7 @@ INTEGER,           INTENT(OUT)   :: KNI          ! number of points
 !* 0.2 Declaration of local variables
 !      ------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM    ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM    ! Name of the article to be read
 INTEGER           :: IRESP
 !
 INTEGER           :: JL        ! loop counter
diff --git a/src/SURFEX/prep_grid_conf_proj.F90 b/src/SURFEX/prep_grid_conf_proj.F90
index 2376c6bc38369154243b234fab6741335ceb4a44..51a9cd44a0a2fbdd738817950b44c78733dd0095 100644
--- a/src/SURFEX/prep_grid_conf_proj.F90
+++ b/src/SURFEX/prep_grid_conf_proj.F90
@@ -64,7 +64,7 @@ INTEGER,           INTENT(OUT)   :: KNI          ! number of points
 !* 0.2 Declaration of local variables
 !      ------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM    ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM    ! Name of the article to be read
 INTEGER           :: IRESP
 !
 !
diff --git a/src/SURFEX/prep_grid_gauss.F90 b/src/SURFEX/prep_grid_gauss.F90
index 113ddcd7c0c49c384920e371fd5d8104074ea159..d032796093b226684261ca619f3f8fdc9df9e367 100644
--- a/src/SURFEX/prep_grid_gauss.F90
+++ b/src/SURFEX/prep_grid_gauss.F90
@@ -65,7 +65,7 @@ INTEGER,           INTENT(OUT)   :: KNI          ! number of points
 !* 0.2 Declaration of local variables
 !      ------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM    ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM    ! Name of the article to be read
 INTEGER           :: IRESP
 !
 !
diff --git a/src/SURFEX/prep_grid_lonlat_reg.F90 b/src/SURFEX/prep_grid_lonlat_reg.F90
index 544cfe75a7f1dd54588aa454772ae7e729dd349d..c859f36a28528929caa16ba5e1dda2e9c6f047ae 100644
--- a/src/SURFEX/prep_grid_lonlat_reg.F90
+++ b/src/SURFEX/prep_grid_lonlat_reg.F90
@@ -63,7 +63,7 @@ INTEGER,           INTENT(OUT)   :: KNI          ! number of points
 !* 0.2 Declaration of local variables
 !      ------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM    ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM    ! Name of the article to be read
 INTEGER           :: IRESP
 !
 INTEGER :: JL        ! loop counter
diff --git a/src/SURFEX/prep_isba_cc_extern.F90 b/src/SURFEX/prep_isba_cc_extern.F90
index 8df3e73b06b8aca5e041e3b3c1050fee60a97b6e..ce633aa2a6d6ec32f876dfd158ee1bd298451a5d 100644
--- a/src/SURFEX/prep_isba_cc_extern.F90
+++ b/src/SURFEX/prep_isba_cc_extern.F90
@@ -67,7 +67,7 @@ LOGICAL,            INTENT(INOUT):: OPREP_AGS
 !
 !*      0.2    declarations of local variables
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: INI            ! total 1D dimension
 INTEGER           :: IPATCH         ! number of patch
diff --git a/src/SURFEX/prep_isba_extern.F90 b/src/SURFEX/prep_isba_extern.F90
index de84ce438551a67dafabfc865bc59cad62c5b44f..b2653569d89e18347e2e907cb3fd06cebeeaa8ca 100644
--- a/src/SURFEX/prep_isba_extern.F90
+++ b/src/SURFEX/prep_isba_extern.F90
@@ -82,7 +82,7 @@ LOGICAL, OPTIONAL,  INTENT(INOUT):: OKEY
 !
 !*      0.2    declarations of local variables
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: INI            ! total 1D dimension
 INTEGER           :: IPATCH         ! number of patch
diff --git a/src/SURFEX/prep_seaflux_extern.F90 b/src/SURFEX/prep_seaflux_extern.F90
index 52b6995d8c2342df0b1622e5f28d173191f127bf..6d259d7ab847540ae49f7e8d23b7dc6412afb489 100644
--- a/src/SURFEX/prep_seaflux_extern.F90
+++ b/src/SURFEX/prep_seaflux_extern.F90
@@ -45,7 +45,7 @@ REAL,DIMENSION(:,:), POINTER    :: PFIELD    ! field to interpolate horizontally
 !
 !
 REAL, DIMENSION(:), ALLOCATABLE :: ZMASK
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 !
 INTEGER           :: INI            ! total 1D dimension
diff --git a/src/SURFEX/prep_snow_extern.F90 b/src/SURFEX/prep_snow_extern.F90
index 2604ed9cfdb56c1638c2a6f6eecc7e72ea375af7..b5b2e1c41d4d4004e61943bb9b783321a55f77fc 100644
--- a/src/SURFEX/prep_snow_extern.F90
+++ b/src/SURFEX/prep_snow_extern.F90
@@ -103,7 +103,7 @@ REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZDEPTH       ! thickness of each layer (m
 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZGRID        ! normalized input grid
 !
 LOGICAL                           :: GTOWN          ! town variables written in the file
- CHARACTER(LEN=12)                 :: YRECFM         ! record name
+ CHARACTER(LEN=LEN_HREC)                 :: YRECFM         ! record name
 INTEGER                           :: IRESP          ! error return code
 INTEGER                           :: IVERSION       ! SURFEX version
 LOGICAL                           :: GOLD_NAME      ! old name flag 
diff --git a/src/SURFEX/prep_teb_extern.F90 b/src/SURFEX/prep_teb_extern.F90
index 1124dea509e3d96bd5060571c62f4d513e25d976..0d53d1e6afa4cd146e39ddfa2a2f5b3962cd70d5 100644
--- a/src/SURFEX/prep_teb_extern.F90
+++ b/src/SURFEX/prep_teb_extern.F90
@@ -68,7 +68,7 @@ REAL, DIMENSION(:,:),   ALLOCATABLE :: ZD  ! intermediate array
 !
 REAL, DIMENSION(:), ALLOCATABLE :: ZMASK
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: ILAYER         ! number of layers
 INTEGER           :: JLAYER         ! loop counter
@@ -399,11 +399,13 @@ ELSE
       CALL OPEN_AUX_IO_SURF(&
                       HFILE,HFILETYPE,'NATURE')
       IF (YSURF=='T_FLOO' .OR. YSURF=='T_CAN ' .OR. YSURF=='TI_ROA') THEN
+        YRECFM='TG2'
         CALL READ_SURF_FIELD2D(&
-               HFILETYPE,ZFIELD(:,:),'TG2         ',HDIR='A')
+               HFILETYPE,ZFIELD(:,:),YRECFM,HDIR='A')
       ELSE
+        YRECFM='TG1'
         CALL READ_SURF_FIELD2D(&
-               HFILETYPE,ZFIELD(:,:),'TG1         ',HDIR='A')
+               HFILETYPE,ZFIELD(:,:),YRECFM,HDIR='A')
       ENDIF
       CALL CLOSE_AUX_IO_SURF(HFILE,HFILETYPE)
       DO JLAYER=1,SIZE(ZFIELD,2)
diff --git a/src/SURFEX/prep_teb_garden_extern.F90 b/src/SURFEX/prep_teb_garden_extern.F90
index 831e16d443c170ed9d5514804308ff6aeb9ddf96..d80403711f1531e77dbda8d6a97ee681f606e0a2 100644
--- a/src/SURFEX/prep_teb_garden_extern.F90
+++ b/src/SURFEX/prep_teb_garden_extern.F90
@@ -85,7 +85,7 @@ REAL,DIMENSION(:,:,:), POINTER  :: PFIELD    ! field to interpolate horizontally
 !
 !*      0.2    declarations of local variables
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: INI            ! total 1D dimension
 INTEGER           :: IPATCH         ! number of patch
@@ -100,7 +100,7 @@ INTEGER                             :: ITEB_PATCH     ! number of TEB patches in
 INTEGER                             :: IVERSION       ! SURFEX version
 INTEGER                             :: IBUGFIX        ! SURFEX bug version
 LOGICAL                             :: GOLD_NAME      ! old name flag for temperatures
- CHARACTER(LEN=12)                   :: YSURF     ! type of field
+ CHARACTER(LEN=LEN_HREC)                   :: YSURF     ! type of field
  CHARACTER(LEN=3)                    :: YPATCH    ! indentificator for TEB patch
 LOGICAL                         :: GTEB      ! flag if TEB fields are present
 LOGICAL                         :: GGARDEN   ! T if gardens are present in the file
diff --git a/src/SURFEX/prep_teb_greenroof_extern.F90 b/src/SURFEX/prep_teb_greenroof_extern.F90
index a54f4713ed52cfef32b67e4a7b75cfb0e60f4e01..44e2273bb6646d2f8786b45917350f7dcb01b437 100644
--- a/src/SURFEX/prep_teb_greenroof_extern.F90
+++ b/src/SURFEX/prep_teb_greenroof_extern.F90
@@ -81,7 +81,7 @@ REAL,DIMENSION(:,:,:), POINTER  :: PFIELD    ! field to interpolate horizontally
 !
 !*      0.2    declarations of local variables
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: INI            ! total 1D dimension
 INTEGER           :: IPATCH         ! number of patch
@@ -93,7 +93,7 @@ REAL, DIMENSION(:,:), POINTER       :: ZD1            ! depth of field in the so
 REAL, DIMENSION(:,:), ALLOCATABLE   :: ZOUT           !
 LOGICAL                             :: GTEB           ! flag if TEB fields are present
 INTEGER                             :: JPATCH         ! loop counter for patch
- CHARACTER(LEN=12)                   :: YSURF          ! type of field
+ CHARACTER(LEN=LEN_HREC)                   :: YSURF          ! type of field
 INTEGER                             :: ITEB_PATCH     ! number of TEB patches in file
 INTEGER                             :: IVERSION       ! SURFEX version
 INTEGER                             :: IBUGFIX        ! SURFEX bug version
diff --git a/src/SURFEX/prep_watflux_extern.F90 b/src/SURFEX/prep_watflux_extern.F90
index 735a8faf2085267ad5199e3e415c20628a8eca81..033c4da70e1c671679028c7175f2113eefca9113 100644
--- a/src/SURFEX/prep_watflux_extern.F90
+++ b/src/SURFEX/prep_watflux_extern.F90
@@ -46,7 +46,7 @@ REAL,DIMENSION(:,:), POINTER    :: PFIELD    ! field to interpolate horizontally
 !
 !
 REAL, DIMENSION(:), ALLOCATABLE :: ZMASK
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IRESP          ! reading return code
 INTEGER           :: ILUOUT
 INTEGER           :: IDIM_WATER
diff --git a/src/SURFEX/read_arrange_cover.F90 b/src/SURFEX/read_arrange_cover.F90
index 51e31f2bdb4bb5d0c8e58b7236e3c26dbc4f3090..11c1304c50c3ffb484f28591d4d81270ff785a5b 100644
--- a/src/SURFEX/read_arrange_cover.F90
+++ b/src/SURFEX/read_arrange_cover.F90
@@ -32,7 +32,7 @@ LOGICAL,           INTENT(OUT) :: OTOWN_TO_ROCK    ! T: Change Town into Rock
 !  ---------------
 !
  CHARACTER(LEN=1) :: YDIR
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 INTEGER           :: IRESP      ! reading return code
 !
 INTEGER           :: IVERSION   ! surface version
diff --git a/src/SURFEX/read_cover_garden.F90 b/src/SURFEX/read_cover_garden.F90
index bc84d1db9667ff0aaffb8db03af9f6f5900b6255..87955be6fb72787da2a1df4db93628b3389cd984 100644
--- a/src/SURFEX/read_cover_garden.F90
+++ b/src/SURFEX/read_cover_garden.F90
@@ -31,7 +31,7 @@ LOGICAL,           INTENT(OUT) :: OGARDEN   ! T: Definition of urban green areas
 !  ---------------
 !
  CHARACTER(LEN=1) :: YDIR
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 INTEGER           :: IRESP      ! reading return code
 !
 INTEGER           :: IVERSION   ! surface version
diff --git a/src/SURFEX/read_covern.F90 b/src/SURFEX/read_covern.F90
index d942958bf2c55f126a819ac00ec7f347c9d658fd..6bdddeab33afaa99467886302e642e9a5885d617 100644
--- a/src/SURFEX/read_covern.F90
+++ b/src/SURFEX/read_covern.F90
@@ -86,7 +86,7 @@ INTEGER           :: IVERSION       ! surface version
 !
 LOGICAL :: GREAD_ALL
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/read_covers_and_av_pgd_on_layers.F90 b/src/SURFEX/read_covers_and_av_pgd_on_layers.F90
index e94fbdc3f0bb71816977940a4929998f84cc939a..91bdb4be37aaf17a363372c88bc762eb7183c824 100644
--- a/src/SURFEX/read_covers_and_av_pgd_on_layers.F90
+++ b/src/SURFEX/read_covers_and_av_pgd_on_layers.F90
@@ -62,7 +62,7 @@ IMPLICIT NONE
 !            ------------------------
 !
 CHARACTER(LEN=6),   INTENT(IN)  :: HFILEPGDTYPE ! type of input file
-CHARACTER(LEN=12),   INTENT(IN) :: HRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC),   INTENT(IN) :: HRECFM         ! Name of the article to be read
 TYPE(DATA_COVER_t), INTENT(INOUT) :: DTCO
 INTEGER,   INTENT(IN) :: KLU                      ! number of points
 INTEGER,   INTENT(IN)  :: KDATA_LAYER  ! number of layers
@@ -92,7 +92,7 @@ LOGICAL, DIMENSION(JPCOVER)          :: GCOVER ! flag to read the covers
 REAL,    DIMENSION(KLU)		 :: ZCOVER ! cover fractions
 CHARACTER(LEN=100) :: YCOMMENT
 INTEGER           :: IRESP          ! reading return code
-CHARACTER(LEN=16) :: YRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !-------------------------------------------------------------------------------
 !
 IF (LHOOK) CALL DR_HOOK('READ_COVERS_AND_AV_PGD_1D_ON_LAYERS',0,ZHOOK_HANDLE)
diff --git a/src/SURFEX/read_dummyn.F90 b/src/SURFEX/read_dummyn.F90
index c0064fdbdec1ffaf70b97cae08eb483a4ef9d24b..0779d4854b88a8b5086b207410e2a994da7533c8 100644
--- a/src/SURFEX/read_dummyn.F90
+++ b/src/SURFEX/read_dummyn.F90
@@ -62,7 +62,7 @@ INTEGER           :: JDUMMY         ! loop counter
  CHARACTER(LEN=3  ):: YSTRING03      ! string
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/read_eco2_irrig.F90 b/src/SURFEX/read_eco2_irrig.F90
index 0e3a6514f4f85a60e206403652a514d31ead61a6..8a7a1f372c34cc5e2ce09c7f53706d89df9e7b8c 100644
--- a/src/SURFEX/read_eco2_irrig.F90
+++ b/src/SURFEX/read_eco2_irrig.F90
@@ -40,7 +40,7 @@ TYPE(DATA_COVER_t), INTENT(INOUT) :: DTCO
 !* local variables
 !  ---------------
 !
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 INTEGER           :: IRESP      ! reading return code
 !
 INTEGER           :: IVERSION   ! surface version
diff --git a/src/SURFEX/read_flake_sbln.F90 b/src/SURFEX/read_flake_sbln.F90
index 15c70fedc0aa722eab0e0df4e8e0239bfd03aa01..6d6105504be365494f80d79ec4d42ba4ce9deb23 100644
--- a/src/SURFEX/read_flake_sbln.F90
+++ b/src/SURFEX/read_flake_sbln.F90
@@ -74,7 +74,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !*       0.2   Declarations of local variables
 !              -------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=3)  :: YREAD
 INTEGER :: ILU     ! 1D physical dimension
 INTEGER :: IRESP   ! Error code after redding
diff --git a/src/SURFEX/read_flaken.F90 b/src/SURFEX/read_flaken.F90
index 5c94dc6c7f4013653f3ca190c5284196412e8af2..cf07ea4eb09d1b4fbf3fe75c2b2154808414f0db 100644
--- a/src/SURFEX/read_flaken.F90
+++ b/src/SURFEX/read_flaken.F90
@@ -76,7 +76,7 @@ INTEGER           :: ILU          ! 1D physical dimension
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/read_from_surfex_file.F90 b/src/SURFEX/read_from_surfex_file.F90
index 41d8ac325d44722f703c801b932e6da9264aade3..d80c1800ff7fbca9dd3813ab6d770be5116392ad 100644
--- a/src/SURFEX/read_from_surfex_file.F90
+++ b/src/SURFEX/read_from_surfex_file.F90
@@ -49,7 +49,7 @@ REAL, DIMENSION(:), INTENT(OUT) :: PFIELD
  CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: HNAM
 !
  CHARACTER(LEN=28)     :: HNAME
- CHARACTER(LEN=12)     :: YRECFM
+ CHARACTER(LEN=LEN_HREC)     :: YRECFM
 INTEGER               :: IRESP, I0
 !
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/read_gr_snow.F90 b/src/SURFEX/read_gr_snow.F90
index 943c003b7b228dd42391143421aeaada16b872b2..21b37f8cdc1ab5b666a9a7deda5d633744b3b72b 100644
--- a/src/SURFEX/read_gr_snow.F90
+++ b/src/SURFEX/read_gr_snow.F90
@@ -88,8 +88,8 @@ INTEGER,            INTENT(IN), OPTIONAL :: KBUGFIX
 !*       0.2   declarations of local variables
 !
 INTEGER             :: IRESP               ! Error code after redding
- CHARACTER(LEN=12)   :: YRECFM              ! Name of the article to be read
- CHARACTER(LEN=16)   :: YRECFM2 
+ CHARACTER(LEN=LEN_HREC)   :: YRECFM              ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC)   :: YRECFM2 
 !
  CHARACTER (LEN=100) :: YFMT                ! format for writing
 INTEGER             :: ISURFTYPE_LEN       ! 
diff --git a/src/SURFEX/read_isba_canopyn.F90 b/src/SURFEX/read_isba_canopyn.F90
index 1ac3fe9b606ba3bf15be71466a93f4b31f0590b5..91aefd8562e86c92688f3b12c3c27f617df28901 100644
--- a/src/SURFEX/read_isba_canopyn.F90
+++ b/src/SURFEX/read_isba_canopyn.F90
@@ -76,7 +76,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !              -------------------------------
 !
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=3)  :: YREAD
 INTEGER :: JLAYER  ! loop counter on layers
 INTEGER :: ILU     ! 1D physical dimension
diff --git a/src/SURFEX/read_isban.F90 b/src/SURFEX/read_isban.F90
index 3201e3069b06e744222ce18c5495461190dbbf59..7bb5aa5d7ab9b5e2a7006730fe30bf8dc9f3f48c 100644
--- a/src/SURFEX/read_isban.F90
+++ b/src/SURFEX/read_isban.F90
@@ -102,7 +102,7 @@ INTEGER           :: ILU          ! 1D physical dimension
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
  CHARACTER(LEN=4)  :: YLVL
 !
@@ -612,7 +612,7 @@ REAL, DIMENSION(:), INTENT(IN) :: PCOFSWI
 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PVAR
 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: PRED_NOISE
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=4) :: YLVL
  CHARACTER(LEN=3) :: YVAR
 REAL :: ZWHITE_NOISE, ZVAR0
diff --git a/src/SURFEX/read_lclim_lai.F90 b/src/SURFEX/read_lclim_lai.F90
index 94f8621b4e3237619b53860785e2aa61846d13ed..80fbf495dc1236284e79d70c462433586f2f3837 100644
--- a/src/SURFEX/read_lclim_lai.F90
+++ b/src/SURFEX/read_lclim_lai.F90
@@ -30,7 +30,7 @@ LOGICAL,              INTENT(OUT)   :: OCLIM_LAI ! flag for use of climatologic
 !* local variables
 !  ---------------
 !
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 INTEGER           :: IRESP      ! reading return code
 !
 INTEGER           :: IVERSION   ! surface version
diff --git a/src/SURFEX/read_lcover.F90 b/src/SURFEX/read_lcover.F90
index 17da413e6b71f3600d82099f81192f20d20a8880..94ca615add4106c359b4aa57a666a6c54850ca19 100644
--- a/src/SURFEX/read_lcover.F90
+++ b/src/SURFEX/read_lcover.F90
@@ -71,7 +71,7 @@ LOGICAL, DIMENSION(JPCOVER)    :: OCOVER   ! list of covers
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! Error code after redding
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IVERSION       ! version of surfex file being read
 LOGICAL, DIMENSION(:), ALLOCATABLE :: GCOVER ! cover list in the file
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/read_lecoclimap.F90 b/src/SURFEX/read_lecoclimap.F90
index 0d848cfa367839f43f75499af094e1166fc671a6..8ea72a9206ffd5e85c554cd4574c5fff72b4e32a 100644
--- a/src/SURFEX/read_lecoclimap.F90
+++ b/src/SURFEX/read_lecoclimap.F90
@@ -30,7 +30,7 @@ LOGICAL,              INTENT(OUT)   :: OECOCLIMAP! flag for ecoclimap
 !* local variables
 !  ---------------
 !
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 INTEGER           :: IRESP      ! reading return code
 !
 INTEGER           :: IVERSION   ! surface version
diff --git a/src/SURFEX/read_oceann.F90 b/src/SURFEX/read_oceann.F90
index 0a3588bc174e25590eb5255e27405df3be790185..a43fef5097758e2af87f78d6ffe111bdd0ebdc3d 100644
--- a/src/SURFEX/read_oceann.F90
+++ b/src/SURFEX/read_oceann.F90
@@ -83,7 +83,7 @@ INTEGER           :: IRESP          ! Error code after redding
 !
  CHARACTER(LEN=4)  :: YLVL
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=14) :: YFORM          ! Writing format
 REAL, DIMENSION(:),ALLOCATABLE  :: ZWORK      ! 1D array to write data in file
 !
diff --git a/src/SURFEX/read_pgd_flaken.F90 b/src/SURFEX/read_pgd_flaken.F90
index 4dd1e1f6fd69bf0652692e5ac742ea9411688cc0..f39244be012b6ead078d4ddd4a122b2c10f42286 100644
--- a/src/SURFEX/read_pgd_flaken.F90
+++ b/src/SURFEX/read_pgd_flaken.F90
@@ -83,7 +83,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !
 INTEGER           :: IRESP          ! Error code after redding
 ! 
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/read_pgd_isba_parn.F90 b/src/SURFEX/read_pgd_isba_parn.F90
index 4c7842a8c5b4f7fbfd391634ad950a238664e69d..fea45320787d07dcac18991f1dcea8d362273d18 100644
--- a/src/SURFEX/read_pgd_isba_parn.F90
+++ b/src/SURFEX/read_pgd_isba_parn.F90
@@ -101,8 +101,8 @@ REAL,    DIMENSION(:,:), ALLOCATABLE :: ZWORK
 INTEGER           :: ILUOUT
 INTEGER           :: ITIME
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
- CHARACTER(LEN=16) :: YRECFM2
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM2
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=1)  :: YDIR
 INTEGER           :: JTIME          ! loop index
diff --git a/src/SURFEX/read_pgd_isban.F90 b/src/SURFEX/read_pgd_isban.F90
index f9ae70ffa20a10171bf2006b918aecbbb55f4942..c8d82407ec528f3d7579eb92a52ce7c67458f46a 100644
--- a/src/SURFEX/read_pgd_isban.F90
+++ b/src/SURFEX/read_pgd_isban.F90
@@ -120,7 +120,7 @@ INTEGER, DIMENSION(:), POINTER :: IMASK  ! mask for packing from complete field
 !
 REAL, DIMENSION(:,:), ALLOCATABLE :: ZWORK
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=4 ) :: YLVL
 !
 INTEGER :: ILU    ! expected physical size of full surface array
diff --git a/src/SURFEX/read_pgd_seaflux_parn.F90 b/src/SURFEX/read_pgd_seaflux_parn.F90
index 72638026bee06c63ace0c26fc12156b1ef553c24..ac8dac9b62b1fa2574da40608cfbd9030cef250f 100644
--- a/src/SURFEX/read_pgd_seaflux_parn.F90
+++ b/src/SURFEX/read_pgd_seaflux_parn.F90
@@ -89,7 +89,7 @@ INTEGER, INTENT(IN) :: KSIZE
 !              -------------------------------
 !
 REAL, DIMENSION(:,:), ALLOCATABLE :: ZDATA_SST
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=1)  :: YDIR
 INTEGER           :: ILUOUT
diff --git a/src/SURFEX/read_pgd_seafluxn.F90 b/src/SURFEX/read_pgd_seafluxn.F90
index eb811ab2e5fda10b84caf854403f49c4b0c302ac..8b4d53a55ff191fb6fc1bc4092a197e979ced8a8 100644
--- a/src/SURFEX/read_pgd_seafluxn.F90
+++ b/src/SURFEX/read_pgd_seafluxn.F90
@@ -87,7 +87,7 @@ TYPE(GRID_CONF_PROJ_t),INTENT(INOUT) :: GCP
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 INTEGER           :: IVERSION   ! surface version
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/read_pgd_teb_garden_parn.F90 b/src/SURFEX/read_pgd_teb_garden_parn.F90
index c342dd9fa4b8a1f02c6106cea947c7e7cef19011..c22ae9bd7daf47033faa41e3010ae40fc8d709bb 100644
--- a/src/SURFEX/read_pgd_teb_garden_parn.F90
+++ b/src/SURFEX/read_pgd_teb_garden_parn.F90
@@ -93,7 +93,7 @@ TYPE(TEB_GRID_t), INTENT(INOUT) :: TG
 !              -------------------------------
 !
 INTEGER                               :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12)                     :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC)                     :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100)                    :: YCOMMENT       ! Comment string
 INTEGER                               :: JI, JLAYER     ! loop index
 INTEGER                               :: JTIME          ! loop index
diff --git a/src/SURFEX/read_pgd_teb_gardenn.F90 b/src/SURFEX/read_pgd_teb_gardenn.F90
index 509137564df7f80583952342a8d43fd1b2e06312..3c0537fbe864179851988fd733a7f099df766977 100644
--- a/src/SURFEX/read_pgd_teb_gardenn.F90
+++ b/src/SURFEX/read_pgd_teb_gardenn.F90
@@ -90,7 +90,7 @@ INTEGER,           INTENT(IN)  :: KBUGFIX
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 INTEGER           :: JLAYER         ! loop counter on layers
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/read_pgd_teb_greenroof_parn.F90 b/src/SURFEX/read_pgd_teb_greenroof_parn.F90
index 74b57ea7ea5f2dd3a198e0abd15a239a32823094..5fd5e0e074604a1e59fb38737ff279d052a76b80 100644
--- a/src/SURFEX/read_pgd_teb_greenroof_parn.F90
+++ b/src/SURFEX/read_pgd_teb_greenroof_parn.F90
@@ -85,7 +85,7 @@ TYPE(TEB_GRID_t), INTENT(INOUT) :: TG
 !              -------------------------------
 !
 INTEGER                               :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12)                     :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC)                     :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100)                    :: YCOMMENT       ! Comment string
 INTEGER                               :: JI             ! loop index
 INTEGER                               :: JTIME          ! loop index
diff --git a/src/SURFEX/read_pgd_teb_greenroofn.F90 b/src/SURFEX/read_pgd_teb_greenroofn.F90
index 0aee2c9c5c3eb829d9e3070b04d2ab528f4368fc..58d61c51a2206b0bf9ab7317f0b52e02b6bf0ddb 100644
--- a/src/SURFEX/read_pgd_teb_greenroofn.F90
+++ b/src/SURFEX/read_pgd_teb_greenroofn.F90
@@ -86,7 +86,7 @@ INTEGER,           INTENT(IN)  :: KVERSION ! version of SURFEX of the file being
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 !
 INTEGER           :: JLAYER         ! loop counter on layers ! not used
diff --git a/src/SURFEX/read_pgd_teb_irrign.F90 b/src/SURFEX/read_pgd_teb_irrign.F90
index e747f459b4d48bfc7ed90f037c6f078cde9a058c..f81dc5f24892dc0afb553a381d07e799892f4427 100644
--- a/src/SURFEX/read_pgd_teb_irrign.F90
+++ b/src/SURFEX/read_pgd_teb_irrign.F90
@@ -73,7 +73,7 @@ TYPE(TEB_IRRIG_t), INTENT(INOUT) :: TIR
 !
 INTEGER           :: ILUOUT         ! output listing logical unit
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=80) :: YCOMMENT       ! Comment of the article to be read
 INTEGER           :: JLAYER         ! loop index
 !
diff --git a/src/SURFEX/read_pgd_teb_parn.F90 b/src/SURFEX/read_pgd_teb_parn.F90
index f98437026f34c12e17c5628630fd8625f74bb66c..f8ff1bd9b58051615752c40ecca41bfe831fe172 100644
--- a/src/SURFEX/read_pgd_teb_parn.F90
+++ b/src/SURFEX/read_pgd_teb_parn.F90
@@ -93,7 +93,7 @@ INTEGER,           INTENT(IN)  :: KNI      ! size of the new domain
 !
 INTEGER           :: ILUOUT         ! output listing logical unit
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: JLAYER         ! loop index
 !
 INTEGER           :: IVERSION       ! surface version
diff --git a/src/SURFEX/read_pgd_tebn.F90 b/src/SURFEX/read_pgd_tebn.F90
index ab0ca29712b0e524941ff91bef01581d5c60e541..0d0dcddf5213af6bc810c238f99f7cb441eedde0 100644
--- a/src/SURFEX/read_pgd_tebn.F90
+++ b/src/SURFEX/read_pgd_tebn.F90
@@ -84,7 +84,7 @@ TYPE(GRID_CONF_PROJ_t),INTENT(INOUT) :: GCP
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 INTEGER           :: IVERSION
 INTEGER           :: IBUGFIX
 !
diff --git a/src/SURFEX/read_pgd_tsz0_parn.F90 b/src/SURFEX/read_pgd_tsz0_parn.F90
index 63395f00cabf22e37a4739d932f35399fb3a52ca..89dda7bb10432ce0d46391620e629d68d7159716 100644
--- a/src/SURFEX/read_pgd_tsz0_parn.F90
+++ b/src/SURFEX/read_pgd_tsz0_parn.F90
@@ -71,7 +71,7 @@ TYPE(DATA_TSZ0_t), INTENT(INOUT) :: DTZ
 INTEGER :: IVERSION  ! surface version
 INTEGER :: IBUGFIX   ! bugfix  of the old file
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/read_pgd_watfluxn.F90 b/src/SURFEX/read_pgd_watfluxn.F90
index 2cd8151b85a9b543b212335735669b26b55ceede..9218dc32dc4caa031f974599d65ed4fcd7b4fb98 100644
--- a/src/SURFEX/read_pgd_watfluxn.F90
+++ b/src/SURFEX/read_pgd_watfluxn.F90
@@ -81,7 +81,7 @@ TYPE(WATFLUX_t), INTENT(INOUT) :: W
 !
 INTEGER           :: IRESP          ! Error code after redding
 ! 
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/read_prep_file_date.F90 b/src/SURFEX/read_prep_file_date.F90
index c46e417ca224b7a58916cd72de120e6a7e9d8a6a..92dbab07e59b20977f244ecebf02840861e63877 100644
--- a/src/SURFEX/read_prep_file_date.F90
+++ b/src/SURFEX/read_prep_file_date.F90
@@ -59,7 +59,7 @@ INTEGER,            INTENT(IN)  :: KLUOUT    ! logical unit of output listing
 !
 !*      0.2    declarations of local variables
 !
- CHARACTER(LEN=12), DIMENSION(3000) :: HREC   ! list of records already read/written
+ CHARACTER(LEN=LEN_HREC), DIMENSION(3000) :: HREC   ! list of records already read/written
 INTEGER                            :: IREC
  CHARACTER(LEN=6)              :: YINMODEL  ! model from which GRIB file originates
  CHARACTER(LEN=10)             :: YGRIDTYPE ! Grid type
diff --git a/src/SURFEX/read_seaflux_sbln.F90 b/src/SURFEX/read_seaflux_sbln.F90
index 571a721a7b74b6c1053558bc269b694dd9f0c784..d079d8a8909a5165c45d085ad6ffddcd521b4a85 100644
--- a/src/SURFEX/read_seaflux_sbln.F90
+++ b/src/SURFEX/read_seaflux_sbln.F90
@@ -75,7 +75,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !              -------------------------------
 !
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=3)  :: YREAD
 INTEGER :: ILU     ! 1D physical dimension
 INTEGER :: IRESP   ! Error code after redding
diff --git a/src/SURFEX/read_seafluxn.F90 b/src/SURFEX/read_seafluxn.F90
index 6549d541dd15a00b4ae8bfecc21e4d508139d4a1..875ea8da44170a0594516e606598950f2ad27ada 100644
--- a/src/SURFEX/read_seafluxn.F90
+++ b/src/SURFEX/read_seafluxn.F90
@@ -85,7 +85,7 @@ INTEGER           :: ILU          ! 1D physical dimension
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 INTEGER           :: IVERSION       ! surface version
 !
@@ -239,7 +239,7 @@ SUBROUTINE CHECK_SEA(HFIELD,PFIELD)
 !
 IMPLICIT NONE
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HFIELD
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HFIELD
 REAL, DIMENSION(:), INTENT(IN) :: PFIELD
 !
 REAL            :: ZMAX,ZMIN
diff --git a/src/SURFEX/read_seaicen.F90 b/src/SURFEX/read_seaicen.F90
index 50ae04ed858a49545858faa38ca6923bc8d1afdd..56b873f543df6ed582d374b852dff28c712073b4 100644
--- a/src/SURFEX/read_seaicen.F90
+++ b/src/SURFEX/read_seaicen.F90
@@ -99,9 +99,9 @@ INTEGER           :: JMTH, INMTH
  CHARACTER(LEN=2 ) :: YMTH
  CHARACTER(LEN=5)  :: YLVL
 !
- CHARACTER(LEN=12) :: YCATEG         ! category to read
- CHARACTER(LEN=12) :: YLEVEL         ! Level to read
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YCATEG         ! category to read
+ CHARACTER(LEN=LEN_HREC) :: YLEVEL         ! Level to read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=200) :: YMESS         ! Error Message
 !
 INTEGER :: JX,JK,JL                 ! loop counter on ice categories and layers and grid points
@@ -447,7 +447,7 @@ SUBROUTINE CHECK_SEAICE(HFIELD,PFIELD)
 !
 IMPLICIT NONE
 !
- CHARACTER(LEN=12),  INTENT(IN) :: HFIELD
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN) :: HFIELD
 REAL, DIMENSION(:), INTENT(IN) :: PFIELD
 !
 REAL            :: ZMAX,ZMIN
diff --git a/src/SURFEX/read_sso_canopyn.F90 b/src/SURFEX/read_sso_canopyn.F90
index bd2c02b60e12b1fd27acf8bd5233dcb154359c00..ec8ae439add13540aa52b07674efe292e901c14d 100644
--- a/src/SURFEX/read_sso_canopyn.F90
+++ b/src/SURFEX/read_sso_canopyn.F90
@@ -74,7 +74,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !*       0.2   Declarations of local variables
 !              -------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM       ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM       ! Name of the article to be read
  CHARACTER(LEN=3)  :: YREAD
 INTEGER :: ILU     ! 1D physical dimension
 INTEGER :: IRESP   ! Error code after redding
diff --git a/src/SURFEX/read_sson.F90 b/src/SURFEX/read_sson.F90
index 145adfb2f6139ba5c58d395908b67e1cb2cfbb04..d213f80c16bfe3a9da0a72fd28dfa4318e6506d0 100644
--- a/src/SURFEX/read_sson.F90
+++ b/src/SURFEX/read_sson.F90
@@ -85,7 +85,7 @@ TYPE(SURF_ATM_SSO_t), INTENT(INOUT) :: USS
 !
 INTEGER           :: IRESP          ! Error code after redding
 ! 
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/read_surf_field2d.F90 b/src/SURFEX/read_surf_field2d.F90
index d2cbd1441ce37786eb06026bc994c2cb96801bb9..e85dc6c31d135b40593d2d1ffdefba76e3343928 100644
--- a/src/SURFEX/read_surf_field2d.F90
+++ b/src/SURFEX/read_surf_field2d.F90
@@ -67,7 +67,7 @@ IMPLICIT NONE
 !
 CHARACTER(LEN=6),                 INTENT(IN) :: HPROGRAM     ! calling program
 REAL, DIMENSION(:,:),          INTENT(INOUT) :: PFIELD2D     ! 2D field to be read
-CHARACTER(LEN=12),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD2D. Example : 'X_Y_TG'
+CHARACTER(LEN=LEN_HREC),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD2D. Example : 'X_Y_TG'
 CHARACTER(LEN=*), OPTIONAL,      INTENT(OUT) :: HCOMMENT   !comment string
 CHARACTER(LEN=1),OPTIONAL,        INTENT(IN) :: HDIR ! type of field :
 !                                             ! 'H' : field with
@@ -82,7 +82,7 @@ REAL, DIMENSION(SIZE(PFIELD2D,1)) :: ZWORK
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
 INTEGER           :: IPATCH         ! number of patches in PFIELD2D
 CHARACTER(LEN=100):: YCOMMENT       ! Comment string
-CHARACTER(LEN=16) :: YRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 CHARACTER(LEN=4 ) :: YPATCH         ! current patch
 INTEGER           :: INB_PROCIO     ! number of processes used for Z-parallel IO with MESO-NH
 !
diff --git a/src/SURFEX/read_surf_field3d.F90 b/src/SURFEX/read_surf_field3d.F90
index 5dfdf90875c4a359a02bd9f9aeb05e81fa047217..49e005418f71407707c71fb5a06876913d37c0d6 100644
--- a/src/SURFEX/read_surf_field3d.F90
+++ b/src/SURFEX/read_surf_field3d.F90
@@ -68,7 +68,7 @@ CHARACTER(LEN=6),                 INTENT(IN) :: HPROGRAM     ! calling program
 REAL, DIMENSION(:,:,:),        INTENT(INOUT) :: PFIELD3D     ! 3D field to be read
 INTEGER,                          INTENT(IN) :: KFIRSTLAYER  ! first layer of PFIELD3D to be read
 INTEGER,                          INTENT(IN) :: KLASTLAYER   ! last layer of PFIELD3D to be read
-CHARACTER(LEN=12),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD3D. Example : 'X_Y_TG'
+CHARACTER(LEN=LEN_HREC),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD3D. Example : 'X_Y_TG'
  CHARACTER(LEN=*), OPTIONAL,     INTENT(OUT) :: HCOMMENT   !comment string
 CHARACTER(LEN=1),OPTIONAL,        INTENT(IN) :: HDIR ! type of field :
 !                                             ! 'H' : field with
@@ -83,7 +83,7 @@ INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
 INTEGER           :: ILAYER         ! number of layers in PFIELD3D
 INTEGER           :: IPATCH         ! number of patches in PFIELD3D
 CHARACTER(LEN=100):: YCOMMENT       ! Comment string
-CHARACTER(LEN=16) :: YRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 CHARACTER(LEN=4 ) :: YLVL           ! current level/layer
 CHARACTER(LEN=4 ) :: YPATCH         ! current patch
 INTEGER           :: INB_PROCIO     ! number of processes used for Z-parallel IO with MESO-NH
diff --git a/src/SURFEX/read_teb_canopyn.F90 b/src/SURFEX/read_teb_canopyn.F90
index 107db89d9035f88b4cb30218bbbe23fef3fb5060..43b8dae95619b0af4e79aa3ae06e58588cd7c1c9 100644
--- a/src/SURFEX/read_teb_canopyn.F90
+++ b/src/SURFEX/read_teb_canopyn.F90
@@ -75,7 +75,7 @@ TYPE(TEB_OPTIONS_t), INTENT(INOUT) :: TOP
 !              -------------------------------
 !
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=3)  :: YREAD
 INTEGER :: JLAYER  ! loop counter on layers
 INTEGER :: ILU     ! 1D physical dimension
diff --git a/src/SURFEX/read_teb_gardenn.F90 b/src/SURFEX/read_teb_gardenn.F90
index 4568cb3f0da9fff1264a149cced87d1a7abd4e1e..61084455f5e1e1eab12f7e3f914e5a4768903a36 100644
--- a/src/SURFEX/read_teb_gardenn.F90
+++ b/src/SURFEX/read_teb_gardenn.F90
@@ -90,7 +90,7 @@ LOGICAL           :: GTOWN          ! town variables written in the file
 INTEGER           :: IVERSION, IBUGFIX
 INTEGER           :: ILU            ! 1D physical dimension
 INTEGER           :: IRESP          ! Error code after redding
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=4)  :: YLVL
 REAL, DIMENSION(:),ALLOCATABLE  :: ZWORK      ! 2D array to write data in file
 !
diff --git a/src/SURFEX/read_teb_patch.F90 b/src/SURFEX/read_teb_patch.F90
index e5bfa4bcd4c475ed39822b896f8ab31d76b9017e..c41c136ffb6a307506a2726b37827bc313d6bbc1 100644
--- a/src/SURFEX/read_teb_patch.F90
+++ b/src/SURFEX/read_teb_patch.F90
@@ -34,7 +34,7 @@ INTEGER,            INTENT(OUT) :: KTEB_PATCH! number of TEB patches
 !* local variables
 !  ---------------
 !
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
 INTEGER           :: IRESP      ! reading return code
 !
 INTEGER           :: IVERSION   ! surface version
diff --git a/src/SURFEX/read_tebn.F90 b/src/SURFEX/read_tebn.F90
index 8a0e0398ca0c026d58cd4cd176db4720db8c8349..6cfdfe3bd58c5f79307f8327ba08ac805f4519a6 100644
--- a/src/SURFEX/read_tebn.F90
+++ b/src/SURFEX/read_tebn.F90
@@ -98,7 +98,7 @@ INTEGER           :: ILU          ! 1D physical dimension
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=3)  :: YPATCH         ! suffix if more than 1 patch
 !
 INTEGER           :: IVERSION, IBUGFIX
diff --git a/src/SURFEX/read_watflux_sbln.F90 b/src/SURFEX/read_watflux_sbln.F90
index b205478ce783daa78ce2af65a6605af4a8274dc4..8798d7a99e8fa6f55e700c98e4ed586fe53db474 100644
--- a/src/SURFEX/read_watflux_sbln.F90
+++ b/src/SURFEX/read_watflux_sbln.F90
@@ -74,7 +74,7 @@ TYPE(WATFLUX_SBL_t), INTENT(INOUT) :: WSB
 !*       0.2   Declarations of local variables
 !              -------------------------------
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=3)  :: YREAD
 INTEGER :: JLAYER  ! loop counter on layers
 INTEGER :: ILU     ! 1D physical dimension
diff --git a/src/SURFEX/read_watfluxn.F90 b/src/SURFEX/read_watfluxn.F90
index c8d58fc0c4dec8939c7467fe6360e267b881e785..9ece26cd00f956749aaaa81964b269f50fc25860 100644
--- a/src/SURFEX/read_watfluxn.F90
+++ b/src/SURFEX/read_watfluxn.F90
@@ -79,7 +79,7 @@ INTEGER           :: ILU          ! 1D physical dimension
 !
 INTEGER           :: IRESP          ! Error code after redding
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
 !-------------------------------------------------------------------------------
diff --git a/src/SURFEX/test_record_len.F90 b/src/SURFEX/test_record_len.F90
index a80b821ef272a02568316ff250e66b8e7c9857ce..4a1c75ea527ec7a484226bd28c511477efb583e2 100644
--- a/src/SURFEX/test_record_len.F90
+++ b/src/SURFEX/test_record_len.F90
@@ -30,23 +30,27 @@ IMPLICIT NONE
 TYPE(DIAG_SURF_ATM_t), INTENT(INOUT) :: DGU
 !
  CHARACTER(LEN=6),   INTENT(IN)  :: HPROGRAM ! calling program
- CHARACTER(LEN=12),  INTENT(IN)  :: HREC     ! name of the article to be written
+ CHARACTER(LEN=LEN_HREC),  INTENT(IN)  :: HREC     ! name of the article to be written
 LOGICAL,            INTENT(OUT) :: ONOWRITE ! flag for article to be written
 !
- CHARACTER(LEN=12) :: YREC
+ CHARACTER(LEN=LEN_HREC) :: YREC
 INTEGER :: IFIELD,JFIELD
 INTEGER :: ILUOUT  ! listing logical unit
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
+
+CHARACTER(LEN=12) :: YFMT
+
 !-------------------------------------------------------------------------------
 IF (LHOOK) CALL DR_HOOK('MODI_WRITE_SURF:TEST_RECORD_LEN',0,ZHOOK_HANDLE)
-IF (LEN_TRIM(HREC)>12) THEN
+IF (LEN_TRIM(HREC)>LEN_HREC) THEN
   CALL GET_LUOUT(HPROGRAM,ILUOUT)
   WRITE(ILUOUT,*) '----------------------------------------------'
   WRITE(ILUOUT,*) 'Error occured when writing a field            '
   WRITE(ILUOUT,*) 'The name of the field is too long             '
-  WRITE(ILUOUT,*) 'The name must not be longer than 12 characters'
+  WRITE(ILUOUT,*) 'The name must not be longer than',LEN_HREC,' characters'
   WRITE(ILUOUT,*) 'Please shorten the name of your field         '
-  WRITE(ILUOUT,FMT='(A32,A12,A1)') ' The field name currently is : "',HREC,'"'
+  WRITE(YFMT,FMT='("(A32,A",I2.2,",A1)")') LEN_HREC
+  WRITE(ILUOUT,FMT=YFMT) ' The field name currently is : "',HREC,'"'
   WRITE(ILUOUT,*) '----------------------------------------------'
   CALL ABOR1_SFX('TEST_RECORD_LEN: FIELD NAME TOO LONG --> '//HREC)
 END IF
diff --git a/src/SURFEX/write_diag_ch_aggr.F90 b/src/SURFEX/write_diag_ch_aggr.F90
index e438507758678261441bc39664925cb1a1c9ff93..837532b2f30d5e3df7b41fa2b1be52d70c0bb71c 100644
--- a/src/SURFEX/write_diag_ch_aggr.F90
+++ b/src/SURFEX/write_diag_ch_aggr.F90
@@ -66,7 +66,7 @@ TYPE(CH_EMIS_FIELD_t), INTENT(INOUT) :: CHE
 !
 
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER           :: JSPEC
diff --git a/src/SURFEX/write_diag_misc_flaken.F90 b/src/SURFEX/write_diag_misc_flaken.F90
index 8bf92ba459acbffda953deee08d7be1ac884b865..af04ee79e84b02381fe4c8040a06e6eac3a154c0 100644
--- a/src/SURFEX/write_diag_misc_flaken.F90
+++ b/src/SURFEX/write_diag_misc_flaken.F90
@@ -62,7 +62,7 @@ TYPE(DIAG_MISC_FLAKE_t), INTENT(INOUT) :: DGMF
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: IZ
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/write_diag_misc_isban.F90 b/src/SURFEX/write_diag_misc_isban.F90
index 9266f97f6dc850215814446fc74883226f992e94..4e12dd80c0dab8aecbce327fc7a1bef98629d999 100644
--- a/src/SURFEX/write_diag_misc_isban.F90
+++ b/src/SURFEX/write_diag_misc_isban.F90
@@ -94,7 +94,7 @@ TYPE(ISBA_t), INTENT(INOUT) :: I
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
  CHARACTER(LEN=1) :: YVAR
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=100):: YCOMMENTUNIT   ! Comment string : unit of the datas in the field to write
  CHARACTER(LEN=2)  :: YLVL
diff --git a/src/SURFEX/write_diag_misc_tebn.F90 b/src/SURFEX/write_diag_misc_tebn.F90
index 77d4be38b37d335a80f97b88049c4a11e9368cd0..3b9c9709f0a527b91f90887c0474cabc9873d500 100644
--- a/src/SURFEX/write_diag_misc_tebn.F90
+++ b/src/SURFEX/write_diag_misc_tebn.F90
@@ -74,7 +74,7 @@ INTEGER,           INTENT(IN)  :: KTEB_PATCH ! patch number being written
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
  CHARACTER(LEN=3)  :: YPATCH         ! Prefix for current patch
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/write_diag_pgd_grdnn.F90 b/src/SURFEX/write_diag_pgd_grdnn.F90
index bb3214a6985bf5f977880009eaf4bb55049ec0cc..46525984a12d20abfa80113332d000ca8565f586 100644
--- a/src/SURFEX/write_diag_pgd_grdnn.F90
+++ b/src/SURFEX/write_diag_pgd_grdnn.F90
@@ -82,7 +82,7 @@ TYPE(TEB_VEG_OPTIONS_t), INTENT(INOUT) :: TVG
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YLVLV, YPAS
 !
diff --git a/src/SURFEX/write_diag_pgd_isban.F90 b/src/SURFEX/write_diag_pgd_isban.F90
index b0ff27cd9fac34b551196d0b611b83620734023d..e22ce8e79714e38d5ea3ed278826ac8823788575 100644
--- a/src/SURFEX/write_diag_pgd_isban.F90
+++ b/src/SURFEX/write_diag_pgd_isban.F90
@@ -91,7 +91,7 @@ REAL, DIMENSION(SIZE(I%XDG,1)            ) :: ZDG2
 REAL, DIMENSION(SIZE(I%XDG,1)            ) :: ZDTOT
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
   CHARACTER(LEN=100):: YCOMMENTUNIT   ! Comment string : unit of the datas in the field to write
  CHARACTER(LEN=2)  :: YLVLV, YPAS
diff --git a/src/SURFEX/write_diag_pgd_tebn.F90 b/src/SURFEX/write_diag_pgd_tebn.F90
index a91d201f1cbebd94b71e35b5c9f4a6d6f84b0ae8..3c9402fee7228be2f36fbaecb56f183e8a659c56 100644
--- a/src/SURFEX/write_diag_pgd_tebn.F90
+++ b/src/SURFEX/write_diag_pgd_tebn.F90
@@ -84,7 +84,7 @@ TYPE(TEB_PANEL_t), INTENT(INOUT) :: TPN
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: JLAYER         ! loop counter on layers
 !
diff --git a/src/SURFEX/write_diag_seb_flaken.F90 b/src/SURFEX/write_diag_seb_flaken.F90
index 638cb8567ec287c34b44042d4d5191914e1910b0..0b390bdb1bf386d3f915d0e0d7d58cd1bc141005 100644
--- a/src/SURFEX/write_diag_seb_flaken.F90
+++ b/src/SURFEX/write_diag_seb_flaken.F90
@@ -81,7 +81,7 @@ TYPE(DIAG_FLAKE_t), INTENT(INOUT) :: DGF
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YNUM
 !
diff --git a/src/SURFEX/write_diag_seb_isban.F90 b/src/SURFEX/write_diag_seb_isban.F90
index b6235af0b1e22b4a1cd53ea726397a0530ca51bf..e8ca82fa3c219512b5b3a4af163dd48375161f08 100644
--- a/src/SURFEX/write_diag_seb_isban.F90
+++ b/src/SURFEX/write_diag_seb_isban.F90
@@ -103,7 +103,7 @@ TYPE(ISBA_t), INTENT(INOUT) :: I
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be write
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be write
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=100):: YCOMMENTUNIT   ! Comment string : unit of the datas in the field to write
  CHARACTER(LEN=2)  :: YNUM
diff --git a/src/SURFEX/write_diag_seb_oceann.F90 b/src/SURFEX/write_diag_seb_oceann.F90
index 5f4d2bc445dd7ad2facd6c3705a315e800fdcb90..33e7937cada2a83df8fdc595c17ab41274b55b74 100644
--- a/src/SURFEX/write_diag_seb_oceann.F90
+++ b/src/SURFEX/write_diag_seb_oceann.F90
@@ -64,7 +64,7 @@ TYPE(DIAG_OCEAN_t), INTENT(INOUT) :: DGO
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/write_diag_seb_seafluxn.F90 b/src/SURFEX/write_diag_seb_seafluxn.F90
index b267767c78355c6364f75a44a34cfc694b1ad4c5..40eb92b65d0d0c829966754a3c4bcc4565e2f6b2 100644
--- a/src/SURFEX/write_diag_seb_seafluxn.F90
+++ b/src/SURFEX/write_diag_seb_seafluxn.F90
@@ -86,7 +86,7 @@ TYPE(SEAFLUX_t), INTENT(INOUT) :: S
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YNUM
 !
diff --git a/src/SURFEX/write_diag_seb_seaicen.F90 b/src/SURFEX/write_diag_seb_seaicen.F90
index 9d9693946d058c2ee87a1f1a19f0ff649ed833e8..0f697c3bf29d514369bb38969e8e48ff54d143a0 100644
--- a/src/SURFEX/write_diag_seb_seaicen.F90
+++ b/src/SURFEX/write_diag_seb_seaicen.F90
@@ -70,7 +70,7 @@ TYPE(SEAFLUX_t), INTENT(INOUT) :: S
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YNUM
 INTEGER           :: JSV, JSW
diff --git a/src/SURFEX/write_diag_seb_surf_atmn.F90 b/src/SURFEX/write_diag_seb_surf_atmn.F90
index 746961547e5390857ab88e1b1e3804079574ec15..35a659f0a0782e860d6e016eb7bb2fb36ae6acf1 100644
--- a/src/SURFEX/write_diag_seb_surf_atmn.F90
+++ b/src/SURFEX/write_diag_seb_surf_atmn.F90
@@ -71,7 +71,7 @@ TYPE(SURF_ATM_GRID_t), INTENT(INOUT) :: UG
 !
 
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YNUM
 !
diff --git a/src/SURFEX/write_diag_seb_tebn.F90 b/src/SURFEX/write_diag_seb_tebn.F90
index 7b022fbb4c324a34d59cb6b049f2a7c978328c88..40c1cbc65b473ef40dff042deb349ec51d6c33c9 100644
--- a/src/SURFEX/write_diag_seb_tebn.F90
+++ b/src/SURFEX/write_diag_seb_tebn.F90
@@ -79,7 +79,7 @@ TYPE(DIAG_UTCI_TEB_t), INTENT(INOUT) :: DGUT
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YNUM
 !
diff --git a/src/SURFEX/write_diag_seb_watfluxn.F90 b/src/SURFEX/write_diag_seb_watfluxn.F90
index e04d1bd1f397c195972ee0e63d7f4baa15b300a7..207dcdbb1451cd65e21e470066ff1eff77ea3b94 100644
--- a/src/SURFEX/write_diag_seb_watfluxn.F90
+++ b/src/SURFEX/write_diag_seb_watfluxn.F90
@@ -82,7 +82,7 @@ TYPE(DIAG_WATFLUX_t), INTENT(INOUT) :: DGW
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be written
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be written
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=2)  :: YNUM
 !
diff --git a/src/SURFEX/write_ecoclimap2_data.F90 b/src/SURFEX/write_ecoclimap2_data.F90
index f92002d6e7ccbc1a7d62584612e27bf9beff6da5..978d4a27ab8c55c780befc18d549501f56f67d73 100644
--- a/src/SURFEX/write_ecoclimap2_data.F90
+++ b/src/SURFEX/write_ecoclimap2_data.F90
@@ -37,7 +37,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !* local variables
 !  ---------------
 !
- CHARACTER(LEN=12) :: YRECFM     ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM     ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT   ! Comment
 INTEGER           :: IRESP      ! reading return code
 !
diff --git a/src/SURFEX/write_lcover.F90 b/src/SURFEX/write_lcover.F90
index f16aba540b0351f066ca614e0ecb2cad6629fba1..d35909aec00d26ae42e3d13c6931323dec3c126a 100644
--- a/src/SURFEX/write_lcover.F90
+++ b/src/SURFEX/write_lcover.F90
@@ -68,7 +68,7 @@ LOGICAL, DIMENSION(JPCOVER)    :: OCOVER   ! list of covers
 TYPE(DIAG_SURF_ATM_t), INTENT(INOUT) :: DGU
 TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 INTEGER           :: IRESP          ! Error code after reading
-CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 LOGICAL, DIMENSION(JPCOVER)    :: GCOVER   ! tmp list of covers
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/write_surf.F90 b/src/SURFEX/write_surf.F90
index 7355d1ec4079b4a9a6fc12afeb7bd5fca4692e95..12c51ed98518795a1e1859c54dd2f1b3886143e4 100644
--- a/src/SURFEX/write_surf.F90
+++ b/src/SURFEX/write_surf.F90
@@ -50,7 +50,7 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 END SUBROUTINE WRITE_SURFX1
 !
      SUBROUTINE WRITE_SURFX2 (DGU, U, &
@@ -71,7 +71,7 @@ INTEGER,              INTENT(OUT) :: KRESP    ! KRESP  : return-code if a proble
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 END SUBROUTINE WRITE_SURFX2
 !
 !RJ: interface to WRITE_SURFX2COV moved out
@@ -111,7 +111,7 @@ INTEGER,               INTENT(OUT) :: KRESP    ! KRESP  : return-code if a probl
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 END SUBROUTINE WRITE_SURFN1
 !
      SUBROUTINE WRITE_SURFC0 (DGU, U, &
@@ -295,7 +295,7 @@ INTEGER,           INTENT(OUT):: KRESP    ! KRESP  : return-code if a problem ap
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 LOGICAL :: LNOWRITE
 REAL   :: XTIME0
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
@@ -453,10 +453,10 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 INTEGER            :: IL
  CHARACTER(LEN=1)   :: YDIR
 LOGICAL :: LNOWRITE
@@ -606,10 +606,10 @@ INTEGER,              INTENT(OUT) :: KRESP    ! KRESP  : return-code if a proble
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 INTEGER            :: IL1
 INTEGER            :: IL2
  CHARACTER(LEN=1)   :: YDIR
@@ -764,7 +764,7 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 LOGICAL :: LNOWRITE
 REAL   :: XTIME0
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
@@ -919,10 +919,10 @@ INTEGER,               INTENT(OUT) :: KRESP    ! KRESP  : return-code if a probl
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 INTEGER            :: IL
  CHARACTER(LEN=1)   :: YDIR
 LOGICAL :: LNOWRITE
@@ -1074,7 +1074,7 @@ INTEGER,             INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
  CHARACTER(LEN=40)  :: YFIELD
 LOGICAL :: LNOWRITE
 REAL   :: XTIME0
@@ -1234,7 +1234,7 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 LOGICAL :: LNOWRITE
 REAL   :: XTIME0
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
@@ -1390,7 +1390,7 @@ INTEGER,               INTENT(OUT) :: KRESP    ! KRESP  : return-code if a probl
 !                                             ! '-' : no horizontal dim.
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 INTEGER            :: IL
  CHARACTER(LEN=1)   :: YDIR
 LOGICAL :: LNOWRITE
@@ -1538,7 +1538,7 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 REAL    :: ZTIME
 REAL   :: XTIME0
 INTEGER :: IDAY
@@ -1691,7 +1691,7 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 INTEGER :: IL1
 REAL ,   DIMENSION(SIZE(TFIELD,1)) :: ZTIME
 INTEGER, DIMENSION(SIZE(TFIELD,1)) :: IDAY
@@ -1824,7 +1824,7 @@ INTEGER,            INTENT(OUT) :: KRESP    ! KRESP  : return-code if a problem
 !
 !*      0.2   Declarations of local variables
 !
- CHARACTER(LEN=12)  :: YREC
+ CHARACTER(LEN=LEN_HREC)  :: YREC
 INTEGER :: IL1, IL2
 REAL ,   DIMENSION(SIZE(TFIELD,1),SIZE(TFIELD,2)) :: ZTIME
 INTEGER, DIMENSION(SIZE(TFIELD,1),SIZE(TFIELD,2)) :: IDAY
diff --git a/src/SURFEX/write_surf_field2d.F90 b/src/SURFEX/write_surf_field2d.F90
index 78c4f2713fb3cf288f8bf458cbd87275175eb42a..5cbdcca8a792cd142921fff8cd513e02ec08b9c9 100644
--- a/src/SURFEX/write_surf_field2d.F90
+++ b/src/SURFEX/write_surf_field2d.F90
@@ -70,21 +70,21 @@ TYPE(DIAG_SURF_ATM_t), INTENT(INOUT) :: DGU
 TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 CHARACTER(LEN=6),                 INTENT(IN) :: HPROGRAM     ! calling program
 REAL, DIMENSION(:,:),             INTENT(IN) :: PFIELD2D     ! 2D field to be written
-CHARACTER(LEN=12),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD2D. Example : 'X_Y_TG'
+CHARACTER(LEN=LEN_HREC),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD2D. Example : 'X_Y_TG'
 CHARACTER(LEN=100),               INTENT(IN) :: HCOMMENT     ! Comment string
 CHARACTER(LEN=100),               INTENT(IN) :: HCOMMENTUNIT ! unit of the datas in PFIELD2D
  CHARACTER(LEN=1),OPTIONAL,       INTENT(IN) :: HDIR ! type of field :
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
  !
 !*       0.2   Declarations of local variables
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
 INTEGER           :: IPATCH         ! number of patches in PFIELD2D
-CHARACTER(LEN=16) :: YRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 CHARACTER(LEN=4 ) :: YPATCH         ! current patch
 CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: INB_PROCIO     ! number of processes used for Z-parallel IO with MESO-NH
diff --git a/src/SURFEX/write_surf_field3d.F90 b/src/SURFEX/write_surf_field3d.F90
index c52a022a92058f8030e84b8c67aa9ccf511cf0e8..05b4d56522732c7e64bf59f316675471e5bfeea9 100644
--- a/src/SURFEX/write_surf_field3d.F90
+++ b/src/SURFEX/write_surf_field3d.F90
@@ -72,14 +72,14 @@ CHARACTER(LEN=6),                 INTENT(IN) :: HPROGRAM     ! calling program
 REAL, DIMENSION(:,:,:),           INTENT(IN) :: PFIELD3D     ! 3D field to be written
 INTEGER,                          INTENT(IN) :: KFIRSTLAYER  ! first layer of PFIELD3D to be written
 INTEGER,                          INTENT(IN) :: KLASTLAYER   ! last layer of PFIELD3D to be written
-CHARACTER(LEN=12),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD3D. Example : 'X_Y_TG'
+CHARACTER(LEN=LEN_HREC),                INTENT(IN) :: HFIELDNAME   ! name of the field PFIELD3D. Example : 'X_Y_TG'
 CHARACTER(LEN=100),               INTENT(IN) :: HCOMMENT     ! Comment string
 CHARACTER(LEN=100),               INTENT(IN) :: HCOMMENTUNIT ! unit of the datas in PFIELD3D
  CHARACTER(LEN=1),OPTIONAL,       INTENT(IN) :: HDIR ! type of field :
 !                                             ! 'H' : field with
 !                                             !       horizontal spatial dim.
 !                                             ! '-' : no horizontal dim.
- CHARACTER(LEN=16), OPTIONAL,  INTENT(IN) :: HNAM_DIM
+ CHARACTER(LEN=LEN_HREC), OPTIONAL,  INTENT(IN) :: HNAM_DIM
 !
 !*       0.2   Declarations of local variables
 !              -------------------------------
@@ -87,7 +87,7 @@ CHARACTER(LEN=100),               INTENT(IN) :: HCOMMENTUNIT ! unit of the datas
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
 INTEGER           :: ILAYER         ! number of layers in PFIELD3D
 INTEGER           :: IPATCH         ! number of patches in PFIELD3D
-CHARACTER(LEN=16) :: YRECFM         ! Name of the article to be read
+CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 CHARACTER(LEN=4 ) :: YLVL           ! current level/layer
 CHARACTER(LEN=4 ) :: YPATCH         ! current patch
 CHARACTER(LEN=100):: YCOMMENT       ! Comment string
diff --git a/src/SURFEX/writesurf_ch_emisn.F90 b/src/SURFEX/writesurf_ch_emisn.F90
index 70088f4ec266c67f67f034b43138d69585986d5a..d542424409f387c0bb01605eef10cc783e8a270f 100644
--- a/src/SURFEX/writesurf_ch_emisn.F90
+++ b/src/SURFEX/writesurf_ch_emisn.F90
@@ -63,7 +63,7 @@ TYPE(CH_EMIS_FIELD_t), INTENT(INOUT) :: CHE
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears 
                                     ! at the open of the file in LFI  routines 
 !
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be written
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be written
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=100):: YCOMMENTUNIT   ! Comment string : unit of the datas in the field to write 
  CHARACTER(LEN=80) :: YNAME          ! emitted species name
diff --git a/src/SURFEX/writesurf_covern.F90 b/src/SURFEX/writesurf_covern.F90
index ecb5d69d7a7c469e54a4296c3a24daf1f1b6b740..27901272b10a47b3bfe8f38778e93ca132a4dcac 100644
--- a/src/SURFEX/writesurf_covern.F90
+++ b/src/SURFEX/writesurf_covern.F90
@@ -71,7 +71,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 INTEGER :: IINFO
diff --git a/src/SURFEX/writesurf_cpl_gcmn.F90 b/src/SURFEX/writesurf_cpl_gcmn.F90
index aa7156dcfd45124b0e24546a9cc4c091297b53ba..cccde84f035bc18f6826eaf27be80affe565c27a 100644
--- a/src/SURFEX/writesurf_cpl_gcmn.F90
+++ b/src/SURFEX/writesurf_cpl_gcmn.F90
@@ -78,7 +78,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !
 !
 INTEGER           :: IRESP          ! Error code after redding
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_dummyn.F90 b/src/SURFEX/writesurf_dummyn.F90
index 5889e72d2ef6b45d2c176c71b8a8b6b875972371..608087835801ef2687c5b1c3200b83097cba2c7f 100644
--- a/src/SURFEX/writesurf_dummyn.F90
+++ b/src/SURFEX/writesurf_dummyn.F90
@@ -64,7 +64,7 @@ INTEGER           :: JDUMMY         ! loop counter
  CHARACTER(LEN=3  ):: YSTRING03      ! string
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_flake_sbln.F90 b/src/SURFEX/writesurf_flake_sbln.F90
index de59c113d02701ebff372bd7d3d4a4297e614623..e2b36cfe3ae4d9663a1abef2ec5537a04c1dca79 100644
--- a/src/SURFEX/writesurf_flake_sbln.F90
+++ b/src/SURFEX/writesurf_flake_sbln.F90
@@ -78,7 +78,7 @@ TYPE(FLAKE_SBL_t), INTENT(INOUT) :: FSB
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER :: JLAYER  ! loop counter on layers
diff --git a/src/SURFEX/writesurf_flaken.F90 b/src/SURFEX/writesurf_flaken.F90
index e55d19c4e7f70e83d362ab87c93126108124f32b..dbaa7e04e57789670f9b52c3c316027d0f151848 100644
--- a/src/SURFEX/writesurf_flaken.F90
+++ b/src/SURFEX/writesurf_flaken.F90
@@ -73,7 +73,7 @@ TYPE(FLAKE_t), INTENT(INOUT) :: F
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_gr_snow.F90 b/src/SURFEX/writesurf_gr_snow.F90
index e4f5a6a7f018a2a7bbe8baf0328e198682f03fca..ad2e8c69f7a1afcee7467574c393d9f9791942de 100644
--- a/src/SURFEX/writesurf_gr_snow.F90
+++ b/src/SURFEX/writesurf_gr_snow.F90
@@ -81,7 +81,7 @@ TYPE(SURF_SNOW),    INTENT(IN) :: TPSNOW     ! snow characteristics
 INTEGER             :: ISURFTYPE_LEN
 !
  CHARACTER (LEN=100) :: YFMT           ! format for writing
- CHARACTER(LEN=12)   :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC)   :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100)  :: YCOMMENT       ! Comment string
  CHARACTER(LEN=100):: YCOMMENTUNIT     ! Comment string : unit of the datas in the field to write 
 INTEGER             :: IRESP          ! IRESP  : return-code if a problem appears
diff --git a/src/SURFEX/writesurf_isba_canopyn.F90 b/src/SURFEX/writesurf_isba_canopyn.F90
index 94ded2338d73c21a53baded8b50274e92cf4c127..f005b0985e68d0c6691c70243b49872bcde4c318 100644
--- a/src/SURFEX/writesurf_isba_canopyn.F90
+++ b/src/SURFEX/writesurf_isba_canopyn.F90
@@ -78,7 +78,7 @@ TYPE(ISBA_t), INTENT(INOUT) :: I
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER :: JLAYER  ! loop counter on layers
diff --git a/src/SURFEX/writesurf_isban.F90 b/src/SURFEX/writesurf_isban.F90
index dd1c27178ac345ef2937a63d068235e7bdfada91..ac09a551e43ab8a86faf1b5cc646adc8b408076c 100644
--- a/src/SURFEX/writesurf_isban.F90
+++ b/src/SURFEX/writesurf_isban.F90
@@ -102,7 +102,7 @@ LOGICAL,           INTENT(IN)  :: OLAND_USE !
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=4 ) :: YLVL
  CHARACTER(LEN=3 ) :: YVAR
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
diff --git a/src/SURFEX/writesurf_oceann.F90 b/src/SURFEX/writesurf_oceann.F90
index a3f22737c99688809de5579309cf698350f7afed..ecfc87ccb734a5ec230ed6c8141876ac344c4044 100644
--- a/src/SURFEX/writesurf_oceann.F90
+++ b/src/SURFEX/writesurf_oceann.F90
@@ -78,7 +78,7 @@ TYPE(OCEAN_REL_t), INTENT(INOUT) :: OR
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=4 ) :: YLVL
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=14) :: YFORM          ! Writing format
diff --git a/src/SURFEX/writesurf_pgd_flaken.F90 b/src/SURFEX/writesurf_pgd_flaken.F90
index 4eccc1abb137aeafb5770f83e5b5ac7c76daa63c..c9a251e117eae0ad80126bd473428a2db644e245 100644
--- a/src/SURFEX/writesurf_pgd_flaken.F90
+++ b/src/SURFEX/writesurf_pgd_flaken.F90
@@ -81,7 +81,7 @@ TYPE(FLAKE_t), INTENT(INOUT) :: F
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_pgd_isba_parn.F90 b/src/SURFEX/writesurf_pgd_isba_parn.F90
index 1ca26a9edcee23d3b4acc265d44513f71539bda0..b7115dab5c20724167f8beb87ced208aacb42f51 100644
--- a/src/SURFEX/writesurf_pgd_isba_parn.F90
+++ b/src/SURFEX/writesurf_pgd_isba_parn.F90
@@ -78,7 +78,7 @@ TYPE(DATA_ISBA_t), INTENT(INOUT) :: DTI
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=100):: YCOMMENTUNIT   ! Comment string : unit of the datas in the field to write
 INTEGER           :: JTIME          ! loop index
diff --git a/src/SURFEX/writesurf_pgd_isban.F90 b/src/SURFEX/writesurf_pgd_isban.F90
index 38cc312480c1be50bd0c2a035e67da0b7e6455f4..62d3e9566eb9c016d824b8db3fce2461faa915cf 100644
--- a/src/SURFEX/writesurf_pgd_isban.F90
+++ b/src/SURFEX/writesurf_pgd_isban.F90
@@ -104,7 +104,7 @@ TYPE(SURF_ATM_t), INTENT(INOUT) :: U
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=100):: YCOMMENTUNIT   ! Comment string : unit of the datas in the field to write
  CHARACTER(LEN=4 ) :: YLVL
diff --git a/src/SURFEX/writesurf_pgd_seaf_parn.F90 b/src/SURFEX/writesurf_pgd_seaf_parn.F90
index d92c4bfa156b6151bfeeebce3ba62200f2ca7bd7..f7b15e420d14634c9689bc713a5c52c12cdfe7d5 100644
--- a/src/SURFEX/writesurf_pgd_seaf_parn.F90
+++ b/src/SURFEX/writesurf_pgd_seaf_parn.F90
@@ -74,7 +74,7 @@ TYPE(DATA_SEAFLUX_t), INTENT(INOUT) :: DTS
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: JTIME          ! loop index
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/writesurf_pgd_seafluxn.F90 b/src/SURFEX/writesurf_pgd_seafluxn.F90
index 70032d7d1632da583343d0de6593b660719fc55a..dcbbaf05fb16b4c99442e7a4645d5840afb0b9b2 100644
--- a/src/SURFEX/writesurf_pgd_seafluxn.F90
+++ b/src/SURFEX/writesurf_pgd_seafluxn.F90
@@ -85,7 +85,7 @@ TYPE(SEAFLUX_t), INTENT(INOUT) :: S
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_pgd_teb_greenroofn.F90 b/src/SURFEX/writesurf_pgd_teb_greenroofn.F90
index 0d402f1bd47e4bb3bfab9b85363daa632209d4ba..d2ca6944fce4128440212844adfbb144b0190009 100644
--- a/src/SURFEX/writesurf_pgd_teb_greenroofn.F90
+++ b/src/SURFEX/writesurf_pgd_teb_greenroofn.F90
@@ -74,7 +74,7 @@ TYPE(TEB_GREENROOF_PGD_t), INTENT(INOUT) :: TGRP
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/writesurf_pgd_teb_irrign.F90 b/src/SURFEX/writesurf_pgd_teb_irrign.F90
index de7f2a738a2ee8984e0c8efd00402aa785a21a20..595d5b48ed88b043eaae63a3ece64b19e90f0135 100644
--- a/src/SURFEX/writesurf_pgd_teb_irrign.F90
+++ b/src/SURFEX/writesurf_pgd_teb_irrign.F90
@@ -73,7 +73,7 @@ TYPE(TEB_IRRIG_t), INTENT(INOUT) :: TIR
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: JLAYER         ! loop index
 INTEGER           :: JTIME          ! loop index
diff --git a/src/SURFEX/writesurf_pgd_teb_parn.F90 b/src/SURFEX/writesurf_pgd_teb_parn.F90
index 60ee430d0130f19c651bd78eb745b697986e2ef8..562b72415151c4c4302f19f17fe016e8fba1bdfa 100644
--- a/src/SURFEX/writesurf_pgd_teb_parn.F90
+++ b/src/SURFEX/writesurf_pgd_teb_parn.F90
@@ -92,7 +92,7 @@ TYPE(TEB_OPTIONS_t), INTENT(INOUT) :: TOP
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: JLAYER         ! loop index
 INTEGER           :: JTIME          ! loop index
diff --git a/src/SURFEX/writesurf_pgd_teb_vegn.F90 b/src/SURFEX/writesurf_pgd_teb_vegn.F90
index 77b839e894eb33dc4f2679dc4cec08ee0cba21b2..e7c7f4e675168e6cf8b3afb6787562536f68a372 100644
--- a/src/SURFEX/writesurf_pgd_teb_vegn.F90
+++ b/src/SURFEX/writesurf_pgd_teb_vegn.F90
@@ -81,7 +81,7 @@ TYPE(TEB_MODEL_t), INTENT(INOUT) :: TM
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=4 ) :: YLVL
 !
diff --git a/src/SURFEX/writesurf_pgd_tebn.F90 b/src/SURFEX/writesurf_pgd_tebn.F90
index 4367b2cda5b87a21b44f20ceb4392a1c96b16127..65e376897161433a4ff85137bff915907c0a39cd 100644
--- a/src/SURFEX/writesurf_pgd_tebn.F90
+++ b/src/SURFEX/writesurf_pgd_tebn.F90
@@ -82,7 +82,7 @@ TYPE(TEB_GREENROOF_MODEL_t), INTENT(INOUT) :: GRM
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/writesurf_pgd_tsz0_parn.F90 b/src/SURFEX/writesurf_pgd_tsz0_parn.F90
index 0b8a9304d92bae2474a79087e5194be0ad7a9311..8e0f2bca931fe868287e1a04aa2bbf325855d726 100644
--- a/src/SURFEX/writesurf_pgd_tsz0_parn.F90
+++ b/src/SURFEX/writesurf_pgd_tsz0_parn.F90
@@ -73,7 +73,7 @@ TYPE(DATA_TSZ0_t), INTENT(INOUT) :: DTZ
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_pgd_watfluxn.F90 b/src/SURFEX/writesurf_pgd_watfluxn.F90
index 7db06730be5c254ac160397908a4de82cdad85d0..02ab630663d1ab0121d12e1979afeafc88b6c69c 100644
--- a/src/SURFEX/writesurf_pgd_watfluxn.F90
+++ b/src/SURFEX/writesurf_pgd_watfluxn.F90
@@ -82,7 +82,7 @@ TYPE(WATFLUX_t), INTENT(INOUT) :: W
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 INTEGER           :: JCOVER         ! loop index
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
diff --git a/src/SURFEX/writesurf_seaflux_sbln.F90 b/src/SURFEX/writesurf_seaflux_sbln.F90
index 51a44764f8d39917aeffe1915ceb5da26f3812b5..369ca85ad52a787b11e1974fd0d67a5cc1724893 100644
--- a/src/SURFEX/writesurf_seaflux_sbln.F90
+++ b/src/SURFEX/writesurf_seaflux_sbln.F90
@@ -79,7 +79,7 @@ TYPE(SEAFLUX_SBL_t), INTENT(INOUT) :: SSB
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER :: JLAYER  ! loop counter on layers
diff --git a/src/SURFEX/writesurf_seafluxn.F90 b/src/SURFEX/writesurf_seafluxn.F90
index f3900c56768a14686cd02108329aaedb0ab08888..6f42fbfbeac1d54a9ec93d084c5cc9430c08ef9d 100644
--- a/src/SURFEX/writesurf_seafluxn.F90
+++ b/src/SURFEX/writesurf_seafluxn.F90
@@ -85,7 +85,7 @@ INTEGER           :: JMTH, INMTH
  CHARACTER(LEN=2 ) :: YMTH
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_seaicen.F90 b/src/SURFEX/writesurf_seaicen.F90
index bf77f09c6df5c719bb389f8fa1c3583c426bfc42..d6326976cff918756c9a46b2da9a188a0c5d3617 100644
--- a/src/SURFEX/writesurf_seaicen.F90
+++ b/src/SURFEX/writesurf_seaicen.F90
@@ -87,9 +87,9 @@ INTEGER           :: JMTH, INMTH
 !
  CHARACTER(LEN=6)  :: YICECAT
  CHARACTER(LEN=20) :: YFORM
- CHARACTER(LEN=12) :: YRECFM           ! Name of the article to be read
- CHARACTER(LEN=12) :: YCATEG           ! Category to write
- CHARACTER(LEN=12) :: YLEVEL           ! Level to write
+ CHARACTER(LEN=LEN_HREC) :: YRECFM           ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YCATEG           ! Category to write
+ CHARACTER(LEN=LEN_HREC) :: YLEVEL           ! Level to write
  CHARACTER(LEN=100):: YCOMMENT         ! Error Message
 !
 INTEGER :: JK,JL                   ! loop counter on ice categories and layes 
diff --git a/src/SURFEX/writesurf_sso_canopyn.F90 b/src/SURFEX/writesurf_sso_canopyn.F90
index bb1ba4dc1e40abf4fadd10f72fc1895694cff28d..dc57b347738443bcd2bcc89061d6a18b2f2ee558 100644
--- a/src/SURFEX/writesurf_sso_canopyn.F90
+++ b/src/SURFEX/writesurf_sso_canopyn.F90
@@ -75,7 +75,7 @@ LOGICAL,           INTENT(IN)  :: OWRITE   ! flag to write canopy terms
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER :: JLAYER  ! loop counter on layers
diff --git a/src/SURFEX/writesurf_sson.F90 b/src/SURFEX/writesurf_sson.F90
index 5e3022fdad0fbc1fb9224882827d0902a60b6e4f..69aa2326115a80bdba45b6b85330329e22cc9469 100644
--- a/src/SURFEX/writesurf_sson.F90
+++ b/src/SURFEX/writesurf_sson.F90
@@ -68,7 +68,7 @@ TYPE(SURF_ATM_SSO_t), INTENT(INOUT) :: USS
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/writesurf_teb_canopyn.F90 b/src/SURFEX/writesurf_teb_canopyn.F90
index a5b350df5ef49c0e3228746c737325dfa1b47bb8..b15269255c5f32af594078747d7fa91036d7d434 100644
--- a/src/SURFEX/writesurf_teb_canopyn.F90
+++ b/src/SURFEX/writesurf_teb_canopyn.F90
@@ -78,7 +78,7 @@ TYPE(TEB_OPTIONS_t), INTENT(INOUT) :: TOP
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER :: JLAYER  ! loop counter on layers
diff --git a/src/SURFEX/writesurf_teb_gardenn.F90 b/src/SURFEX/writesurf_teb_gardenn.F90
index 0699edb362d4757c96d8e795355aa6171bf39247..4f663720a33679ecd492cbee95966050896e3f22 100644
--- a/src/SURFEX/writesurf_teb_gardenn.F90
+++ b/src/SURFEX/writesurf_teb_gardenn.F90
@@ -79,7 +79,7 @@ TYPE(TEB_GARDEN_MODEL_t), INTENT(INOUT) :: GDM
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=14) :: YFORM          ! Writing format
  CHARACTER(LEN=4 ) :: YLVL
diff --git a/src/SURFEX/writesurf_tebn.F90 b/src/SURFEX/writesurf_tebn.F90
index 281a1d0a8b16dbfaa8f955fe68f0afda620b5fb8..de62ce8b9ab4e7e35caf401aa28f8b2876282502 100644
--- a/src/SURFEX/writesurf_tebn.F90
+++ b/src/SURFEX/writesurf_tebn.F90
@@ -87,7 +87,7 @@ INTEGER,           INTENT(IN)  :: KPATCH   ! current TEB patch
 !              -------------------------------
 !
 INTEGER           :: IRESP           ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
  CHARACTER(LEN=3)  :: YPATCH         ! Patch identificator
  CHARACTER(LEN=7)  :: YDIR           ! Direction identificator
diff --git a/src/SURFEX/writesurf_watflux_sbln.F90 b/src/SURFEX/writesurf_watflux_sbln.F90
index 730920380161b0c01fb2f81a4d1354f62ed74e42..7482434877be73117169263c613632c371352352 100644
--- a/src/SURFEX/writesurf_watflux_sbln.F90
+++ b/src/SURFEX/writesurf_watflux_sbln.F90
@@ -79,7 +79,7 @@ TYPE(WATFLUX_SBL_t), INTENT(INOUT) :: WSB
 !              -------------------------------
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 !
 INTEGER :: JLAYER  ! loop counter on layers
diff --git a/src/SURFEX/writesurf_watfluxn.F90 b/src/SURFEX/writesurf_watfluxn.F90
index 47443e674cfecf1a6a25241bd45b42a1b12a28b7..ee5c6a1a60d7931969c5357fe256482bb717257d 100644
--- a/src/SURFEX/writesurf_watfluxn.F90
+++ b/src/SURFEX/writesurf_watfluxn.F90
@@ -76,7 +76,7 @@ INTEGER          :: JMTH,INMTH
  CHARACTER(LEN=2) :: YMTH
 !
 INTEGER           :: IRESP          ! IRESP  : return-code if a problem appears
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
  CHARACTER(LEN=100):: YCOMMENT       ! Comment string
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 !
diff --git a/src/SURFEX/zoom_pgd_orography.F90 b/src/SURFEX/zoom_pgd_orography.F90
index 6c141f0cc75dd6417d57e9fea250d605743be9e4..6f21dd21b7b9fe21cd49291b3889d7ffa35a2faa 100644
--- a/src/SURFEX/zoom_pgd_orography.F90
+++ b/src/SURFEX/zoom_pgd_orography.F90
@@ -115,7 +115,7 @@ REAL, DIMENSION(:), POINTER :: ZHO2IP
 REAL, DIMENSION(:), POINTER :: ZHO2IM
 REAL, DIMENSION(:), POINTER :: ZHO2JP
 REAL, DIMENSION(:), POINTER :: ZHO2JM
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
 INTEGER :: IINFO_ll
 !------------------------------------------------------------------------------
diff --git a/src/SURFEX/zoom_pgd_teb.F90 b/src/SURFEX/zoom_pgd_teb.F90
index a20b844dcd101f51c8dbd054d77d9e35c5e5249b..43271ee5777e3b9487f394601e3765e955bb1e46 100644
--- a/src/SURFEX/zoom_pgd_teb.F90
+++ b/src/SURFEX/zoom_pgd_teb.F90
@@ -274,7 +274,7 @@ REAL, DIMENSION(:,:), POINTER     :: ZIN     ! field  on all surface points
 REAL, DIMENSION(INI)              :: ZFIELD  ! field read
 REAL, DIMENSION(ILU,1)            :: ZOUT    ! final field
 REAL(KIND=JPRB) :: ZHOOK_HANDLE
- CHARACTER(LEN=12) :: YRECFM         ! Name of the article to be read
+ CHARACTER(LEN=LEN_HREC) :: YRECFM         ! Name of the article to be read
 !
 IF (LHOOK) CALL DR_HOOK('ZOOM_PGD_TEB:ZOOM_PGD_TEB_GARDEN',0,ZHOOK_HANDLE)
 !
diff --git a/src/configure b/src/configure
index 30a4c4b53d450d23766705444b578aa92d415889..4d26378b4191c4310f6222ce7454f09a62682721 100755
--- a/src/configure
+++ b/src/configure
@@ -23,6 +23,8 @@ export VERSION_OASIS=${VERSION_OASIS:-"mct_v3"}
 export VERSION_TOY=${VERSION_TOY:-"v1-0"}
 export VERSION_NCL=${VERSION_NCL:-"ncl-6.3.0"}
 
+export LEN_HREC=${LEN_HREC:-16}
+
 #
 export NEED_TOOLS=YES
 #