diff --git a/src/MNH/ini_budget.f90 b/src/MNH/ini_budget.f90
index 7d49b14513fe73a7a7bf7084a3a3244a91d77367..9283fc94736ba81ef3d5759d7fab55e371898950 100644
--- a/src/MNH/ini_budget.f90
+++ b/src/MNH/ini_budget.f90
@@ -7,6 +7,7 @@
 !  P. Wautelet 17/08/2020: add Budget_preallocate subroutine
 !  P. Wautelet 11/01/2021: ignore xbuwri for cartesian boxes (write at every xbulen interval)
 !  P. Wautelet 01/02/2021: bugfix: add missing CEDS source terms for SV budgets
+!  P. Wautelet 02/02/2021: budgets: add missing source terms for SV budgets in LIMA
 !-----------------------------------------------------------------
 module mode_ini_budget
 
@@ -3134,6 +3135,16 @@ SV_BUDGETS: do jsv = 1, ksv
 
       else if ( jsv >= nsv_lima_ccn_acti .and. jsv <= nsv_lima_ccn_acti + nmod_ccn - 1 ) then SV_LIMA
         ! Activated CCN concentration
+        gcond = lptsplit .and. lwarm_lima  .and. lacti_lima .and. nmod_ccn >= 1
+        tzsource%cmnhname  = 'HENU'
+        tzsource%clongname = 'CCN activation'
+        call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup )
+
+        gcond = lptsplit .and. lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima
+        tzsource%cmnhname  = 'HINC'
+        tzsource%clongname = 'heterogeneous nucleation by contact'
+        call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup )
+
         gcond = lwarm_lima
         tzsource%cmnhname  = 'CEDS'
         tzsource%clongname = 'adjustment to saturation'
@@ -3262,6 +3273,23 @@ SV_BUDGETS: do jsv = 1, ksv
 
       else if ( jsv >= nsv_lima_ifn_nucl .and. jsv <= nsv_lima_ifn_nucl + nmod_ifn - 1 ) then SV_LIMA
         ! Nucleated IFN concentration
+        gcond = lptsplit .and. lcold_lima .and. lnucl_lima .and. lmeyers_lima .and. jsv == nsv_lima_ifn_nucl
+        tzsource%cmnhname  = 'HINC'
+        tzsource%clongname = 'heterogeneous nucleation by contact'
+        call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup )
+
+        gcond = lptsplit .and.                                                                               &
+                     ( lcold_lima .and. lnucl_lima .and.       lmeyers_lima .and. jsv == nsv_lima_ifn_nucl ) &
+                .or. ( lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima                                )
+        tzsource%cmnhname  = 'HIND'
+        tzsource%clongname = 'heterogeneous nucleation by deposition'
+        call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup )
+
+        gcond = lptsplit .or. ( lcold_lima .and. lwarm_lima  )
+        tzsource%cmnhname  = 'IMLT'
+        tzsource%clongname = 'ice melting'
+        call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup )
+
         gcond = lcold_lima
         tzsource%cmnhname  = 'CEDS'
         tzsource%clongname = 'adjustment to saturation'
@@ -3270,6 +3298,11 @@ SV_BUDGETS: do jsv = 1, ksv
 
       else if ( jsv >= nsv_lima_imm_nucl .and. jsv <= nsv_lima_imm_nucl + nmod_imm - 1 ) then SV_LIMA
         ! Nucleated IMM concentration
+        gcond = lptsplit .and. lcold_lima .and. lnucl_lima .and. .not. lmeyers_lima
+        tzsource%cmnhname  = 'HINC'
+        tzsource%clongname = 'heterogeneous nucleation by contact'
+        call Budget_source_add( tbudgets(ibudget), tzsource, gcond, igroup )
+
         gcond = lcold_lima
         tzsource%cmnhname  = 'CEDS'
         tzsource%clongname = 'adjustment to saturation'
diff --git a/src/MNH/lima_meyers.f90 b/src/MNH/lima_meyers.f90
index 04a1a18dec57bb7d7b90ccd629f12fc8c519c959..94f19c64c6f4792ff458db9171b930073747426f 100644
--- a/src/MNH/lima_meyers.f90
+++ b/src/MNH/lima_meyers.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2021 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.
@@ -109,6 +109,7 @@ END MODULE MODI_LIMA_MEYERS
 !  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
 !  P. Wautelet 28/05/2019: move COUNTJV function to tools.f90
 !  P. Wautelet    02/2020: use the new data structures and subroutines for budgets
