diff --git a/src/MNH/lima.f90 b/src/MNH/lima.f90
index cb3a852199af91fb1f60889b166a340697d38608..9b11af0aaffb8eea18a0480fcab9f5d5e70c11f3 100644
--- a/src/MNH/lima.f90
+++ b/src/MNH/lima.f90
@@ -2,6 +2,7 @@
 !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.
+!-----------------------------------------------------------------
 !      ######spl
 MODULE MODI_LIMA
 !      ####################
@@ -19,6 +20,7 @@ INTERFACE
                      PEVAP3D                                         )
 !
 USE MODD_IO_ll, ONLY: TFILEDATA
+USE MODD_NSV,   only: NSV_LIMA_BEG
 !
 INTEGER,                  INTENT(IN)    :: KKA   !near ground array index  
 INTEGER,                  INTENT(IN)    :: KKU   !uppest atmosphere array index
@@ -43,12 +45,12 @@ INTEGER,                  INTENT(IN)    :: NIMM       ! for array size declarati
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PDTHRAD    ! Theta at time t-dt
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT       ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT        ! Mixing ratios at time t
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT       ! Concentrations at time t
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PW_NU      ! w for CCN activation
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS       ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS        ! Mixing ratios sources
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS       ! Concentrations sources
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 REAL, DIMENSION(:,:),     INTENT(OUT)   :: PINPRC     ! Cloud instant precip
 REAL, DIMENSION(:,:),     INTENT(OUT)   :: PINDEP     ! Cloud droplets deposition
@@ -95,9 +97,11 @@ END MODULE MODI_LIMA
 !!    -------------
 !!      Original   15/03/2018
 !!
-!!      B.Vié  02/2019 : minor correction on budget
-!!  P. Wautelet 26/02/2020: bugfix: corrected condition to write budget CORR_BU_RRS
-!!      B.Vié 03/03/2020 : use DTHRAD instead of dT/dt in Smax diagnostic computation
+!  B. Vié         02/2019: minor correction on budget
+!  P. Wautelet 26/02/2020: bugfix: corrected condition to write budget CORR_BU_RRS
+!  B. Vié      03/03/2020: use DTHRAD instead of dT/dt in Smax diagnostic computation
+!  P. Wautelet 28/05/2020: bugfix: correct array start for PSVT and PSVS
+!-----------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
 !              ------------
@@ -113,7 +117,8 @@ USE MODD_PARAM_LIMA_WARM,ONLY : XLBC, XLBEXC, XAC, XBC, XAR, XBR
 USE MODD_PARAM_LIMA_COLD,ONLY : XAI, XBI
 USE MODD_BUDGET,         ONLY : LBU_ENABLE, LBUDGET_TH, LBUDGET_RV, LBUDGET_RC, LBUDGET_RR,     &
                                 LBUDGET_RI, LBUDGET_RS, LBUDGET_RG, LBUDGET_RH, LBUDGET_SV
-USE MODD_NSV,            ONLY : NSV_LIMA_NC, NSV_LIMA_NR, NSV_LIMA_CCN_FREE, NSV_LIMA_CCN_ACTI, &
+USE MODD_NSV,            ONLY : NSV_LIMA_BEG,                                                   &
+                                NSV_LIMA_NC, NSV_LIMA_NR, NSV_LIMA_CCN_FREE, NSV_LIMA_CCN_ACTI, &
                                 NSV_LIMA_SCAVMASS, NSV_LIMA_NI, NSV_LIMA_IFN_FREE,              &
                                 NSV_LIMA_IFN_NUCL, NSV_LIMA_IMM_NUCL, NSV_LIMA_HOM_HAZE
 USE MODD_CST,            ONLY : XCI, XCL, XCPD, XCPV, XLSTT, XLVTT, XTT, XRHOLW, XP00, XRD
@@ -153,12 +158,12 @@ INTEGER,                  INTENT(IN)    :: NIMM       ! for array size declarati
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PDTHRAD    ! Theta at time t-dt
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT       ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT        ! Mixing ratios at time t
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT       ! Concentrations at time t
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PW_NU      ! w for CCN activation
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS       ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS        ! Mixing ratios sources
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS       ! Concentrations sources
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 REAL, DIMENSION(:,:),     INTENT(OUT)   :: PINPRC     ! Cloud instant precip
 REAL, DIMENSION(:,:),     INTENT(OUT)   :: PINDEP     ! Cloud droplets deposition
