From 49a580b1c200381034c14ce7376a329a823be070 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Beno=C3=AEt=20Vi=C3=A9?= <benoit.vie@meteo.fr>
Date: Mon, 19 Sep 2022 09:22:57 +0200
Subject: [PATCH] bugfix

---
 src/MNH/BASIC.f90                     | 12 ++--
 src/MNH/ini_lima_cold_mixed.f90       |  4 +-
 src/MNH/lima.f90                      | 74 +++++++++++-----------
 src/MNH/lima_ice_aggregation_snow.f90 |  2 +-
 src/MNH/read_exsegn.f90               | 89 +++++++++++++++------------
 src/MNH/sources_neg_correct.f90       | 34 +++++-----
 6 files changed, 112 insertions(+), 103 deletions(-)

diff --git a/src/MNH/BASIC.f90 b/src/MNH/BASIC.f90
index 728fe4558..0ae237052 100644
--- a/src/MNH/BASIC.f90
+++ b/src/MNH/BASIC.f90
@@ -39368,9 +39368,9 @@ IMPLICIT NONE
 !!    EXECUTABLE STATEMENTS
 !!    ---------------------
 ! check if output array is large enough
-!IF (KSPARSEDIM.LT.753) THEN
-!  call Print_msg( NVERB_FATAL, 'GEN', 'CH_SPARSE_AQ', 'array KSPARSE is too small' )
-!END IF
+IF (KSPARSEDIM.LT.753) THEN
+  call Print_msg( NVERB_FATAL, 'GEN', 'CH_SPARSE_AQ', 'array KSPARSE is too small' )
+END IF
 !O3/O3
  KSPARSE(1, 1)=1
  KSPARSE(2, 1)=1
@@ -41684,9 +41684,9 @@ IMPLICIT NONE
 !!    EXECUTABLE STATEMENTS
 !!    ---------------------
 ! check if output array is large enough
-!IF (KSPARSEDIM.LT.457) THEN
-!+  call Print_msg( NVERB_FATAL, 'GEN', 'CH_SPARSE_GAZ', 'array KSPARSE is too small' )
-!END IF
+IF (KSPARSEDIM.LT.457) THEN
+  call Print_msg( NVERB_FATAL, 'GEN', 'CH_SPARSE_GAZ', 'array KSPARSE is too small' )
+END IF
 !O3/O3
  KSPARSE(1, 1)=1
  KSPARSE(2, 1)=1
diff --git a/src/MNH/ini_lima_cold_mixed.f90 b/src/MNH/ini_lima_cold_mixed.f90
index b40d35366..496f53870 100644
--- a/src/MNH/ini_lima_cold_mixed.f90
+++ b/src/MNH/ini_lima_cold_mixed.f90
@@ -341,8 +341,8 @@ IF (GFLAG) THEN
   WRITE(UNIT=ILUOUT0,FMT='(" XLBEXH =",E13.6," XLBH =",E13.6)') XLBEXH,XLBH
 END IF
 !
-XLBDAS_MAX = 500000. * XTRANS_MP_GAMMAS ! LBDAS_MAX doit être compare avec LBDAS avec une forme de Marshall-Palmer
-XLBDAS_MIN = 1000. * XTRANS_MP_GAMMAS
+XLBDAS_MAX = 500000. ! used only before transforming lambda for non MP PSD
+XLBDAS_MIN = 1000. *1.E-10
 XLBDAG_MAX = 100000.0
 !
 ZCONC_MAX  = 1.E6 ! Maximal concentration for falling particules set to 1 per cc
diff --git a/src/MNH/lima.f90 b/src/MNH/lima.f90
index 5de7b55a3..2085d5333 100644
--- a/src/MNH/lima.f90
+++ b/src/MNH/lima.f90
@@ -769,35 +769,35 @@ IF (LWARM .AND. LDEPOC) THEN
 END IF
 !
 !
