Skip to content
Snippets Groups Projects
rain_ice_red.f90 143 KiB
Newer Older
  • Learn to ignore specific revisions
  • !MNH_LIC Copyright 1995-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.
    !-----------------------------------------------------------------
    !     ######spl
           MODULE MODI_RAIN_ICE_RED
    !      ########################
    !
    INTERFACE
          SUBROUTINE RAIN_ICE_RED ( KIT, KJT, KKT, KSIZE,                                 &
                                OSEDIC, HSEDIM, HSUBG_AUCV_RC, HSUBG_AUCV_RI, &
                                OWARM, KKA, KKU, KKL,   &
                                PTSTEP, KRR, ODMICRO, PEXN,             &
                                PDZZ, PRHODJ, PRHODREF, PEXNREF, PPABST, PCIT, PCLDFR,&
                                PHLC_HRC, PHLC_HCF, PHLI_HRI, PHLI_HCF,&
                                PTHT, PRVT, PRCT, PRRT, PRIT, PRST,                   &
                                PRGT, PTHS, PRVS, PRCS, PRRS, PRIS, PRSS, PRGS,       &
                                PINPRC,PINPRR, PEVAP3D,           &
                                PINPRS, PINPRG, PINDEP, PRAINFR, PSIGS, PSEA, PTOWN,  &
                                PRHT, PRHS, PINPRH, PFPR                              )
    !
    !
    INTEGER,                  INTENT(IN)    :: KIT, KJT, KKT ! arrays size
    INTEGER,                  INTENT(IN)    :: KSIZE
    LOGICAL,                  INTENT(IN)    :: OSEDIC ! Switch for droplet sedim.
    CHARACTER(LEN=4),         INTENT(IN)    :: HSEDIM ! Sedimentation scheme
    CHARACTER(LEN=4),         INTENT(IN)    :: HSUBG_AUCV_RC ! Switch for rc->rr Subgrid autoconversion
                                            ! Kind of Subgrid autoconversion method
    CHARACTER(LEN=80),        INTENT(IN)    :: HSUBG_AUCV_RI ! Switch for ri->rs Subgrid autoconversion
                                            ! Kind of Subgrid autoconversion method
    LOGICAL,                  INTENT(IN)    :: OWARM   ! .TRUE. allows raindrops to
                                                       !   form by warm processes
                                                       !      (Kessler scheme)
    !
    INTEGER,                  INTENT(IN)    :: KKA   !near ground array index  
    INTEGER,                  INTENT(IN)    :: KKU   !uppest atmosphere array index
    INTEGER,                  INTENT(IN)    :: KKL   !vert. levels type 1=MNH -1=ARO
    REAL,                     INTENT(IN)    :: PTSTEP  ! Double Time step
                                                       ! (single if cold start)
    INTEGER,                  INTENT(IN)    :: KRR     ! Number of moist variable
    LOGICAL, DIMENSION(:,:,:), INTENT(IN)   :: ODMICRO ! mask to limit computation
    !
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PEXN    ! Exner function
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PDZZ    ! Layer thikness (m)
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRHODJ  ! Dry density * Jacobian
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRHODREF! Reference density
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PEXNREF ! Reference Exner function
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PPABST  ! absolute pressure at t
    !
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PCIT    ! Pristine ice n.c. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PCLDFR  ! Cloud fraction
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLC_HRC
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLC_HCF
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLI_HRI
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLI_HCF
    !
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT    ! Theta at time t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRVT    ! Water vapor m.r. at t 
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRCT    ! Cloud water m.r. at t 
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRRT    ! Rain water m.r. at t 
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRIT    ! Pristine ice m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRST    ! Snow/aggregate m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRGT    ! Graupel/hail m.r. at t
    !
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS    ! Theta source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRVS    ! Water vapor m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRCS    ! Cloud water m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRRS    ! Rain water m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRIS    ! Pristine ice m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRSS    ! Snow/aggregate m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRGS    ! Graupel m.r. source
    
    !
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRC! Cloud instant precip
    REAL, DIMENSION(:,:), INTENT(INOUT)     :: PINDEP  ! Cloud instant deposition
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRR! Rain instant precip
    REAL, DIMENSION(:,:,:), INTENT(OUT)     :: PEVAP3D! Rain evap profile
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRS! Snow instant precip
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRG! Graupel instant precip
    REAL, DIMENSION(:,:,:), INTENT(OUT)     :: PRAINFR! Rain fraction
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PSIGS   ! Sigma_s at t
    REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PSEA ! Sea Mask
    REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PTOWN! Fraction that is town 
    REAL, DIMENSION(:,:,:), OPTIONAL,  INTENT(IN)    :: PRHT    ! Hail m.r. at t
    REAL, DIMENSION(:,:,:), OPTIONAL,  INTENT(INOUT) :: PRHS    ! Hail m.r. source
    REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT)      :: PINPRH! Hail instant precip
    REAL, DIMENSION(:,:,:,:), OPTIONAL, INTENT(OUT)  :: PFPR ! upper-air precipitation fluxes
    !
    END SUBROUTINE RAIN_ICE_RED
    END INTERFACE
    END MODULE MODI_RAIN_ICE_RED
    !     ######spl
          SUBROUTINE RAIN_ICE_RED ( KIT, KJT, KKT, KSIZE,                                 &
                                OSEDIC, HSEDIM, HSUBG_AUCV_RC, HSUBG_AUCV_RI,  &
                                OWARM,KKA,KKU,KKL,&
                                PTSTEP, KRR, ODMICRO, PEXN,                           &
                                PDZZ, PRHODJ, PRHODREF, PEXNREF, PPABST, PCIT, PCLDFR,&
                                PHLC_HRC, PHLC_HCF, PHLI_HRI,  PHLI_HCF,     &
                                PTHT, PRVT, PRCT, PRRT, PRIT, PRST,                   &
                                PRGT, PTHS, PRVS, PRCS, PRRS, PRIS, PRSS, PRGS,       &
                                PINPRC,PINPRR, PEVAP3D,           &
                                PINPRS, PINPRG, PINDEP, PRAINFR, PSIGS, PSEA, PTOWN,  &
                                PRHT, PRHS, PINPRH, PFPR                              )
    !     ######################################################################
    !
    !!****  * -  compute the explicit microphysical sources
    !!
    !!    PURPOSE
    !!    -------
    !!      The purpose of this routine is to compute the slow microphysical sources
    !!    which can be computed explicitly
    !!
    !!
    !!**  METHOD
    !!    ------
    !!      The autoconversion computation follows Kessler (1969).
    !!      The sedimentation rate is computed with a time spliting technique and
    !!    an upstream scheme, written as a difference of non-advective fluxes. This
    !!    source term is added to the future instant ( split-implicit process ).
    !!      The others microphysical processes are evaluated at the central instant
    !!    (split-explicit process ): autoconversion, accretion and rain evaporation.
    !!      These last 3 terms are bounded in order not to create negative values
    !!    for the water species at the future instant.
    !!
    !!    EXTERNAL
    !!    --------
    !!      None
    !!
    !!
    !!    IMPLICIT ARGUMENTS
    !!    ------------------
    !!      Module MODD_PARAMETERS
    !!          JPHEXT       : Horizontal external points number
    !!          JPVEXT       : Vertical external points number
    !!      Module MODD_CONF :
    !!          CCONF configuration of the model for the first time step
    !!      Module MODD_CST
    !!          XP00               ! Reference pressure
    !!          XRD,XRV            ! Gaz  constant for dry air, vapor
    !!          XMD,XMV            ! Molecular weight for dry air, vapor
    !!          XCPD               ! Cpd (dry air)
    !!          XCL                ! Cl (liquid)
    !!          XCI                ! Ci (solid)
    !!          XTT                ! Triple point temperature
    !!          XLVTT              ! Vaporization heat constant
    !!          XALPW,XBETAW,XGAMW ! Constants for saturation vapor pressure
    !!                               function over liquid water
    !!          XALPI,XBETAI,XGAMI ! Constants for saturation vapor pressure
    !!                               function over solid ice
    !!      Module MODD_BUDGET:
    !!         NBUMOD       : model in which budget is calculated
    !!         CBUTYPE      : type of desired budget
    !!                          'CART' for cartesian box configuration
    !!                          'MASK' for budget zone defined by a mask
    !!                          'NONE'  ' for no budget
    !!         LBU_RTH      : logical for budget of RTH (potential temperature)
    !!                        .TRUE. = budget of RTH
    !!                        .FALSE. = no budget of RTH
    !!         LBU_RRV      : logical for budget of RRV (water vapor)
    !!                        .TRUE. = budget of RRV
    !!                        .FALSE. = no budget of RRV
    !!         LBU_RRC      : logical for budget of RRC (cloud water)
    !!                        .TRUE. = budget of RRC
    !!                        .FALSE. = no budget of RRC
    !!         LBU_RRI      : logical for budget of RRI (cloud ice)
    !!                        .TRUE. = budget of RRI
    !!                        .FALSE. = no budget of RRI
    !!         LBU_RRR      : logical for budget of RRR (rain water)
    !!                        .TRUE. = budget of RRR
    !!                        .FALSE. = no budget of RRR
    !!         LBU_RRS      : logical for budget of RRS (aggregates)
    !!                        .TRUE. = budget of RRS
    !!                        .FALSE. = no budget of RRS
    !!         LBU_RRG      : logical for budget of RRG (graupeln)
    !!                        .TRUE. = budget of RRG
    !!                        .FALSE. = no budget of RRG
    !!
    !!    REFERENCE
    !!    ---------
    !!
    !!      Book1 and Book2 of documentation ( routine RAIN_ICE )
    !!
    !!    AUTHOR
    !!    ------
    !!      J.-P. Pinty      * Laboratoire d'Aerologie*
    !!
    !!    MODIFICATIONS
    !!    -------------
    !!      Original    02/11/95
    !!      (J.Viviand) 04/02/97  debug accumulated prcipitation & convert
    !!                            precipitation rate in m/s
    !!      (J.-P. Pinty) 17/02/97  add budget calls
    !!      (J.-P. Pinty) 17/11/97  set ice sedim. for cirrus ice, reset RCHONI
    !!                              and RRHONG, reverse order for DEALLOCATE
    !!      (J.-P. Pinty) 11/02/98  correction of the air dynamical viscosity and
    !!                              add advance of the budget calls
    !!      (J.-P. Pinty) 18/05/98  correction of the air density in the RIAUTS
    !!                              process
    !!      (J.-P. Pinty) 18/11/98  split the main routine
    !!      (V. Masson)   18/11/98  bug in IVEC1 and IVEC2 upper limits
    !!      (J. Escobar & J.-P. Pinty)
    !!                    11/12/98  contains and rewrite count+pack
    !!      (J. Stein & J.-P. Pinty)
    !!                    14/10/99  correction for very small RIT
    !!      (J. Escobar & J.-P. Pinty)
    !!                    24/07/00  correction for very samll m.r. in
    !!                              the sedimentation subroutine
    !!      (M. Tomasini) 11/05/01  Autoconversion of rc into rr modification to take
    !!                              into account the subgrid variance
    !!                              (cf Redelsperger & Sommeria JAS 86)
    !!      (G. Molinie)  21/05/99  bug in RRCFRIG process, RHODREF**(-1) missing
    !!                              in RSRIMCG
    !!      (G. Molinie & J.-P. Pinty)
    !!                    21/06/99  bug in RACCS process
    !!      (P. Jabouille) 27/05/04 safety test for case where esw/i(T)> pabs (~Z>40km)
    !!      (J-.P. Chaboureau) 12/02/05  temperature depending ice-to-snow autocon-
    !                              version threshold (Chaboureau and Pinty GRL 2006)
    !!      (J.-P. Pinty) 01/01/O1  add the hail category and correction of the
    !!                              wet growth rate of the graupeln
    !!      (S.Remy & C.Lac) 06/06 Add the cloud sedimentation
    !!      (S.Remy & C.Lac) 06/06 Sedimentation becoming the last process
    !!      to settle the precipitating species created during the current time step
    !!      (S.Remy & C.Lac) 06/06 Modification of the algorithm of sedimentation
    !!      to settle n times the precipitating species created during Dt/n instead
    !!      of Dt
    !!      (C.Lac) 11/06 Optimization of the sedimentation loop for NEC
    !!      (J.Escobar) 18/01/2008 Parallel Bug in Budget when IMICRO >= 1
    !!                  --> Path inhibit this test by IMICRO >= 0 allway true
    !!      (Y.Seity) 03/2008 Add Statistic sedimentation
    !!      (Y.Seity) 10/2009 Added condition for the raindrop accretion of the aggregates
    !!         into graupeln process (5.2.6) to avoid negative graupel mixing ratio
    !!      (V.Masson, C.Lac) 09/2010 Correction in split sedimentation for
    !!                                reproducibility
    !!      (S. Riette) Oct 2010 Better vectorisation of RAIN_ICE_SEDIMENTATION_STAT
    !!      (Y. Seity), 02-2012  add possibility to run with reversed vertical levels
    !!      (L. Bengtsson), 02-2013 Passing in land/sea mask and town fraction in
    !!                      order to use different cloud droplet number conc. over
    !!                      land, sea and urban areas in the cloud sedimentation.
    !!      (D. Degrauwe), 2013-11: Export upper-air precipitation fluxes PFPR.
    !!      (S. Riette) Nov 2013 Protection against null sigma
    !!      (C. Lac) FIT temporal scheme : instant M removed
    !!      (JP Pinty), 01-2014 : ICE4 : partial reconversion of hail to graupel
    !!              July, 2015 (O.Nuissier/F.Duffourg) Add microphysics diagnostic for
    !!                                      aircraft, ballon and profiler
    !!      J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1
    !!      C.Lac : 10/2016 : add droplet deposition
    !!      C.Lac : 01/2017 : correction on droplet deposition
    !!      J.Escobar : 10/2017 : for real*4 , limit exp() in RAIN_ICE_SLOW with XMNH_HUGE_12_LOG
    !!      (C. Abiven, Y. Léauté, V. Seigner, S. Riette) Phasing of Turner rain subgrid param
    !!      (S. Riette) Source code split into several files
    !!                  02/2019 C.Lac add rain fraction as an output field
    !  P. Wautelet 10/04/2019: replace ABORT and STOP calls by Print_msg
    !  P. Wautelet 28/05/2019: move COUNTJV function to tools.f90
    !  P. Wautelet 29/05/2019: remove PACK/UNPACK intrinsics (to get more performance and better OpenACC support)
    !  P. Wautelet 17/01/2020: move Quicksort to tools.f90
    !  P. Wautelet    02/2020: use the new data structures and subroutines for budgets
    !  P. Wautelet 25/02/2020: bugfix: add missing budget: WETH_BU_RRG
    !-----------------------------------------------------------------
    !
    !*       0.    DECLARATIONS
    !              ------------
    !
    USE PARKIND1, ONLY : JPRB
    USE YOMHOOK , ONLY : LHOOK, DR_HOOK
    
    use modd_budget,         only: lbu_enable,                                                                                     &
                                   lbudget_th, lbudget_rv, lbudget_rc, lbudget_rr, lbudget_ri, lbudget_rs, lbudget_rg, lbudget_rh, &
                                   NBUDGET_TH, NBUDGET_RV, NBUDGET_RC, NBUDGET_RR, NBUDGET_RI, NBUDGET_RS, NBUDGET_RG, NBUDGET_RH, &
                                   tbudgets
    USE MODD_CST,            ONLY: XCI,XCL,XCPD,XCPV,XLSTT,XLVTT,XTT
    USE MODD_PARAMETERS,     ONLY: JPVEXT,XUNDEF
    USE MODD_PARAM_ICE,      ONLY: CSUBG_PR_PDF,CSUBG_RC_RR_ACCR,CSUBG_RR_EVAP,LDEPOSC,LFEEDBACKT,LSEDIM_AFTER, &
                                   NMAXITER,XMRSTEP,XTSTEP_TS,XVDEPOSC
    USE MODD_RAIN_ICE_DESCR, ONLY: XRTMIN
    USE MODD_VAR_ll,         ONLY: IP
    
    use mode_budget,                   only: Budget_store_add, Budget_store_init, Budget_store_end
    USE MODE_ll
    
    #ifdef MNH_OPENACC
    USE MODE_MNH_ZWORK,      ONLY: MNH_MEM_GET, MNH_MEM_POSITION_PIN, MNH_MEM_RELEASE
    #endif
    
    USE MODE_MPPDB
    USE MODE_MSG
    use mode_tools,          only: Countjv
    #ifdef MNH_OPENACC
    use mode_tools,          only: Countjv_device
    #endif
    
    USE MODI_ICE4_NUCLEATION_WRAPPER
    USE MODI_ICE4_RAINFR_VERT
    USE MODI_ICE4_SEDIMENTATION_SPLIT
    USE MODI_ICE4_SEDIMENTATION_STAT
    USE MODI_ICE4_TENDENCIES
    
    IMPLICIT NONE
    !
    !*       0.1   Declarations of dummy arguments :
    !
    !
    !
    INTEGER,                  INTENT(IN)    :: KIT, KJT, KKT ! arrays size
    INTEGER,                  INTENT(IN)    :: KSIZE
    LOGICAL,                  INTENT(IN)    :: OSEDIC ! Switch for droplet sedim.
    CHARACTER(LEN=4),         INTENT(IN)    :: HSEDIM ! Sedimentation scheme
    CHARACTER(LEN=4),         INTENT(IN)    :: HSUBG_AUCV_RC ! Kind of Subgrid autoconversion method
    CHARACTER(LEN=80),        INTENT(IN)    :: HSUBG_AUCV_RI ! Kind of Subgrid autoconversion method
    LOGICAL,                  INTENT(IN)    :: OWARM   ! .TRUE. allows raindrops to
                                                       !   form by warm processes
                                                       !      (Kessler scheme)
    INTEGER,                  INTENT(IN)    :: KKA   !near ground array index
    INTEGER,                  INTENT(IN)    :: KKU   !uppest atmosphere array index
    INTEGER,                  INTENT(IN)    :: KKL   !vert. levels type 1=MNH -1=ARO
    REAL,                     INTENT(IN)    :: PTSTEP  ! Double Time step (single if cold start)
    INTEGER,                  INTENT(IN)    :: KRR     ! Number of moist variable
    LOGICAL, DIMENSION(:,:,:), INTENT(IN)   :: ODMICRO ! mask to limit computation
    !
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PEXN    ! Exner function
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PDZZ    ! Layer thikness (m)
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRHODJ  ! Dry density * Jacobian
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRHODREF! Reference density
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PEXNREF ! Reference Exner function
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PPABST  ! absolute pressure at t
    !
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PCIT    ! Pristine ice n.c. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PCLDFR  ! Convective Mass Flux Cloud fraction
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLC_HRC
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLC_HCF
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLI_HRI
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PHLI_HCF
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PTHT    ! Theta at time t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRVT    ! Water vapor m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRCT    ! Cloud water m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRRT    ! Rain water m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRIT    ! Pristine ice m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRST    ! Snow/aggregate m.r. at t
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PRGT    ! Graupel/hail m.r. at t
    !
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PTHS    ! Theta source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRVS    ! Water vapor m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRCS    ! Cloud water m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRRS    ! Rain water m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRIS    ! Pristine ice m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRSS    ! Snow/aggregate m.r. source
    REAL, DIMENSION(:,:,:),   INTENT(INOUT) :: PRGS    ! Graupel m.r. source
    !
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRC! Cloud instant precip
    REAL, DIMENSION(:,:), INTENT(INOUT)     :: PINDEP  ! Cloud instant deposition
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRR! Rain instant precip
    REAL, DIMENSION(:,:,:), INTENT(OUT)     :: PEVAP3D! Rain evap profile
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRS! Snow instant precip
    REAL, DIMENSION(:,:), INTENT(OUT)       :: PINPRG! Graupel instant precip
    REAL, DIMENSION(:,:,:), INTENT(OUT)     :: PRAINFR! Rain fraction
    REAL, DIMENSION(:,:,:),   INTENT(IN)    :: PSIGS   ! Sigma_s at t
    REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PSEA ! Sea Mask
    REAL, DIMENSION(:,:), OPTIONAL, INTENT(IN) :: PTOWN! Fraction that is town 
    REAL, DIMENSION(:,:,:), OPTIONAL,  INTENT(IN)    :: PRHT    ! Hail m.r. at t
    REAL, DIMENSION(:,:,:), OPTIONAL,  INTENT(INOUT) :: PRHS    ! Hail m.r. source
    REAL, DIMENSION(:,:), OPTIONAL, INTENT(OUT)      :: PINPRH! Hail instant precip
    REAL, DIMENSION(:,:,:,:), OPTIONAL, INTENT(OUT)  :: PFPR ! upper-air precipitation fluxes
    !
    
    #ifdef MNH_COMPILER_CCE
    STOP "RAIN_ICE_RED TROP LENT A COMPILER AVEC CRAY/CCE >> 30 Minutes "
    STOP "ENLEVE LE ifdefMNH_COMPILER_CCE , SI VOUS EN AVEZ BESOIN sur GPU AMD "
    #else
    !
    
    !*       0.2   Declarations of local variables :
    !
    INTEGER :: IIB           !  Define the domain where is
    INTEGER :: IIE           !  the microphysical sources have to be computed
    INTEGER :: IJB           !
    INTEGER :: IJE           !
    INTEGER :: IKB, IKTB     !
    INTEGER :: IKE, IKTE     !
    !
    INTEGER :: IDX, JI, JJ, JK
    INTEGER :: IMICRO ! Case r_x>0 locations
    
    INTEGER, DIMENSION(:), allocatable :: I1,I2,I3 ! Used to replace the COUNT
    INTEGER                             :: JL       ! and PACK intrinsics
    !
    !Arrays for nucleation call outisde of ODMICRO points
    REAL,    DIMENSION(:,:,:), allocatable :: ZW ! work array
    REAL,    DIMENSION(:,:,:), allocatable :: ZT ! Temperature
    REAL, DIMENSION(:,:,:), allocatable :: &
                                      & ZZ_RVHENI_MR, & ! heterogeneous nucleation mixing ratio change
                                      & ZZ_RVHENI       ! heterogeneous nucleation
    real, dimension(:,:,:), allocatable :: zw1, zw2, zw3, zw4, zw5, zw6 !Work arrays
    real, dimension(:,:,:), allocatable :: zz_diff
    REAL, DIMENSION(:,:,:), allocatable :: ZZ_LVFACT, ZZ_LSFACT, ZLSFACT3D
    !
    !Diagnostics
    REAL, DIMENSION(:,:,:), allocatable :: &
                                    & ZHLC_HCF3D,& ! HLCLOUDS cloud fraction in high water content part
                                    & ZHLC_LCF3D,& ! HLCLOUDS cloud fraction in low water content part
                                    & ZHLC_HRC3D,& ! HLCLOUDS cloud water content in high water content
                                    & ZHLC_LRC3D,& ! HLCLOUDS cloud water content in low water content
                                    & ZHLI_HCF3D,& ! HLCLOUDS cloud fraction in high ice content part
                                    & ZHLI_LCF3D,& ! HLCLOUDS cloud fraction in low ice content part
                                    & ZHLI_HRI3D,& ! HLCLOUDS cloud water content in high ice content
                                    & ZHLI_LRI3D   ! HLCLOUDS cloud water content in high ice content
    
    REAL, DIMENSION(:,:), allocatable :: ZINPRI ! Pristine ice instant precip
    !
    !Packed variables
    REAL, DIMENSION(:), allocatable :: ZRVT,     & ! Water vapor m.r. at t
                                     & ZRCT,     & ! Cloud water m.r. at t
                                     & ZRRT,     & ! Rain water m.r. at t
                                     & ZRIT,     & ! Pristine ice m.r. at t
                                     & ZRST,     & ! Snow/aggregate m.r. at t
                                     & ZRGT,     & ! Graupel m.r. at t
                                     & ZRHT,     & ! Hail m.r. at t
                                     & ZCIT,     & ! Pristine ice conc. at t
                                     & ZTHT,     & ! Potential temperature
                                     & ZRHODREF, & ! RHO Dry REFerence
                                     & ZZT,      & ! Temperature
                                     & ZPRES,    & ! Pressure
                                     & ZEXN,     & ! EXNer Pressure
                                     & ZLSFACT,  & ! L_s/(Pi*C_ph)
                                     & ZLVFACT,  & ! L_v/(Pi*C_ph)
                                     & ZSIGMA_RC,& ! Standard deviation of rc at time t
                                     & ZCF,      & ! Cloud fraction
                                     & ZHLC_HCF, & ! HLCLOUDS : fraction of High Cloud Fraction in grid
                                     & ZHLC_LCF, & ! HLCLOUDS : fraction of Low  Cloud Fraction in grid
                                                   !    note that ZCF = ZHLC_HCF + ZHLC_LCF
                                     & ZHLC_HRC, & ! HLCLOUDS : LWC that is High LWC in grid
                                     & ZHLC_LRC, & ! HLCLOUDS : LWC that is Low  LWC in grid
                                                   !    note that ZRC = ZHLC_HRC + ZHLC_LRC
                                     & ZHLI_HCF, &
                                     & ZHLI_LCF, &
                                     & ZHLI_HRI, &
                                     & ZHLI_LRI
    !
    !Output packed tendencies (for budgets only)
    REAL, DIMENSION(:), allocatable :: ZRVHENI_MR, & ! heterogeneous nucleation mixing ratio change
                                     & ZRCHONI, & ! Homogeneous nucleation
                                     & ZRRHONG_MR, & ! Spontaneous freezing mixing ratio change
                                     & ZRVDEPS, & ! Deposition on r_s,
                                     & ZRIAGGS, & ! Aggregation on r_s
                                     & ZRIAUTS, & ! Autoconversion of r_i for r_s production
                                     & ZRVDEPG, & ! Deposition on r_g
                                     & ZRCAUTR,  & ! Autoconversion of r_c for r_r production
                                     & ZRCACCR, & ! Accretion of r_c for r_r production
                                     & ZRREVAV, & ! Evaporation of r_r
                                     & ZRIMLTC_MR, & ! Cloud ice melting mixing ratio change
                                     & ZRCBERI, & ! Bergeron-Findeisen effect
                                     & ZRHMLTR, & ! Melting of the hailstones
                                     & ZRSMLTG, & ! Conversion-Melting of the aggregates
                                     & ZRCMLTSR, & ! Cloud droplet collection onto aggregates by positive temperature
                                     & ZRRACCSS, ZRRACCSG, ZRSACCRG, & ! Rain accretion onto the aggregates
                                     & ZRCRIMSS, ZRCRIMSG, ZRSRIMCG, ZRSRIMCG_MR, & ! Cloud droplet riming of the aggregates
                                     & ZRICFRRG, ZRRCFRIG, ZRICFRR, & ! Rain contact freezing
                                     & ZRCWETG, ZRIWETG, ZRRWETG, ZRSWETG, &  ! Graupel wet growth
                                     & ZRCDRYG, ZRIDRYG, ZRRDRYG, ZRSDRYG, &  ! Graupel dry growth
                                     & ZRWETGH, & ! Conversion of graupel into hail
                                     & ZRWETGH_MR, & ! Conversion of graupel into hail, mr change
                                     & ZRGMLTR, & ! Melting of the graupel
                                     & ZRCWETH, ZRIWETH, ZRSWETH, ZRGWETH, ZRRWETH, & ! Dry growth of hailstone
                                     & ZRCDRYH, ZRIDRYH, ZRSDRYH, ZRRDRYH, ZRGDRYH, & ! Wet growth of hailstone
                                     & ZRDRYHG    ! Conversion of hailstone into graupel
    !
    !Output packed total mixing ratio change (for budgets only)
    REAL, DIMENSION(:), allocatable :: ZTOT_RVHENI, & ! heterogeneous nucleation mixing ratio change
                                     & ZTOT_RCHONI, & ! Homogeneous nucleation
                                     & ZTOT_RRHONG, & ! Spontaneous freezing mixing ratio change
                                     & ZTOT_RVDEPS, & ! Deposition on r_s,
                                     & ZTOT_RIAGGS, & ! Aggregation on r_s
                                     & ZTOT_RIAUTS, & ! Autoconversion of r_i for r_s production
                                     & ZTOT_RVDEPG, & ! Deposition on r_g
                                     & ZTOT_RCAUTR,  & ! Autoconversion of r_c for r_r production
                                     & ZTOT_RCACCR, & ! Accretion of r_c for r_r production
                                     & ZTOT_RREVAV, & ! Evaporation of r_r
                                     & ZTOT_RCRIMSS, ZTOT_RCRIMSG, ZTOT_RSRIMCG, & ! Cloud droplet riming of the aggregates
                                     & ZTOT_RIMLTC, & ! Cloud ice melting mixing ratio change
                                     & ZTOT_RCBERI, & ! Bergeron-Findeisen effect
                                     & ZTOT_RHMLTR, & ! Melting of the hailstones
                                     & ZTOT_RSMLTG, & ! Conversion-Melting of the aggregates
                                     & ZTOT_RCMLTSR, & ! Cloud droplet collection onto aggregates by positive temperature
                                     & ZTOT_RRACCSS, ZTOT_RRACCSG, ZTOT_RSACCRG, & ! Rain accretion onto the aggregates
                                     & ZTOT_RICFRRG, ZTOT_RRCFRIG, ZTOT_RICFRR, & ! Rain contact freezing
                                     & ZTOT_RCWETG, ZTOT_RIWETG, ZTOT_RRWETG, ZTOT_RSWETG, &  ! Graupel wet growth
                                     & ZTOT_RCDRYG, ZTOT_RIDRYG, ZTOT_RRDRYG, ZTOT_RSDRYG, &  ! Graupel dry growth
                                     & ZTOT_RWETGH, & ! Conversion of graupel into hail
                                     & ZTOT_RGMLTR, & ! Melting of the graupel
                                     & ZTOT_RCWETH, ZTOT_RIWETH, ZTOT_RSWETH, ZTOT_RGWETH, ZTOT_RRWETH, & ! Dry growth of hailstone
                                     & ZTOT_RCDRYH, ZTOT_RIDRYH, ZTOT_RSDRYH, ZTOT_RRDRYH, ZTOT_RGDRYH, & ! Wet growth of hailstone
                                     & ZTOT_RDRYHG    ! Conversion of hailstone into graupel
    !
    !For time- or mixing-ratio- splitting
    REAL, DIMENSION(:), allocatable :: Z0RVT,     &   ! Water vapor m.r. at the beginig of the current loop
                                     & Z0RCT,     &   ! Cloud water m.r. at the beginig of the current loop
                                     & Z0RRT,     &   ! Rain water m.r. at the beginig of the current loop
                                     & Z0RIT,     &   ! Pristine ice m.r. at the beginig of the current loop
                                     & Z0RST,     &   ! Snow/aggregate m.r. at the beginig of the current loop
                                     & Z0RGT,     &   ! Graupel m.r. at the beginig of the current loop
                                     & Z0RHT,     &   ! Hail m.r. at the beginig of the current loop
                                     & ZA_TH, ZA_RV, ZA_RC, ZA_RR, ZA_RI, ZA_RS, ZA_RG, ZA_RH, &
                                     & ZB_TH, ZB_RV, ZB_RC, ZB_RR, ZB_RI, ZB_RS, ZB_RG, ZB_RH
    !
    !To take into acount external tendencies inside the splitting
    REAL, DIMENSION(:), allocatable :: ZEXT_RV,   &   ! External tendencie for rv
                                       ZEXT_RC,   &   ! External tendencie for rc
                                       ZEXT_RR,   &   ! External tendencie for rr
                                       ZEXT_RI,   &   ! External tendencie for ri
                                       ZEXT_RS,   &   ! External tendencie for rs
                                       ZEXT_RG,   &   ! External tendencie for rg
                                       ZEXT_RH,   &   ! External tendencie for rh
                                       ZEXT_TH        ! External tendencie for th
    LOGICAL :: GEXT_TEND
    !
    INTEGER, DIMENSION(:), allocatable :: IITER ! Number of iterations done (with real tendencies computation)
    INTEGER :: INB_ITER_MAX ! Maximum number of iterations (with real tendencies computation)
    REAL, DIMENSION(:), allocatable :: ZTIME,    & ! Current integration time (starts with 0 and ends with PTSTEP)
                                     & ZMAXTIME, & ! Time on which we can apply the current tendencies
                                     & ZTIME_THRESHOLD, & ! Time to reach threshold
                                     & ZTIME_LASTCALL     ! Integration time when last tendecies call has been done
    REAL, DIMENSION(:), allocatable :: ZW1D
    REAL, DIMENSION(:), allocatable :: ZCOMPUTE ! Points where we must compute tendenceis
    LOGICAL :: GSOFT ! Must we really compute tendencies or only adjust them to new T variables
    LOGICAL, DIMENSION(:,:,:), allocatable :: GDNOTMICRO ! = .NOT.ODMICRO
    REAL :: ZTSTEP ! length of sub-timestep in case of time splitting
    REAL :: ZINV_TSTEP ! Inverse ov PTSTEP
    REAL, DIMENSION(:,:), allocatable :: ZRS_TEND
    REAL, DIMENSION(:,:), allocatable :: ZRG_TEND
    REAL, DIMENSION(:,:), allocatable :: ZRH_TEND
    REAL, DIMENSION(:),   allocatable :: ZSSI
    !
    !For total tendencies computation
    REAL, DIMENSION(:,:,:), allocatable :: &
    
            &ZW_RVS, ZW_RCS, ZW_RRS, ZW_RIS, ZW_RSS, ZW_RGS, ZW_RHS, ZW_THS
    
    REAL, DIMENSION(:,:,:), allocatable :: ZTEMP_BUD
    #else
    INTEGER, DIMENSION(:), POINTER, CONTIGUOUS :: I1,I2,I3 ! Used to replace the COUNT
    INTEGER                                    :: JL       ! and PACK intrinsics
    
    !Arrays for nucleation call outisde of ODMICRO points
    REAL,    DIMENSION(:,:,:), POINTER, CONTIGUOUS :: ZW ! work array
    REAL,    DIMENSION(:,:,:), POINTER, CONTIGUOUS :: ZT ! Temperature
    REAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: &
                                      & ZZ_RVHENI_MR, & ! heterogeneous nucleation mixing ratio change
                                      & ZZ_RVHENI       ! heterogeneous nucleation
    real, dimension(:,:,:), POINTER, CONTIGUOUS :: zw1, zw2, zw3, zw4, zw5, zw6 !Work arrays
    real, dimension(:,:,:), POINTER, CONTIGUOUS :: zz_diff
    REAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: ZZ_LVFACT, ZZ_LSFACT, ZLSFACT3D
    
    !Diagnostics
    REAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: &
                                    & ZHLC_HCF3D,& ! HLCLOUDS cloud fraction in high water content part
                                    & ZHLC_LCF3D,& ! HLCLOUDS cloud fraction in low water content part
                                    & ZHLC_HRC3D,& ! HLCLOUDS cloud water content in high water content
                                    & ZHLC_LRC3D,& ! HLCLOUDS cloud water content in low water content
                                    & ZHLI_HCF3D,& ! HLCLOUDS cloud fraction in high ice content part
                                    & ZHLI_LCF3D,& ! HLCLOUDS cloud fraction in low ice content part
                                    & ZHLI_HRI3D,& ! HLCLOUDS cloud water content in high ice content
                                    & ZHLI_LRI3D   ! HLCLOUDS cloud water content in high ice content
    
    REAL, DIMENSION(:,:), POINTER, CONTIGUOUS :: ZINPRI ! Pristine ice instant precip
    !
    !Packed variables
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZRVT,     & ! Water vapor m.r. at t
                                               ZRCT,     & ! Cloud water m.r. at t
                                               ZRRT,     & ! Rain water m.r. at t
                                               ZRIT,     & ! Pristine ice m.r. at t
                                               ZRST,     & ! Snow/aggregate m.r. at t
                                               ZRGT,     & ! Graupel m.r. at t
                                               ZRHT,     & ! Hail m.r. at t
                                               ZCIT,     & ! Pristine ice conc. at t
                                               ZTHT,     & ! Potential temperature
                                               ZRHODREF, & ! RHO Dry REFerence
                                               ZZT,      & ! Temperature
                                               ZPRES,    & ! Pressure
                                               ZEXN,     & ! EXNer Pressure
                                               ZLSFACT,  & ! L_s/(Pi*C_ph)
                                               ZLVFACT,  & ! L_v/(Pi*C_ph)
                                               ZSIGMA_RC,& ! Standard deviation of rc at time t
                                               ZCF,      & ! Cloud fraction
                                               ZHLC_HCF, & ! HLCLOUDS : fraction of High Cloud Fraction in grid
                                               ZHLC_LCF, & ! HLCLOUDS : fraction of Low  Cloud Fraction in grid
                                                           !    note that ZCF = ZHLC_HCF + ZHLC_LCF
                                               ZHLC_HRC, & ! HLCLOUDS : LWC that is High LWC in grid
                                               ZHLC_LRC, & ! HLCLOUDS : LWC that is Low  LWC in grid
                                                           !    note that ZRC = ZHLC_HRC + ZHLC_LRC
                                               ZHLI_HCF, &
                                               ZHLI_LCF, &
                                               ZHLI_HRI, &
                                               ZHLI_LRI
    !
    !Output packed tendencies (for budgets only)
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZRVHENI_MR, & ! heterogeneous nucleation mixing ratio change
                                               ZRCHONI, & ! Homogeneous nucleation
                                               ZRRHONG_MR, & ! Spontaneous freezing mixing ratio change
                                               ZRVDEPS, & ! Deposition on r_s,
                                               ZRIAGGS, & ! Aggregation on r_s
                                               ZRIAUTS, & ! Autoconversion of r_i for r_s production
                                               ZRVDEPG, & ! Deposition on r_g
                                               ZRCAUTR,  & ! Autoconversion of r_c for r_r production
                                               ZRCACCR, & ! Accretion of r_c for r_r production
                                               ZRREVAV, & ! Evaporation of r_r
                                               ZRIMLTC_MR, & ! Cloud ice melting mixing ratio change
                                               ZRCBERI, & ! Bergeron-Findeisen effect
                                               ZRHMLTR, & ! Melting of the hailstones
                                               ZRSMLTG, & ! Conversion-Melting of the aggregates
                                               ZRCMLTSR, & ! Cloud droplet collection onto aggregates by positive temperature
                                               ZRRACCSS, ZRRACCSG, ZRSACCRG, & ! Rain accretion onto the aggregates
                                               ZRCRIMSS, ZRCRIMSG, ZRSRIMCG, ZRSRIMCG_MR, & ! Cloud droplet riming of the aggregates
                                               ZRICFRRG, ZRRCFRIG, ZRICFRR, & ! Rain contact freezing
                                               ZRCWETG, ZRIWETG, ZRRWETG, ZRSWETG, &  ! Graupel wet growth
                                               ZRCDRYG, ZRIDRYG, ZRRDRYG, ZRSDRYG, &  ! Graupel dry growth
                                               ZRWETGH, & ! Conversion of graupel into hail
                                               ZRWETGH_MR, & ! Conversion of graupel into hail, mr change
                                               ZRGMLTR, & ! Melting of the graupel
                                               ZRCWETH, ZRIWETH, ZRSWETH, ZRGWETH, ZRRWETH, & ! Dry growth of hailstone
                                               ZRCDRYH, ZRIDRYH, ZRSDRYH, ZRRDRYH, ZRGDRYH, & ! Wet growth of hailstone
                                               ZRDRYHG    ! Conversion of hailstone into graupel
    !
    !Output packed total mixing ratio change (for budgets only)
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZTOT_RVHENI, & ! heterogeneous nucleation mixing ratio change
                                               ZTOT_RCHONI, & ! Homogeneous nucleation
                                               ZTOT_RRHONG, & ! Spontaneous freezing mixing ratio change
                                               ZTOT_RVDEPS, & ! Deposition on r_s,
                                               ZTOT_RIAGGS, & ! Aggregation on r_s
                                               ZTOT_RIAUTS, & ! Autoconversion of r_i for r_s production
                                               ZTOT_RVDEPG, & ! Deposition on r_g
                                               ZTOT_RCAUTR,  & ! Autoconversion of r_c for r_r production
                                               ZTOT_RCACCR, & ! Accretion of r_c for r_r production
                                               ZTOT_RREVAV, & ! Evaporation of r_r
                                               ZTOT_RCRIMSS, ZTOT_RCRIMSG, ZTOT_RSRIMCG, & ! Cloud droplet riming of the aggregates
                                               ZTOT_RIMLTC, & ! Cloud ice melting mixing ratio change
                                               ZTOT_RCBERI, & ! Bergeron-Findeisen effect
                                               ZTOT_RHMLTR, & ! Melting of the hailstones
                                               ZTOT_RSMLTG, & ! Conversion-Melting of the aggregates
                                               ZTOT_RCMLTSR, & ! Cloud droplet collection onto aggregates by positive temperature
                                               ZTOT_RRACCSS, ZTOT_RRACCSG, ZTOT_RSACCRG, & ! Rain accretion onto the aggregates
                                               ZTOT_RICFRRG, ZTOT_RRCFRIG, ZTOT_RICFRR, & ! Rain contact freezing
                                               ZTOT_RCWETG, ZTOT_RIWETG, ZTOT_RRWETG, ZTOT_RSWETG, &  ! Graupel wet growth
                                               ZTOT_RCDRYG, ZTOT_RIDRYG, ZTOT_RRDRYG, ZTOT_RSDRYG, &  ! Graupel dry growth
                                               ZTOT_RWETGH, & ! Conversion of graupel into hail
                                               ZTOT_RGMLTR, & ! Melting of the graupel
                                               ZTOT_RCWETH, ZTOT_RIWETH, ZTOT_RSWETH, ZTOT_RGWETH, ZTOT_RRWETH, & ! Dry growth of hailstone
                                               ZTOT_RCDRYH, ZTOT_RIDRYH, ZTOT_RSDRYH, ZTOT_RRDRYH, ZTOT_RGDRYH, & ! Wet growth of hailstone
                                               ZTOT_RDRYHG    ! Conversion of hailstone into graupel
    !
    !For time- or mixing-ratio- splitting
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: Z0RVT,     &   ! Water vapor m.r. at the beginig of the current loop
                                               Z0RCT,     &   ! Cloud water m.r. at the beginig of the current loop
                                               Z0RRT,     &   ! Rain water m.r. at the beginig of the current loop
                                               Z0RIT,     &   ! Pristine ice m.r. at the beginig of the current loop
                                               Z0RST,     &   ! Snow/aggregate m.r. at the beginig of the current loop
                                               Z0RGT,     &   ! Graupel m.r. at the beginig of the current loop
                                               Z0RHT,     &   ! Hail m.r. at the beginig of the current loop
                                               ZA_TH, ZA_RV, ZA_RC, ZA_RR, ZA_RI, ZA_RS, ZA_RG, ZA_RH, &
                                               ZB_TH, ZB_RV, ZB_RC, ZB_RR, ZB_RI, ZB_RS, ZB_RG, ZB_RH
    !
    !To take into acount external tendencies inside the splitting
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZEXT_RV,   &   ! External tendencie for rv
                                               ZEXT_RC,   &   ! External tendencie for rc
                                               ZEXT_RR,   &   ! External tendencie for rr
                                               ZEXT_RI,   &   ! External tendencie for ri
                                               ZEXT_RS,   &   ! External tendencie for rs
                                               ZEXT_RG,   &   ! External tendencie for rg
                                               ZEXT_RH,   &   ! External tendencie for rh
                                               ZEXT_TH        ! External tendencie for th
    LOGICAL :: GEXT_TEND
    !
    INTEGER, DIMENSION(:), POINTER, CONTIGUOUS :: IITER ! Number of iterations done (with real tendencies computation)
    INTEGER :: INB_ITER_MAX ! Maximum number of iterations (with real tendencies computation)
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZTIME,    & ! Current integration time (starts with 0 and ends with PTSTEP)
                                               ZMAXTIME, & ! Time on which we can apply the current tendencies
                                               ZTIME_THRESHOLD, & ! Time to reach threshold
                                               ZTIME_LASTCALL     ! Integration time when last tendecies call has been done
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZW1D
    REAL, DIMENSION(:), POINTER, CONTIGUOUS :: ZCOMPUTE ! Points where we must compute tendenceis
    LOGICAL :: GSOFT ! Must we really compute tendencies or only adjust them to new T variables
    LOGICAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: GDNOTMICRO ! = .NOT.ODMICRO
    REAL :: ZTSTEP ! length of sub-timestep in case of time splitting
    REAL :: ZINV_TSTEP ! Inverse ov PTSTEP
    REAL, DIMENSION(:,:), POINTER, CONTIGUOUS :: ZRS_TEND
    REAL, DIMENSION(:,:), POINTER, CONTIGUOUS :: ZRG_TEND
    REAL, DIMENSION(:,:), POINTER, CONTIGUOUS :: ZRH_TEND
    REAL, DIMENSION(:),   POINTER, CONTIGUOUS :: ZSSI
    !
    !For total tendencies computation
    REAL, DIMENSION(:,:,:), POINTER, CONTIGUOUS :: &
            &ZW_RVS, ZW_RCS, ZW_RRS, ZW_RIS, ZW_RSS, ZW_RGS, ZW_RHS, ZW_THS
    !
    REAL, DIMENSION(:,:,:), pointer, contiguous :: ZTEMP_BUD
    
    !
    LOGICAL :: GTEST ! temporary variable for OpenACC character limitation (Cray CCE)
    
    !$acc data present( ODMICRO, PEXN, PDZZ, PRHODJ, PRHODREF, PEXNREF, PPABST, PCIT, PCLDFR, &
    !$acc &             PHLC_HRC, PTHT, PRVT,                                                 &
    !$acc &             PRCT, PHLC_HCF, PHLI_HRI, PHLI_HCF, PRRT, PRIT, PRST, PRGT, PSIGS,    &
    !$acc &             PTHS, PRVS, PRCS, PRRS, PRIS, PRSS, PRGS,                             &
    !$acc &             PINPRC, PINDEP, PINPRR, PEVAP3D, PINPRS, PINPRG, PRAINFR,             &
    !$acc &             PSEA, PTOWN, PRHT, PRHS, PINPRH, PFPR )
    
    IF (MPPDB_INITIALIZED) THEN
      !Check all IN arrays
      CALL MPPDB_CHECK(ODMICRO,"RAIN_ICE_RED beg:ODMICRO")
      CALL MPPDB_CHECK(PEXN,"RAIN_ICE_RED beg:PEXN")
      CALL MPPDB_CHECK(PDZZ,"RAIN_ICE_RED beg:PDZZ")
      CALL MPPDB_CHECK(PRHODJ,"RAIN_ICE_RED beg:PRHODJ")
      CALL MPPDB_CHECK(PRHODREF,"RAIN_ICE_RED beg:PRHODREF")
      CALL MPPDB_CHECK(PEXNREF,"RAIN_ICE_RED beg:PEXNREF")
      CALL MPPDB_CHECK(PPABST,"RAIN_ICE_RED beg:PPABST")
      CALL MPPDB_CHECK(PCLDFR,"RAIN_ICE_RED beg:PCLDFR")
      CALL MPPDB_CHECK(PHLC_HRC,"RAIN_ICE_RED beg:PHLC_HRC")
      CALL MPPDB_CHECK(PHLC_HCF,"RAIN_ICE_RED beg:PHLC_HCF")
      CALL MPPDB_CHECK(PHLI_HRI,"RAIN_ICE_RED beg:PHLI_HRI")
      CALL MPPDB_CHECK(PHLI_HCF,"RAIN_ICE_RED beg:PHLI_HCF")
      CALL MPPDB_CHECK(PTHT,"RAIN_ICE_RED beg:PTHT")
      CALL MPPDB_CHECK(PRVT,"RAIN_ICE_RED beg:PRVT")
      CALL MPPDB_CHECK(PRCT,"RAIN_ICE_RED beg:PRCT")
      CALL MPPDB_CHECK(PRRT,"RAIN_ICE_RED beg:PRRT")
      CALL MPPDB_CHECK(PRIT,"RAIN_ICE_RED beg:PRIT")
      CALL MPPDB_CHECK(PRST,"RAIN_ICE_RED beg:PRST")
      CALL MPPDB_CHECK(PRGT,"RAIN_ICE_RED beg:PRGT")
      CALL MPPDB_CHECK(PSIGS,"RAIN_ICE_RED beg:PSIGS")
      IF (PRESENT(PSEA)) CALL MPPDB_CHECK(PSEA,"RAIN_ICE_RED beg:PSEA")
      IF (PRESENT(PTOWN)) CALL MPPDB_CHECK(PTOWN,"RAIN_ICE_RED beg:PTOWN")
      IF (PRESENT(PRHT)) CALL MPPDB_CHECK(PRHT,"RAIN_ICE_RED beg:PRHT")
      !Check all INOUT arrays
      CALL MPPDB_CHECK(PCIT,"RAIN_ICE_RED beg:PCIT")
      CALL MPPDB_CHECK(PTHS,"RAIN_ICE_RED beg:PTHS")
      CALL MPPDB_CHECK(PRVS,"RAIN_ICE_RED beg:PRVS")
      CALL MPPDB_CHECK(PRCS,"RAIN_ICE_RED beg:PRCS")
      CALL MPPDB_CHECK(PRRS,"RAIN_ICE_RED beg:PRRS")
      CALL MPPDB_CHECK(PRIS,"RAIN_ICE_RED beg:PRIS")
      CALL MPPDB_CHECK(PRSS,"RAIN_ICE_RED beg:PRSS")
      CALL MPPDB_CHECK(PRGS,"RAIN_ICE_RED beg:PRGS")
      CALL MPPDB_CHECK(PINDEP,"RAIN_ICE_RED beg:PINDEP")
      IF (PRESENT(PRHS)) CALL MPPDB_CHECK(PRHS,"RAIN_ICE_RED beg:PRHS")
    END IF
    
    !$acc kernels
    imicro = count(odmicro)
    !$acc end kernels
    
    
    JIU = SIZE( ptht, 1 )
    JJU = SIZE( ptht, 2 )
    JKU = SIZE( ptht, 3 )
    
    allocate( i1(imicro ) )
    allocate( i2(imicro ) )
    allocate( i3(imicro ) )
    
    allocate( zw(size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) )
    allocate( zt(size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) ) )
    
    
    allocate( zz_rvheni_mr(jiu, jju, jku ) )
    allocate( zz_rvheni   (jiu, jju, jku ) )
    allocate( zz_lvfact   (jiu, jju, jku ) )
    allocate( zz_lsfact   (jiu, jju, jku ) )
    allocate( zlsfact3d   (jiu, jju, jku ) )
    
    allocate( ZHLC_HCF3D(jiu, jju, jku ) )
    allocate( ZHLC_LCF3D(jiu, jju, jku ) )
    allocate( ZHLC_HRC3D(jiu, jju, jku ) )
    allocate( ZHLC_LRC3D(jiu, jju, jku ) )
    allocate( ZHLI_HCF3D(jiu, jju, jku ) )
    allocate( ZHLI_LCF3D(jiu, jju, jku ) )
    allocate( ZHLI_HRI3D(jiu, jju, jku ) )
    allocate( ZHLI_LRI3D(jiu, jju, jku ) )
    
    
    allocate( zrvt     (imicro ) )
    allocate( zrct     (imicro ) )
    allocate( zrrt     (imicro ) )
    allocate( zrit     (imicro ) )
    allocate( zrst     (imicro ) )
    allocate( zrgt     (imicro ) )
    allocate( zrht     (imicro ) )
    allocate( zcit     (imicro ) )
    allocate( ztht     (imicro ) )
    allocate( zrhodref (imicro ) )
    allocate( zzt      (imicro ) )
    allocate( zpres    (imicro ) )
    allocate( zexn     (imicro ) )
    allocate( zlsfact  (imicro ) )
    allocate( zlvfact  (imicro ) )
    allocate( zsigma_rc(imicro ) )
    allocate( zcf      (imicro ) )
    allocate( zhlc_hcf (imicro ) )
    allocate( zhlc_lcf (imicro ) )
    allocate( zhlc_hrc (imicro ) )
    allocate( zhlc_lrc (imicro ) )
    allocate( ZHLI_HCF (imicro ) )
    allocate( ZHLI_LCF (imicro ) )
    allocate( ZHLI_HRI (imicro ) )
    allocate( ZHLI_LRI (imicro ) )
    
    allocate( zrvheni_mr (imicro ) )
    allocate( zrchoni    (imicro ) )
    allocate( zrrhong_mr (imicro ) )
    allocate( zrvdeps    (imicro ) )
    allocate( zriaggs    (imicro ) )
    allocate( zriauts    (imicro ) )
    allocate( zrvdepg    (imicro ) )
    allocate( zrcautr    (imicro ) )
    allocate( zrcaccr    (imicro ) )
    allocate( zrrevav    (imicro ) )
    allocate( zrimltc_mr (imicro ) )
    allocate( zrcberi    (imicro ) )
    allocate( zrhmltr    (imicro ) )
    allocate( zrsmltg    (imicro ) )
    allocate( zrcmltsr   (imicro ) )
    allocate( zrraccss   (imicro ) )
    allocate( zrraccsg   (imicro ) )
    allocate( zrsaccrg   (imicro ) )
    allocate( zrcrimss   (imicro ) )
    allocate( zrcrimsg   (imicro ) )
    allocate( zrsrimcg   (imicro ) )
    allocate( zrsrimcg_mr(imicro ) )
    allocate( zricfrrg   (imicro ) )
    allocate( zrrcfrig   (imicro ) )
    allocate( zricfrr    (imicro ) )
    allocate( zrcwetg    (imicro ) )
    allocate( zriwetg    (imicro ) )
    allocate( zrrwetg    (imicro ) )
    allocate( zrswetg    (imicro ) )
    allocate( zrcdryg    (imicro ) )
    allocate( zridryg    (imicro ) )
    allocate( zrrdryg    (imicro ) )
    allocate( zrsdryg    (imicro ) )
    allocate( zrwetgh    (imicro ) )
    allocate( zrwetgh_mr (imicro ) )
    allocate( zrgmltr    (imicro ) )
    allocate( zrcweth    (imicro ) )
    allocate( zriweth    (imicro ) )
    allocate( zrsweth    (imicro ) )
    allocate( zrgweth    (imicro ) )
    allocate( zrrweth    (imicro ) )
    allocate( zrcdryh    (imicro ) )
    allocate( zridryh    (imicro ) )
    allocate( zrsdryh    (imicro ) )
    allocate( zrrdryh    (imicro ) )
    allocate( zrgdryh    (imicro ) )
    allocate( zrdryhg    (imicro ) )
    
    allocate( ztot_rvheni (imicro ) )
    allocate( ztot_rchoni (imicro ) )
    allocate( ztot_rrhong (imicro ) )
    allocate( ztot_rvdeps (imicro ) )
    allocate( ztot_riaggs (imicro ) )
    allocate( ztot_riauts (imicro ) )
    allocate( ztot_rvdepg (imicro ) )
    allocate( ztot_rcautr (imicro ) )
    allocate( ztot_rcaccr (imicro ) )
    allocate( ztot_rrevav (imicro ) )
    allocate( ztot_rcrimss(imicro ) )
    allocate( ztot_rcrimsg(imicro ) )
    allocate( ztot_rsrimcg(imicro ) )
    allocate( ztot_rimltc (imicro ) )
    allocate( ztot_rcberi (imicro ) )
    allocate( ztot_rhmltr (imicro ) )
    allocate( ztot_rsmltg (imicro ) )
    allocate( ztot_rcmltsr(imicro ) )
    allocate( ztot_rraccss(imicro ) )
    allocate( ztot_rraccsg(imicro ) )
    allocate( ztot_rsaccrg(imicro ) )
    allocate( ztot_ricfrrg(imicro ) )
    allocate( ztot_rrcfrig(imicro ) )
    allocate( ztot_ricfrr (imicro ) )
    allocate( ztot_rcwetg (imicro ) )
    allocate( ztot_riwetg (imicro ) )
    allocate( ztot_rrwetg (imicro ) )
    allocate( ztot_rswetg (imicro ) )
    allocate( ztot_rcdryg (imicro ) )
    allocate( ztot_ridryg (imicro ) )
    allocate( ztot_rrdryg (imicro ) )
    allocate( ztot_rsdryg (imicro ) )
    allocate( ztot_rwetgh (imicro ) )
    allocate( ztot_rgmltr (imicro ) )
    allocate( ztot_rcweth (imicro ) )
    allocate( ztot_riweth (imicro ) )
    allocate( ztot_rsweth (imicro ) )
    allocate( ztot_rgweth (imicro ) )
    allocate( ztot_rrweth (imicro ) )
    allocate( ztot_rcdryh (imicro ) )
    allocate( ztot_rdryhg (imicro ) )
    allocate( ztot_ridryh (imicro ) )
    allocate( ztot_rsdryh (imicro ) )
    allocate( ztot_rrdryh (imicro ) )
    allocate( ztot_rgdryh (imicro ) )
    
    allocate( z0rvt(imicro ) )
    allocate( z0rct(imicro ) )
    allocate( z0rrt(imicro ) )
    allocate( z0rit(imicro ) )
    allocate( z0rst(imicro ) )
    allocate( z0rgt(imicro ) )
    allocate( z0rht(imicro ) )
    allocate( za_th(imicro ) )
    allocate( za_rv(imicro ) )
    allocate( za_rc(imicro ) )
    allocate( za_rr(imicro ) )
    allocate( za_ri(imicro ) )
    allocate( za_rs(imicro ) )
    allocate( za_rg(imicro ) )
    allocate( za_rh(imicro ) )
    allocate( zb_th(imicro ) )
    allocate( zb_rv(imicro ) )
    allocate( zb_rc(imicro ) )
    allocate( zb_rr(imicro ) )
    allocate( zb_ri(imicro ) )
    allocate( zb_rs(imicro ) )
    allocate( zb_rg(imicro ) )
    allocate( zb_rh(imicro ) )
    
    allocate( zext_rv(imicro ) )
    allocate( zext_rc(imicro ) )
    allocate( zext_rr(imicro ) )
    allocate( zext_ri(imicro ) )
    allocate( zext_rs(imicro ) )
    allocate( zext_rg(imicro ) )
    allocate( zext_rh(imicro ) )
    allocate( zext_th(imicro ) )
    
    allocate( iiter(imicro ) )
    
    allocate( ztime(imicro ) )
    allocate( zmaxtime(imicro ) )
    allocate( ztime_threshold(imicro ) )
    allocate( ztime_lastcall(imicro ) )
    
    allocate( zw1d    (imicro ) )
    allocate( zcompute(imicro ) )
    
    allocate( gdnotmicro(size( odmicro, 1 ), size( odmicro, 2 ), size( odmicro, 3 ) ) )
    
    allocate( zrs_tend(imicro, 8  ) )
    allocate( zrg_tend(imicro, 8  ) )
    allocate( zrh_tend(imicro, 10 ) )
    
    allocate( zssi(imicro ) )
    
    
    allocate( zw_rvs(jiu, jju, jku ) )
    allocate( zw_rcs(jiu, jju, jku ) )
    allocate( zw_rrs(jiu, jju, jku ) )
    allocate( zw_ris(jiu, jju, jku ) )
    allocate( zw_rss(jiu, jju, jku ) )
    allocate( zw_rgs(jiu, jju, jku ) )
    allocate( zw_rhs(jiu, jju, jku ) )
    allocate( zw_ths(jiu, jju, jku ) )
    
    allocate( ZTEMP_BUD(JIU,JJU,JKU) )
    #else
    !Pin positions in the pools of MNH memory
    CALL MNH_MEM_POSITION_PIN()
    
    CALL MNH_MEM_GET( i1, imicro )
    CALL MNH_MEM_GET( i2, imicro )
    CALL MNH_MEM_GET( i3, imicro )
    
    CALL MNH_MEM_GET( zw, size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) )
    CALL MNH_MEM_GET( zt, size( pexnref, 1 ), size( pexnref, 2 ), size( pexnref, 3 ) )
    
    
    CALL MNH_MEM_GET( zz_rvheni_mr, jiu, jju, jku )
    CALL MNH_MEM_GET( zz_rvheni,    jiu, jju, jku )
    CALL MNH_MEM_GET( zz_lvfact,    jiu, jju, jku )
    CALL MNH_MEM_GET( zz_lsfact,    jiu, jju, jku )
    CALL MNH_MEM_GET( zlsfact3d,    jiu, jju, jku )
    
    CALL MNH_MEM_GET( ZHLC_HCF3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLC_LCF3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLC_HRC3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLC_LRC3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLI_HCF3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLI_LCF3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLI_HRI3D, jiu, jju, jku )
    CALL MNH_MEM_GET( ZHLI_LRI3D, jiu, jju, jku )
    
    
    CALL MNH_MEM_GET( zrvt     , imicro )
    CALL MNH_MEM_GET( zrct     , imicro )
    CALL MNH_MEM_GET( zrrt     , imicro )
    CALL MNH_MEM_GET( zrit     , imicro )
    CALL MNH_MEM_GET( zrst     , imicro )
    CALL MNH_MEM_GET( zrgt     , imicro )
    CALL MNH_MEM_GET( zrht     , imicro )
    CALL MNH_MEM_GET( zcit     , imicro )
    CALL MNH_MEM_GET( ztht     , imicro )
    CALL MNH_MEM_GET( zrhodref , imicro )
    CALL MNH_MEM_GET( zzt      , imicro )
    CALL MNH_MEM_GET( zpres    , imicro )
    CALL MNH_MEM_GET( zexn     , imicro )
    CALL MNH_MEM_GET( zlsfact  , imicro )
    CALL MNH_MEM_GET( zlvfact  , imicro )
    CALL MNH_MEM_GET( zsigma_rc, imicro )
    CALL MNH_MEM_GET( zcf      , imicro )
    CALL MNH_MEM_GET( zhlc_hcf , imicro )
    CALL MNH_MEM_GET( zhlc_lcf , imicro )
    CALL MNH_MEM_GET( zhlc_hrc , imicro )
    CALL MNH_MEM_GET( zhlc_lrc , imicro )
    CALL MNH_MEM_GET( ZHLI_HCF , imicro )