Newer
Older

WAUTELET Philippe
committed
!MNH_LIC Copyright 1994-2024 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_READ_EXSEG_n
! ######################
!
INTERFACE
!

WAUTELET Philippe
committed
SUBROUTINE READ_EXSEG_n(KMI,TPEXSEGFILE,HCONF,OFLAT,OUSERV, &
OUSERC,OUSERR,OUSERI,OUSECI,OUSERS,OUSERG,OUSERH, &
OUSECHEM,OUSECHAQ,OUSECHIC,OCH_PH,OCH_CONV_LINOX,OSALT, &

Gaelle Tanguy
committed
ODEPOS_SLT, ODUST,ODEPOS_DST, OCHTRANS, &
OORILAM,ODEPOS_AER, OLG,OPASPOL, OFIRE, &
#ifdef MNH_FOREFIRE
OFOREFIRE, &
#endif
OCONDSAMP,OBLOWSNOW, &
KRIMX,KRIMY, KSV_USER, &
HTURB,HTOM,ORMC01,HRAD,HDCONV,HSCONV,HCLOUD,HELEC, &

RODIER Quentin
committed
HEQNSYS,PTSTEP_ALL,HINIFILEPGD )

WAUTELET Philippe
committed
!

WAUTELET Philippe
committed
USE MODD_IO, ONLY: TFILEDATA
USE MODD_PARAMETERS, ONLY: NFILENAMELGTMAX

WAUTELET Philippe
committed
!
INTEGER, INTENT(IN) :: KMI ! Model index

WAUTELET Philippe
committed
TYPE(TFILEDATA), INTENT(IN) :: TPEXSEGFILE ! EXSEG file
! The following variables are read by READ_DESFM in DESFM descriptor :
CHARACTER (LEN=*), INTENT(IN) :: HCONF ! configuration var. linked to FMfile
LOGICAL, INTENT(IN) :: OFLAT ! Logical for zero orography
LOGICAL, INTENT(IN) :: OUSERV,OUSERC,OUSERR,OUSERI,OUSERS, &
OUSERG,OUSERH ! kind of moist variables in
! FMfile
LOGICAL, INTENT(IN) :: OUSECI ! ice concentration in
! FMfile
LOGICAL, INTENT(IN) :: OUSECHEM ! Chemical FLAG in FMFILE
LOGICAL, INTENT(IN) :: OUSECHAQ ! Aqueous chemical FLAG in FMFILE
LOGICAL, INTENT(IN) :: OUSECHIC ! Ice chemical FLAG in FMFILE
LOGICAL, INTENT(IN) :: OCH_PH ! pH FLAG in FMFILE
LOGICAL, INTENT(IN) :: OCH_CONV_LINOX ! LiNOx FLAG in FMFILE
LOGICAL, INTENT(IN) :: ODUST ! Dust FLAG in FMFILE
LOGICAL,DIMENSION(:), INTENT(IN) :: ODEPOS_DST ! Dust wet deposition FLAG in FMFILE
LOGICAL,DIMENSION(:), INTENT(IN) :: ODEPOS_SLT ! Sea Salt wet deposition FLAG in FMFILE
LOGICAL,DIMENSION(:), INTENT(IN) :: ODEPOS_AER ! Orilam wet deposition FLAG in FMFILE
LOGICAL, INTENT(IN) :: OSALT ! Sea Salt FLAG in FMFILE
LOGICAL, INTENT(IN) :: OORILAM ! Orilam FLAG in FMFILE
LOGICAL, INTENT(IN) :: OPASPOL ! Passive pollutant FLAG in FMFILE
LOGICAL, INTENT(IN) :: OFIRE ! Blaze FLAG in FMFILE
#ifdef MNH_FOREFIRE
LOGICAL, INTENT(IN) :: OFOREFIRE ! ForeFire FLAG in FMFILE
#endif
LOGICAL, INTENT(IN) :: OLNOX_EXPLICIT ! explicit LNOx FLAG in FMFILE
LOGICAL, INTENT(IN) :: OCONDSAMP ! Conditional sampling FLAG in FMFILE
LOGICAL, INTENT(IN) :: OBLOWSNOW ! Blowing snow FLAG in FMFILE

