Skip to content
Snippets Groups Projects
Commit c2a04d11 authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 01/12/2023: resolved_cloud: allocate electricity arrays only if...

Philippe 01/12/2023: resolved_cloud: allocate electricity arrays only if needed + remove 3 unused arrays
parent 27f9a017
No related branches found
No related tags found
No related merge requests found
!MNH_LIC Copyright 1994-2021 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 1994-2023 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 This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1. !MNH_LIC for details. version 1.
...@@ -501,16 +501,13 @@ LOGICAL :: GWEST,GEAST,GNORTH,GSOUTH ...@@ -501,16 +501,13 @@ LOGICAL :: GWEST,GEAST,GNORTH,GSOUTH
LOGICAL :: LMFCONV ! =SIZE(PMFCONV)!=0 LOGICAL :: LMFCONV ! =SIZE(PMFCONV)!=0
! BVIE work array waiting for PINPRI ! BVIE work array waiting for PINPRI
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2)):: ZINPRI REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2)):: ZINPRI
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)):: ZICEFR
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)):: ZPRCFR
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)):: ZTM
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2)) :: ZSIGQSAT2D REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2)) :: ZSIGQSAT2D
TYPE(DIMPHYEX_t) :: YLDIMPHYEX TYPE(DIMPHYEX_t) :: YLDIMPHYEX
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)):: ZDUM REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)):: ZDUM
! !
! variables for cloud electricity ! variables for cloud electricity
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)) :: ZCND, ZDEP REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZCND, ZDEP
REAL, DIMENSION(SIZE(PZZ,1),SIZE(PZZ,2),SIZE(PZZ,3)) :: ZRCS_BEF, ZRIS_BEF REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZRCS_BEF, ZRIS_BEF
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZQCT, ZQRT, ZQIT, ZQST, ZQGT, ZQHT, ZQPIT, ZQNIT REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZQCT, ZQRT, ZQIT, ZQST, ZQGT, ZQHT, ZQPIT, ZQNIT
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZQCS, ZQRS, ZQIS, ZQSS, ZQGS, ZQHS, ZQPIS, ZQNIS REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZQCS, ZQRS, ZQIS, ZQSS, ZQGS, ZQHS, ZQPIS, ZQNIS
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLATHAM_IAGGS ! E Function to simulate REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLATHAM_IAGGS ! E Function to simulate
...@@ -848,6 +845,13 @@ SELECT CASE ( HCLOUD ) ...@@ -848,6 +845,13 @@ SELECT CASE ( HCLOUD )
! !
allocate( zexn( size( pzz, 1 ), size( pzz, 2 ), size( pzz, 3 ) ) ) allocate( zexn( size( pzz, 1 ), size( pzz, 2 ), size( pzz, 3 ) ) )
ZEXN(:,:,:)= (PPABST(:,:,:)/CST%XP00)**(CST%XRD/CST%XCPD) ZEXN(:,:,:)= (PPABST(:,:,:)/CST%XP00)**(CST%XRD/CST%XCPD)
IF (HELEC == 'ELE4') THEN
ALLOCATE( ZCND (SIZE(PZZ,1), SIZE(PZZ,2), SIZE(PZZ,3)) )
ALLOCATE( ZDEP (SIZE(PZZ,1), SIZE(PZZ,2), SIZE(PZZ,3)) )
ALLOCATE( ZRCS_BEF(SIZE(PZZ,1), SIZE(PZZ,2), SIZE(PZZ,3)) )
ALLOCATE( ZRIS_BEF(SIZE(PZZ,1), SIZE(PZZ,2), SIZE(PZZ,3)) )
END IF
! !
!* 9.1 Compute the explicit microphysical sources !* 9.1 Compute the explicit microphysical sources
! !
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment