Newer
Older
!MNH_LIC Copyright 1994-2014 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.
5
6
7
8
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
65
66
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
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
182
! ######spl
MODULE MODI_SPAWN_MODEL2
!########################
!
INTERFACE
!
SUBROUTINE SPAWN_MODEL2 (KRR,KSV_USER,HTURB,HSURF,HCLOUD, &
HCHEM_INPUT_FILE,HSPAFILE,HSPANBR, &
HSONFILE,HINIFILE,HINIFILEPGD,OSPAWN_SURF )
!
INTEGER, INTENT(IN) :: KRR ! Number of moist variables
INTEGER, INTENT(IN) :: KSV_USER ! Number of Users Scalar Variables
CHARACTER (LEN=4), INTENT(IN) :: HTURB ! Kind of turbulence parameterization
CHARACTER (LEN=4), INTENT(IN) :: HSURF ! Kind of surface parameterization
CHARACTER (LEN=4), INTENT(IN) :: HCLOUD ! Kind of cloud parameterization
! model 2 physical domain
CHARACTER (LEN=*), INTENT(IN) :: HSPAFILE ! possible name of the output FM-file
CHARACTER (LEN=*), INTENT(IN) :: HSPANBR ! NumBeR associated to the SPAwned file
CHARACTER (LEN=*), INTENT(IN) :: HSONFILE ! name of the input FM-file SON
CHARACTER (LEN=80), INTENT(IN) :: HCHEM_INPUT_FILE
CHARACTER (LEN=*), INTENT(IN) :: HINIFILE ! Input file
CHARACTER (LEN=*), INTENT(IN) :: HINIFILEPGD ! Input pgd file
LOGICAL, INTENT(IN) :: OSPAWN_SURF ! flag to spawn surface fields
!
END SUBROUTINE SPAWN_MODEL2
!
END INTERFACE
!
END MODULE MODI_SPAWN_MODEL2
! ######spl
SUBROUTINE SPAWN_MODEL2 (KRR,KSV_USER,HTURB,HSURF,HCLOUD, &
HCHEM_INPUT_FILE,HSPAFILE,HSPANBR, &
HSONFILE,HINIFILE,HINIFILEPGD,OSPAWN_SURF )
! #######################################################################
!
!!**** *SPAWN_MODEL2 * - subroutine to prepare by horizontal interpolation and
!! write an initial FM-file spawned from an other FM-file.
!!
!! PURPOSE
!! -------
!!
!! Initializes by horizontal interpolation, the model 2 in a sub-domain of
!! model 1, possibly overwrites model 2 information by model SON1,
!! and writes the resulting fields in a FM-file.
!!
!!
!!** METHOD
!! ------
!!
!! In this routine, only the model 2 variables are known through the
!! MODD_... calls.
!!
!! The directives to perform the preparation of the initial FM
!! file are stored in EXSPA.nam file.
!!
!! The following SPAWN_MODEL2 routine :
!!
!! - sets default values of DESFM files
!! - reads the namelists part of EXSPA file which gives the
!! directives concerning the spawning to perform
!! - controls the domain size of model 2 and initializes its
!! configuration for parameterizations and LBC
!! - allocates memory for arrays
!! - computes the interpolation coefficients needed to spawn model 2
!! 2 types of interpolations are used:
!! 1. Clark and Farley (JAS 1984) on 9 points
!! 2. Bikhardt on 16 points
!! - initializes fields
!! - reads SON1 fields and overwrites on common domain
!! - writes the DESFM file (variables written have been initialized
!! by reading the DESFM file concerning the model 1)
!! - writes the LFIFM file.
!!
!! Finally some control prints are performed on the output listing.
!!
!! EXTERNAL
!! --------
!!
!! FMATTR : to associate a logical unit number to a file
!! Module MODE_GRIDPROJ : contains conformal projection routines
!! SM_GRIDPROJ : to compute some grid variables, in
!! case of conformal projection.
!! Module MODE_GRIDCART : contains cartesian geometry routines
!! SM_GRIDCART : to compute some grid variables, in
!! case of cartesian geometry.
!! SET_REF : to compute rhoJ
!! TOTAL_DMASS : to compute the total mass of dry air
!! ANEL_BALANCE2 : to apply an anelastic correction in the case of changing
!! resolution between the two models
!! FMOPEN : to open a FM-file (DESFM + LFIFM)
!! WRITE_DESFM : to write the DESFM file
!! WRITE_LFIFM : to write the LFIFM file
!! FMCLOS : to close a FM-file (DESFM + LFIFM)
!! INI_BIKHARDT2 : initializes Bikhardt coefficients
!!
!!
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!!
!! Module MODD_PARAMETERS : contains parameters
!! Module MODD_CONF : contains configuration variables for all models
!! Module MODD_CTURB :
!! XTKEMIN : mimimum value for the TKE
!! Module MODD_GRID : contains grid variables for all models
!! Module USE MODD_DYN : contains configuration for the dynamics
!! Module MODD_REF : contains reference state variables for
!! all models
!!
!! Module MODD_DIM2 : contains dimensions
!! Module MODD_CONF2 : contains configuration variables
!! Module MODD_GRID2 : contains grid variables
!! Module MODD_TIME2 : contains time variables and uses MODD_TIME
!! Module MODD_REF2 : contains reference state variables
!! Module MODD_FIELD2 : contains prognostic variables
!! Module MODD_LSFIELD2 : contains Larger Scale fields
!! Module MODD_GR_FIELD2 : contains surface fields
!! Module MODD_DYN2 : contains dynamic control variables for model 2
!! Module MODD_LBC2 : contains lbc control variables for model 2
!! Module MODD_PARAM2 : contains configuration for physical parameterizations
!!
!! REFERENCE
!! ---------
!!
!! PROGRAM SPAWN_MODEL2 (Book2 of the documentation)
!!
!!
!! AUTHOR
!! ------
!!
!! J.P. Lafore * METEO-FRANCE *
!!
!! MODIFICATIONS
!! -------------
!!
!! Original 11/01/95
!! Modification 27/04/95 (I.Mallet) remove R from the historical variables
!! Modification 16/04/96 (Lafore) Different resolution ratio case introduction
!! Modification 24/04/96 (Lafore & Masson) Initialization of LUSERWs
!! Modification 24/04/96 (Masson) Correction of positivity on Rw and TKE
!! Modification 25/04/96 (Masson) Copies of internal zs on external points
!! Modification 02/05/96 (Stein Jabouille) initialize CCONF
!! Modification 31/05/96 (Lafore) Cumputing time analysis
!! Modification 10/06/96 (Masson) Call to anel_balance in all cases
!! Modification 10/06/96 (Masson) Bikhardt and Clark_and_Farley coefficients
!! incorporated in modules
!! Modification 12/06/96 (Masson) default values of NJMAX and KDYRATIO
!! if 2D version of the model
!! Modification 13/06/96 (Masson) choice of the name of the spawned file
!! Modification 30/07/96 (Lafore) MY_NAME and DAD_NAME writing for nesting
!! Modification 25/09/96 (Masson) grid optionnaly given by a fm file
!! and number of points given relatively
!! to model 1
!! Modification 10/10/96 (Masson) L1D and L2D verifications
!! Modification 12/11/96 (Masson) allocations of XSRCM and XSRCT
!! Modification 19/11/96 (Masson) add deep convection
!! Modification 26/11/96 (Lafore) spawning configuration writing on the FM-file
!! Modification 26/11/96 (Lafore) replacing of TOTAL_DMASS by REAL_DMASS
!! Modification 27/02/97 (Lafore) "surfacic" LS fields
!! Modification 10/04/97 (Lafore) proper treatment of minima
!! Modification 09/07/97 (Masson) absolute pressure and directional z0
!! Modification 10/07/97 (Masson) routines SPAWN_PRESSURE2 and DRY_MASS
!! Modification 17/07/97 (Masson) vertical interpolations and EPS
!! Modification 29/07/97 (Masson) split mode_lfifm_pgd
!! Modification 10/08/97 (Lafore) initialization of LUSERV
!! Modification 14/09/97 (Masson) use of relative humidity
!! Modification 08/12/97 (Masson) deallocation of model 1 variables
!! Modification 24/12/97 (Masson) directional z0 parameters and orographies
!! Modification 20/07/98 (Stein ) add the LB fields
!! Modification 15/03/99 (Masson) cover types
!! Modification 15/07/99 (Jabouille) shift domain initialization in INI_SIZE_SPAWN
!! Modification 04/01/00 (Masson) removes TSZ0 option
!! Modification 29/11/02 (Pinty) add C3R5, ICE2, ICE4
!! Modification 07/07/05 (D.Barbary) spawn with 2 input files (father+son1)
!! Modification 20/05/06 Remove EPS, Clark and Farley interpolation
!! Replace DRY_MASS by TOTAL_DMASS
!! Modification 06/12 (M.Tomasini) Interpolation of the advective forcing (ADVFRC)
!! and of the turbulent fluxes (EDDY_FLUX)
!! Modification 07/13 (Bosseur & Filippi) Adds Forefire
!-------------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------
!
USE MODD_PARAMETERS ! Declarative modules
USE MODD_CST
USE MODD_CONF
USE MODD_CTURB
USE MODD_GRID
USE MODD_REF
USE MODD_DYN
USE MODD_NESTING
USE MODD_SPAWN
USE MODD_NSV
USE MODD_PASPOL
!
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
Loading
Loading full blame...