+!  P. Wautelet 02/02/2021: budgets: add missing source terms for SV budgets in LIMA
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -119,7 +120,7 @@ use modd_budget,          only: lbu_enable, nbumod,
                                 NBUDGET_TH, NBUDGET_RV, NBUDGET_RC, NBUDGET_RI, NBUDGET_SV1, &
                                 tbudgets
 USE MODD_CST
-USE MODD_NSV,             ONLY: NSV_LIMA_NC, NSV_LIMA_NI
+USE MODD_NSV,             ONLY: NSV_LIMA_NC, NSV_LIMA_NI, NSV_LIMA_IFN_NUCL
 USE MODD_PARAMETERS
 USE MODD_PARAM_LIMA
 USE MODD_PARAM_LIMA_COLD
@@ -321,6 +322,8 @@ IF( INEGT >= 1 ) THEN
     if ( lbudget_rv ) call Budget_store_init( tbudgets(NBUDGET_RV),                    'HIND', prvs(:, :, :) * prhodj(:, :, :) )
     if ( lbudget_ri ) call Budget_store_init( tbudgets(NBUDGET_RI),                    'HIND', pris(:, :, :) * prhodj(:, :, :) )
     if ( lbudget_sv ) call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'HIND', pcis(:, :, :) * prhodj(:, :, :) )
+    if ( lbudget_sv ) &
+      call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl), 'HIND', pins(:, :, :, 1) * prhodj(:, :, :) )
   end if
 
   DO JL=1,INEGT
@@ -337,8 +340,6 @@ IF( INEGT >= 1 ) THEN
   END WHERE
 !
   ZINS(:,1)     = ZINS(:,1) + ZZX(:)
-  ZW(:,:,:)     = PINS(:,:,:,1)
-  PINS(:,:,:,1) = UNPACK( ZINS(:,1), MASK=GNEGT(:,:,:), FIELD=ZW(:,:,:)  )
 !
   ZRVS(:) = ZRVS(:) - ZZW(:)
   ZRIS(:) = ZRIS(:) + ZZW(:)
@@ -356,6 +357,8 @@ IF( INEGT >= 1 ) THEN
                                              Unpack ( zris(:), mask = gnegt(:, :, :), field = pris(:, :, :) ) * prhodj(:, :, :) )
     if ( lbudget_sv ) call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'HIND', &
                                              Unpack ( zcis(:), mask = gnegt(:, :, :), field = pcis(:, :, :) ) * prhodj(:, :, :) )
+    if ( lbudget_sv ) call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl), 'HIND', &
+                                       Unpack ( zins(:, 1), mask = gnegt(:, :, :), field = pins(:, :, :, 1) ) * prhodj(:, :, :) )
   end if
 !
 !*            compute the heterogeneous nucleation by contact: RVHNCI
@@ -370,12 +373,11 @@ IF( INEGT >= 1 ) THEN
       call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'HINC', pccs(:, :, :) * prhodj(:, :, :) )
       call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'HINC', &
                                        Unpack ( zcis(:), mask = gnegt(:, :, :), field = pcis(:, :, :) ) * prhodj(:, :, :) )
+      call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl), 'HINC', &
+                                 Unpack ( zins(:, 1), mask = gnegt(:, :, :), field = pins(:, :, :, 1) ) * prhodj(:, :, :) )
     end if
   end if
 
-  DO JL=1,INEGT
-    ZINS(JL,1) = PINS(I1(JL),I2(JL),I3(JL),1)
-  END DO
   ZZW(:) = 0.0
   ZZX(:) = 0.0
   ZZY(:) = 0.0
@@ -420,6 +422,7 @@ IF( INEGT >= 1 ) THEN
     if ( lbudget_sv ) then
       call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'HINC', pccs(:, :, :) * prhodj(:, :, :) )
       call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'HINC', pcis(:, :, :) * prhodj(:, :, :) )
+      call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl), 'HINC', pins(:, :, :, 1) * prhodj(:, :, :) )
     end if
   end if
 
diff --git a/src/MNH/lima_mixed.f90 b/src/MNH/lima_mixed.f90
index 1b7ae8655015b68373022ab333b942cee44b1237..49024b7b518893f1b9b101175676fb8a5d18f558 100644
--- a/src/MNH/lima_mixed.f90
+++ b/src/MNH/lima_mixed.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2021 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.
@@ -95,6 +95,7 @@ END MODULE MODI_LIMA_MIXED
 !  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
 !  P. Wautelet    03/2020: use the new data structures and subroutines for budgets (no more call to budget in this subroutine)
 !  P. Wautelet 28/05/2020: bugfix: correct array start for PSVT and PSVS
