Skip to content
Snippets Groups Projects
default_desfmn.f90 34.6 KiB
Newer Older
!MNH_LIC Copyright 1994-2020 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 MODI_DEFAULT_DESFM_n
!     ###########################
!
INTERFACE
!
SUBROUTINE DEFAULT_DESFM_n(KMI)
INTEGER,         INTENT(IN)  :: KMI       ! Model index
END SUBROUTINE DEFAULT_DESFM_n
!
END INTERFACE
!
END MODULE MODI_DEFAULT_DESFM_n
!
!
!
!     ###############################
      SUBROUTINE DEFAULT_DESFM_n(KMI)
!     ###############################
!
!!****  *DEFAULT_DESFM_n * - set default values for descriptive variables of
!!                         model KMI
!!
!!    PURPOSE
!!    -------
!       The purpose of this routine is to set default values for the variables
!     in descriptor files by filling the corresponding variables which
!     are stored in modules.
!
!
!!**  METHOD
!!    ------
!!      Each variable in modules, which can be initialized by  reading its
!!    value in the descriptor file is set to a default value.
!!     When this routine is used during INIT, the modules of the first model
!!   are used to temporarily store  the variables associated with a nested
!!   model.
!!     When this routine is used during  SPAWNING, the modules of a second
!!   model must be initialized.
!!     Default values for variables common to all models are set only
!!   at the first call of DEFAULT_DESFM_n (i.e. when KMI=1)
!!
!!
!!    EXTERNAL
!!    --------
!!     NONE
!!
!!    IMPLICIT ARGUMENTS
!!    ------------------
!!      Module MODD_PARAMETERS : JPHEXT,JPVEXT
!!
!!      Module MODD_CONF       : CCONF,L2D,L1D,LFLAT,NMODEL,NVERB
!!
!!      Module MODD_DYN        : XSEGLEN,XASSELIN,LCORIO,LNUMDIFF
!!                               XALKTOP,XALZBOT
!!
!!
!!      Module MODD_NESTING    : NDAD(m),NDTRATIO(m),XWAY(m)
!!
!!      Module MODD_CONF_n    : LUSERV,LUSERC,LUSERR,LUSERI,LUSERS
!!                              LUSERG,LUSERH,CSEG,CEXP
!!
!!      Module MODD_LUNIT_n   : CINIFILE,CCPLFILE
!!
!!
!!      Module MODD_DYN_n     : XTSTEP,CPRESOPT,NITR,XRELAX,LHO_RELAX
!!         LVE_RELAX,XRIMKMAX,NRIMX,NRIMY
!!
!!      Module MODD_ADV_n : CUVW_ADV_SCHEME,CMET_ADV_SCHEME,CSV_ADV_SCHEME,NLITER
!!
!!      Module MODD_PARAM_n : CTURB,CRAD,CDCONV,CSCONV
!!
!!      Module MODD_LBC_n : CLBCX, CLBCY,NLBLX,NLBLY,XCPHASE,XCPHASE_PBL,XPOND
!!
!!      Module MODD_TURB_n : XIMPL,CTURBLEN,CTURBDIM,LTURB_FLX,LTURB_DIAG,LSUBG_COND
!!                           LTGT_FLX
!!
!!
!!      Module MODD_PARAM_RAD_n:
!!          XDTRAD,XDTRAD_CLONLY,LCLEAR_SKY,NRAD_COLNBR, NRAD_DIAG
!!
!!      Module MODD_BUDGET : CBUTYPE,NBUMOD,XBULEN,NBUKL, NBUKH,LBU_KCP,XBUWRI
!!         NBUIL, NBUIH,NBUJL, NBUJH,LBU_ICP,LBU_JCP,NBUMASK
!!
!!      Module MODD_BLANK :
!!
!!          XDUMMYi, NDUMMYi, LDUMMYi, CDUMMYi
!!
!!      Module MODD_FRC :
!!
!!          LGEOST_UV_FRC,LGEOST_TH_FRC,LTEND_THRV_FRC
!!          LVERT_MOTION_FRC,LRELAX_THRV_FRC,LRELAX_UV_FRC,XRELAX_TIME_FRC
!!          XRELAX_HEIGHT_FRC,CRELAX_HEIGHT_TYPE,LTRANS,XUTRANS,XVTRANS,
!!          LPGROUND_FRC
!!
!!      Module MODD_PARAM_ICE :
!!
!!          LWARM,CPRISTINE_ICE
!!
!!      Module MODD_PARAM_KAFR_n :
!!
!!          XDTCONV,LREFRESH_ALL,LDOWN,NICE,LCHTRANS
!!
!!      Module MODD_PARAM_MFSHALL_n :
!!
!!         CMF_UPDRAFT,LMIXUV,CMF_CLOUD,XIMPL_MF,LMF_FLX              
!!
!!
!!
!!
!!    REFERENCE
!!    ---------
!!      Book2 of the documentation (routine DEFAULT_DESFM_n)
!!
!!
!!    AUTHOR
!!    ------
!!      V. Ducrocq       * Meteo France *
!!
!!    MODIFICATIONS
!!    -------------
!!      Original      02/06/94
!!      Modifications 17/10/94  (Stein)  For LCORIO
!!      Modifications 06/12/94  (Stein)  remove LBOUSS+add LABSLAYER, LNUMDIFF
!!                                       ,LSTEADYLS
!!      Modifications 06/12/94  (Stein)  remove LABSLAYER, add LHO_RELAX,
!!                                       LVE_RELAX, NRIMX, NRIMY, XRIMKMAX
!!      Modifications 09/01/95  (Lafore) add LSTEADY_DMASS
!!      Modifications 09/01/95  (Stein)  add the turbulence scheme namelist
!!      Modifications 09/01/95  (Stein)  add the 1D switch
!!      Modifications 10/03/95  (Mallet) add the coupling files
!!                    29/06/95  ( Stein, Nicolau, Hereil) add the budgets
!!      Modifications 25/09/95  ( Stein )add the LES tools
!!      Modifications 25/10/95  ( Stein )add the radiations
!!      Modifications 23/10/95  (Vila, lafore) new scalar advection scheme
!!      Modifications 24/02/96  (Stein)  change the default value for CCPLFILE
!!      Modifications 12/02/96  (Lafore) transformation to DEFAULT_DESFM_n for
!!                                       spawning
!!      Modifications 25/04/96  (Suhre)  add the blank module
!!      Modifications 29/07/96  (Pinty&Suhre) add module MODD_FRC
!!      Modifications 11/04/96  (Pinty)  add the rain-ice scheme and modify
!!                                       the splitted arrays in MODD_PARAM_RAD_n
!!      Modifications 11/01/97  (Pinty)  add the deep convection scheme
!!      Modifications 24/11/96  (Masson)  add LREFRESH_ALL in deep convection
!!      Modifications 12/02/96  (Lafore) transformation to DEFAULT_DESFM_n for spawning
!!      Modifications 22/07/96  (Lafore) gridnesting implementation
!!      Modifications 29/07/96  (Lafore) add the module MODD_FMOUT (renamed MODD_BAKOUT)
!!      Modifications 23/06/97  (Stein)  add the equation system name
!!      Modifications 10/07/97  (Masson) add MODD_PARAM_GROUNDn : CROUGH
!!      Modifications 28/07/97  (Masson) remove LREFRESH_ALL and LSTEADY_DMASS
!!      Modifications 08/10/97  (Stein)  switch (_n=1) to initialize the
!!                                       parameters common to all models
!!      Modifications 24/01/98 (Bechtold) add LREFRESH_ALL, LCHTRANS,
!!                                         LTEND_THRV_FR and LSST_FRC
!!      Modifications 18/07/99  (Stein)  add LRAD_DIAG
!!      Modification  15/03/99 (Masson)  use of XUNDEF
!!      Modification  11/12/00 (Tomasini) Add CSEA_FLUX to MODD_PARAMn
!!      Modification  22/01/01 (Gazen) delete NSV and add LHORELAX_SVC2R2
!!                                     LHORELAX_SVCHEM,LHORELAX_SVLG
!!      Modification 15/03/02 (Solmon) radiation scheme: remove NSPOT and add
!!                                   default for aerosol and cloud rad. prop. control
!!      Modification 22/05/02 (Jabouille) put chimical default here
!!      Modification 01/2004  (Masson) removes surface (externalization)
!!                      09/04 (M. Tomasini) New namelist to modify the
!!                                             Cloud mixing length
!!                   07/05 (P.Tulet) New namelists for dust and aerosol
!!      Modification 01/2007  (Malardel, Pergaud) Add MODD_PARAM_MFSHALL_n
!!      Modification 10/2009  (Aumond) Add user multimasks for LES
!!      Modification 10/2009  (Aumond) Add MEAN_FIELD              
!!      Modification 12/04/07 (Leriche) add LUSECHAQ for aqueous chemistry
!!      Modification 30/05/07 (Leriche) add LCH_PH and XCH_PHINIT for pH
!!      Modification 25/04/08 (Leriche) add XRTMIN_AQ LWC threshold for aq. chemistry
!!                   16/07/10           add LHORELAX_SVIC
!!                   16/09/10           add LUSECHIC
!!                   13/01/11           add LCH_RET_ICE
!!                   01/07/11 (F.Couvreux) Add CONDSAMP
!!                   01/07/11 (B.Aouizerats) Add CAOP    
!!                   07/2013  (Bosseur & Filippi) adds Forefire
!!                   08/2015  (Redelsperger & Pianezze) add XPOND coefficient for LBC
!!      Modification 24/03/16 (Leriche) remove LCH_SURFACE_FLUX 
!!                                      put NCH_VEC_LENGTH = 50 instead of 1000
!!
!!                   04/2016 (C.LAC) negative contribution to the budget splitted between advection, turbulence and microphysics for KHKO/C2R2
Gaelle TANGUY's avatar
Gaelle TANGUY committed
!!      Modification    01/2016  (JP Pinty) Add LIMA
!!      Modification 24/03/16 (Leriche) remove LCH_SURFACE_FLUX 
!!                                      put NCH_VEC_LENGTH = 50 instead of 1000
!!                   10/2016 (C.Lac) VSIGQSAT change from 0 to 0.02 for coherence with AROME
!!                    10/2016 (C.Lac) Add droplet deposition
!!                   10/2016  (R.Honnert and S.Riette) : Improvement of EDKF and adaptation to the grey zone
!!                   10/2016  (F Brosse) add prod/loss terms computation for chemistry
!!                   07/2017  (V. Masson) adds time step for output files writing.
!!                   09/2017 Q.Rodier add LTEND_UV_FRC
Loading
Loading full blame...