diff --git a/src/LIB/SURCOUCHE/src/mode_io_file.f90 b/src/LIB/SURCOUCHE/src/mode_io_file.f90
index 6ed3a03c255e7690965e101065a6892fee7c1d7c..663059f07193f44eb708c9ee48604c4460cddd2c 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_file.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_file.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 1994-2022 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 1994-2023 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.
@@ -39,6 +39,7 @@
 !  P. Wautelet 05/09/2019: disable IO_Coordvar_write_nc4 for Z-split files
 !  P. Wautelet 01/10/2020: bugfix: add missing initializations for IRESP
 !  P. Wautelet 19/08/2022: bugfix: IO_File_check_format_exist: broadcast cformat if changed
+!  P. Wautelet 13/01/2023: IO_File_close: add optional dummy argument TPDTMODELN to force written model time
 !-----------------------------------------------------------------
 module mode_io_file
 
@@ -492,10 +493,11 @@ END FUNCTION SUFFIX
 END SUBROUTINE IO_File_doopen
 
 
-recursive SUBROUTINE IO_File_close(TPFILE,KRESP,HPROGRAM_ORIG)
+recursive SUBROUTINE IO_File_close( TPFILE, KRESP, HPROGRAM_ORIG, TPDTMODELN )
 !
 use modd_conf,             only: cprogram
 use modd_io,               only: nnullunit
+use modd_type_date,        only: date_time
 
 use mode_io_file_lfi,      only: IO_File_close_lfi
 #ifdef MNH_IOCDF4
@@ -507,7 +509,7 @@ use mode_io_manage_struct, only: IO_File_find_byname
 TYPE(TFILEDATA),            INTENT(INOUT) :: TPFILE ! File structure
 INTEGER,          OPTIONAL, INTENT(OUT)   :: KRESP  ! Return code
 CHARACTER(LEN=*), OPTIONAL, INTENT(IN)    :: HPROGRAM_ORIG !To emulate a file coming from this program
-!
+TYPE(DATE_TIME),  OPTIONAL, INTENT(IN)    :: TPDTMODELN    !Time of model (to force model date written in file)
 character(len=256)      :: yioerrmsg
 INTEGER                 :: IRESP, JI
 TYPE(TFILEDATA),POINTER :: TZFILE_DES
@@ -565,7 +567,7 @@ SELECT CASE(TPFILE%CTYPE)
 #ifdef MNH_IOCDF4
     !Write coordinates variables in NetCDF file
     IF (TPFILE%CMODE == 'WRITE' .AND. (TPFILE%CFORMAT=='NETCDF4' .OR. TPFILE%CFORMAT=='LFICDF4')) THEN
-      CALL IO_Coordvar_write_nc4(TPFILE,HPROGRAM_ORIG=HPROGRAM_ORIG)
+      CALL IO_Coordvar_write_nc4( TPFILE, HPROGRAM_ORIG = HPROGRAM_ORIG, TPDTMODELN = TPDTMODELN )
     END IF
 #endif
 
diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
index 1858061aca8c64004e509568935f9ab6ebd00d24..f91733cddbe8dd78fce9e7f7af08cc3648080449 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
@@ -31,6 +31,7 @@
 !  P. Wautelet 22/03/2022: correct time_les_avg and time_les_avg_bounds coordinates
 !  P. Wautelet    06/2022: reorganize flyers
 !  P. Wautelet 21/06/2022: bugfix: time_budget was not computed correctly (tdtexp -> tdtseg)
+!  P. Wautelet 13/01/2023: IO_Coordvar_write_nc4: add optional dummy argument TPDTMODELN to force written model time
 !-----------------------------------------------------------------
 #ifdef MNH_IOCDF4
 module mode_io_write_nc4
@@ -1429,7 +1430,7 @@ if ( Present( kvertlevel ) ) deallocate( tzfield )
 end subroutine IO_Field_partial_write_nc4_N4
 
 
-subroutine IO_Coordvar_write_nc4( tpfile, hprogram_orig )
+subroutine IO_Coordvar_write_nc4( tpfile, hprogram_orig, tpdtmodeln )
 use modd_aircraft_balloon
 use modd_budget,     only: cbutype, lbu_icp, lbu_jcp, lbu_kcp, nbuih, nbuil, nbujh, nbujl, nbukh, nbukl, nbukmax, &
                            nbustep, nbutotwrite
@@ -1472,6 +1473,7 @@ use mode_nest_ll,    only: Get_model_number_ll, Go_tomodel_ll
 
 type(tfiledata),            intent(in) :: tpfile
 character(len=*), optional, intent(in) :: hprogram_orig !To emulate a file coming from this program
+type(date_time),  optional, intent(in) :: tpdtmodeln    !Time of model (to force model date written in file)
 
 character(len=:),                         allocatable :: ystdnameprefix
 character(len=:),                         allocatable :: yprogram
@@ -1661,8 +1663,13 @@ END IF
 if ( tpfile%lmaster ) then !time scale is the same on all processes
   if ( Trim( yprogram ) /= 'PGD' .and. Trim( yprogram ) /= 'NESPGD' .and. Trim( yprogram ) /= 'ZOOMPG' &
       .and. .not. ( Trim( yprogram ) == 'REAL' .and. cstorage_type == 'SU' ) ) then !condition to detect prep_surfex
-    if ( tpfile%ctype /= 'MNHDIACHRONIC' .and. Associated( tdtcur ) ) &
-      call Write_time_coord( tpfile%tncdims%tdims(nmnhdim_time), 'time axis', [ tdtcur ] )
+    if ( tpfile%ctype /= 'MNHDIACHRONIC' ) then
+      if ( Present( tpdtmodeln ) ) then
+        call Write_time_coord( tpfile%tncdims%tdims(nmnhdim_time), 'time axis', [ tpdtmodeln ] )
+      else if ( Associated( tdtcur ) ) then
+        call Write_time_coord( tpfile%tncdims%tdims(nmnhdim_time), 'time axis', [ tdtcur ] )
+      end if
+    end if
   end if
 end if