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.
!-----------------------------------------------------------------
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
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
!
INTERFACE
!
SUBROUTINE MODEL_n(KTCOUNT,OEXIT)
!
INTEGER, INTENT(IN) :: KTCOUNT ! temporal loop index of model KMODEL
LOGICAL, INTENT(INOUT):: OEXIT ! switch for the end of the temporal loop
!
END SUBROUTINE MODEL_n
!
END INTERFACE
!
END MODULE MODI_MODEL_n
! ###################################
SUBROUTINE MODEL_n(KTCOUNT, OEXIT)
! ###################################
!
!!**** *MODEL_n * -monitor of the model version _n
!!
!! PURPOSE
!! -------
! The purpose of this routine is to build up a typical model version
! by sequentially calling the specialized routines.
!
!!** METHOD
!! ------
!! Some preliminary initializations are performed in the first section.
!! Then, specialized routines are called to update the guess of the future
!! instant XRxxS of the variable xx by adding the effects of all the
!! different sources of evolution.
!!
!! (guess of xx at t+dt) * Rhod_ref * Jacobian
!! XRxxS = -------------------------------------------
!! 2 dt
!!
!! At this level, the informations are transferred with a USE association
!! from the INIT step, where the modules have been previously filled. The
!! transfer to the subroutines computing each source term is performed by
!! argument in order to avoid repeated compilations of these subroutines.
!! This monitor model_n, must therefore be duplicated for each model,
!! model1 corresponds in this case to the outermost model, model2 is used
!! for the first level of gridnesting,....
!! The effect of all parameterizations is computed in PHYS_PARAM_n, which
!! is itself a monitor. This is due to a possible large number of
!! parameterizations, which can be activated and therefore, will require a
!! very large list of arguments. To circumvent this problem, we transfer by
!! a USE association, the necessary informations in this monitor, which will
!! dispatch the pertinent information to every parametrization.
!! Some elaborated diagnostics, LES tools, budget storages are also called
!! at this level because they require informations about the fields at every
!! timestep.
!!
!!
!! EXTERNAL
!! --------

WAUTELET Philippe
committed
!! Subroutine IO_File_open: to open a file
!! Subroutine WRITE_DESFM: to write the descriptive part of a FMfile
!! Subroutine WRITE_LFIFM: to write the binary part of a FMfile
!! Subroutine SET_MASK : to compute all the masks selected for budget
!! computations
!! Subroutine BOUNDARIES : set the fields at the marginal points in every
!! directions according the selected boundary conditions
!! Subroutine INITIAL_GUESS: initializes the guess of the future instant
!! Subroutine LES_FLX_SPECTRA: computes the resolved fluxes and the
!! spectra of some quantities when running in LES mode.
!! Subroutine ADVECTION: computes the advection terms.
!! Subroutine DYN_SOURCES: computes the curvature, Coriolis, gravity terms.
!! Subroutine NUM_DIFF: applies the fourth order numerical diffusion.
!! Subroutine RELAXATION: performs the relaxation to Larger Scale fields
!! in the upper levels and outermost vertical planes
!! Subroutine PHYS_PARAM_n : computes the parameterized physical terms
!! Subroutine RAD_BOUND: prepares the velocity normal components for the bc.
!! Subroutine RESOLVED_CLOUD : computes the sources terms for water in any
!! form
!! Subroutine PRESSURE : computes the pressure gradient term and the
!! absolute pressure
!! Subroutine EXCHANGE : updates the halo of each subdomains
!! Subroutine ENDSTEP : advances in time the fields.
!! Subroutines UVW_LS_COUPLING and SCALAR_LS_COUPLING:
!! compute the large scale fields, used to
!! couple Model_n with outer informations.
!! Subroutine ENDSTEP_BUDGET: writes the budget informations.