+!  P. Wautelet 02/02/2021: budgets: add missing source terms for SV budgets in LIMA
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -178,19 +179,10 @@ REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3))  &
                                        PCRS,    & ! Rain water C. source
                                        PCIS       ! Ice crystal C. source
 !
-REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: PNFS     ! CCN C. available source
-                                                  !used as Free ice nuclei for
-                                                  !HOMOGENEOUS nucleation of haze
-REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: PNAS     ! Cloud  C. nuclei C. source
-                                                  !used as Free ice nuclei for
-                                                  !IMMERSION freezing
 REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: PIFS     ! Free ice nuclei C. source 
                                                   !for DEPOSITION and CONTACT
 REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: PINS     ! Activated ice nuclei C. source
                                                   !for DEPOSITION and CONTACT
-REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: PNIS     ! Activated ice nuclei C. source
-                                                  !for IMMERSION
-REAL, DIMENSION(:,:,:),   ALLOCATABLE :: PNHS     ! Hom. freezing of CCN
 !
 ! Replace PACK
 LOGICAL, DIMENSION(SIZE(PRHODREF,1),SIZE(PRHODREF,2),SIZE(PRHODREF,3)) :: GMICRO
@@ -309,18 +301,6 @@ IF ( LWARM ) PCCS(:,:,:) = PSVS(:,:,:,NSV_LIMA_NC)
 IF ( LWARM .AND. LRAIN ) PCRS(:,:,:) = PSVS(:,:,:,NSV_LIMA_NR)
 IF ( LCOLD ) PCIS(:,:,:) = PSVS(:,:,:,NSV_LIMA_NI)
 !
-IF ( NMOD_CCN .GE. 1 ) THEN
-   ALLOCATE( PNFS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),NMOD_CCN) )
-   ALLOCATE( PNAS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),NMOD_CCN) )
-   PNFS(:,:,:,:) = PSVS(:,:,:,NSV_LIMA_CCN_FREE:NSV_LIMA_CCN_FREE+NMOD_CCN-1)
-   PNAS(:,:,:,:) = PSVS(:,:,:,NSV_LIMA_CCN_ACTI:NSV_LIMA_CCN_ACTI+NMOD_CCN-1)
-ELSE
-   ALLOCATE( PNFS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),1) )
-   ALLOCATE( PNAS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),1) )
-   PNFS(:,:,:,:) = 0.
-   PNAS(:,:,:,:) = 0.
-END IF
-!
 IF ( NMOD_IFN .GE. 1 ) THEN
    ALLOCATE( PIFS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),NMOD_IFN) )
    ALLOCATE( PINS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),NMOD_IFN) )
@@ -333,22 +313,6 @@ ELSE
    PINS(:,:,:,:) = 0.
 END IF
 !
-IF ( NMOD_IMM .GE. 1 ) THEN
-   ALLOCATE( PNIS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),NMOD_IMM) )
-   PNIS(:,:,:,:) = PSVS(:,:,:,NSV_LIMA_IMM_NUCL:NSV_LIMA_IMM_NUCL+NMOD_IMM-1)
-ELSE
-   ALLOCATE( PNIS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3),1) )
-   PNIS(:,:,:,:) = 0.0
-END IF
-!
-IF ( OHHONI ) THEN
-   ALLOCATE( PNHS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3)) )
-   PNHS(:,:,:) = PSVS(:,:,:,NSV_LIMA_HOM_HAZE)
-ELSE
-   ALLOCATE( PNHS(SIZE(PRHODJ,1),SIZE(PRHODJ,2),SIZE(PRHODJ,3)) )
-   PNHS(:,:,:) = 0.0
-END IF
-!
 !-------------------------------------------------------------------------------
 !
 !
@@ -529,7 +493,7 @@ IF( IMICRO >= 1 ) THEN
                                   ZLBDAI, ZLBDAG,               &
                                   ZRHODJ, GMICRO, PRHODJ, KMI,  &
                                   PTHS, PRVS, PRCS, PRIS, PRGS, &
-                                  PCCS, PCIS                    )
+                                  PCCS, PCIS, PINS              )
 ! 
 !-------------------------------------------------------------------------------
 !
