diff --git a/fort.90 b/fort.90
index fb603223a921e3028196463bb54b46357c2ccbe6..e0d2e31b38d8ce82e8c7d26c916b38ccaa432791 100644
--- a/fort.90
+++ b/fort.90
@@ -1,5 +1,5 @@
 &BASIC
-  nrun       = 99999999
+  nrun       = 1e6
   dt         = 0.01
   tmax       = 50
   maxruntime = 72000
@@ -45,6 +45,7 @@
   write_dens  = .t.
   write_fvel  = .t.
   write_temp  = .t.
+  !diag_mode   = 'txtonly'
 /
 &MODEL_PAR
   LINEARITY = 'nonlinear'
diff --git a/src/diagnose.F90 b/src/diagnose.F90
index 271e7e8931c359a3c725e87acfaaf48e55c65e0f..7973aa3ce4403fc1d6ac6eadf2f14cdfb67de1f4 100644
--- a/src/diagnose.F90
+++ b/src/diagnose.F90
@@ -1,7 +1,7 @@
 SUBROUTINE diagnose(kstep)
   !   Diagnostics, writing simulation state to disk
   USE basic,           ONLY: lu_in, chrono_runt, cstep, dt, time, tmax, display_h_min_s
-  USE diagnostics_par, ONLY: input_fname
+  USE diagnostics_par, ONLY: input_fname, diag_mode
   USE processing,      ONLY: pflux_x, hflux_x
   USE parallel,        ONLY: my_id
   IMPLICIT NONE
@@ -15,12 +15,15 @@ SUBROUTINE diagnose(kstep)
   IF (kstep .EQ. -1) THEN
      ! Display total run time
      CALL display_h_min_s(chrono_runt%ttot)
-     ! Show last state transport values
-     IF (my_id .EQ. 0) &
-      WRITE(*,"(A,G10.2,A8,G10.2,A)") 'Final transport values : | Gxi = ',pflux_x(1),'| Qxi = ',hflux_x(1),'|'
   END IF
   !! Specific diagnostic calls
-  CALL diagnose_full(kstep)
+  SELECT CASE(diag_mode)
+  CASE('full')
+    CALL diagnose_full(kstep)
+  CASE('txtonly')
+    CALL diagnose_txtonly(kstep)
+  END SELECT
+
   ! Terminal info
   IF ((kstep .GE. 0) .AND. (MOD(cstep, INT(1.0/dt)) == 0) .AND. (my_id .EQ. 0)) THEN
     WRITE(*,"(A,F6.0,A1,F6.0,A8,G10.2,A8,G10.2,A)")'|t/tmax = ', time,"/",tmax,'| Gxi = ',pflux_x(1),'| Qxi = ',hflux_x(1),'|'
@@ -269,6 +272,39 @@ SUBROUTINE diagnose_full(kstep)
   END IF
 END SUBROUTINE diagnose_full
 
+!! This routine outputs only txt file 0D data (flux and time)
+SUBROUTINE diagnose_txtonly(kstep)
+  USE basic
+  USE diagnostics_par
+  USE processing,      ONLY: pflux_x, hflux_x, compute_radial_transport, compute_radial_heatflux
+  USE parallel,        ONLY: my_id, comm0
+  USE futils,          ONLY: creatf, creatg, creatd, attach, putfile, closef
+  IMPLICIT NONE
+  INTEGER, INTENT(in) :: kstep
+  INTEGER, parameter  :: BUFSIZE = 2
+  INTEGER :: rank = 0, ierr
+  INTEGER :: dims(1) = (/0/)
+  IF (kstep .GE. 0) THEN
+    ! output the transport in a txt file
+    IF ( MOD(cstep, nsave_0d) == 0 ) THEN
+      CALL compute_radial_transport
+      CALL compute_radial_heatflux
+      IF (my_id .EQ. 0) &
+        WRITE(1,*) time, pflux_x(1), hflux_x(1)
+    END IF
+  !! Save the last state
+  ELSEIF (kstep .EQ. -1) THEN
+    CALL init_outfile(comm0,   resfile0,resfile,fidres)
+    CALL creatg(fidres, "/data/var5d", "5d profiles")
+    CALL creatd(fidres, rank, dims,  "/data/var5d/time",     "Time t*c_s/R")
+    CALL creatd(fidres, rank, dims, "/data/var5d/cstep", "iteration number")
+    CALL creatg(fidres, "/data/var5d/moments", "full moments array")
+    CALL attach(fidres,"/data/var5d/" , "frames", iframe5d)
+    CALL diagnose_5d
+    CALL closef(fidres)
+  ENDIF
+END SUBROUTINE diagnose_txtonly
+
 !!-------------- Auxiliary routines -----------------!!
 SUBROUTINE diagnose_0d
   USE basic
diff --git a/src/diagnostics_par_mod.F90 b/src/diagnostics_par_mod.F90
index 0bb60ee0a09138e065aade86e4c3921273a2c691..2a8630f8267f54ef5bcbfa3bd22e071763c45695 100644
--- a/src/diagnostics_par_mod.F90
+++ b/src/diagnostics_par_mod.F90
@@ -13,7 +13,8 @@ MODULE diagnostics_par
 
   INTEGER, PUBLIC, PROTECTED :: nsave_0d, nsave_1d, nsave_2d, nsave_3d, nsave_5d ! save data every n step
   REAL,    PUBLIC, PROTECTED :: dtsave_0d, dtsave_1d, dtsave_2d, dtsave_3d, dtsave_5d ! save data every dt time unit
-
+  ! Change diagnostic mode (full/txtonly)
+  CHARACTER(len=256), PUBLIC, PROTECTED :: diag_mode = "full"
   !  HDF5 file
   CHARACTER(len=256), PUBLIC :: resfile,resfile0 = "outputs"            ! Head of main result file name
   CHARACTER(len=256), PUBLIC :: momfile,momfile0 = "moments"   ! Head of the moment spectrum file (N_a(p,j,z))
@@ -44,6 +45,7 @@ CONTAINS
     NAMELIST /OUTPUT_PAR/ write_doubleprecision, write_gamma, write_hf, write_phi
     NAMELIST /OUTPUT_PAR/ write_Na00, write_Napj, write_Sapj
     NAMELIST /OUTPUT_PAR/ write_dens, write_fvel, write_temp
+    NAMELIST /OUTPUT_PAR/ diag_mode
 
     READ(lu_in,output_par)