diff --git a/src/MNH/ini_cpl.f90 b/src/MNH/ini_cpl.f90
index 0646747bacba903a0b9d57db46473508237d4a84..4a294b7366a9ba3f14e4b63932a1149e064a2ed7 100644
--- a/src/MNH/ini_cpl.f90
+++ b/src/MNH/ini_cpl.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1995-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1995-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -146,7 +146,6 @@ END MODULE MODI_INI_CPL
 !!      IO_File_close : to close a FM-file
 !!      INI_LS      : to initialize larger scale fields
 !!      INI_LB      : to initialize "2D" surfacic LB fields 
-!!      DATETIME_DISTANCE : compute the temporal distance in seconds between 2 dates
 !!
 !!      Module MODE_TIME : contains SM_PRINT_TIME routine
 !!                         and uses module MODD_TIME (for definition
@@ -157,7 +156,6 @@ END MODULE MODI_INI_CPL
 !!      Module MODD_PARAMETERS 
 !!         JPHEXT : Horizontal external points number
 !!         JPVEXT : Vertical external points number
-!!         JPCPLFILEMAX : Maximum allowed number of coupling files
 !!
 !!      Module MODD_CONF   
 !!         NVERB      : Level of informations on output-listing
@@ -313,12 +311,9 @@ INTEGER                :: IRESP
 CHARACTER (LEN=40)     :: YTITLE                     !  Title for date print 
 INTEGER                :: JCI                        !  Loop index on number of
                                                      ! coupling files
-CHARACTER (LEN=2)      :: YCI                        !  String for coupling files
+CHARACTER (LEN=6)      :: YCI                        !  String for coupling files
                                                      ! index
 REAL                   :: ZLENG                      ! Interpolation length
-LOGICAL                :: GEND                    !  Logical to see if coupling
-                                                  ! times respect the chronolo.
-                                                  ! order or the segment length
 INTEGER                :: IIMAX,IJMAX,IKMAX       !  Dimensions  of the physical 
                                                   ! part of the arrays stored in
                                                   ! coupling file
@@ -326,11 +321,11 @@ INTEGER                :: IKU             !  Dimensions of arrays in
                                                   ! initial file
 
 INTEGER                :: ICPLEND                 ! number of the last cpl file
-LOGICAL, DIMENSION(JPCPLFILEMAX)    :: GSKIP      ! array to skip or not after
-                                                  ! a cpl file
+LOGICAL, DIMENSION(NCPL_NBR) :: GSKIP             ! array to skip or not after a cpl file
 REAL                   :: ZDIST                   ! temporal distance in secunds
                                                   ! between 2 dates
 LOGICAL :: GLSOURCE ! switch for the source term (for ini_ls and ini_lb)
+TYPE (DATE_TIME), DIMENSION(NCPL_NBR) :: TZDTCPL ! Time and Date of the CouPLing files
 !CHARACTER(LEN=4), DIMENSION(KSV)    :: YGETSVM
 !
 !-------------------------------------------------------------------------------
@@ -339,7 +334,7 @@ LOGICAL :: GLSOURCE ! switch for the source term (for ini_ls and ini_lb)
 !              --------------------
 !
 GSKIP(:)=.FALSE.
-GEND=.FALSE.
+ALLOCATE( NCPL_TIMES(NCPL_NBR, NMODEL) )
 NCPL_TIMES(:,:) = NUNDEF
 ILUOUT = TLUOUT%NLU
 !
@@ -349,58 +344,57 @@ ILUOUT = TLUOUT%NLU
 !              --------------------------
 !
 DO JCI=1,NCPL_NBR
-  WRITE(YCI,'(I2.0)') JCI
+  WRITE(YCI,'(I0)') JCI
   CALL IO_File_add2list(TCPLFILE(JCI)%TZFILE,CCPLFILE(JCI),'MNH','READ',KLFITYPE=2,KLFIVERB=NVERB)
   CALL IO_File_open(TCPLFILE(JCI)%TZFILE,KRESP=IRESP)
   IF (IRESP /= 0) THEN
-    CALL PRINT_MSG(NVERB_FATAL,'IO','INI_CPL','problem when opening coupling file '//TRIM(YCI))
+    WRITE( CMNHMSG(1), '( "problem when opening coupling file ", I0 )' ) JCI
+    CALL PRINT_MSG( NVERB_ERROR, 'IO', 'INI_CPL' )
+    GSKIP(JCI) = .TRUE.
+    CYCLE
   END IF
 !
 !*       2.1   Read current time in coupling files
 !
-  CALL IO_Field_read(TCPLFILE(JCI)%TZFILE,'DTCUR',TDTCPL(JCI))
+  CALL IO_Field_read(TCPLFILE(JCI)%TZFILE,'DTCUR',TZDTCPL(JCI))
 !
 !*       2.2   Check chronological order
 !
-  CALL DATETIME_DISTANCE(TDTCUR,TDTCPL(JCI),ZDIST)
+  ZDIST = TZDTCPL(JCI) - TDTCUR
   !
-  IF ( ZDIST <=0. ) THEN
+  IF ( ZDIST <= 0. ) THEN
     WRITE(ILUOUT,FMT=9002) 1
     WRITE(ILUOUT,*) 'YOUR COUPLING FILE ',JCI,' IS PREVIOUS TO THE DATE &
                & CORRESPONDING TO THE BEGINNING OF THE SEGMENT. IT WILL &
                & NOT BE TAKEN INTO ACCOUNT.'
     YTITLE='CURRENT DATE AND TIME IN THE INITIAL FILE'
     CALL SM_PRINT_TIME(TDTCUR,TLUOUT,YTITLE)
-    YTITLE='CURRENT DATE AND TIME OF THE FILE'//YCI
-    CALL SM_PRINT_TIME(TDTCPL(JCI),TLUOUT,YTITLE)
+    YTITLE='CURRENT DATE AND TIME OF THE FILE '//YCI
+    CALL SM_PRINT_TIME(TZDTCPL(JCI),TLUOUT,YTITLE)
+    CALL PRINT_MSG( NVERB_ERROR, 'GEN', 'INI_CPL', '' )
     GSKIP(JCI)=.TRUE.      ! flag to skip after this coupling file
-    CALL PRINT_MSG(NVERB_FATAL,'GEN','INI_CPL','')      
   ELSE
     NCPL_TIMES(JCI,1) = NINT( ZDIST / PTSTEP ) + 2
   END IF
   !
+  ! Check that the coupling files are in chronological order
   IF (JCI > 1) THEN
-    CALL DATETIME_DISTANCE(TDTCPL(JCI-1),TDTCPL(JCI),ZDIST)
+    ZDIST = TZDTCPL(JCI) - TZDTCPL(JCI)
     !
     IF ( ZDIST < 0. ) THEN
       WRITE(ILUOUT,FMT=9003) 1
       WRITE(ILUOUT,*) 'YOU MUST SPECIFY THE COUPLING FILES IN A CHRONOLOGICAL &
                        & ORDER'
-      YTITLE='CURRENT DATE AND TIME OF THE FILE'//YCI
-      CALL SM_PRINT_TIME(TDTCPL(JCI),TLUOUT,YTITLE)
-      WRITE(YCI,'(I2.0)') JCI-1        
-      YTITLE='CURRENT DATE AND TIME OF THE FILE'//YCI
-      CALL SM_PRINT_TIME(TDTCPL(JCI-1),TLUOUT,YTITLE)
-      GEND=.TRUE.           ! error flag set to true
+      YTITLE='CURRENT DATE AND TIME OF THE FILE '//YCI
+      CALL SM_PRINT_TIME(TZDTCPL(JCI),TLUOUT,YTITLE)
+      WRITE(YCI,'(I0)') JCI-1
+      YTITLE='CURRENT DATE AND TIME OF THE FILE '//YCI
+      CALL SM_PRINT_TIME(TZDTCPL(JCI-1),TLUOUT,YTITLE)
       CALL PRINT_MSG(NVERB_FATAL,'GEN','INI_CPL','')      
     END IF
   !   
   END IF
 END DO
-!  exit when a fatal error has been encountered
-IF ( GEND ) THEN
-  RETURN
-END IF
 !
 !*       2.3   Find the current coupling file and the last one
 !
@@ -427,7 +421,7 @@ IF (ICPLEND==NCPL_NBR .AND. NCPL_TIMES(NCPL_NBR,1) < KSTOP) THEN
   WRITE(ILUOUT,*) 'PLEASE, REFER TO THE USER GUIDE TO OBTAIN MORE INFORMATIONS'
   WRITE(ILUOUT,*) 'ON THE TEMPORAL GRID.'
   YTITLE='CURRENT DATE AND TIME OF THE LAST FILE'
-  CALL SM_PRINT_TIME(TDTCPL(NCPL_NBR),TLUOUT,YTITLE)
+  CALL SM_PRINT_TIME(TZDTCPL(NCPL_NBR),TLUOUT,YTITLE)
   YTITLE='DATE AND TIME OF THE BEGINNING OF THE SEGMENT YOU WANT TO BE PERFORMED'
   CALL SM_PRINT_TIME(TDTCUR,TLUOUT,YTITLE)
   WRITE(ILUOUT,*) 'XSEGLEN = ', XSEGLEN 
@@ -525,11 +519,7 @@ CALL IO_File_close(TCPLFILE(NCPL_CUR)%TZFILE)
 !*      6.    FORMATS
 !             -------
 !
-9000  FORMAT(/,'NOTE  IN INI_CPL FOR MODEL ', I2, ' : ',/, &
-             '--------------------------------')
-9001  FORMAT(/,'CAUTION ERROR IN INI_CPL FOR MODEL ', I2,' : ',/, &
-             '----------------------------------------' )
-9002  FORMAT(/,'WARNING IN INI_CPL FOR MODEL ', I2,' : ',/, &
+9002  FORMAT(/,'ERROR IN INI_CPL FOR MODEL ', I2,' : ',/, &
              '----------------------------------' )
 9003  FORMAT(/,'FATAL ERROR IN INI_CPL FOR MODEL ', I2,' : ',/, &
              '--------------------------------------' )
diff --git a/src/MNH/ini_segn.f90 b/src/MNH/ini_segn.f90
index e086a5757ecd1ea24926319fb754962956310717..ab8d86ea096c12575ee7714d3c8561db88272bc8 100644
--- a/src/MNH/ini_segn.f90
+++ b/src/MNH/ini_segn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -327,7 +327,7 @@ CALL POSNAM( TZFILE_DES, 'NAM_LUNITN', GFOUND )
 IF (GFOUND) THEN
   CALL INIT_NAM_LUNITn
   READ(UNIT=ILUSEG,NML=NAM_LUNITn)
-  CALL UPDATE_NAM_LUNITn
+  CALL UPDATE_NAM_LUNITn(KMI)
   IF (LEN_TRIM(CINIFILEPGD)==0 .AND. CSURF=='EXTE') THEN
     !callabortstop
     CALL PRINT_MSG(NVERB_FATAL,'GEN','INI_SEG_n','error in namelist NAM_LUNITn: you need to specify CINIFILEPGD')
diff --git a/src/MNH/ini_spawn_lsn.f90 b/src/MNH/ini_spawn_lsn.f90
index 3e31fdc9bb522c60f03c41674d8d2fdb8d1fceef..7a291f256bb15ebd66497a0c596af9b1e8727493 100644
--- a/src/MNH/ini_spawn_lsn.f90
+++ b/src/MNH/ini_spawn_lsn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1997-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1997-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -114,7 +114,7 @@ END MODULE MODI_INI_SPAWN_LS_n
 !!       Function   MZF,MXM,MYM   : averages operators
 !!    IMPLICIT ARGUMENTS
 !!    ------------------
-!!      Module MODD_PARAMETERS: JPHEXT,JPVEXT,JPCPLFILEMAX
+!!      Module MODD_PARAMETERS: JPHEXT,JPVEXT
 !!
 !!      Module MODD_DYN: XTSTEP_MODEL1,NCPL_TIMES
 !!
@@ -347,7 +347,7 @@ IF ( GVERT_INTERP ) THEN
 END IF
 !
 IF ( SIZE(PLSTHS,1) /= 0 ) THEN
-  DO JI=1,JPCPLFILEMAX
+  DO JI = 1, SIZE( NCPL_TIMES, DIM=1 )
     IF ( NCPL_TIMES(JI,1) /= NUNDEF ) THEN
       NCPL_TIMES(JI,KMI) =  NINT( ((NCPL_TIMES(JI,1)-2)*XTSTEP_MODEL1)   &
                  / PTSTEP ) + 2
diff --git a/src/MNH/modd_dyn.f90 b/src/MNH/modd_dyn.f90
index 244a67f95a1145e3ffc00102a82b4285d18cba98..b4d85475fda48fc9e8609b3770cf98f79fd3dd72 100644
--- a/src/MNH/modd_dyn.f90
+++ b/src/MNH/modd_dyn.f90
@@ -1,14 +1,8 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt  
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$ $Date$
-!-----------------------------------------------------------------
-!-----------------------------------------------------------------
-!-----------------------------------------------------------------
 !     ################
       MODULE MODD_DYN
 !     ################
@@ -79,8 +73,8 @@ LOGICAL, SAVE, DIMENSION(JPMODELMAX) :: LUSERV_G, LUSERC_G, LUSERR_G, LUSERI_G
 LOGICAL, SAVE, DIMENSION(JPMODELMAX) :: LUSERS_G, LUSERH_G, LUSERG_G
 LOGICAL, SAVE, DIMENSION(JPMODELMAX) :: LUSETKE
 LOGICAL, SAVE, DIMENSION(JPSVMAX,JPMODELMAX) :: LUSESV
-REAL,    SAVE, DIMENSION(JPCPLFILEMAX,JPMODELMAX)          :: NCPL_TIMES   ! array of
-                ! the number for the coupling instants of every nested model
+REAL,    SAVE, DIMENSION(:,:), ALLOCATABLE :: NCPL_TIMES ! array of the timestep numbers for the coupling instants
+                                                         ! for each nested model
 REAL,    SAVE                       :: XTSTEP_MODEL1  ! time step of the
                                                       ! outermost model
 END MODULE MODD_DYN
diff --git a/src/MNH/modd_lunitn.f90 b/src/MNH/modd_lunitn.f90
index f6e78680445ac5c0e10a5cfca0acc637ea53d244..0b4fafb18772431fca14675d9bec148abd4492a8 100644
--- a/src/MNH/modd_lunitn.f90
+++ b/src/MNH/modd_lunitn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -43,10 +43,12 @@
 !
 !
 USE MODD_IO,         ONLY: TFILEDATA, TPTR2FILE
-USE MODD_PARAMETERS, ONLY: JPMODELMAX, JPCPLFILEMAX, NFILENAMELGTMAX
+USE MODD_PARAMETERS, ONLY: JPMODELMAX, NFILENAMELGTMAX
 
 IMPLICIT NONE
 
+INTEGER, PARAMETER :: NPCPLFILEMAX = 1000 ! Maximum allowed number of CouPLing FILEs
+
 TYPE LUNIT_t
 ! 
   CHARACTER(LEN=NFILENAMELGTMAX) :: CINIFILE = 'INIFILE'    ! Name of the input FM-file
@@ -83,8 +85,8 @@ INTEGER, INTENT(IN) :: KFROM, KTO
 !
 !JUAN
 IF (LUNIT_FIRST_CALL(KTO)) THEN
-ALLOCATE (LUNIT_MODEL(KTO)%CCPLFILE(JPCPLFILEMAX))
-ALLOCATE (LUNIT_MODEL(KTO)%TCPLFILE(JPCPLFILEMAX))
+ALLOCATE (LUNIT_MODEL(KTO)%CCPLFILE(NPCPLFILEMAX))
+ALLOCATE (LUNIT_MODEL(KTO)%TCPLFILE(NPCPLFILEMAX))
 LUNIT_FIRST_CALL(KTO) = .FALSE.
 ENDIF
 !JUAN
diff --git a/src/MNH/modd_parameters.f90 b/src/MNH/modd_parameters.f90
index 0e378863e4a99efa0634a49c9a86c21fdde2077c..d8083f24c608f253c3c638589c303ff096214564 100644
--- a/src/MNH/modd_parameters.f90
+++ b/src/MNH/modd_parameters.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -59,7 +59,6 @@ INTEGER,SAVE      :: JPHEXT = 1     ! Horizontal External points number
 INTEGER, PARAMETER :: JPVEXT = 1      ! Vertical External points number
 INTEGER, PARAMETER :: JPVEXT_TURB = 1      ! Vertical External points number
 INTEGER, PARAMETER :: JPMODELMAX = 8  ! Maximum allowed number of nested models 
-INTEGER, PARAMETER :: JPCPLFILEMAX = 24 ! Maximum allowed number of CouPLing FILEs
 INTEGER, PARAMETER :: JPRIMMAX = 6    ! Maximum number of points for the
                        ! horizontal relaxation for the outermost verticals
 INTEGER, PARAMETER :: JPSVMAX  = 200  ! Maximum number of scalar variables
diff --git a/src/MNH/modd_time.f90 b/src/MNH/modd_time.f90
index 77cf747d666fd48596600c52406fe5b337835d65..b1752e05bb7149dc90e2b736d085b0907ee88062 100644
--- a/src/MNH/modd_time.f90
+++ b/src/MNH/modd_time.f90
@@ -1,13 +1,8 @@
-!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt  
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
-!--------------- special set of characters for RCS information
-!-----------------------------------------------------------------
-! $Source$ $Revision$
-! MASDEV4_7 modd 2006/05/18 13:07:25
-!-----------------------------------------------------------------
 !     #################
       MODULE MODD_TIME
 !     #################
@@ -35,7 +30,6 @@
 !!    MODIFICATIONS
 !!    -------------
 !!      Original    07/07/94                      
-!!      Modification 10/03/95 (I.Mallet)   add the coupling times
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
@@ -50,6 +44,4 @@ IMPLICIT NONE
 TYPE (DATE_TIME), SAVE :: TDTEXP      ! Time and Date of Experiment beginning 
 TYPE (DATE_TIME), SAVE :: TDTSEG      ! Time and Date of the  segment beginning 
 !
-TYPE (DATE_TIME), SAVE, DIMENSION(JPCPLFILEMAX) :: TDTCPL ! Time and Date of 
-                                                          ! the CouPLing files
 END MODULE MODD_TIME
diff --git a/src/MNH/modn_lunitn.f90 b/src/MNH/modn_lunitn.f90
index 019714869bb43ed8235776948e4a558296e56c53..a498e3694a8a134acb98277f8979a5c87724999c 100644
--- a/src/MNH/modn_lunitn.f90
+++ b/src/MNH/modn_lunitn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -38,33 +38,94 @@
 !*       0.   DECLARATIONS
 !             ------------
 !
-USE MODD_PARAMETERS, ONLY: JPCPLFILEMAX, NFILENAMELGTMAX
+USE MODD_PARAMETERS, ONLY: NFILENAMELGTMAX
 USE MODD_LUNIT_n,    ONLY: CINIFILE_n    => CINIFILE,    &
                            CINIFILEPGD_n => CINIFILEPGD, &
-                           CCPLFILE_n    => CCPLFILE
+                           CCPLFILE_n    => CCPLFILE,    &
+                           NPCPLFILEMAX
 !
 IMPLICIT NONE
 !
 SAVE
 !
-CHARACTER(LEN=NFILENAMELGTMAX)                          :: CINIFILE
-CHARACTER(LEN=NFILENAMELGTMAX)                          :: CINIFILEPGD
-CHARACTER(LEN=NFILENAMELGTMAX), DIMENSION(JPCPLFILEMAX) :: CCPLFILE
+CHARACTER(LEN=NFILENAMELGTMAX)                            :: CINIFILE
+CHARACTER(LEN=NFILENAMELGTMAX)                            :: CINIFILEPGD
+CHARACTER(LEN=NFILENAMELGTMAX), DIMENSION(:), ALLOCATABLE :: CCPLFILE
 !
 NAMELIST/NAM_LUNITn/CINIFILE,CINIFILEPGD,CCPLFILE
 !
 CONTAINS
 !
-SUBROUTINE INIT_NAM_LUNITn
+SUBROUTINE INIT_NAM_LUNITn( OWRITE )
+  LOGICAL, OPTIONAL, INTENT(IN) :: OWRITE
+
+  CHARACTER(LEN=NFILENAMELGTMAX), DIMENSION(:), ALLOCATABLE :: YCPLFILE_TMP
+  LOGICAL :: GWRITE
+
+  IF ( PRESENT(OWRITE) ) THEN
+    GWRITE = OWRITE
+  ELSE
+    GWRITE = .FALSE.
+  END IF
+
   CINIFILE = CINIFILE_n
-  CINIFILEPGD = CINIFILEPGD_n  
-  CCPLFILE = CCPLFILE_n
+  CINIFILEPGD = CINIFILEPGD_n
+
+  ! Reallocate CCPLFILE_n to the NPCPLFILEMAX size (necessary to read again/decompact)
+  ! if write: keep the compact version (in that case, we assume that CCPLFILE_n is already associated)
+  IF ( .NOT.GWRITE) THEN
+    IF ( ASSOCIATED(CCPLFILE_n) ) THEN
+      ALLOCATE( YCPLFILE_TMP, SOURCE = CCPLFILE_n ) ! sourced allocation, YCPLFILE_TMP is allocated to a clone of CCPLFILE_N
+      DEALLOCATE( CCPLFILE_n )
+    ELSE
+      ALLOCATE( CHARACTER(LEN=NFILENAMELGTMAX) :: YCPLFILE_TMP(NPCPLFILEMAX) )
+      YCPLFILE_TMP(:) = ''
+    END IF
+
+    ALLOCATE( CHARACTER(LEN=NFILENAMELGTMAX) :: CCPLFILE_n(NPCPLFILEMAX) )
+    CCPLFILE_n(1:SIZE(YCPLFILE_TMP)) = YCPLFILE_TMP(:)
+    IF ( SIZE(YCPLFILE_TMP) < SIZE(CCPLFILE_n) ) CCPLFILE_n(SIZE(YCPLFILE_TMP)+1:) = ''
+  END IF
+
+  IF ( ALLOCATED( CCPLFILE ) ) DEALLOCATE( CCPLFILE )
+  ALLOCATE( CCPLFILE, SOURCE = CCPLFILE_N ) ! sourced allocation, CCPLFILE is allocated to a clone of CCPLFILE_N
 END SUBROUTINE INIT_NAM_LUNITn
 
-SUBROUTINE UPDATE_NAM_LUNITn
+SUBROUTINE UPDATE_NAM_LUNITn(KMI)
+  USE MODD_DYN, ONLY: NCPL_NBR
+
+  INTEGER, INTENT(IN) :: KMI ! Model number
+
+  CHARACTER(LEN=NFILENAMELGTMAX), DIMENSION(:), ALLOCATABLE :: YCPLFILE_TMP
+  INTEGER :: ICPL_NBR
+  INTEGER :: JCI
+
   CINIFILE_n = CINIFILE
-  CINIFILEPGD_n = CINIFILEPGD  
-  CCPLFILE_n = CCPLFILE
+  CINIFILEPGD_n = CINIFILEPGD
+
+  ! Compress the coupling file list + find the number of coupling files
+  ICPL_NBR = 0
+  DO JCI = 1, SIZE(CCPLFILE)
+    IF ( LEN_TRIM(CCPLFILE(JCI)) /= 0 ) THEN
+      ICPL_NBR = ICPL_NBR + 1
+      IF ( JCI /= ICPL_NBR ) THEN
+        CCPLFILE(ICPL_NBR) = CCPLFILE(JCI)
+        CCPLFILE(JCI) = ''
+      END IF
+    END IF
+  END DO
+
+  ALLOCATE( CHARACTER(LEN=NFILENAMELGTMAX) :: YCPLFILE_TMP(ICPL_NBR) )
+  YCPLFILE_TMP(:) = CCPLFILE(1:ICPL_NBR)
+  CALL MOVE_ALLOC( FROM = YCPLFILE_TMP, TO = CCPLFILE )
+
+  ! NCPL_NBR is only for the outermost model
+  IF ( KMI == 1 ) NCPL_NBR = ICPL_NBR
+
+  ! Reallocate CCPLFILE_n because CCPLFILE could have been reallocated (and resized/compacted)
+  DEALLOCATE( CCPLFILE_n )
+  ALLOCATE( CCPLFILE_n, SOURCE = CCPLFILE ) ! sourced allocation, CCPLFILE_n is allocated to a clone of CCPLFILE
+
 END SUBROUTINE UPDATE_NAM_LUNITn
 
 END MODULE MODN_LUNIT_n
diff --git a/src/MNH/read_desfmn.f90 b/src/MNH/read_desfmn.f90
index e556cdf016d37b3dca6cdb0d5a722e59b60c259e..072a5fb79ded567a553b82e07863eaa2afd64aea 100644
--- a/src/MNH/read_desfmn.f90
+++ b/src/MNH/read_desfmn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -360,8 +360,8 @@ CALL POSNAM( TZDESFILE, 'NAM_LUNITN', GFOUND )
 CALL INIT_NAM_LUNITN
 IF (GFOUND) THEN 
   READ(UNIT=ILUDES,NML=NAM_LUNITn)
-  CALL UPDATE_NAM_LUNITN
 END IF
+CALL UPDATE_NAM_LUNITN(KMI)
 CALL POSNAM( TZDESFILE, 'NAM_CONFN', GFOUND )
 CALL INIT_NAM_CONFN
 IF (GFOUND) THEN 
diff --git a/src/MNH/read_exsegn.f90 b/src/MNH/read_exsegn.f90
index 9d3ee4b520c60bc620b8522c6238dec2802abac7..4fc0ef4ee94eafd4e6b33202ca56c2bb89b3bb80 100644
--- a/src/MNH/read_exsegn.f90
+++ b/src/MNH/read_exsegn.f90
@@ -480,7 +480,7 @@ CHARACTER (LEN=NFILENAMELGTMAX), INTENT(IN) :: HINIFILEPGD ! name of PGD file
 !
 CHARACTER(LEN=3) :: YMODEL
 INTEGER :: ILUSEG,ILUOUT ! logical unit numbers of EXSEG file and outputlisting
-INTEGER :: JS,JCI,JI,JSV       ! Loop indexes 
+INTEGER :: JS,JI,JSV       ! Loop indexes
 LOGICAL :: GRELAX              
 LOGICAL :: GFOUND              ! Return code when searching namelist
 !
@@ -2476,33 +2476,7 @@ END IF
 !
 !*       4.    CHECK COHERENCE BETWEEN EXSEG VARIABLES
 !              ---------------------------------------
-!        
-!*       4.1  coherence between coupling variables in EXSEG file  
-!                      
-IF (KMI == 1) THEN
-  NCPL_NBR = 0
-  DO JCI = 1,JPCPLFILEMAX
-    IF (LEN_TRIM(CCPLFILE(JCI)) /= 0) THEN        ! Finds the number 
-      NCPL_NBR = NCPL_NBR + 1                     ! of coupling files
-    ENDIF
-    IF (JCI/=JPCPLFILEMAX) THEN                   ! Deplaces the coupling files
-      IF ((LEN_TRIM(CCPLFILE(JCI)) == 0) .AND.   &! names if one missing
-          (LEN_TRIM(CCPLFILE(JCI+1)) /= 0)) THEN
-        DO JI=JCI,JPCPLFILEMAX-1
-          CCPLFILE(JI)=CCPLFILE(JI+1)
-        END DO
-        CCPLFILE(JPCPLFILEMAX)=''
-      END IF
-    END IF
-  END DO
 !
-  IF (NCPL_NBR /= 0) THEN         
-    LSTEADYLS = .FALSE.
-  ELSE
-    LSTEADYLS = .TRUE.
-  ENDIF 
-END IF
-!        
 !*       4.3   check consistency in forcing switches
 !
 IF ( LFORCING ) THEN
@@ -3109,7 +3083,14 @@ END IF
 !*       5.    WE DO NOT FORGET TO UPDATE ALL DOLLARN NAMELIST VARIABLES
 !              ---------------------------------------------------------
 !
-CALL UPDATE_NAM_LUNITN
+CALL UPDATE_NAM_LUNITN(KMI)
+IF ( KMI == 1 ) THEN
+  IF (NCPL_NBR /= 0) THEN !To be done after UPDATE_NAM_LUNITN
+    LSTEADYLS = .FALSE.
+  ELSE
+    LSTEADYLS = .TRUE.
+  END IF
+END IF
 CALL UPDATE_NAM_CONFN
 CALL UPDATE_NAM_DRAGTREEN
 CALL UPDATE_NAM_DRAGBLDGN
diff --git a/src/MNH/read_pre_idea_namn.f90 b/src/MNH/read_pre_idea_namn.f90
index b80718cde2332badec8b71e40ab446bafe2c3119..b63def8efe1018b8b74ef0ae90eac0c17a94db79 100644
--- a/src/MNH/read_pre_idea_namn.f90
+++ b/src/MNH/read_pre_idea_namn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -91,7 +91,7 @@ CALL POSNAM( TPFILEPRE, 'NAM_LUNITN', GFOUND )
 IF (GFOUND) THEN 
   CALL INIT_NAM_LUNITn 
   READ(UNIT=ILUPRE,NML=NAM_LUNITn)
-  CALL UPDATE_NAM_LUNITn
+  CALL UPDATE_NAM_LUNITn(1)
 END IF
 
 !------------------------------------------------------------------------------
diff --git a/src/MNH/write_desfmn.f90 b/src/MNH/write_desfmn.f90
index 50210c832df24a366f4c738aeebce932e7c8f49d..f227e237e4876086145593530972bfe5546e93c3 100644
--- a/src/MNH/write_desfmn.f90
+++ b/src/MNH/write_desfmn.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2023 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt  
 !MNH_LIC for details. version 1.
@@ -258,7 +258,7 @@ IF (.NOT.ASSOCIATED(TPDATAFILE%TDESFILE)) &
 !
 ILUSEG = TPDATAFILE%TDESFILE%NLU
 !
-CALL INIT_NAM_LUNITn
+CALL INIT_NAM_LUNITn( OWRITE=.TRUE. )
 WRITE(UNIT=ILUSEG,NML=NAM_LUNITn)
 IF (CPROGRAM/='MESONH') THEN
   LUSECI=.FALSE.