@@ -664,27 +628,14 @@ PSVS(:,:,:,NSV_LIMA_NC) = PCCS(:,:,:)
 IF ( LRAIN ) PSVS(:,:,:,NSV_LIMA_NR) = PCRS(:,:,:)
 PSVS(:,:,:,NSV_LIMA_NI) = PCIS(:,:,:)
 !
-IF ( NMOD_CCN .GE. 1 ) THEN
-   PSVS(:,:,:,NSV_LIMA_CCN_FREE:NSV_LIMA_CCN_FREE+NMOD_CCN-1) = PNFS(:,:,:,:)
-   PSVS(:,:,:,NSV_LIMA_CCN_ACTI:NSV_LIMA_CCN_ACTI+NMOD_CCN-1) = PNAS(:,:,:,:)
-END IF
-!
 IF ( NMOD_IFN .GE. 1 ) THEN
    PSVS(:,:,:,NSV_LIMA_IFN_FREE:NSV_LIMA_IFN_FREE+NMOD_IFN-1) = PIFS(:,:,:,:)
    PSVS(:,:,:,NSV_LIMA_IFN_NUCL:NSV_LIMA_IFN_NUCL+NMOD_IFN-1) = PINS(:,:,:,:)
 END IF
 !
-IF ( NMOD_IMM .GE. 1 ) THEN
-   PSVS(:,:,:,NSV_LIMA_IMM_NUCL:NSV_LIMA_IMM_NUCL+NMOD_IMM-1) = PNIS(:,:,:,:)
-END IF
-!
 !++cb++
-IF (ALLOCATED(PNFS)) DEALLOCATE(PNFS)
-IF (ALLOCATED(PNAS)) DEALLOCATE(PNAS)
 IF (ALLOCATED(PIFS)) DEALLOCATE(PIFS)
 IF (ALLOCATED(PINS)) DEALLOCATE(PINS)
-IF (ALLOCATED(PNIS)) DEALLOCATE(PNIS)
-IF (ALLOCATED(PNHS)) DEALLOCATE(PNHS)
 !--cb--
 !
 !-------------------------------------------------------------------------------
diff --git a/src/MNH/lima_mixed_slow_processes.f90 b/src/MNH/lima_mixed_slow_processes.f90
index 0c5570bd1464ae53b86079d410db37e913f0991f..6ef9b55f5035df58c4423f6250ebb369fcbed506 100644
--- a/src/MNH/lima_mixed_slow_processes.f90
+++ b/src/MNH/lima_mixed_slow_processes.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2021 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,7 +16,7 @@ INTERFACE
                                            ZLBDAI, ZLBDAG,               &
                                            PRHODJ1D, GMICRO, PRHODJ, KMI,&
                                            PTHS, PRVS, PRCS, PRIS, PRGS, &
-                                           PCCS, PCIS                    )
+                                           PCCS, PCIS, PINS              )
 !
 REAL, DIMENSION(:),   INTENT(IN)    :: ZRHODREF  ! RHO Dry REFerence
 REAL, DIMENSION(:),   INTENT(IN)    :: ZZT       ! Temperature
@@ -57,6 +57,7 @@ REAL,    DIMENSION(:,:,:), INTENT(IN) :: PRIS
 REAL,    DIMENSION(:,:,:), INTENT(IN) :: PRGS
 REAL,    DIMENSION(:,:,:), INTENT(IN) :: PCCS
 REAL,    DIMENSION(:,:,:), INTENT(IN) :: PCIS
+REAL,    DIMENSION(:,:,:,:), INTENT(IN) :: PINS
 !
 END SUBROUTINE LIMA_MIXED_SLOW_PROCESSES
 END INTERFACE
@@ -71,7 +72,7 @@ END MODULE MODI_LIMA_MIXED_SLOW_PROCESSES
                                            ZLBDAI, ZLBDAG,               &
                                            PRHODJ1D, GMICRO, PRHODJ, KMI,&
                                            PTHS, PRVS, PRCS, PRIS, PRGS, &
-                                           PCCS, PCIS                    )
+                                           PCCS, PCIS, PINS              )
 !     #######################################################################
 !
 !!
@@ -111,6 +112,7 @@ END MODULE MODI_LIMA_MIXED_SLOW_PROCESSES
 !!      Original             ??/??/13 
 !!      C. Barthe  * LACy *  jan. 2014   add budgets
 !  P. Wautelet    03/2020: use the new data structures and subroutines for budgets