diff --git a/src/MNH/lima_adjust.f90 b/src/MNH/lima_adjust.f90
index bb3c7195d7fcb8d091f81af11a7c1a017841fc18..68bffde7fe2c22f79a75c785c9e89143cb52743f 100644
--- a/src/MNH/lima_adjust.f90
+++ b/src/MNH/lima_adjust.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2018 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2020 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.
@@ -16,6 +16,7 @@ INTERFACE
                              PTHS, PSRCS, PCLDFR                               )
 !
 USE MODD_IO_ll, ONLY: TFILEDATA
+USE MODD_NSV,   only: NSV_LIMA_BEG
 !
 INTEGER,                  INTENT(IN)   :: KRR        ! Number of moist variables
 INTEGER,                  INTENT(IN)   :: KMI        ! Model index 
@@ -41,9 +42,9 @@ REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT       ! m.r. at t
 !
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS       ! m.r. source
 !
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT      ! Concentrations at t
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS      ! Concentration source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS      ! Theta source
 !
@@ -134,8 +135,8 @@ END MODULE MODI_LIMA_ADJUST
 !!      Original             ??/??/13 
 !!      C. Barthe  * LACy*   jan. 2014  add budgets
 !!      JP Chaboureau *LA*   March 2014  fix the calculation of icy cloud fraction
-!!  Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!!
+!  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
+!  P. Wautelet 28/05/2020: bugfix: correct array start for PSVT and PSVS
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -190,9 +191,9 @@ REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT       ! m.r. at t
 !
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS       ! m.r. source
 !
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT      ! Concentrations at t
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS      ! Concentration source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS      ! Theta source
 !
diff --git a/src/MNH/lima_cold.f90 b/src/MNH/lima_cold.f90
index debd6a9ded1b10655e2358871066fc5d8d5f4e54..f5c8726ede8158f27e61371666eb3c98522c6842 100644
--- a/src/MNH/lima_cold.f90
+++ b/src/MNH/lima_cold.f90
@@ -1,6 +1,6 @@
-!MNH_LIC Copyright 2013-2018 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2020 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
 !      #####################
@@ -16,7 +16,9 @@ INTERFACE
                            PTHS, PRS, PSVS,                                &
                            PINPRS, PINPRG, PINPRH)
 !
-LOGICAL,                  INTENT(IN)    :: OSEDI   ! switch to activate the 
+USE MODD_NSV,   only: NSV_LIMA_BEG
+!
+LOGICAL,                  INTENT(IN)    :: OSEDI   ! switch to activate the
                                                    ! cloud ice sedimentation
 LOGICAL,                  INTENT(IN)    :: OHHONI  ! enable haze freezing
 INTEGER,                  INTENT(IN)    :: KSPLITG ! Number of small time step 
@@ -39,11 +41,11 @@ REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PPABSM  ! abs. pressure at time t-dt
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT    ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT     ! m.r. at t 
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT    ! Concentrations at t 
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS    ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS     ! m.r. source
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS    ! Concentrations source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 REAL, DIMENSION(:,:),     INTENT(INOUT) :: PINPRS  ! Snow instant precip
 REAL, DIMENSION(:,:),     INTENT(INOUT) :: PINPRG  ! Graupel instant precip
@@ -106,8 +108,8 @@ END MODULE MODI_LIMA_COLD
 !!    MODIFICATIONS
 !!    -------------
 !!      Original             ??/??/13 
-!!  Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!!
+!  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
+!  P. Wautelet 28/05/2020: bugfix: correct array start for PSVT and PSVS
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -151,11 +153,11 @@ REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PPABSM  ! abs. pressure at time t-dt
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT    ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT     ! m.r. at t 
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT    ! Concentrations at t 
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS    ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS     ! m.r. source
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS    ! Concentrations source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 REAL, DIMENSION(:,:),     INTENT(INOUT) :: PINPRS  ! Snow instant precip
 REAL, DIMENSION(:,:),     INTENT(INOUT) :: PINPRG  ! Graupel instant precip
diff --git a/src/MNH/lima_mixed.f90 b/src/MNH/lima_mixed.f90
index 38a3cce6526425acc5a07d4001c8b91f885ad7ec..c71914ed7349b3a658111aaffca3dc0f6c1c4681 100644
--- a/src/MNH/lima_mixed.f90
+++ b/src/MNH/lima_mixed.f90
@@ -1,6 +1,6 @@
-!MNH_LIC Copyright 2013-2018 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2020 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
 !      ######################