-Z_RR_CVRC(:,:,:) = 0.
-Z_CR_CVRC(:,:,:) = 0.
-IF (LWARM .AND. LRAIN) THEN
-   if( lbu_enable ) then
-    if ( lbudget_rc ) call Budget_store_init( tbudgets(NBUDGET_RC),                    'R2C1', zrcs(:, :, :) * prhodj(:, :, :) )
-    if ( lbudget_rr ) call Budget_store_init( tbudgets(NBUDGET_RR),                    'R2C1', zrrs(:, :, :) * prhodj(:, :, :) )
-    if ( lbudget_sv .and. nmom_c.ge.2) &
-         call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'R2C1', zccs(:, :, :) * prhodj(:, :, :) )
-    if ( lbudget_sv .and. nmom_r.ge.2) &
-         call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nr), 'R2C1', zcrs(:, :, :) * prhodj(:, :, :) )
-   end if
-
-   CALL LIMA_DROPS_TO_DROPLETS_CONV(PRHODREF, ZRCS*PTSTEP, ZRRS*PTSTEP, ZCCS*PTSTEP, ZCRS*PTSTEP, &
-                                    Z_RR_CVRC, Z_CR_CVRC)
-   !
-   ZRCS(:,:,:) = ZRCS(:,:,:) - Z_RR_CVRC(:,:,:)/PTSTEP
-   ZRRS(:,:,:) = ZRRS(:,:,:) + Z_RR_CVRC(:,:,:)/PTSTEP
-   ZCCS(:,:,:) = ZCCS(:,:,:) - Z_CR_CVRC(:,:,:)/PTSTEP
-   ZCRS(:,:,:) = ZCRS(:,:,:) + Z_CR_CVRC(:,:,:)/PTSTEP
-
-   if( lbu_enable ) then
-    if ( lbudget_rc ) call Budget_store_end( tbudgets(NBUDGET_RC),                    'R2C1', zrcs(:, :, :) * prhodj(:, :, :) )
-    if ( lbudget_rr ) call Budget_store_end( tbudgets(NBUDGET_RR),                    'R2C1', zrrs(:, :, :) * prhodj(:, :, :) )
-    if ( lbudget_sv .and. nmom_c.ge.2) &
-         call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'R2C1', zccs(:, :, :) * prhodj(:, :, :) )
-    if ( lbudget_sv .and. nmom_r.ge.2) &
-         call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nr), 'R2C1', zcrs(:, :, :) * prhodj(:, :, :) )
-   end if
-END IF
+!!$Z_RR_CVRC(:,:,:) = 0.
+!!$Z_CR_CVRC(:,:,:) = 0.
+!!$IF (LWARM .AND. LRAIN) THEN
+!!$   if( lbu_enable ) then
+!!$    if ( lbudget_rc ) call Budget_store_init( tbudgets(NBUDGET_RC),                    'R2C1', zrcs(:, :, :) * prhodj(:, :, :) )
+!!$    if ( lbudget_rr ) call Budget_store_init( tbudgets(NBUDGET_RR),                    'R2C1', zrrs(:, :, :) * prhodj(:, :, :) )
+!!$    if ( lbudget_sv .and. nmom_c.ge.2) &
+!!$         call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'R2C1', zccs(:, :, :) * prhodj(:, :, :) )
+!!$    if ( lbudget_sv .and. nmom_r.ge.2) &
+!!$         call Budget_store_init( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nr), 'R2C1', zcrs(:, :, :) * prhodj(:, :, :) )
+!!$   end if
+!!$
+!!$   CALL LIMA_DROPS_TO_DROPLETS_CONV(PRHODREF, ZRCS*PTSTEP, ZRRS*PTSTEP, ZCCS*PTSTEP, ZCRS*PTSTEP, &
+!!$                                    Z_RR_CVRC, Z_CR_CVRC)
+!!$   !
+!!$   ZRCS(:,:,:) = ZRCS(:,:,:) - Z_RR_CVRC(:,:,:)/PTSTEP
+!!$   ZRRS(:,:,:) = ZRRS(:,:,:) + Z_RR_CVRC(:,:,:)/PTSTEP
+!!$   ZCCS(:,:,:) = ZCCS(:,:,:) - Z_CR_CVRC(:,:,:)/PTSTEP
+!!$   ZCRS(:,:,:) = ZCRS(:,:,:) + Z_CR_CVRC(:,:,:)/PTSTEP
+!!$
+!!$   if( lbu_enable ) then
+!!$    if ( lbudget_rc ) call Budget_store_end( tbudgets(NBUDGET_RC),                    'R2C1', zrcs(:, :, :) * prhodj(:, :, :) )
+!!$    if ( lbudget_rr ) call Budget_store_end( tbudgets(NBUDGET_RR),                    'R2C1', zrrs(:, :, :) * prhodj(:, :, :) )
+!!$    if ( lbudget_sv .and. nmom_c.ge.2) &
+!!$         call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nc), 'R2C1', zccs(:, :, :) * prhodj(:, :, :) )
+!!$    if ( lbudget_sv .and. nmom_r.ge.2) &
+!!$         call Budget_store_end( tbudgets(NBUDGET_SV1 - 1 + nsv_lima_nr), 'R2C1', zcrs(:, :, :) * prhodj(:, :, :) )
+!!$   end if
+!!$END IF
 !
 ! Update variables
 !
