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

Philippe 18/03/2021: use JPSVNAMELGTMAX parameter for scalar variable names

parent d7eb19c4
No related branches found
No related tags found
No related merge requests found
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 2002-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 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.
!----------------------------------------------------------------- !-----------------------------------------------------------------
!--------------- special set of characters for RCS information
!-----------------------------------------------------------------
! $Source$ $Revision$
! MASDEV4_7 modd 2006/06/27 13:57:12
!-----------------------------------------------------------------
! ####################### ! #######################
MODULE MODD_ELEC_DESCR MODULE MODD_ELEC_DESCR
! ####################### ! #######################
...@@ -42,6 +37,8 @@ ...@@ -42,6 +37,8 @@
!* 0. DECLARATIONS !* 0. DECLARATIONS
! ------------ ! ------------
! !
USE MODD_PARAMETERS, ONLY: JPSVNAMELGTMAX
IMPLICIT NONE IMPLICIT NONE
! !
! Namelist ! Namelist
...@@ -161,7 +158,7 @@ INTEGER :: NNB_CG ! Nb of CG flashes ...@@ -161,7 +158,7 @@ INTEGER :: NNB_CG ! Nb of CG flashes
INTEGER :: NNB_CG_POS ! Nb of positive CG flashes INTEGER :: NNB_CG_POS ! Nb of positive CG flashes
REAL :: XALT_CG ! Altitude (m) at which CG are detected REAL :: XALT_CG ! Altitude (m) at which CG are detected
! !
CHARACTER(LEN=10), DIMENSION(8) & CHARACTER(LEN=JPSVNAMELGTMAX), DIMENSION(8) &
:: CELECNAMES=(/'QNIONP','QCELEC','QRELEC','QIELEC','QSELEC', & :: CELECNAMES=(/'QNIONP','QCELEC','QRELEC','QIELEC','QSELEC', &
'QGELEC','QHELEC','QNIONN'/) 'QGELEC','QHELEC','QNIONN'/)
! QNIONP (QNIONN): Positive (Negative) ion concentration ! QNIONP (QNIONN): Positive (Negative) ion concentration
......
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 2000-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 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.
!----------------------------------------------------------------- !-----------------------------------------------------------------
!--------------- special set of characters for RCS information
!-----------------------------------------------------------------
! $Source$ $Revision$
! MASDEV4_7 modd 2006/05/18 13:07:25
!-----------------------------------------------------------------
! ########################## ! ##########################
MODULE MODD_ICE_C1R3_DESCR MODULE MODD_ICE_C1R3_DESCR
! ########################## ! ##########################
...@@ -53,6 +48,7 @@ ...@@ -53,6 +48,7 @@
!! J.-P. Pinty 29/11/02 add C1R3NAMES !! J.-P. Pinty 29/11/02 add C1R3NAMES
!! !!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
USE MODD_PARAMETERS, ONLY: JPSVNAMELGTMAX
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
! ------------ ! ------------
...@@ -77,8 +73,8 @@ REAL,SAVE :: XLBEXG,XLBG ! Graupel distribution parameters ...@@ -77,8 +73,8 @@ REAL,SAVE :: XLBEXG,XLBG ! Graupel distribution parameters
REAL,SAVE :: XLBDAS_MAX,XLBDAG_MAX ! Max values allowed for the shape REAL,SAVE :: XLBDAS_MAX,XLBDAG_MAX ! Max values allowed for the shape
! parameters (snow,graupeln) ! parameters (snow,graupeln)
! !
CHARACTER(LEN=10),DIMENSION(2),PARAMETER & CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(2),PARAMETER &
:: C1R3NAMES=(/'CICE ','CIN '/) :: C1R3NAMES=(/'CICE','CIN '/)
! basenames of the SV articles stored ! basenames of the SV articles stored
! in the binary files ! in the binary files
! !
......
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 2001-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 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.
!----------------------------------------------------------------- !-----------------------------------------------------------------
!--------------- special set of characters for RCS information
!-----------------------------------------------------------------
! $Source$ $Revision$
! MASDEV4_7 modd 2006/05/18 13:07:25
!-----------------------------------------------------------------
! ############## ! ##############
MODULE MODD_LG MODULE MODD_LG
! ############## ! ##############
...@@ -31,11 +26,14 @@ ...@@ -31,11 +26,14 @@
!! ------------- !! -------------
!! Original 27/06/2001 !! Original 27/06/2001
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
USE MODD_PARAMETERS, ONLY: JPSVNAMELGTMAX
IMPLICIT NONE
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
! ------------ ! ------------
! !
CHARACTER(LEN=10),DIMENSION(3),PARAMETER :: CLGNAMES=(/'LGX','LGY','LGZ'/) CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(3),PARAMETER :: CLGNAMES=(/'LGX','LGY','LGZ'/)
! basenames of the lagrangian articles stored ! basenames of the lagrangian articles stored
! in the binary files ! in the binary files
REAL,PARAMETER :: XLG1MIN=-1.E+9, XLG2MIN=-1.E+9, XLG3MIN=0. REAL,PARAMETER :: XLG1MIN=-1.E+9, XLG2MIN=-1.E+9, XLG3MIN=0.
......
!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.
!-----------------------------------------------------------------
! ########################### ! ###########################
MODULE MODD_PARAM_LIMA_COLD MODULE MODD_PARAM_LIMA_COLD
! ########################### ! ###########################
...@@ -16,6 +21,7 @@ ...@@ -16,6 +21,7 @@
!! Original ??/??/13 !! Original ??/??/13
!! !!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
USE MODD_PARAMETERS, ONLY: JPSVNAMELGTMAX
! !
IMPLICIT NONE IMPLICIT NONE
! !
...@@ -48,7 +54,7 @@ REAL,SAVE :: XAS,XBS,XCS,XDS,XCCS,XCXS,XF0S,XF1S,XC1S ! Snow/agg. charact. ...@@ -48,7 +54,7 @@ REAL,SAVE :: XAS,XBS,XCS,XDS,XCCS,XCXS,XF0S,XF1S,XC1S ! Snow/agg. charact.
REAL,SAVE :: XLBDAS_MAX ! Max values allowed for the shape REAL,SAVE :: XLBDAS_MAX ! Max values allowed for the shape
! parameter of snow ! parameter of snow
! !
CHARACTER(LEN=8),DIMENSION(5),PARAMETER & CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(5),PARAMETER &
:: CLIMA_COLD_NAMES=(/'CICE ','CIFNFREE','CIFNNUCL', & :: CLIMA_COLD_NAMES=(/'CICE ','CIFNFREE','CIFNNUCL', &
'CCNINIMM','CCCNNUCL'/) 'CCNINIMM','CCCNNUCL'/)
! basenames of the SV articles stored ! basenames of the SV articles stored
...@@ -57,7 +63,7 @@ CHARACTER(LEN=8),DIMENSION(5),PARAMETER & ...@@ -57,7 +63,7 @@ CHARACTER(LEN=8),DIMENSION(5),PARAMETER &
! IN:Ice-nuclei Nucleated (activated IFN by Dep/Cond) ! IN:Ice-nuclei Nucleated (activated IFN by Dep/Cond)
! NI:Nuclei Immersed (activated IFN by Imm) ! NI:Nuclei Immersed (activated IFN by Imm)
! HF:Homogeneous Freezing ! HF:Homogeneous Freezing
CHARACTER(LEN=3),DIMENSION(5),PARAMETER & CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(5),PARAMETER &
:: CLIMA_COLD_CONC=(/'NI ','NIF','NIN','NNI','NNH'/)!for DIAG :: CLIMA_COLD_CONC=(/'NI ','NIF','NIN','NNI','NNH'/)!for DIAG
! !
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
......
!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.
!-----------------------------------------------------------------
! ########################### ! ###########################
MODULE MODD_PARAM_LIMA_WARM MODULE MODD_PARAM_LIMA_WARM
! ########################### ! ###########################
...@@ -16,6 +21,7 @@ ...@@ -16,6 +21,7 @@
!! Original ??/??/13 !! Original ??/??/13
!! !!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
USE MODD_PARAMETERS, ONLY: JPSVNAMELGTMAX
! !
IMPLICIT NONE IMPLICIT NONE
! !
...@@ -30,17 +36,17 @@ REAL,SAVE :: XAR,XBR,XCR,XDR,XF0R,XF1R, & ! Raindrop charact. ...@@ -30,17 +36,17 @@ REAL,SAVE :: XAR,XBR,XCR,XDR,XF0R,XF1R, & ! Raindrop charact.
XAC,XBC,XCC,XDC,XF0C,XF2C,XC1C ! Cloud droplet charact. XAC,XBC,XCC,XDC,XF0C,XF2C,XC1C ! Cloud droplet charact.
! !
! !
CHARACTER(LEN=8),DIMENSION(4),PARAMETER & CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(4),PARAMETER &
:: CLIMA_WARM_NAMES=(/'CCLOUD ','CRAIN ','CCCNFREE','CCCNACTI'/) :: CLIMA_WARM_NAMES=(/'CCLOUD ','CRAIN ','CCCNFREE','CCCNACTI'/)
! basenames of the SV articles stored ! basenames of the SV articles stored
! in the binary files ! in the binary files
CHARACTER(LEN=5),DIMENSION(4),PARAMETER & CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(4),PARAMETER &
:: CLIMA_WARM_CONC=(/'NC ','NR ','NFREE','NCCN '/) :: CLIMA_WARM_CONC=(/'NC ','NR ','NFREE','NCCN '/)
! ! basenames of the SV articles stored ! ! basenames of the SV articles stored
! ! in the binary files for DIAG ! ! in the binary files for DIAG
! !
!* Special issue for Below-Cloud SCAVenging of Aerosol particles !* Special issue for Below-Cloud SCAVenging of Aerosol particles
CHARACTER(LEN=6),DIMENSION(2) :: CAERO_MASS =(/'MASSAP', 'MAP '/) CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(2) :: CAERO_MASS =(/'MASSAP', 'MAP '/)
! !
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
......
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 2000-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 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.
!----------------------------------------------------------------- !-----------------------------------------------------------------
!--------------- special set of characters for RCS information
!-----------------------------------------------------------------
! $Source$ $Revision$
! MASDEV4_7 modd 2006/05/18 13:07:25
!-----------------------------------------------------------------
! ########################### ! ###########################
MODULE MODD_RAIN_C2R2_DESCR MODULE MODD_RAIN_C2R2_DESCR
! ########################### ! ###########################
...@@ -50,6 +45,7 @@ ...@@ -50,6 +45,7 @@
!! J.-P. Pinty 29/11/02 add cloud doplet fall speed parameters !! J.-P. Pinty 29/11/02 add cloud doplet fall speed parameters
!! !!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
USE MODD_PARAMETERS, ONLY: JPSVNAMELGTMAX
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
! ------------ ! ------------
...@@ -66,7 +62,7 @@ REAL,DIMENSION(:),SAVE,ALLOCATABLE :: XCTMIN ...@@ -66,7 +62,7 @@ REAL,DIMENSION(:),SAVE,ALLOCATABLE :: XCTMIN
REAL,SAVE :: XLBC, XLBEXC, & ! shape parameters of the cloud droplets REAL,SAVE :: XLBC, XLBEXC, & ! shape parameters of the cloud droplets
XLBR, XLBEXR ! shape parameters of the raindrops XLBR, XLBEXR ! shape parameters of the raindrops
! !
CHARACTER(LEN=10),DIMENSION(4),PARAMETER & CHARACTER(LEN=JPSVNAMELGTMAX),DIMENSION(4),PARAMETER &
:: C2R2NAMES=(/'CCCN ','CCLOUD','CRAIN ','SUPSAT'/) :: C2R2NAMES=(/'CCCN ','CCLOUD','CRAIN ','SUPSAT'/)
! basenames of the SV articles stored ! basenames of the SV articles stored
! in the binary files ! in the binary files
......
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