Newer
Older

WAUTELET Philippe
committed
!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

WAUTELET Philippe
committed
!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_INI_MODEL_n
! #######################
!
INTERFACE
!

WAUTELET Philippe
committed
SUBROUTINE INI_MODEL_n(KMI,TPINIFILE)

WAUTELET Philippe
committed
USE MODD_IO, ONLY: TFILEDATA

WAUTELET Philippe
committed
INTEGER, INTENT(IN) :: KMI ! Model Index
TYPE(TFILEDATA), INTENT(IN) :: TPINIFILE ! Initial file
!
END SUBROUTINE INI_MODEL_n
!
END INTERFACE
!
END MODULE MODI_INI_MODEL_n

WAUTELET Philippe
committed
! ############################################

WAUTELET Philippe
committed
SUBROUTINE INI_MODEL_n(KMI,TPINIFILE)

WAUTELET Philippe
committed
! ############################################
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
!
!!**** *INI_MODEL_n* - routine to initialize the nested model _n
!!
!! PURPOSE
!! -------
! The purpose of this routine is to initialize the variables
! of the nested model _n.
!
!!** METHOD
!! ------
!! The initialization of the model _n is performed as follows :
!! - Memory for arrays are then allocated :
!! * If turbulence kinetic energy variable is not needed
!! (CTURB='NONE'), XTKET, XTKEM and XTKES are zero-size arrays.
!! * If dissipation of TKE variable is not needed
!! (CTURBLEN /='KEPS'), XEPST, XEPSM and XREPSS are zero-size arrays.
!! * Memory for mixing ratio arrays is allocated according to the
!! value of logicals LUSERn (the number NRR of moist variables is deduced).
!! * The latitude (XLAT), longitude (XLON) and map factor (XMAP)
!! arrays are zero-size arrays if Cartesian geometry (LCARTESIAN=.TRUE.)
!! * Memory for reference state without orography ( XRHODREFZ and
!! XTHVREFZ) is only allocated in INI_MODEL1
!! * The horizontal Coriolis parameters (XCORIOX and XCORIOY) arrays
!! are zero-size arrays if thinshell approximation (LTHINSHELL=.TRUE.)
!! * The Curvature coefficients (XCURVX and XCURVY) arrays
!! are zero-size arrays if Cartesian geometry (LCARTESIAN=.TRUE.)
!! * Memory for the Jacobian (ZJ) local array is allocated
!! (This variable is computed in SET_GRID and used in SET_REF).
!! - The spatial and temporal grid variables are initialized by SET_GRID.
!! - The metric coefficients are computed by METRICS (they are using in
!! the SET-REF call).
!! - The prognostic variables and are read in initial
!! LFIFM file (in READ_FIELD)
!! - The reference state variables are initialized by SET_REF.
!! - The temporal indexes of the outputs are computed by SET_OUTPUT_TIMES
!! - The large scale sources are computed in case of coupling case by
!! INI_CPL.
!! - The initialization of the parameters needed for the dynamics
!! of the model n is realized in INI_DYNAMICS.

WAUTELET Philippe
committed
!! - Then the initial file (DESFM+LFIFM files) is closed by IO_File_close.
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
!! - The initialization of the parameters needed for the ECMWF radiation
!! code is realized in INI_RADIATIONS.
!! - The contents of the scalar variables are overwritten by
!! the chemistry initialization subroutine CH_INIT_FIELDn when
!! the flags LUSECHEM and LCH_INIT_FIELD are set to TRUE.
!! This allows easy initialization of the chemical fields at a
!! restart of the model.
!!
!! EXTERNAL
!! --------
!! SET_DIM : to initialize dimensions
!! SET_GRID : to initialize grid
!! METRICS : to compute metric coefficients
!! READ_FIELD : to initialize field
!! FMCLOS : to close a FM-file
!! SET_REF : to initialize reference state for anelastic approximation
!! INI_DYNAMICS: to initialize parameters for the dynamics
!! INI_TKE_EPS : to initialize the TKE
!! SET_DIRCOS : to compute the director cosinus of the orography
!! INI_RADIATIONS : to initialize radiation computations
!! CH_INIT_CCS: to initialize the chemical core system
!! CH_INIT_FIELDn: to (re)initialize the scalar variables
!! INI_DEEP_CONVECTION : to initialize the deep convection scheme
!! CLEANLIST_ll : deaalocate a list
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!!
!! Module MODD_PARAMETERS : contains declaration of parameter variables
!! JPHEXT : Horizontal external points number
!! JPVEXT : Vertical external points number
!!
!! Module MODD_MODD_DYN : contains declaration of parameters
!! for the dynamics
!! Module MODD_CONF : contains declaration of configuration variables
!! for all models
!! NMODEL : Number of nested models
!! NVERB : Level of informations on output-listing
!! 0 for minimum prints
!! 5 for intermediate level of prints
!! 10 for maximum prints
!!
!! Module MODD_REF : contains declaration of reference state
!! variables for all models
!! Module MODD_FIELD_n : contains declaration of prognostic fields
!! Module MODD_LSFIELD_n : contains declaration of Larger Scale fields
!! Module MODD_GRID_n : contains declaration of spatial grid variables
!! Module MODD_TIME_n : contains declaration of temporal grid variables
!! Module MODD_REF_n : contains declaration of reference state
!! variables
!! Module MODD_CURVCOR_n : contains declaration of curvature and Coriolis
!! variables
!! Module MODD_BUDGET : contains declarations of the budget parameters
!! Module MODD_RADIATIONS_n:contains declaration of the variables of the
!! radiation interface scheme
!! Module MODD_STAND_ATM : contains declaration of the 5 standard
!! atmospheres used for the ECMWF-radiation code
!! Module MODD_FRC : contains declaration of the control variables
!! and of the forcing fields
!! Module MODD_CH_MNHC_n : contains the control parameters for chemistry
!! Module MODD_DEEP_CONVECTION_n: contains declaration of the variables of
!! the deep convection scheme