@@ -1439,14 +1439,14 @@ DO WHILE(ANY(ZTIME(IIB:IIE,IJB:IJE,IKTB:IKTE)<PTSTEP))
          IITER(I1(II),I2(II),I3(II))     = IITER1D(II)
       END DO
       !
-      IF (NMOM_C.GE.2 .AND. NMOM_R.GE.2) THEN
-         CALL LIMA_DROPS_TO_DROPLETS_CONV(PRHODREF, ZRCT, ZRRT, ZCCT, ZCRT, &
-              Z_RR_CVRC, Z_CR_CVRC    )
-         ZRCT(:,:,:) = ZRCT(:,:,:) - Z_RR_CVRC(:,:,:)
-         ZRRT(:,:,:) = ZRRT(:,:,:) + Z_RR_CVRC(:,:,:)
-         ZCCT(:,:,:) = ZCCT(:,:,:) - Z_CR_CVRC(:,:,:)
-         ZCRT(:,:,:) = ZCRT(:,:,:) + Z_CR_CVRC(:,:,:)
-      END IF
+!!$      IF (NMOM_C.GE.2 .AND. NMOM_R.GE.2) THEN
+!!$         CALL LIMA_DROPS_TO_DROPLETS_CONV(PRHODREF, ZRCT, ZRRT, ZCCT, ZCRT, &
+!!$              Z_RR_CVRC, Z_CR_CVRC    )
+!!$         ZRCT(:,:,:) = ZRCT(:,:,:) - Z_RR_CVRC(:,:,:)
+!!$         ZRRT(:,:,:) = ZRRT(:,:,:) + Z_RR_CVRC(:,:,:)
+!!$         ZCCT(:,:,:) = ZCCT(:,:,:) - Z_CR_CVRC(:,:,:)
+!!$         ZCRT(:,:,:) = ZCRT(:,:,:) + Z_CR_CVRC(:,:,:)
+!!$      END IF
       !
       !***       4.4 Unpacking for budgets
       !
diff --git a/src/MNH/lima_ice_aggregation_snow.f90 b/src/MNH/lima_ice_aggregation_snow.f90
index beb9ac95b..26b230057 100644
--- a/src/MNH/lima_ice_aggregation_snow.f90
+++ b/src/MNH/lima_ice_aggregation_snow.f90
@@ -104,7 +104,7 @@ P_RI_AGGS(:) = 0.
 P_CI_AGGS(:) = 0.
 !
 !
-IF (NMOM_I.EQ.1) THEN 
+IF (NMOM_I.EQ.1) THEN
    WHERE ( PRIT(:)>XRTMIN(4) .AND. PRST(:)>XRTMIN(5) .AND. LDCOMPUTE(:) )
       ZZW1(:) = XFIAGGS * EXP( XCOLEXIS*(PT(:)-XTT) ) &
                         * PRIT(:)                     &
diff --git a/src/MNH/read_exsegn.f90 b/src/MNH/read_exsegn.f90
index 29b1f5791..2d3bddad5 100644
--- a/src/MNH/read_exsegn.f90
+++ b/src/MNH/read_exsegn.f90
@@ -383,9 +383,10 @@ USE MODN_PARAM_ECRAD_n
 USE MODN_PARAM_ICE
 USE MODN_PARAM_KAFR_n
 USE MODN_PARAM_LIMA, ONLY : FINI_CCN=>HINI_CCN,NAM_PARAM_LIMA,NMOD_CCN,LSCAV, &
-                            CPRISTINE_ICE_LIMA, CHEVRIMED_ICE_LIMA, NMOD_IFN, &
+                            CPRISTINE_ICE_LIMA, CHEVRIMED_ICE_LIMA, NMOD_IFN, NMOD_IMM, &
                             LCOLD, LACTI, LNUCL, XALPHAC, XNUC, LMEYERS, LHAIL,&
-                            LPTSPLIT
+                            LPTSPLIT, LSPRO, LADJ, LKHKO, LRAIN, LSNOW, FWARM=>LWARM,&
+                            NMOM_C, NMOM_R, NMOM_I, NMOM_S, NMOM_G, NMOM_H
 USE MODN_PARAM_MFSHALL_n
 USE MODN_PARAM_n    ! realized in subroutine ini_model n
 USE MODN_PARAM_RAD_n
@@ -1243,7 +1244,7 @@ SELECT CASE ( CCLOUD )
       CGETCLOUD = 'READ' ! This is automatically done
     END IF
 !
-    IF (LWARM) THEN
+    IF (FWARM) THEN
       LUSERV=.TRUE. ; LUSERC=.TRUE. ; LUSERR=.TRUE.
       LUSERI=.FALSE.; LUSERS=.FALSE. ; LUSERG=.FALSE.; LUSERH=.FALSE.
     END IF
@@ -1253,25 +1254,57 @@ SELECT CASE ( CCLOUD )
       LUSERI=.TRUE. ; LUSERS=.TRUE. ; LUSERG=.TRUE.
       LUSERH=LHAIL
     END IF
+    !
+    IF (LSPRO) LADJ=.FALSE.
+    IF (.NOT.LRAIN) NMOM_R=0
+    IF (.NOT.LWARM) THEN
+       NMOM_C=0
+       NMOM_R=0
+    END IF
+    IF (.NOT.LSNOW) THEN
+       NMOM_S=0
+       NMOM_G=0
+       NMOM_H=0
+       LHAIL=.FALSE.
+    END IF
+    IF (.NOT.LHAIL) NMOM_H=0
+    IF (.NOT.LCOLD) THEN
+       NMOM_I=0
+       NMOM_S=0
+       NMOM_G=0
+       NMOM_H=0
+       LSNOW=.FALSE.
+       LHAIL=.FALSE.
+       LNUCL=.FALSE.
+       NMOD_IFN=0
+       NMOD_IMM=0
+    END IF
+    IF (.NOT.LPTSPLIT) THEN
+       IF (NMOM_C==1) NMOM_C=2
+       IF (NMOM_R==1) NMOM_R=2
+       IF (NMOM_I==1) NMOM_I=2
+       IF (NMOM_S==2 .OR. NMOM_G==2 .OR. (LHAIL .AND. NMOM_H==2)) THEN
+          NMOM_S=2
+          NMOM_G=2
+          IF (LHAIL) NMOM_H=2
+       END IF
+    END IF
 !