WAUTELET Philippe
committed
!! Subroutine IO_File_close: closes a file
!! Subroutine DATETIME_CORRECTDATE: transform the current time in GMT
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
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
!! Subroutine FORCING : computes forcing terms
!! Subroutine ADD3DFIELD_ll : add a field to 3D-list
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! MODD_DYN
!! MODD_CONF
!! MODD_NESTING
!! MODD_BUDGET
!! MODD_PARAMETERS
!! MODD_CONF_n
!! MODD_CURVCOR_n
!! MODD_DYN_n
!! MODD_DIM_n
!! MODD_ADV_n
!! MODD_FIELD_n
!! MODD_LSFIELD_n
!! MODD_GRID_n
!! MODD_METRICS_n
!! MODD_LBC_n
!! MODD_PARAM_n
!! MODD_REF_n
!! MODD_LUNIT_n
!! MODD_OUT_n
!! MODD_TIME_n
!! MODD_TURB_n
!! MODD_CLOUDPAR_n
!! MODD_TIME
!!
!! REFERENCE
!! ---------
!!
!! AUTHOR
!! ------
!! J.-P. Pinty * LA *
!!
!! MODIFICATIONS
!! -------------
!! Original 15/09/94
!! Modification 20/10/94 (J.Stein) for the outputs and abs_layers routines
!! Modification 10/11/94 (J.Stein) change ABS_LAYER_FIELDS call
!! Modification 16/11/94 (J.Stein) add call to the renormalization
!! Modification 17/11/94 (J.-P. Lafore and J.-P. Pinty) call NUM_DIFF
!! Modification 08/12/94 (J.Stein) cleaning + remove (RENORM + ABS_LAYER..
!! ..) + add RELAXATION + LS fiels in the arguments
!! Modification 19/12/94 (J.Stein) switch for the num diff
!! Modification 22/12/94 (J.Stein) update tdtcur + change dyn_source call
!! Modification 05/01/95 (J.Stein) add the parameterization monitor
!! Modification 09/01/95 (J.Stein) add the 1D switch
!! Modification 10/01/95 (J.Stein) displace the TDTCUR computation
!! Modification 03/01/95 (J.-P. Lafore) Absolute pressure diagnosis
!! Modification Jan 19, 1995 (J. Cuxart) Shunt the DYN_SOURCES in 1D cases.
!! Modification Jan 24, 1995 (J. Stein) Interchange Boundaries and
!! Initial_guess to correct a bug in 2D configuration
!! Modification Feb 02, 1995 (I.Mallet) update BOUNDARIES and RAD_BOUND
!! calls
!! Modification Mar 10, 1995 (I.Mallet) add call to SET_COUPLING
!! March,21, 1995 (J. Stein) remove R from the historical var.
!! March,26, 1995 (J. Stein) add the EPS variable
!! April 18, 1995 (J. Cuxart) add the LES call
!! Sept 20,1995 (Lafore) coupling for the dry mass Md
!! Nov 2,1995 (Stein) displace the temporal counter increase
!! Jan 2,1996 (Stein) rm the test on the temporal counter
!! Modification Feb 5,1996 (J. Vila) implementation new advection
!! schemes for scalars
!! Modification Feb 20,1996 (J.Stein) doctor norm
!! Dec95 - Jul96 (Georgelin, Pinty, Mari, Suhre) FORCING
!! June 17,1996 (Vincent, Lafore, Jabouille)
!! statistics of computing time
!! Aug 8, 1996 (K. Suhre) add chemistry
!! October 12, 1996 (J. Stein) save the PSRC value
!! Sept 05,1996 (V.Masson) print of loop index for debugging
!! purposes
!! July 22,1996 (Lafore) improve write of computing time statistics
!! July 29,1996 (Lafore) nesting introduction
!! Aug. 1,1996 (Lafore) synchronization between models
!! Sept. 4,1996 (Lafore) modification of call to routine SET_COUPLING
!! now split in 2 routines
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
!! (UVW_LS_COUPLING and SCALAR_LS_COUPLING)
!! Sept 5,1996 (V.Masson) print of loop index for debugging
!! purposes
!! Sept 25,1996 (V.Masson) test for coupling performed here
!! Oct. 29,1996 (Lafore) one-way nesting implementation
!! Oct. 12,1996 (J. Stein) save the PSRC value
!! Dec. 12,1996 (Lafore) change call to RAD_BOUND
!! Dec. 21,1996 (Lafore) two-way nesting implementation
!! Mar. 12,1997 (Lafore) introduction of "surfacic" LS fields
!! Nov 18, 1996 (J.-P. Pinty) FORCING revisited (translation)
!! Dec 04, 1996 (J.-P. Pinty) include mixed-phase clouds
!! Dec 20, 1996 (J.-P. Pinty) update the budgets
!! Dec 23, 1996 (J.-P. Pinty) add the diachronic file control
!! Jan 11, 1997 (J.-P. Pinty) add the deep convection control
!! Dec 20,1996 (V.Masson) call boundaries before the writing
!! Fev 25, 1997 (P.Jabouille) modify the LES tools
!! April 3,1997 (Lafore) merging of the nesting
!! developments on MASTER3
!! Jul. 8,1997 (Lafore) print control for nesting (NVERB>=7)
!! Jul. 28,1997 (Masson) supress LSTEADY_DMASS
!! Aug. 19,1997 (Lafore) full Clark's formulation introduction
!! Sept 26,1997 (Lafore) LS source calculation at restart
!! (temporarily test to have LS at instant t)
!! Jan. 28,1998 (Bechtold) add SST forcing
!! fev. 10,1998 (Lafore) RHODJ computation and storage for budget
!! Jul. 10,1998 (Stein ) sequentiel loop for nesting
!! Apr. 07,1999 (Stein ) cleaning of the nesting subroutines
!! oct. 20,1998 (Jabouille) //
!! oct. 20,2000 (J.-P. Pinty) add the C2R2 scheme
!! fev. 01,2001 (D.Gazen) add module MODD_NSV for NSV variables
!! mar, 4,2002 (V.Ducrocq) call to temporal series
!! mar, 8, 2001 (V. Masson) advection of perturbation of theta in neutral cases.
!! Nov, 6, 2002 (V. Masson) time counters for budgets & LES
!! mars 20,2001 (Pinty) add ICE4 and C3R5 options
!! jan. 2004 (Masson) surface externalization
!! sept 2004 (M. Tomasini) Cloud mixing length modification
!! june 2005 (P. Tulet) add aerosols / dusts
!! Jul. 2005 (N. Asencio) two_way and phys_param calls:
!! Add the surface parameters : precipitating
!! hydrometeors, Short and Long Wave , MASKkids array
!! Fev. 2006 (M. Leriche) add aqueous phase chemistry
!! april 2006 (T.Maric) Add halo related to 4th order advection scheme
!! May 2006 Remove KEPS
!! Oct 2008 (C.Lac) FIT for variables advected with PPM
!! July 2009 : Displacement of surface diagnostics call to be
!! coherent with surface diagnostics obtained with DIAG
!! 10/11/2009 (P. Aumond) Add mean moments
!! Nov, 12, 2009 (C. Barthe) add cloud electrification and lightning flashes
!! July 2010 (M. Leriche) add ice phase chemical species
!! April 2011 (C.Lac) : Remove instant M
!! April 2011 (C.Lac, V.Masson) : Time splitting for advection

ESCOBAR MUNOZ Juan
committed
!! J.Escobar 21/03/2013: for HALOK comment all NHALO=1 test

Gaelle Tanguy
committed
!! P. Tulet Nov 2014 accumulated moles of aqueous species that fall at the surface
!! Dec 2014 (C.Lac) : For reproducibility START/RESTA
!! J.Escobar 20/04/2015: missing UPDATE_HALO before UPDATE_HALO2

Gaelle Tanguy
committed
!! July, 2015 (O.Nuissier/F.Duffourg) Add microphysics diagnostic for
!! aircraft, ballon and profiler
Loading
Loading full blame...