WAUTELET Philippe
committed
!!
!!
!!
!!
!! Module MODN_CONF_n : contains declaration of namelist NAM_CONFn and
!! uses module MODD_CONF_n (configuration variables)
!! Module MODN_LUNIT_n : contains declaration of namelist NAM_LUNITn and
!! uses module MODD_LUNIT_n (Logical units)
!! Module MODN_DYN_n : contains declaration of namelist NAM_DYNn and
!! uses module MODD_DYN_n (control of dynamics)
!! Module MODN_PARAM_n : contains declaration of namelist NAM_PARAMn and
!! uses module MODD_PARAM_n (control of physical
!! parameterization)
!! Module MODN_LBC_n : contains declaration of namelist NAM_LBCn and
!! uses module MODD_LBC_n (lateral boundaries)
!! Module MODN_TURB_n : contains declaration of namelist NAM_TURBn and
!! uses module MODD_TURB_n (turbulence scheme)
!! Module MODN_PARAM_RAD_n: contains declaration of namelist NAM_PARAM_RADn
!!
!! REFERENCE
!! ---------
!! Book2 of documentation (routine INI_MODEL_n)

WAUTELET Philippe
committed
!!
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
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
!!
!! AUTHOR
!! ------
!! V. Ducrocq * Meteo France *
!!
!! MODIFICATIONS
!! -------------
!! Original 10/06/94
!! Modification 17/10/94 (Stein) For LCORIO
!! Modification 20/10/94 (Stein) For SET_GRID and NAMOUTN
!! Modification 26/10/94 (Stein) Modifications of the namelist names
!! Modification 10/11/94 (Lafore) allocatation of tke fields
!! Modification 22/11/94 (Stein) change the READ_FIELDS call ( add
!! pressure function
!! Modification 06/12/94 (Stein) add the LS fields
!! 12/12/94 (Stein) rename END_INI in INI_DYNAMICS
!! Modification 09/01/95 (Stein) add the turbulence scheme
!! Modification Jan 19, 1995 (J. Cuxart) add the TKE initialization
!! Jan 23, 1995 (J. Stein ) remove the condition
!! LTHINSHELL=T LCARTESIAN=T => stop
!! Modification Feb 16, 1995 (I.Mallet) add the METRICS call and
!! change the SET_REF call (add
!! the lineic mass)
!! Modification Mar 10, 1995 (I. Mallet) add the COUPLING initialization
!! June 29,1995 (Ph. Hereil, J. Stein) add the budget init.
!! Modification Sept. 1, 1995 (S. Belair) Reading of the surface variables
!! and parameters for ISBA (i.e., add a
!! CALL READ_GR_FIELD)
!! Modification 18/08/95 (J.P.Lafore) time step change case
!! 25/09/95 (J. Cuxart and J.Stein) add LES variables
!! and the diachronic file initialization
!! Modification Sept 20,1995 (Lafore) coupling for the dry mass Md
!! Modification Sept. 12, 1995 (J.-P. Pinty) add the initialization of
!! the ECMWF radiation code
!! Modification Sept. 13, 1995 (J.-P. Pinty) control the allocation of the
!! arrays of MODD_GR_FIELD_n
!! Modification Nove. 17, 1995 (J.Stein) control of the control !!
!! March 01, 1996 (J. Stein) add the cloud fraction
!! April 03, 1996 (J. Stein) unify the ISBA and TSZ0 cases
!! Modification 13/12/95 (M. Georgelin) add the forcing variables in
!! the call read_field, and their
!! allocation.
!! Mai 23, 1996 (J. Stein) allocate XSEA in the TSZ0 case
!! June 11, 1996 (V. Masson) add XSILT and XLAKE of
!! MODD_GR_FIELD_n
!! August 7, 1996 (K. Suhre) add (re)initialization of
!! chemistry
!! Octo. 11, 1996 (J. Stein ) add XSRCT and XSRCM
!! October 8, 1996 (J. Cuxart, E. Sanchez) Moist LES diagnostics
Loading
Loading full blame...