-!!$    IF (LSUBG_COND .AND. LCOLD)  THEN
-!!$      WRITE(UNIT=ILUOUT,FMT=9003) KMI
-!!$      WRITE(UNIT=ILUOUT,FMT=*) 'YOU WANT TO USE BOTH THE SIMPLE MIXED PHASE'
-!!$      WRITE(UNIT=ILUOUT,FMT=*) 'MICROPHYS. SCHEME AND THE SUBGRID COND. SCHEME.'
-!!$      WRITE(UNIT=ILUOUT,FMT=*) 'THIS IS NOT YET AVAILABLE. SET LSUBG_COND '
-!!$      WRITE(UNIT=ILUOUT,FMT=*) 'TO FALSE OR CCLOUD TO "REVE", "KESS" '
-!!$ !callabortstop
-!!$      CALL PRINT_MSG(NVERB_FATAL,'GEN','READ_EXSEG_n','')
-!!$    END IF 
-!
-    IF (CCLOUD == 'LIMA' .AND. LSUBG_COND .AND. (.NOT. LPTSPLIT)) THEN
+    IF (LSUBG_COND .AND. (.NOT. LPTSPLIT)) THEN
       WRITE(UNIT=ILUOUT,FMT=9001) KMI
       WRITE(UNIT=ILUOUT,FMT=*) 'YOU MUST USE LPTSPLIT=T with CCLOUD=LIMA'
       WRITE(UNIT=ILUOUT,FMT=*) 'AND LSUBG_COND '
       CALL PRINT_MSG(NVERB_FATAL,'GEN','READ_EXSEG_n','use LPTSPLIT=T with LIMA and LSUBG_COND=T')
     END IF
+!
+    IF (LSUBG_COND .AND. (.NOT. LADJ)) THEN
+      WRITE(UNIT=ILUOUT,FMT=9001) KMI
+      WRITE(UNIT=ILUOUT,FMT=*) 'YOU MUST USE LADJ=T with CCLOUD=LIMA'
+      WRITE(UNIT=ILUOUT,FMT=*) 'AND LSUBG_COND '
+      CALL PRINT_MSG(NVERB_FATAL,'GEN','READ_EXSEG_n','use LADJ=T with LIMA and LSUBG_COND=T')
+    END IF
 !    
-    IF ( XALPHAC /= 3.0 .OR. XNUC /= 2.0) THEN
+    IF ( LKHKO .AND. (XALPHAC /= 3.0 .OR. XNUC /= 2.0) ) THEN
       WRITE(UNIT=ILUOUT,FMT=9001) KMI
       WRITE(UNIT=ILUOUT,FMT=*) 'IT IS ADVISED TO USE XALPHAC=3. and XNUC=2.'
       WRITE(UNIT=ILUOUT,FMT=*) 'FOR STRATOCUMULUS. '
@@ -1283,31 +1316,7 @@ SELECT CASE ( CCLOUD )
       WRITE(UNIT=ILUOUT,FMT=*) ' IT IS ADVISED TO USE CEFRADL=LIMA '
       WRITE(UNIT=ILUOUT,FMT=*) ' WITH A 2-MOMENT MICROPHYSICAL SCHEME "LIMA"'
     END IF
-
-!UPG*PT
-!    IF (LUSECHEM )  THEN
-!      WRITE(UNIT=ILUOUT,FMT=*) 'YOU WANT TO USE BOTH LIMA MICROPHYS. SCHEME AND CHEMISTRY'
-!      WRITE(UNIT=ILUOUT,FMT=*) 'THIS IS NOT YET AVAILABLE. SET LUSECHEM '
-!      WRITE(UNIT=ILUOUT,FMT=*) 'TO FALSE OR CCLOUD TO "ICE3" '
-! !callabortstop
-!      CALL PRINT_MSG(NVERB_FATAL,'GEN','READ_EXSEG_n','')
-!    END IF 
-!    IF (LDUST )  THEN
-!      WRITE(UNIT=ILUOUT,FMT=*) 'YOU WANT TO USE BOTH LIMA MICROPHYS. SCHEME AND DUSTS '
-!      WRITE(UNIT=ILUOUT,FMT=*) 'THIS IS NOT YET AVAILABLE. SET LDUST '
-!      WRITE(UNIT=ILUOUT,FMT=*) 'TO FALSE OR CCLOUD TO "ICE3" '
-! !callabortstop
-!      CALL PRINT_MSG(NVERB_FATAL,'GEN','READ_EXSEG_n','')
-!    END IF   
-!  IF (LSALT )  THEN
-!      WRITE(UNIT=ILUOUT,FMT=*) 'YOU WANT TO USE BOTH LIMA MICROPHYS. SCHEME AND SEA SALTS '
-!      WRITE(UNIT=ILUOUT,FMT=*) 'THIS IS NOT YET AVAILABLE. SET LSALT '
-!      WRITE(UNIT=ILUOUT,FMT=*) 'TO FALSE OR CCLOUD TO "ICE3" '
-! !callabortstop
-!      CALL PRINT_MSG(NVERB_FATAL,'GEN','READ_EXSEG_n','')
-!    END IF 
-!
-!UPG*PT
+!
 END SELECT
 !
 LUSERV_G(KMI) = LUSERV