Gaelle Tanguy
committed
LOGICAL, INTENT(IN) :: OCHTRANS ! LCHTRANS FLAG in FMFILE
LOGICAL, INTENT(IN) :: OLG ! lagrangian FLAG in FMFILE
INTEGER, INTENT(IN) :: KRIMX, KRIMY ! number of points for the
! horizontal relaxation for the outermost verticals
INTEGER, INTENT(IN) :: KSV_USER ! number of additional scalar
! variables in FMfile
CHARACTER (LEN=*), INTENT(IN) :: HTURB ! Kind of turbulence parameterization
! used to produce FMFILE
CHARACTER (LEN=*), INTENT(IN) :: HTOM ! Kind of third order moment
LOGICAL, INTENT(IN) :: ORMC01 ! flag for RMC01 SBL computations
CHARACTER (LEN=*), INTENT(IN) :: HRAD ! Kind of radiation scheme
CHARACTER (LEN=4), INTENT(IN) :: HDCONV ! Kind of deep convection scheme
CHARACTER (LEN=4), INTENT(IN) :: HSCONV ! Kind of shallow convection scheme
CHARACTER (LEN=4), INTENT(IN) :: HCLOUD ! Kind of microphysical scheme
CHARACTER (LEN=4), INTENT(IN) :: HELEC ! Kind of electrical scheme
CHARACTER (LEN=*), INTENT(IN) :: HEQNSYS! type of equations' system
REAL,DIMENSION(:), INTENT(INOUT):: PTSTEP_ALL ! Time STEP of ALL models

WAUTELET Philippe
committed
CHARACTER (LEN=NFILENAMELGTMAX), INTENT(IN) :: HINIFILEPGD ! name of PGD file
!
END SUBROUTINE READ_EXSEG_n
!
END INTERFACE
!
END MODULE MODI_READ_EXSEG_n
!
!
! #########################################################################

