diff --git a/src/MNH/default_desfmn.f90 b/src/MNH/default_desfmn.f90
index 6ec7ad809f8020b5f2f758d3d6e9ae805e9a7abf..618f2611ae98c9b8bdc6858de97e3fe99880efd6 100644
--- a/src/MNH/default_desfmn.f90
+++ b/src/MNH/default_desfmn.f90
@@ -219,6 +219,7 @@ END MODULE MODI_DEFAULT_DESFM_n
 !!                    10/2016 (C.Lac) Add droplet deposition
 !!                   10/2016  (R.Honnert and S.Riette) : Improvement of EDKF and adaptation to the grey zone
 !!                   10/2016  (F Brosse) add prod/loss terms computation for chemistry
+!!                   07/2017  (V. Masson) adds time step for output files writing.
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -492,7 +493,10 @@ XTNUDGING = 21600.
 !*      9.    SET DEFAULT VALUES FOR MODD_FMOUT and MODD_OUT_n :
 !             ------------------------------------------------
 !
-IF (KMI == 1) XFMOUT (:,:) = XUNDEF
+IF (KMI == 1) THEN
+  XFMOUT (:,:) = XUNDEF
+  XTSTEP_OUTPUT = XUNDEF
+END IF
 !
 !
 !-------------------------------------------------------------------------------
diff --git a/src/MNH/modd_fmout.f90 b/src/MNH/modd_fmout.f90
index 23a3613585af574e224fede1b36ea89d2513a581..108233c5152e75cece666d48e014ddf45978f580 100644
--- a/src/MNH/modd_fmout.f90
+++ b/src/MNH/modd_fmout.f90
@@ -38,6 +38,7 @@
 !!    MODIFICATIONS
 !!    -------------
 !!      Original    26/07/96                     
+!!                   07/2017  (V. Masson) adds time step for output files writing.
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
@@ -47,6 +48,7 @@ USE MODD_PARAMETERS
 !
 IMPLICIT NONE
 !
+REAL                                       ::   XTSTEP_OUTPUT   ! constant timestep during each output
 REAL,SAVE, DIMENSION(JPMODELMAX,JPOUTMAX)  ::   XFMOUT    ! XFMOUT(m,i) array of 
 ! the increments in seconds from the beginning of the segment to the
 ! instant where the i-th fields output on FM-files is realized by model "m"
diff --git a/src/MNH/modn_fmout.f90 b/src/MNH/modn_fmout.f90
index 2168e596643d2b90d97bf6254a7829018d449dcd..dc5d6c608a4dde1ed5110128431cc73d4df11f6c 100644
--- a/src/MNH/modn_fmout.f90
+++ b/src/MNH/modn_fmout.f90
@@ -39,6 +39,7 @@
 !!    MODIFICATIONS
 !!    -------------
 !!      Original    26/07/96                      
+!!                   07/2017  (V. Masson) adds time step for output files writing.
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
@@ -48,6 +49,6 @@ USE MODD_FMOUT
 !
 IMPLICIT NONE
 !
-NAMELIST/NAM_FMOUT/XFMOUT
+NAMELIST/NAM_FMOUT/XFMOUT, XTSTEP_OUTPUT
 !
 END MODULE MODN_FMOUT
diff --git a/src/MNH/set_grid.f90 b/src/MNH/set_grid.f90
index e96bab6072ad186132c6ab4c36661005b8ec6c3f..ceaf6f3d0ad30f39cb6d8ef1ede7e556105dc98a 100644
--- a/src/MNH/set_grid.f90
+++ b/src/MNH/set_grid.f90
@@ -231,6 +231,7 @@ END MODULE MODI_SET_GRID
 !!      J. STEIN    01/02/99  change the orography at the boundary for the
 !!                            grid-nesting lbc
 !!     V.MASSON 12/10/00 read of the orography in all cases, even if LFLAT=T
+!!     V. MASSON     07/2017  adds time step for output files writing.
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -514,6 +515,15 @@ KSTOP = NINT(PSEGLEN/PTSTEP)
 !
 !*       2.3    Temporal grid - outputs managment
 !
+!*       2.3.0  case of regular temporal outputs: initializes XFMOUT arrays (MODD_FMOUT)
+!
+IF (XTSTEP_OUTPUT /= XUNDEF .AND. XTSTEP_OUTPUT>0.) THEN
+  XFMOUT(:,:) = XUNDEF
+  DO JOUT=1,NINT(PSEGLEN/XTSTEP_OUTPUT)
+    XFMOUT(:,JOUT) = JOUT*XTSTEP_OUTPUT
+  END DO
+END IF
+!
 !*       2.3.1  a) synchronization between nested models through XFMOUT arrays (MODD_FMOUT)
 !
 DO JOUT = 1,JPOUTMAX