diff --git a/src/MNH/sources_neg_correct.f90 b/src/MNH/sources_neg_correct.f90
index 0201f4db2..3e41b1feb 100644
--- a/src/MNH/sources_neg_correct.f90
+++ b/src/MNH/sources_neg_correct.f90
@@ -30,7 +30,7 @@ use modd_cst,        only: xci, xcl, xcpd, xcpv, xlstt, xlvtt, xp00, xrd, xtt
 use modd_nsv,        only: nsv_c2r2beg, nsv_c2r2end, nsv_lima_beg, nsv_lima_end, nsv_lima_nc, nsv_lima_nr,&
                            nsv_lima_ni, nsv_lima_ns, nsv_lima_ng, nsv_lima_nh
 use modd_param_lima, only: lcold_lima => lcold, lrain_lima => lrain, lspro_lima => lspro, lwarm_lima => lwarm, &
-                           xctmin_lima => xctmin, xrtmin_lima => xrtmin, nmom_c, nmom_r, nmom_i, nmom_s, nmom_g, nmom_h
+                           xctmin_lima => xctmin, xrtmin_lima => xrtmin
 
 use mode_budget,         only: Budget_store_init, Budget_store_end
 use mode_msg
@@ -242,7 +242,7 @@ CLOUD: select case ( hcloud )
 ! Correction where rc<0 or Nc<0
      if ( krr.GE.2 ) then
         zmask(:,:,:)=(prrs(:, :, :, 2) < xrtmin_lima(2) / ptstep)
-        if (nmom_c.ge.2) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_nc) < 0. )
+        if (nsv_lima_nc.gt.0) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_nc) < xctmin_lima(2) / ptstep )
         where ( zmask(:,:,:) )
            prrs(:, :, :, 1) = prrs(:, :, :, 1) + prrs(:, :, :, 2)
            prths(:, :, :) = prths(:, :, :) - prrs(:, :, :, 2) * zlv(:, :, :) /  &
@@ -255,28 +255,28 @@ CLOUD: select case ( hcloud )
                 ( zcph(:, :, :) * zexn(:, :, :) )
            prrs(:, :, :, 2) = 0.
         end where
-        if (nmom_c.ge.2) then
+        if (nsv_lima_nc.gt.0) then
            where (prrs(:, :, :, 2) == 0.)  prsvs(:, :, :, nsv_lima_nc) = 0.
         end if
      end if
 ! Correction where rr<0 or Nr<0
-     if ( krr.GE.3 ) then
+     if ( krr.GE.3 .and. hbudname.ne.'NETUR' ) then
         zmask(:,:,:)=(prrs(:, :, :, 3) < xrtmin_lima(3) / ptstep)
-        if (nmom_r.ge.2) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_nr) < 0. )
+        if (nsv_lima_nr.gt.0) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_nr) < xctmin_lima(3) / ptstep )
         where ( zmask(:,:,:) )
            prrs(:, :, :, 1) = prrs(:, :, :, 1) + prrs(:, :, :, 3)
            prths(:, :, :) = prths(:, :, :) - prrs(:, :, :, 3) * zlv(:, :, :) /  &
                 ( zcph(:, :, :) * zexn(:, :, :) )
            prrs(:, :, :, 3)  = 0.
         end where
-        if (nmom_r.ge.2) then
+        if (nsv_lima_nr.gt.0) then
            where (prrs(:, :, :, 3) == 0.)  prsvs(:, :, :, nsv_lima_nr) = 0.
         end if
      end if
 ! Correction where ri<0 or Ni<0
      if ( krr.GE.4 ) then
         zmask(:,:,:)=(prrs(:, :, :, 4) < xrtmin_lima(4) / ptstep)
