diff --git a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
index fa9b89acef45eb3ede380b4027a62ceba59c96a1..8f5182b6b3c21b11b420d23cc2f501655894364e 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
@@ -851,6 +851,15 @@ SUBROUTINE IO_BOX_PREPARE( KMI )
     IF ( TOUT_BOXES(JI)%NKSUP < TOUT_BOXES(JI)%NKINF ) &
                                            CALL Print_msg( NVERB_ERROR, 'GEN', 'IO_BOX_PREPARE', 'NOUT_BOX_KSUP < NOUT_BOX_KINF' )
 
+    IF ( DYN_MODEL(IMI)%LVE_RELAX .AND. LOUT_TOP_ABSORBING_LAYER_REMOVE(IMI) ) THEN
+      ! Remark: NKSUP can not be modified here to remove the Top Absorbing Layer levels because NALBOT is not yet computed
+      ! NKSUP will be modified just before writing dimensions to the file
+      OUT_MODEL(IMI)%LOUT_TAL_REMOVE = LOUT_TOP_ABSORBING_LAYER_REMOVE(IMI)
+    ELSE
+      ! There is no Top Absorbing Layer (enabled only if LVE_RELAX=.TRUE.)
+      OUT_MODEL(IMI)%LOUT_TAL_REMOVE = .FALSE.
+    END IF
+
     ! Field the list of variables to write for each box (in addition to the NOUTFIELDLIST which is common to all the boxes)
     CALL IO_OUT_FIELDLIST_FILL( COUT_BOX_VAR_SUPP(IMI,JI,:), .FALSE., TOUT_BOXES(JI)%NFIELDLIST_SUPP )
 
diff --git a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
index 08d6e4748f4ca8c90bf70a6f61f1830610b36a00..79e732b6b1c91f46249da60a02c5da92f8e4d957 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
@@ -255,7 +255,7 @@ USE MODD_CONF_n,        ONLY: CSTORAGE_TYPE
 USE MODD_DIAG_FLAG,     ONLY: LTRAJ
 USE MODD_DIM_n,         ONLY: NIMAX_ll, NJMAX_ll, NKMAX
 use modd_dyn,           only: xseglen
-use modd_dyn_n,         only: dyn_model
+use modd_dyn_n,         only: dyn_model, nalbot
 use modd_field,         only: NMNHDIM_NI, NMNHDIM_NJ, NMNHDIM_NI_U, NMNHDIM_NJ_U, NMNHDIM_NI_V, NMNHDIM_NJ_V,   &
                               NMNHDIM_LEVEL, NMNHDIM_LEVEL_W, NMNHDIM_TIME,                                     &
                               NMNHDIM_ONE,  NMNHDIM_NSWB, NMNHDIM_NLWB, NMNHDIM_TRAJ_TIME, NMNHDIM_COMPLEX,     &
@@ -280,7 +280,7 @@ use modd_field,         only: NMNHDIM_NI, NMNHDIM_NJ, NMNHDIM_NI_U, NMNHDIM_NJ_U
 use modd_les,           only: lles_pdf, nles_k, npdf, nspectra_k, xles_temp_mean_start, xles_temp_mean_step, xles_temp_mean_end
 use modd_les_n,         only: nles_times, nspectra_ni, nspectra_nj
 use modd_nsv,           only: nsv
-use modd_out_n,         only: nout_nboxes, tout_boxes
+use modd_out_n,         only: lout_tal_remove, nout_nboxes, tout_boxes
 USE MODD_PARAMETERS_ll, ONLY: JPHEXT, JPVEXT
 use modd_param_n,       only: crad
 use modd_profiler_n,    only: lprofiler, tprofilers_time
@@ -373,6 +373,17 @@ if ( tpfile%ctype == 'MNHOUTPUT' ) then
     tpfile%tboxncdims(jbox)%nmaxdims = NMNHDIM_BOX_LAST_ENTRY - NMNHDIM_BOX_FIRST_ENTRY + 1
     Allocate( tpfile%tboxncdims(jbox)%tdims(NMNHDIM_BOX_FIRST_ENTRY:NMNHDIM_BOX_LAST_ENTRY) )
 