@@ -15,7 +15,9 @@ INTERFACE
                              PTHT, PRT, PSVT,                     &
                              PTHS, PRS, PSVS)
 !
-LOGICAL,                  INTENT(IN)    :: OSEDI   ! switch to activate the 
+USE MODD_NSV,   only: NSV_LIMA_BEG
+!
+LOGICAL,                  INTENT(IN)    :: OSEDI   ! switch to activate the
                                                    ! cloud ice sedimentation
 LOGICAL,                  INTENT(IN)    :: OHHONI  ! enable haze freezing
 INTEGER,                  INTENT(IN)    :: KSPLITG ! Number of small time step 
@@ -38,12 +40,11 @@ REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PPABSM  ! abs. pressure at time t-dt
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT    ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT     ! m.r. at t 
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT    ! Concentrations at t 
-
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS    ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS     ! m.r. source
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS    ! Concentrations source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 END SUBROUTINE LIMA_MIXED
 END INTERFACE
@@ -91,9 +92,9 @@ END MODULE MODI_LIMA_MIXED
 !!    -------------
 !!      Original             ??/??/13 
 !!      C. Barthe  * LACy *  jan. 2014   add budgets
-!!  Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!!      B.Vie 03/2020 Correction of budgets parallelization
-!!
+!  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
+!  B. Vie         03/2020: correction of budgets parallelization
+!  P. Wautelet 28/05/2020: bugfix: correct array start for PSVT and PSVS
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -146,12 +147,11 @@ REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PPABSM  ! abs. pressure at time t-dt
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT    ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT     ! m.r. at t 
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT    ! Concentrations at t 
-
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS    ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS     ! m.r. source
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS    ! Concentrations source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 !*       0.2   Declarations of local variables :
 !
diff --git a/src/MNH/lima_warm.f90 b/src/MNH/lima_warm.f90
index 95b4f82dd7414e229a53ba61f78d9c43665cbcdc..01b4c413d081f414ddec6c8d8bf45777e04ea0e9 100644
--- a/src/MNH/lima_warm.f90
+++ b/src/MNH/lima_warm.f90
@@ -1,6 +1,6 @@
-!MNH_LIC Copyright 2013-2018 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2020 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
 !-----------------------------------------------------------------
 !      #####################
@@ -17,6 +17,7 @@ INTERFACE
                             PINPRC, PINPRR, PINDEP, PINPRR3D, PEVAP3D     )
 !
 USE MODD_IO_ll,   ONLY: TFILEDATA
+USE MODD_NSV,     only: NSV_LIMA_BEG
 !
 LOGICAL,                  INTENT(IN)    :: OACTIT     ! Switch to activate the
                                                       ! activation by radiative
@@ -51,11 +52,11 @@ REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRCM       ! Cloud water m.r. at t-dt
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT       ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT        ! m.r. at t 
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT       ! Concentrations at t 
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS       ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS        ! m.r. source
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS       ! Concentrations source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 !
 !
@@ -126,9 +127,10 @@ END MODULE MODI_LIMA_WARM
 !!      Original             ??/??/13 
 !!      C. Barthe  * LACy *  jan. 2014   add budgets
 !!      J. Escobar : for real*4 , use XMNH_HUGE
-!!  Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
-!!  B.Vié 03/02/2020 : correction of activation of water deposition on the ground
-!!  B.Vié 03/03/2020 : use DTHRAD instead of dT/dt in Smax diagnostic computation
+!  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
+!  B. Vié      03/02/2020: correction of activation of water deposition on the ground
+!  B. Vié      03/03/2020: use DTHRAD instead of dT/dt in Smax diagnostic computation
+!  P. Wautelet 28/05/2020: bugfix: correct array start for PSVT and PSVS
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -192,11 +194,11 @@ REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRCM       ! Cloud water m.r. at t-dt
 !
 REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT       ! Theta at time t
 REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PRT        ! m.r. at t 
-REAL, DIMENSION(:,:,:,:), INTENT(IN)    :: PSVT       ! Concentrations at t 
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(IN)    :: PSVT ! Concentrations at time t
 !
 REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS       ! Theta source
 REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PRS        ! m.r. source
-REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PSVS       ! Concentrations source
+REAL, DIMENSION(:,:,:,NSV_LIMA_BEG:), INTENT(INOUT) :: PSVS ! Concentration sources
 !
 !
 !