-        if (nmom_i.ge.2) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_ni) < xctmin_lima(4) / ptstep)
+        if (nsv_lima_ni.gt.0) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_ni) < xctmin_lima(4) / ptstep)
         where ( zmask(:,:,:) )
            prrs(:, :, :, 1) = prrs(:, :, :, 1) + prrs(:, :, :, 4)
            prths(:, :, :) = prths(:, :, :) - prrs(:, :, :, 4) * zls(:, :, :) /  &
@@ -292,49 +292,49 @@ CLOUD: select case ( hcloud )
            prrs(:, :, :, 4) = prrs(:, :, :, 4) - zcor(:, :, :)
         end where
         deallocate( zcor )
-        if (nmom_i.ge.2) then
+        if (nsv_lima_ni.gt.0) then
            where (prrs(:, :, :, 4) == 0.)  prsvs(:, :, :, nsv_lima_ni) = 0.
         end if
      end if
 ! Snow     
-     if ( krr.GE.5 ) then
+     if ( krr.GE.5 .and. hbudname.ne.'NETUR' ) then
         zmask(:,:,:)=(prrs(:, :, :, 5) < xrtmin_lima(5) / ptstep)
-        if (nmom_s.ge.2) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_ns) < 0. )
+        if (nsv_lima_ns.gt.0) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_ns) < xctmin_lima(5) / ptstep )
         where ( zmask(:,:,:) )
            prrs(:, :, :, 1) = prrs(:, :, :, 1) + prrs(:, :, :, 5)
            prths(:, :, :) = prths(:, :, :) - prrs(:, :, :, 5) * zls(:, :, :) /  &
                 ( zcph(:, :, :) * zexn(:, :, :) )
            prrs(:, :, :, 5)  = 0.
         end where
-        if (nmom_s.ge.2) then
+        if (nsv_lima_ns.gt.0) then
            where (prrs(:, :, :, 5) == 0.)  prsvs(:, :, :, nsv_lima_ns) = 0.
         end if
      end if
 ! Graupel
-     if ( krr.GE.6 ) then
+     if ( krr.GE.6 .and. hbudname.ne.'NETUR' ) then
         zmask(:,:,:)=(prrs(:, :, :, 6) < xrtmin_lima(6) / ptstep)
-        if (nmom_g.ge.2) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_ng) < 0. )
+        if (nsv_lima_ng.gt.0) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_ng) < xctmin_lima(6) / ptstep )
         where ( zmask(:,:,:) )
            prrs(:, :, :, 1) = prrs(:, :, :, 1) + prrs(:, :, :, 6)
            prths(:, :, :) = prths(:, :, :) - prrs(:, :, :, 6) * zls(:, :, :) /  &
                 ( zcph(:, :, :) * zexn(:, :, :) )
            prrs(:, :, :, 6)  = 0.
         end where
-        if (nmom_g.ge.2) then
+        if (nsv_lima_ng.gt.0) then
            where (prrs(:, :, :, 6) == 0.)  prsvs(:, :, :, nsv_lima_ng) = 0.
         end if
      end if
 ! Hail
-     if ( krr.GE.7 ) then
+     if ( krr.GE.7 .and. hbudname.ne.'NETUR' ) then
         zmask(:,:,:)=(prrs(:, :, :, 7) < xrtmin_lima(7) / ptstep)
-        if (nmom_h.ge.2) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_nh) < 0. )
+        if (nsv_lima_nh.gt.0) zmask(:,:,:)=(zmask(:,:,:) .or. prsvs(:, :, :, nsv_lima_nh) < xctmin_lima(7) / ptstep )
         where ( zmask(:,:,:) )
            prrs(:, :, :, 1) = prrs(:, :, :, 1) + prrs(:, :, :, 7)
            prths(:, :, :) = prths(:, :, :) - prrs(:, :, :, 7) * zls(:, :, :) /  &
                 ( zcph(:, :, :) * zexn(:, :, :) )
            prrs(:, :, :, 7)  = 0.
         end where
-        if (nmom_h.ge.2) then
+        if (nsv_lima_nh.gt.0) then
            where (prrs(:, :, :, 7) == 0.)  prsvs(:, :, :, nsv_lima_nh) = 0.
         end if
      end if
-- 
GitLab