WAUTELET Philippe
committed
SUBROUTINE READ_EXSEG_n(KMI,TPEXSEGFILE,HCONF,OFLAT,OUSERV, &
OUSERC,OUSERR,OUSERI,OUSECI,OUSERS,OUSERG,OUSERH, &
OUSECHEM,OUSECHAQ,OUSECHIC,OCH_PH,OCH_CONV_LINOX,OSALT, &

Gaelle Tanguy
committed
ODEPOS_SLT, ODUST,ODEPOS_DST, OCHTRANS, &
OORILAM,ODEPOS_AER, OLG,OPASPOL, OFIRE, &
#ifdef MNH_FOREFIRE
OFOREFIRE, &
#endif
OCONDSAMP, OBLOWSNOW, &
KRIMX,KRIMY, KSV_USER, &
HTURB,HTOM,ORMC01,HRAD,HDCONV,HSCONV,HCLOUD,HELEC, &

RODIER Quentin
committed
HEQNSYS,PTSTEP_ALL,HINIFILEPGD )
! #########################################################################
!
!!**** *READ_EXSEG_n * - routine to read the descriptor file EXSEG
!!
!! PURPOSE
!! -------
! The purpose of this routine is to read the descriptor file called
! EXSEG and to control the coherence with FMfile data .
!
!!
!!** METHOD
!! ------
!! The descriptor file is read. Namelists (NAMXXXn) which contain
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
!! variables linked to one nested model are at the beginning of the file.
!! Namelists (NAMXXX) which contain variables common to all models
!! are at the end of the file. When the model index is different from 1,
!! the end of the file (namelists NAMXXX) is not read.
!!
!! Coherence between the initial file (description read in DESFM file)
!! and the segment to perform (description read in EXSEG file)
!! is checked for segment achievement configurations
!! or postprocessing configuration. The get indicators are set according
!! to the following check :
!!
!! - segment achievement and preinit configurations :
!!
!! * if there is no turbulence kinetic energy in initial
!! file (HTURB='NONE'), and the segment to perform requires a turbulence
!! parameterization (CTURB /= 'NONE'), the get indicators for turbulence
!! kinetic energy variables are set to 'INIT'; i.e. these variables will be
!! set equal to zero by READ_FIELD according to the get indicators.
!! * The same procedure is applied to the dissipation of TKE.
!! * if there is no moist variables RRn in initial file (OUSERn=.FALSE.)
!! and the segment to perform requires moist variables RRn
!! (LUSERn=.TRUE.), the get indicators for moist variables RRn are set
!! equal to 'INIT'; i.e. these variables will be set equal to zero by
!! READ_FIELD according to the get indicators.
!! * if there are KSV_USER additional scalar variables in initial file and the
!! segment to perform needs more than KSV_USER additional variables, the get
!! indicators for these (NSV_USER-KSV_USER) additional scalar variables are set
!! equal to 'INIT'; i.e. these variables will be set equal to zero by
!! READ_FIELD according to the get indicators. If the segment to perform
!! needs less additional scalar variables than there are in initial file,
!! the get indicators for these (KSV_USER - NSV_USER) additional scalar variables are
!! set equal to 'SKIP'.
!! * warning messages are printed if the fields in initial file are the
!! same at time t and t-dt (HCONF='START') and a leap-frog advance
!! at first time step will be used for the segment to perform
!! (CCONF='RESTA'); It is likewise when HCONF='RESTA' and CCONF='START'.
!! * A warning message is printed if the orography in initial file is zero
!! (OFLAT=.TRUE.) and the segment to perform considers no-zero orography
!! (LFLAT=.FALSE.). It is likewise for LFLAT=.TRUE. and OFLAT=.FALSE..
!! If the segment to perform requires zero orography (LFLAT=.TRUE.), the
!! orography (XZS) will not read in initial file but set equal to zero
!! by SET_GRID.
!! * check of the depths of the Lateral Damping Layer in x and y
!! direction is performed
!! * If some coupling files are specified, LSTEADYLS is set to T
!! * If no coupling files are specified, LSTEADYLS is set to F
!!
!!
!! EXTERNAL
!! --------
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! Module MODN_CONF : CCONF,LTHINSHELL,LFLAT,NMODEL,NVERB
!!
!! Module MODN_DYN : LCORIO, LZDIFFU
!!
!! Module MODN_NESTING : NDAD(m),NDTRATIO(m),XWAY(m)
!!
!! Module MODN_BUDGET : CBUTYPE,XBULEN
!!
!! Module MODN_CONF1 : LUSERV,LUSERC,LUSERR,LUSERI,LUSERS,LUSERG,LUSERH,CSEG
!!
!! Module MODN_DYN1 : XTSTEP,CPRESOPT,NITR,XRELAX
!!
!! Module MODD_ADV1 : CMET_ADV_SCHEME,CSV_ADV_SCHEME,CUVW_ADV_SCHEME,NLITER
!!
!! Module MODN_PARAM1 : CTURB,CRAD,CDCONV,CSCONV
!!
!! Module MODN_LUNIT1 :
!! Module MODN_LBC1 : CLBCX,CLBCY,NLBLX,NLBLY,XCPHASE,XPOND
!!
!! Module MODN_TURB_n : CTURBLEN,CTURBDIM
!!
!! Module MODD_GET1:
!! CGETTKEM,CGETTKET,
!! CGETRVM,CGETRCM,CGETRRM,CGETRIM,CGETRSM,CGETRGM,CGETRHM
!! CGETRVT,CGETRCT,CGETRRT,CGETRIT,CGETRST,CGETRGT,CGETRHT,CGETSVM
!! CGETSVT,CGETSIGS,CGETSRCM,CGETSRCT
!! NCPL_NBR,NCPL_TIMES,NCPL_CUR
!! Module MODN_LES : contains declaration of the control parameters
!! for Large Eddy Simulations' storages
!! for the forcing
!!
!! REFERENCE
!! ---------
!! Book2 of the documentation (routine READ_EXSEG_n)
!!
!!
Loading
Loading full blame...