+!  P. Wautelet 02/02/2021: budgets: add missing source terms for SV budgets in LIMA
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -172,6 +174,7 @@ REAL,    DIMENSION(:,:,:), INTENT(IN) :: PRIS
 REAL,    DIMENSION(:,:,:), INTENT(IN) :: PRGS
 REAL,    DIMENSION(:,:,:), INTENT(IN) :: PCCS
 REAL,    DIMENSION(:,:,:), INTENT(IN) :: PCIS
+REAL,    DIMENSION(:,:,:,:), INTENT(IN) :: PINS
 !
 !*       0.2   Declarations of local variables :
 !
@@ -220,6 +223,10 @@ END IF
     if ( lbudget_sv ) then
       call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'IMLT', pccs(:, :, :) * prhodj(:, :, :) )
       call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'IMLT', pcis(:, :, :) * prhodj(:, :, :) )
+      do jmod_ifn = 1,nmod_ifn
+        call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl + jmod_ifn - 1), 'IMLT', &
+                                pins(:, :, :, jmod_ifn) * prhodj(:, :, :) )
+      enddo
     end if
   end if
 
@@ -252,6 +259,10 @@ END IF
                                            Unpack( zccs(:), mask = gmicro(:, :, :), field = pccs(:, :, :) ) * prhodj(:, :, :) )
       call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'IMLT', &
                                            Unpack( zcis(:), mask = gmicro(:, :, :), field = pcis(:, :, :) ) * prhodj(:, :, :) )
+      do jmod_ifn = 1,nmod_ifn
+        call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl + jmod_ifn - 1), 'IMLT', &
+                          Unpack( zins(:, jmod_ifn), mask = gmicro(:, :, :), field = pins(:, :, :, jmod_ifn) ) * prhodj(:, :, :) )
+      enddo
     end if
   end if
 !
diff --git a/src/MNH/lima_phillips.f90 b/src/MNH/lima_phillips.f90
index 05224e4935d533be1169cac97ec2e2fb44b6d556..1ca330e353e142451acd53c6bec902cae233b4b8 100644
--- a/src/MNH/lima_phillips.f90
+++ b/src/MNH/lima_phillips.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-2021 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.
@@ -118,6 +118,7 @@ END MODULE MODI_LIMA_PHILLIPS
 !  P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
 !  P. Wautelet 28/05/2019: move COUNTJV function to tools.f90
 !  P. Wautelet    03/2020: use the new data structures and subroutines for budgets
+!  P. Wautelet 02/02/2021: budgets: add missing source terms for SV budgets in LIMA
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -130,7 +131,7 @@ use modd_budget,          only: lbu_enable, nbumod,
 USE MODD_CST,             ONLY : XP00, XRD, XMV, XMD, XCPD, XCPV, XCL, XCI,        &
                                  XTT, XLSTT, XLVTT, XALPI, XBETAI, XGAMI,          &
                                  XALPW, XBETAW, XGAMW, XPI
-USE MODD_NSV, ONLY : NSV_LIMA_NC, NSV_LIMA_NI, NSV_LIMA_IFN_FREE
+USE MODD_NSV, ONLY : NSV_LIMA_NC, NSV_LIMA_NI, NSV_LIMA_CCN_ACTI, NSV_LIMA_IFN_FREE, NSV_LIMA_IFN_NUCL, NSV_LIMA_IMM_NUCL
 USE MODD_PARAMETERS,      ONLY : JPHEXT, JPVEXT
 USE MODD_PARAM_LIMA,      ONLY : NMOD_IFN, NSPECIE, XFRAC,                         &
                                  NMOD_CCN, NMOD_IMM, NIND_SPECIE, NINDICE_CCN_IMM,  &
@@ -445,6 +446,8 @@ if ( nbumod == kmi .and. lbu_enable ) then
     do jl = 1, nmod_ifn
       idx = NBUDGET_SV1 - 1 + nsv_lima_ifn_free -1 + jl
       call Budget_store_init( tbudgets(idx), 'HIND', pifs(:, :, :, jl) * prhodj(:, :, :) )
+      idx = NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl -1 + jl
+      call Budget_store_init( tbudgets(idx), 'HIND', pins(:, :, :, jl) * prhodj(:, :, :) )
     end do
   end if
 end if
@@ -495,6 +498,8 @@ if ( nbumod == kmi .and. lbu_enable ) then
     do jl = 1, nmod_ifn
       idx = NBUDGET_SV1 - 1 + nsv_lima_ifn_free -1 + jl
       call Budget_store_end( tbudgets(idx), 'HIND', pifs(:, :, :, jl) * prhodj(:, :, :) )