+    !Remove the Top Absorbing Layer if necessary (done here because it was too early
+    !in IO_Bakout_struct_prepare because nalbot was not yet available)
+    if ( lout_tal_remove ) then
+      tout_boxes(jbox)%nksup = min( tout_boxes(jbox)%nksup, nalbot - JPVEXT )
+      if ( tout_boxes(jbox)%nksup < tout_boxes(jbox)%nkinf ) then
+        call Print_msg( NVERB_ERROR, 'IO', 'IO_Fieldlist_1field_write', trim(tout_boxes(jbox)%cname) &
+                        // ': NKSUP < NKINF after removing the Top Absorbing Layer' )
+        tout_boxes(jbox)%nksup = tout_boxes(jbox)%nkinf
+      end if
+    end if
+
     !Write the box dimensions
     call IO_Add_dim_box_nc4( tpfile, jbox, NMNHDIM_BOX_NI,      'box_ni',      tout_boxes(jbox)%nisup-tout_boxes(jbox)%niinf+1 )
     call IO_Add_dim_box_nc4( tpfile, jbox, NMNHDIM_BOX_NI_U,    'box_ni_u',    tout_boxes(jbox)%nisup-tout_boxes(jbox)%niinf+1 )
diff --git a/src/MNH/modd_bakout.f90 b/src/MNH/modd_bakout.f90
index 28fe4a0ca45bdbc0b651cc80d4b9212134cfdc0b..e9283580b3d71329b71da02a85bb0db121a40392 100644
--- a/src/MNH/modd_bakout.f90
+++ b/src/MNH/modd_bakout.f90
@@ -99,6 +99,7 @@ CHARACTER(LEN=NMNHNAMELGTMAX), DIMENSION(:,:,:), ALLOCATABLE :: COUT_BOX_VAR_SUP
                                                                                   ! in the different boxes (added to the COUT_VAR)
 LOGICAL, DIMENSION(JPMODELMAX) :: LOUT_MAINDOMAIN_WRITE = .FALSE. ! True to write the main domain
                                                                   ! (automatically forced to .TRUE. if NOUT_BOXES=0)
+LOGICAL, DIMENSION(JPMODELMAX) :: LOUT_TOP_ABSORBING_LAYER_REMOVE = .TRUE. ! Remove the top absorbing layer
 
 INTEGER, DIMENSION(:,:), ALLOCATABLE :: NOUT_BOX_IINF ! Box coordinates in physical domain (for each model and for each box)
 INTEGER, DIMENSION(:,:), ALLOCATABLE :: NOUT_BOX_ISUP
diff --git a/src/MNH/modd_outn.f90 b/src/MNH/modd_outn.f90
index a4258e395987f52c678d88cb74f3f29782d4a07b..b52bdc2667017665e6b76d8c15c6a9a783113174 100644
--- a/src/MNH/modd_outn.f90
+++ b/src/MNH/modd_outn.f90
@@ -69,7 +69,9 @@ TYPE OUT_t
   INTEGER, DIMENSION(:), ALLOCATABLE :: NBAK_STEPLIST                  ! List of time steps to do backups (except regular series)
   INTEGER, DIMENSION(:), ALLOCATABLE :: NOUT_STEPLIST                  ! List of time steps to do outputs (except regular series)
   INTEGER, DIMENSION(:), ALLOCATABLE :: NOUT_FIELDLIST                 ! List of fields to write in outputs
-  LOGICAL                            :: LOUT_BIGBOX_WRITE = .TRUE.     ! Write the maix box/domain (if there are boxes)
+  LOGICAL                            :: LOUT_BIGBOX_WRITE = .TRUE.     ! Write the main box/domain (if there are boxes)
+  LOGICAL                            :: LOUT_TAL_REMOVE   = .TRUE.     ! Remove the top absorbing layer
+
   TYPE(TOUTBOXMETADATA), DIMENSION(:), ALLOCATABLE :: TOUT_BOXES
 END TYPE OUT_t
 
@@ -87,6 +89,7 @@ INTEGER, DIMENSION(:), POINTER :: NBAK_STEPLIST      => NULL()
 INTEGER, DIMENSION(:), POINTER :: NOUT_STEPLIST      => NULL()
 INTEGER, DIMENSION(:), POINTER :: NOUT_FIELDLIST     => NULL()
 LOGICAL,               POINTER :: LOUT_BIGBOX_WRITE  => NULL()
+LOGICAL,               POINTER :: LOUT_TAL_REMOVE    => NULL()
 TYPE(TOUTBOXMETADATA), DIMENSION(:), POINTER :: TOUT_BOXES  => NULL()
 
 CONTAINS
@@ -107,6 +110,7 @@ NBAK_STEPLIST      => OUT_MODEL(KTO)%NBAK_STEPLIST
 NOUT_STEPLIST      => OUT_MODEL(KTO)%NOUT_STEPLIST
 NOUT_FIELDLIST     => OUT_MODEL(KTO)%NOUT_FIELDLIST
 LOUT_BIGBOX_WRITE  => OUT_MODEL(KTO)%LOUT_BIGBOX_WRITE
+LOUT_TAL_REMOVE    => OUT_MODEL(KTO)%LOUT_TAL_REMOVE
 TOUT_BOXES         => OUT_MODEL(KTO)%TOUT_BOXES
 
 END SUBROUTINE OUT_GOTO_MODEL
diff --git a/src/MNH/modn_output.f90 b/src/MNH/modn_output.f90
index e1db16f4a51aa44817648b7f8852c5410162300c..01e1f49ec8666f9edabb1309af40b1c7c368b346 100644
--- a/src/MNH/modn_output.f90
+++ b/src/MNH/modn_output.f90
@@ -54,7 +54,8 @@ NAMELIST/NAM_OUTPUT/LOUT_BEG,LOUT_END,&
                    LOUT_COMPRESS, NOUT_COMPRESS_LEVEL,&
                    LOUT_COMPRESS_LOSSY, COUT_COMPRESS_LOSSY_ALGO, NOUT_COMPRESS_LOSSY_NSD, &
                    COUT_DIR, &
-                   NOUT_BOXES, COUT_BOX_NAME, COUT_BOX_VAR_SUPP, LOUT_MAINDOMAIN_WRITE, &
+                   NOUT_BOXES, COUT_BOX_NAME, COUT_BOX_VAR_SUPP, &
+                   LOUT_MAINDOMAIN_WRITE, LOUT_TOP_ABSORBING_LAYER_REMOVE, &
                    NOUT_BOX_IINF, NOUT_BOX_ISUP, NOUT_BOX_JINF, NOUT_BOX_JSUP, NOUT_BOX_KINF, NOUT_BOX_KSUP
 
 LOGICAL, SAVE, PRIVATE :: LOUTPUT_NML_ALLOCATED = .FALSE.