+      idx = NBUDGET_SV1 - 1 + nsv_lima_ifn_nucl -1 + jl
+      call Budget_store_end( tbudgets(idx), 'HIND', pins(:, :, :, jl) * prhodj(:, :, :) )
     end do
   end if
 end if
@@ -514,6 +519,14 @@ if ( nbumod == kmi .and. lbu_enable ) then
     call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'HINC', pccs(:, :, :) * prhodj(:, :, :) )
     call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'HINC', &
                                     Unpack ( zcis(:), mask = gnegt(:, :, :), field = pcis(:, :, :) ) * prhodj(:, :, :) )
+    do jl = 1, nmod_ccn
+      idx = NBUDGET_SV1 - 1 + nsv_lima_ccn_acti - 1 + jl
+      call Budget_store_init( tbudgets(idx), 'HINC', pnas(:, :, :, jl) * prhodj(:, :, :) )
+    end do
+    do jl = 1, nmod_imm
+      idx = NBUDGET_SV1 - 1 + nsv_lima_imm_nucl - 1 + jl
+      call Budget_store_init( tbudgets(idx), 'HINC', pnis(:, :, :, jl) * prhodj(:, :, :) )
+    end do
   end if
 end if
 !
@@ -570,6 +583,14 @@ if ( nbumod == kmi .and. lbu_enable ) then
                                     Unpack ( zccs(:), mask = gnegt(:, :, :), field = pccs(:, :, :) ) * prhodj(:, :, :) )
     call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_ni), 'HINC', &
                                     Unpack ( zcis(:), mask = gnegt(:, :, :), field = pcis(:, :, :) ) * prhodj(:, :, :) )
+    do jl = 1, nmod_ccn
+      idx = NBUDGET_SV1 - 1 + nsv_lima_ccn_acti - 1 + jl
+      call Budget_store_end( tbudgets(idx), 'HINC', pnas(:, :, :, jl) * prhodj(:, :, :) )
+    end do
+    do jl = 1, nmod_imm
+      idx = NBUDGET_SV1 - 1 + nsv_lima_imm_nucl - 1 + jl
+      call Budget_store_end( tbudgets(idx), 'HINC', pnis(:, :, :, jl) * prhodj(:, :, :) )
+    end do
   end if
 end if
 !-------------------------------------------------------------------------------
diff --git a/src/MNH/lima_warm.f90 b/src/MNH/lima_warm.f90
index 9337e92f7a985fe464b6f976260ead2602a5bd76..ff1523ffd7e7d2fd9f3f116a3feefc0ffcd2f2b1 100644
--- a/src/MNH/lima_warm.f90
+++ b/src/MNH/lima_warm.f90
@@ -130,6 +130,7 @@ END MODULE MODI_LIMA_WARM
 !  B. Vie      03/02/2020: correction of activation of water deposition on the ground
 !  B. Vie      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
+!  P. Wautelet 02/02/2021: budgets: add missing source terms for SV budgets in LIMA
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -369,6 +370,8 @@ IF ( LACTI .AND. NMOD_CCN > 0 ) THEN
     do jl = 1, nmod_ccn
       idx = NBUDGET_SV1 - 1 + nsv_lima_ccn_free - 1 + jl
       call Budget_store_init( tbudgets(idx), 'HENU', znfs(:, :, :, jl) * prhodj(:, :, :) )
+      idx = NBUDGET_SV1 - 1 + nsv_lima_ccn_acti - 1 + jl
+      call Budget_store_init( tbudgets(idx), 'HENU', znas(:, :, :, jl) * prhodj(:, :, :) )
     end do
   end if
 
@@ -385,6 +388,8 @@ IF ( LACTI .AND. NMOD_CCN > 0 ) THEN
     do jl = 1, nmod_ccn
       idx = NBUDGET_SV1 - 1 + nsv_lima_ccn_free - 1 + jl
       call Budget_store_end( tbudgets(idx), 'HENU', znfs(:, :, :, jl) * prhodj(:, :, :) )
+      idx = NBUDGET_SV1 - 1 + nsv_lima_ccn_acti - 1 + jl
+      call Budget_store_end( tbudgets(idx), 'HENU', znas(:, :, :, jl) * prhodj(:, :, :) )
     end do
   end if
 END IF ! LACTI