Newer
Older
!MNH_LIC Copyright 1995-2021 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.
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
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
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
!-----------------------------------------------------------------
! ######################
PROGRAM PREP_REAL_CASE
! ######################
!
!!**** *PREP_REAL_CASE* - program to write an initial FM file from real case
!! situation.
!!
!! PURPOSE
!! -------
!!
!! The purpose of this program is to prepare an initial meso-NH file
!! (LFIFM and DESFM files) filled by some fields of a real situation.
!! General data are given by the MESO-NH user in the namelist file
!! 'PRE_REAL1.nam'. The fields are obtained from three sources:
!! - an atmospheric input file, which can be:
!! * an Aladin file, itself obtained from an Arpege file with
!! the Aladin routine "FULLPOS".
!! * a grib file (ECMWF, Grib Arpege or Grib Aladin)
!! * a MESONH file
!! - an physiographic data file.
!!
!! 1) Fields obtained from the Atmospheric file:
!! -----------------------------------------
!!
!! - the projection parameters (checked with PGD file):
!! reference latitude and longitude
!! parameter of projection
!! angle of rotation of the domain
!!
!! - the horizontal grid definition (checked with PGD file):
!! grid mesh
!! latitude and longitude of the reference point
!! (with data from PRE_REAL1.nam)
!!
!! - thermodynamical 3D and 2D fields:
!! potential temperature
!! vapor mixing ratio
!!
!! - dynamical fields:
!! three components of the wind
!!
!! - reference anelastic state variables:
!! profile of virtual potential temperature
!! profile of dry density
!! Exner function at model top
!!
!! - total dry air mass
!!
!!
!! 2) Fields obtained from the physiographic data file:
!! ------------------------------------------------
!!
!! - the projection parameters:
!! reference latitude and longitude
!! parameter of projection
!! angle of rotation of the domain
!!
!! - the horizontal grid definition:
!! grid mesh
!! latitude and longitude of the reference point
!! (with data from PRE_REAL1.nam)
!! - physiografic fields: (orographic, vegetation, soil and radiation fields)
!!
!!
!! 3) Data obtained from the namelist file PRE_REAL1.nam:
!! --------------------------------------------------
!!
!! - type of equations system
!! - vertical grid definition
!! - number of points in x and y directions
!! - level of verbosity
!! - name of the different files
!!
!!
!!** METHOD
!! ------
!! In this program, once the MESO-NH domain is calculated, all the
!! 2D or 3D fields are computed on the MESO-NH horizontal domain WITH
!! the external points. This is particularly important for the large
!! scale fields during the MESO-NH run.
!!
!! 1) The following PREP_REAL_CASE program:
!!
!! - set default values for global variables which will be written in
!! DESFM file (by calling DEFAULT_DESFM1); lateral boundary conditions
!! are open.
!!
!! - opens the different files (by calling OPEN_PRC_FILES).
!!
!! - initializes physical constants (by calling INI_CST).
!!
!! - initializes the horizontal domain from the data read in the
!! descriptive part of the Aladin file and the directives read in the
!! namelist file (routines READ_GENERAL and SET_SUBDOMAIN in
!! READ_ALL_DATA). This MESO-NH domain is a part of the Aladin domain.
!!
!! - initializes global variables from namelists and the MESO-NH
!! vertical grid definition variables in the namelist file
!! (routine READ_VER_GRID).
!!
!! - initializes the physiographic 2D fields from the physiographic data
!! file, in particular the MESO-NH orography.
!!
!! - reads the 3D and 2D variable fields in the Grib file
!! (routine READ_ALL_DATA_GRIB_CASE),
!! if HATMFILETYPE='GRIBEX':
!! absolute temperature
!! specific humidity
!! horizontal contravariant wind
!! surface pressure
!! large scale orography
!!
!! - reads the 3D and 2D variable fields in the input MESONH file
!! (routine READ_ALL_DATA_MESONH_CASE), if HATMFILETYPE='MESONH':
!! potential temperature
!! vapor mixing ratio
!! horizontal wind
!! other mixing ratios
!! turbulence prognostic and semi-prognostic variables
!! large scale orography
!!
!! - computes some geometric variables (routines SM_GRIDPROJ and METRICS),
!! in particular:
!! * altitude 3D array
!! * metric coefficients
!! * jacobian
!!
!! - initializes MESO-NH thermodynamical fields:
!! * changes of variables (routine VER_PREP_mmmmmm_CASE):
!! absolute temperature --> virtual potential temperature
!! specific humidity --> vapor mixing ratio
!! * interpolates/extrapolates the fields from the large scale
!! orography to the MESO-NH one (routine VER_INT_THERMO in
!! VER_THERMO, by using a shifting function method).
!! in water vapor case, the interpolations are always performed
!! on relative humidity.
!! * the pressure is computed on each grid by integration of the
!! hydrostatic equation from bottom or top. When input atmospheric
!! file is a MESO-NH one, information about the difference between
!! hydrostatic pressure and total pressure is kept and interpolated
!! during the entire PREP_REAL_CASE process.
!! * interpolates the fields to the MESO-NH vertical grid
!! (also by routine VER_INT_THERMO in VER_THERMO).
!! * computes the potential temperature (routine VER_THERMO).
!! * sets to zero the mixing ratios, except the vapor mixing ratio
!! (VER_THERMO).
!!
!! - initializes the reference anelastic state variables (routine SET_REFZ
!! in VER_THERMO).
!!
!! - computes the total dry air mass (routine DRY_MASS in VER_THERMO).
!!
!! - initializes MESO-NH dynamical variables:
!! * changes Aladin contravariant wind into true horizontal wind
!! (in subroutine VER_PREP).
!! * interpolates/extrapolates the momentum from the large scale
!! orography to the MESO-NH one (routine VER_INT_DYN in
!! VER_DYN, by using a shifting function method).
!! * interpolates the fields to the MESO-NH vertical grid
!! (also by routine VER_INT_DYN in VER_DYN). The fields
!! are located on a horizontal Arakawa A-grid, as the Aladin fields.
!! * The momentum is interpolated to the Arakawa C-grid
!! (routine VER_DYN).
!! * A first guess of the vertical momentum, verifying the
!! uncompressible continuity equation and the material lower boundary
!! condition against the ground, is computed (routine WGUESS).
!! * computes the final non-divergent wind field (routine
!! ANEL_BALANCE).
!!
!! - copies the interpolated fields also at t-dt and in the large scale
!! fields (routine INI_PROG_VAR).
!!
!! - writes the DESFM and LFIFM files (routines WRITE_DESFM1 and
!! WRITE_LFIFM1).
!!
!!
!! 2) Some conventions are used in this program and its subroutines because
!! of the number of different grids and fields:
!!
!! - subscripts:
!! * the subscripts I and J are used for all the horizontal grid.
!! * the subcript K is used for the MESO-NH vertical grid (increasing
!! from bottom to top).
!! * the subscript L is used for the Aladin or input Mesonh grids
!! (increasing from bottom to top).
!!
!! - suffixes:
!! * _LS:
!! If used for a geographic or horizontal grid definition variable,
!! this variable is connected to the large horizontal domain.
!! If used for a surface variable, this variable corresponds to
!! the large scale orography, and therefore will be modified.
!! If used for another variable, this variable is discretized
!! on the Aladin or input MESONH file vertical grid
!! (large-scale orography with input vertical discretization,
!! either coming from eta levels or input Gal-Chen grid).
!! * _MX:
!! Such a variable is discretized on the mixed grid.
!! (large-scale orography with output Gal-Chen vertical grid
!! discretization)
!! * _SH:
!! Such a variable is discretized on the shifted grid.
!! (fine orography with a shifted vertical grid, NOT Gal-Chen)
!! * no suffix:
!! The variable is discretized on the MESO-NH grid.
!! (fine orography with output Gal-Chen vertical grid discretization)
!!
!! - additional pre-suffixes: (for pressure, Exner and altitude fields)
!! * MASS:
!! The variable is discretized on a mass point
!! * FLUX:
!! The variable is discretized on a flux point
!!
!!
!! - names of variables: for a physical variable VAR:
!! * pVARs is the variable itself.
!! * pRHODVARs is the variable multiplied by the dry density rhod.
!! * pRHODJVARs is the variable multiplied by the dry density rhod
!! and the Jacobian.
!! * pRVARs is the variable multiplied by rhod_ref, the anelastic
!! reference state dry density and the Jacobian.
!! where p and s are the appropriate prefix and suffix.
!!
!! - allocation of arrays: the arrays are allocated
!! * just before their initialization for the general arrays stored in
!! modules.
!! * in the subroutine in which they are declared for the local arrays
!! in a subroutine.
!! * in the routine in which they are initialized for the arrays
!! defined in the monitor PREP_REAL_CASE. In this case they are in
!! fact passed as pointer to the subroutines to allow their
!! dynamical allocation (exception which confirms the rule: ZJ).
!!
!!
!! EXTERNAL
!! --------
!!
!! Routine DEFAULT_DESFM1 : to set default values for variables which can be
!! contained in DESFM file.
!! Routine OPEN_PRC_FILES: to open all files.
!! Routine INI_CST : to initialize physical constants.
!! Routine READ_ALL_DATA_GRIB_CASE : to read all input data.
!! Routine READ_ALL_DATA_MESONH_CASE : to read all input data.
!! Routine SM_GRIDPROJ : to compute some grid variables, in case of
!! conformal projection.
!! Routine METRICS : to compute metric coefficients.
!! Routine VER_PREP_GRIBEX_CASE : to prepare the interpolations.
!! Routine VER_PREP_MESONH_CASE : to prepare the interpolations.
!! Routine VER_THERMO : to perform the interpolation of thermodynamical
!! variables.
!! Routine VER_DYN : to perform the interpolation of dynamical
!! variables.
!! Routine INI_PROG_VAR : to initialize the prognostic varaibles not yet
!! initialized
!! Routine WRITE_DESFM1 : to write a DESFM file.
!! Routine WRITE_LFIFM1 : to write a LFIFM file.

WAUTELET Philippe
committed
!! Routine IO_File_close : to close a FM-file (DESFM + LFIFM).
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
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
!!
!! Module MODE_GRIDPROJ : contains conformal projection routines
!!
!! Module MODI_DEFAULT_DESFM1 : interface module for routine DEFAULT_DESFM1
!! Module MODI_OPEN_PRC_FILES : interface module for routine OPEN_PRC_FILES
!! Module MODI_READ_ALL_DATA_MESONH_CASE : interface module for routine
!! READ_ALL_DATA_MESONH_CASE
!! Module MODI_METRICS : interface module for routine METRICS
!! Module MODI_VER_PREP_GRIBEX_CASE : interface module for routine
!! VER_PREP_GRIBEX_CASE
!! Module MODI_VER_PREP_MESONH_CASE : interface module for routine
!! VER_PREP_MESONH_CASE
!! Module MODI_VER_THERMO : interface module for routine VER_THERMO
!! Module MODI_VER_DYN : interface module for routine VER_DYN
!! Module MODI_INI_PROG_VAR : interface module for routine INI_PROG_VAR
!! Module MODI_WRITE_DESFM1 : interface module for routine WRITE_DESFM1
!! Module MODI_WRITE_LFIFM1 : interface module for routine WRITE_LFIFM1
!!
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!!
!! Module MODD_CONF : contains configuration variables for all models.
!! NVERB : verbosity level for output-listing
!! Module MODD_CONF1 : contains configuration variables for model 1.
!! NRR : number of moist variables
!! Module MODD_LUNIT : contains logical unit and names of files.
!! Module MODD_LUNIT : contains logical unit and names of files (model1).
!! CINIFILE: name of the FM file which will be used for the MESO-NH run.
!! Module MODD_GRID1 : contains grid variables.
!! XLAT : latitude of the grid points
!! XLON : longitudeof the grid points
!! XXHAT : position xhat in the conformal plane
!! XYHAT : position yhat in the conformal plane
!! XDXHAT : horizontal local meshlength on the conformal plane
!! XDYHAT : horizontal local meshlength on the conformal plane
!! XZS : MESO-NH orography
!! XZZ : altitude
!! XZHAT : height zhat
!! XMAP : map factor
!! Module MODD_LBC1 : contains declaration of lateral boundary conditions
!! CLBCX : X-direction LBC type at left(1) and right(2) boundaries
!! CLBCY : Y-direction LBC type at left(1) and right(2) boundaries
!! Module MODD_PARAM1 : contains declaration of the parameterizations' names
!!
!! REFERENCE
!! ---------
!!
!! Book 2
!!
!! AUTHOR
!! ------
!!
!! V.Masson Meteo-France
!!
!! MODIFICATIONS
!! -------------
!! Original 01/01/95
!! Sept. 21, 1995 (J.Stein and V.Masson) surface pressure
!! Jan. 09, 1996 (V. Masson) pressure function deduced from
!! hydrostatic pressure
!! Jan. 31, 1996 (V. Masson) possibility to initialize
!! atmospheric fields from MESONH file
!! Mar. 18, 1996 (V. Masson) new vertical extrapolation of Ts
!! in case of initialization with MESONH file
!! Apr 17, 1996 (J. Stein ) change the DEFAULT_DESFM CALL
!! May 25, 1996 (V. Masson) Variable CSTORAGE_TYPE
!! Aug 26, 1996 (V. Masson) Only thinshell approximation is
!! currently available.
!! Sept 24, 1996 (V. Masson) add writing of varaibles for
!! nesting ('DAD_NAME', 'DXRATIO', 'DYRATIO')
!! Oct 11, 1996 (V. Masson) L1D and L2D configurations
!! Oct 28, 1996 (V. Masson) add deallocations and NVERB
!! default set to 1
!! Dec 02, 1996 (V. Masson) vertical interpolation of
!! surface fields in aladin case
!! Dec 12, 1996 (V. Masson) add LS vertical velocity
!! Jan 16, 1997 (J. Stein) Durran's anelastic system
!! May 07, 1997 (V. Masson) add LS tke
!! Jun 27, 1997 (V. Masson) add absolute pressure
!! Jul 09, 1997 (V. Masson) add namelist NAM_REAL_CONF
!! Jul 10, 1997 (V. Masson) add LS epsilon
!! Aug 25, 1997 (V. Masson) add computing time analysis
!! Jan 20, 1998 (J. Stein) add LB and LS fields
!! Apr, 30, 1998 (V. Masson) Large scale VEG and LAI
!! Jun, 04, 1998 (V. Masson) Large scale D2 and Aladin ISBA
!! files
!! Jun, 04, 1998 (V. Masson) Add new soil interface var.
!! Jan 20, 1999 (J. Stein) add a Boundaries call
!! March 15 1999 (J. Pettre, V. Bousquet and V. Masson)
!! initialization from GRIB files
!! Jul 2000 (F.solmon/V.Masson) Adaptation for patch
!! according to GRIB or MESONH case
!! Nov 22, 2000 (P.Tulet, I. Mallet) initialization
!! from GRIB MOCAGE file
!! Fev 01, 2001 (D.Gazen) add module MODD_NSV for NSV variable
!! Jul 02, 2001 (J.Stein) add LCARTESIAN case
!! Oct 15, 2001 (I.Mallet) allow namelists in different orders
!! Dec 2003 (V.Masson) removes surface calls
!! Jun 01, 2002 (O.Nuissier) filtering of tropical cyclone
!! Aou 09, 2005 (D.Barbary) add CDADATMFILE CDADBOGFILE
!! May 2006 Remove KEPS
!! Feb 02, 2012 (C. Mari) interpolation from MOZART
!! add call to READ_CHEM_NETCDF_CASE &
!! VER_PREP_NETCDF_CASE
!! Mar 2012 Add NAM_NCOUT for netcdf output
!! July 2013 (Bosseur & Filippi) Adds Forefire
!! Mars 2014 (J.Escobar) Missing 'full' UPDATE_METRICS for arp2lfi // run
!! 2014 (M.Faivre)
!! Fevr 2015 (M.Moge) Cleaning up
!! Aug 2015 (M.Moge) removing EXTRAPOL on XDXX and XDYY in part 8
!! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1
!! M.Leriche 2015 : add LUSECHEM dans NAM_CH_CONF
!! Feb 02, 2012 (C. Mari & BV) interpolation from CAMS
!! add call to READ_CAMS_NETCDF_CASE &
!! VER_PREP_NETCDF_CASE
!! Modification 01/2016 (JP Pinty) Add LIMA
!! Modification 02/2016 (JP Pinty) Convert CAMS mix ratio to nbr conc
!
!! P.Wautelet : 08/07/2016 : removed MNH_NCWRIT define
!! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O

WAUTELET Philippe
committed
! P. Wautelet 07/02/2019: force TYPE to a known value for IO_File_add2list

WAUTELET Philippe
committed
! P. Wautelet 14/02/2019: remove CLUOUT/CLUOUT0 and associated variables

WAUTELET Philippe
committed
! S. Bielli 02/2019: sea salt: significant sea wave height influences salt emission; 5 salt modes

WAUTELET Philippe
committed
! P. Wautelet 20/03/2019: missing use MODI_INIT_SALT

WAUTELET Philippe
committed
! P. Wautelet 20/05/2019: add name argument to ADDnFIELD_ll + new ADD4DFIELD_ll subroutine

WAUTELET Philippe
committed
! T.Nagel 02/2021: add IBM

WAUTELET Philippe
committed
! P. Wautelet 06/07/2021: use FINALIZE_MNH
!! M. Leriche 26/01/2022: add reading of CAMS reanalysis for chemistry
!! and/or for LIMA
!-------------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------
!
USE MODD_CH_M9_n
USE MODD_CH_MNHC_n, ONLY: LUSECHAQ_n=>LUSECHAQ,LUSECHIC_n=>LUSECHIC, LUSECHEM_n=>LUSECHEM
USE MODD_CONF
USE MODD_CONF_n
USE MODD_CST
USE MODD_DIM_n
!UPG*PT
USE MODD_CH_AEROSOL
USE MODD_DUST, ONLY: LDUST, NMODE_DST, CRGUNITD, XINISIG, XINIRADIUS, XN0MIN,&
LDSTCAMS
!UPG*PT
USE MODD_DYN_n, CPRESOPT_n=>CPRESOPT, LRES_n=>LRES, XRES_n=>XRES , NITR_n=>NITR
USE MODD_FIELD_n
USE MODD_GR_FIELD_n
USE MODD_GRID
USE MODD_GRID_n
USE MODD_HURR_CONF

WAUTELET Philippe
committed
USE MODD_IBM_LSF, ONLY: CIBM_TYPE, LIBM_LSF, NIBM_SMOOTH, XIBM_SMOOTH
USE MODD_IBM_PARAM_n, ONLY: XIBM_LS

WAUTELET Philippe
committed
USE MODD_IO, ONLY: TFILEDATA, TFILE_SURFEX
USE MODD_LBC_n

RODIER Quentin
committed
USE MODD_LES, ONLY: LES_ASSOCIATE
USE MODD_LSFIELD_n

WAUTELET Philippe
committed
USE MODD_LUNIT, ONLY: TPGDFILE,TLUOUT0,TOUTDATAFILE
USE MODD_LUNIT_n, ONLY: CINIFILE,TINIFILE,TLUOUT
USE MODD_METRICS_n
USE MODD_MNH_SURFEX_n
USE MODD_NESTING
USE MODD_NSV
USE MODD_PARAMETERS
USE MODD_PARAM_n
USE MODD_PARAM_ICE, ONLY: PARAM_ICE_ASSOCIATE
USE MODD_PREP_REAL
USE MODD_REF_n
!UPG*PT
USE MODD_SALT, ONLY: LSALT, NMODE_SLT, CRGUNITS, XINISIG_SLT, XINIRADIUS_SLT, XN0MIN_SLT,&
LSLTCAMS
USE MODD_CH_AERO_n, ONLY: XM3D, XRHOP3D, XSIG3D, XRG3D, XN3D, XCTOTA3D
!UPG*PT
USE MODD_TURB_n
!
USE MODE_EXTRAPOL

WAUTELET Philippe
committed
use mode_field, only: Alloc_field_scalars, Ini_field_list, Ini_field_scalars

WAUTELET Philippe
committed
USE MODE_FINALIZE_MNH, only: FINALIZE_MNH
USE MODE_GRIDCART
USE MODE_GRIDPROJ

WAUTELET Philippe
committed
USE MODE_IO, only: IO_Init
USE MODE_IO_FIELD_READ, only: IO_Field_read
USE MODE_IO_FIELD_WRITE, only: IO_Header_write
USE MODE_IO_FILE, only: IO_File_close, IO_File_open

WAUTELET Philippe
committed
USE MODE_IO_MANAGE_STRUCT, only: IO_File_add2list, IO_File_find_byname
USE MODE_ll
USE MODE_MODELN_HANDLER
USE MODE_MPPDB
USE MODE_MSG
USE MODE_POS
USE MODE_SPLITTINGZ_ll
USE MODI_COMPARE_DAD
USE MODI_DEALLOC_PARA_LL
USE MODI_DEFAULT_DESFM_n
USE MODI_ERROR_ON_TEMPERATURE

RODIER Quentin
committed
USE MODI_IBM_INIT_LS
USE MODI_INI_PROG_VAR

WAUTELET Philippe
committed
USE MODI_INIT_SALT
USE MODI_LIMA_MIXRAT_TO_NCONC
USE MODI_METRICS
USE MODI_MNHREAD_ZS_DUMMY_n
USE MODI_MNHWRITE_ZS_DUMMY_n
USE MODI_OPEN_PRC_FILES
USE MODI_PRESSURE_IN_PREP
USE MODI_READ_ALL_DATA_GRIB_CASE
USE MODI_READ_ALL_DATA_MESONH_CASE
USE MODI_READ_ALL_NAMELISTS
!UPG*PT
!USE MODI_READ_CAMS_DATA_NETCDF_CASE
!USE MODI_READ_CHEM_DATA_NETCDF_CASE
USE MODI_READ_CHEM_DATA_MOZART_CASE
USE MODI_READ_CHEM_DATA_CAMS_CASE
USE MODI_READ_LIMA_DATA_NETCDF_CASE
USE MODI_AER2LIMA
USE MODI_CH_AER_EQM_INIT_n
!UPG*PT
USE MODI_READ_VER_GRID
USE MODI_SECOND_MNH
USE MODI_SET_REF
USE MODI_UPDATE_METRICS
USE MODI_VER_DYN
USE MODI_VER_PREP_GRIBEX_CASE
USE MODI_VER_PREP_MESONH_CASE
USE MODI_VER_PREP_NETCDF_CASE
USE MODI_VER_THERMO
USE MODI_WRITE_DESFM_n
USE MODI_WRITE_LFIFM_n

ESCOBAR MUNOZ Juan
committed
!
USE MODN_CONF, ONLY: JPHEXT , NHALO
USE MODN_CONFZ
USE MODN_PARAM_LIMA
IMPLICIT NONE
!
!* 0.1 Declaration of local variables
! ------------------------------
!
CHARACTER(LEN=28) :: YATMFILE ! name of the Atmospheric file
CHARACTER(LEN=6) :: YATMFILETYPE! type of the Atmospheric file
CHARACTER(LEN=28) :: YCHEMFILE ! name of the Chemical file
CHARACTER(LEN=6) :: YCHEMFILETYPE! type of the Chemical file
!UP*PT
!CHARACTER(LEN=28) :: YCAMSFILE ! name of the input CAMS file
!CHARACTER(LEN=6) :: YCAMSFILETYPE! type of the input CAMS file
CHARACTER(LEN=28) :: YLIMAFILE ! name of the input MACC file
CHARACTER(LEN=6) :: YLIMAFILETYPE! type of the input MACC file
!UP*PT
CHARACTER(LEN=28) :: YSURFFILE ! name of the Surface file
CHARACTER(LEN=6) :: YSURFFILETYPE! type of the Surface file
CHARACTER(LEN=28) :: YPGDFILE ! name of the physiographic data
! ! file
!
CHARACTER(LEN=28) :: YDAD_NAME ! true name of the atmospheric file
!
!* other variables
!
REAL,DIMENSION(:,:,:), ALLOCATABLE:: ZJ ! Jacobian
!
!* file management variables and counters
!
INTEGER :: ILUOUT0 ! logical unit for listing file
INTEGER :: IPRE_REAL1 ! logical unit for namelist file
INTEGER :: IRESP ! return code in FM routines
LOGICAL :: GFOUND ! Return code when searching namelist

RODIER Quentin
committed
INTEGER :: NIU,NJU,NKU ! Upper bounds in x,y,z directions
!
REAL :: ZSTART, ZEND, ZTIME1, ZTIME2, ZTOT, ZALL ! for computing time analysis
REAL :: ZMISC, ZREAD, ZHORI, ZPREP, ZSURF, ZTHERMO, ZDYN, ZDIAG, ZWRITE
REAL :: ZDG ! diagnostics time in routines
INTEGER :: IINFO_ll ! return code of // routines
! Namelist model variables
CHARACTER(LEN=5) :: CPRESOPT
INTEGER :: NITR
LOGICAL :: LRES
REAL :: XRES
LOGICAL :: LSHIFT ! flag to perform vertical shift or not.
LOGICAL :: LDUMMY_REAL ! flag to read and interpolate
!dummy fields from GRIBex file
INTEGER :: JRR ! loop counter for moist var.
LOGICAL :: LUSECHAQ
LOGICAL :: LUSECHIC
INTEGER :: JN

WAUTELET Philippe
committed
TYPE(TFILEDATA),POINTER :: TZATMFILE => NULL()

WAUTELET Philippe
committed
TYPE(TFILEDATA),POINTER :: TZPRE_REAL1FILE => NULL()
!
!
!* 0.3 Declaration of namelists
! ------------------------
!
NAMELIST/NAM_REAL_CONF/ NVERB, CEQNSYS, CPRESOPT, LSHIFT, LDUMMY_REAL, &
LRES, XRES, NITR,LCOUPLING, NHALO , JPHEXT
! Filtering and balancing of the large-scale and radar tropical cyclone
NAMELIST/NAM_HURR_CONF/ LFILTERING, CFILTERING, &
XLAMBDA, NK, XLATGUESS, XLONGUESS, XBOXWIND, XRADGUESS, NPHIL, NDIAG_FILT, &
NLEVELR0,LBOGUSSING, &
XLATBOG, XLONBOG, XVTMAXSURF, XRADWINDSURF, &
XMAX, XC, XRHO_Z, XRHO_ZZ, XB_0, XBETA_Z, XBETA_ZZ,&
XANGCONV0, XANGCONV1000, XANGCONV2000, &
CDADATMFILE, CDADBOGFILE
NAMELIST/NAM_AERO_CONF/ LORILAM, LINITPM, LDUST, XINIRADIUSI, XINIRADIUSJ,&
XINISIGI, XINISIGJ, XN0IMIN, XN0JMIN, CRGUNIT, CRGUNITD,&
LSALT, CRGUNITS, NMODE_DST, XINISIG, XINIRADIUS, XN0MIN,&
!UPG*PT
XINISIG_SLT, XINIRADIUS_SLT, XN0MIN_SLT, NMODE_SLT, &
LDSTCAMS, LSLTCAMS,CACTCCN,CCLOUD, NMOD_IFN, NMOD_CCN
!UPG*PT
NAMELIST/NAM_CH_CONF/ LUSECHAQ,LUSECHIC,LUSECHEM

RODIER Quentin
committed
!
NAMELIST/NAM_IBM_LSF/ LIBM_LSF, CIBM_TYPE, NIBM_SMOOTH, XIBM_SMOOTH
!
! name of dad of input FM file
INTEGER :: II, IJ, IGRID, ILENGTH
CHARACTER (LEN=100) :: HCOMMENT
TYPE(LIST_ll), POINTER :: TZFIELDS_ll=>NULL() ! list of fields to exchange
!UPG*PT
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLBXRHO, ZLBYRHO
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLBXZZ, ZLBYZZ
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZLBXPABST, ZLBYPABST
INTEGER :: ILBX,ILBY,IIB,IJB,IIE,IJE
!UPG*PT
!-------------------------------------------------------------------------------
!

ESCOBAR MUNOZ Juan
committed
CALL MPPDB_INIT()
!
CALL GOTO_MODEL(1,ONOFIELDLIST=.TRUE.)
!
ZDIAG = 0.
CALL SECOND_MNH (ZSTART)
!
ZHORI = 0.
ZSURF = 0.
ZTIME1 = ZSTART
!
!* 1. SET DEFAULT VALUES
! ------------------
!
CALL VERSION
CPROGRAM='REAL '
!
CALL PARAM_ICE_ASSOCIATE()
CALL TBUCONF_ASSOCIATE()

RODIER Quentin
committed
CALL LES_ASSOCIATE()

WAUTELET Philippe
committed
IDX_RVT = 1
!
!-------------------------------------------------------------------------------
!
!* 2. OPENNING OF THE FILES
! ---------------------

WAUTELET Philippe
committed
CALL IO_Init()

WAUTELET Philippe
committed
CALL OPEN_PRC_FILES(TZPRE_REAL1FILE,YATMFILE, YATMFILETYPE,TZATMFILE &
,YCHEMFILE,YCHEMFILETYPE &
,YSURFFILE,YSURFFILETYPE &
,YPGDFILE,TPGDFILE &
!UPG*PT
! ,YCAMSFILE,YCAMSFILETYPE)
,YLIMAFILE,YLIMAFILETYPE)
!UPG*PT
!
IF (YATMFILETYPE=='MESONH') THEN
LSHIFT = .FALSE.
ELSE IF (YATMFILETYPE=='GRIBEX') THEN
LSHIFT = .TRUE.
ELSE
LSHIFT = .TRUE.
WRITE(ILUOUT0,FMT=*) 'HATMFILETYPE WAS SET TO: '//TRIM(YATMFILETYPE)
WRITE(ILUOUT0,FMT=*) 'ONLY TWO VALUES POSSIBLE FOR HATMFILETYPE:'
WRITE(ILUOUT0,FMT=*) 'EITHER MESONH OR GRIBEX'
WRITE(ILUOUT0,FMT=*) '-> JOB ABORTED'
!callabortstop
CALL PRINT_MSG(NVERB_FATAL,'GEN','PREP_REAL_CASE','')
END IF
!
LCPL_AROME=.FALSE.
!
!-------------------------------------------------------------------------------
!
!* 3. INITIALIZATION OF PHYSICAL CONSTANTS
! ------------------------------------
!
CALL INI_CST
!
!-------------------------------------------------------------------------------
!
!* 4. READING OF NAMELIST
! -------------------
!
!* 4.1 reading of configuration variables
!

WAUTELET Philippe
committed
IPRE_REAL1 = TZPRE_REAL1FILE%NLU
CALL INIT_NMLVAR
CALL POSNAM(IPRE_REAL1,'NAM_REAL_CONF',GFOUND,ILUOUT0)
IF (GFOUND) READ(IPRE_REAL1,NAM_REAL_CONF)
CALL POSNAM(IPRE_REAL1,'NAM_PARAM_LIMA',GFOUND,ILUOUT0)
IF (GFOUND) READ(IPRE_REAL1,NAM_PARAM_LIMA)

WAUTELET Philippe
committed
CALL INI_FIELD_LIST(1)
!* 4.2 reading of values of some configuration variables in namelist
!
!
!JUAN REALZ from prep_surfex
!
IF (YATMFILETYPE == 'GRIBEX') THEN
!
!* 4.1 Vertical Spatial grid
!
CALL INIT_NMLVAR()

WAUTELET Philippe
committed
CALL READ_VER_GRID(TZPRE_REAL1FILE)

WAUTELET Philippe
committed
CALL IO_Field_read(TPGDFILE,'IMAX',NIMAX)
CALL IO_Field_read(TPGDFILE,'JMAX',NJMAX)
!
NIMAX_ll=NIMAX !! _ll variables are global variables
NJMAX_ll=NJMAX !! but the old names are kept in PRE_IDEA1.nam file
!
CALL SET_JP_ll(JPMODELMAX,JPHEXT,JPVEXT,JPHEXT)
CALL SET_DAD0_ll()
!JUAN 4/04/2014 correction for PREP_REAL_CASE on Gribex files
!CALL SET_DIM_ll(NIMAX_ll, NJMAX_ll, 128)
CALL SET_DIM_ll(NIMAX_ll, NJMAX_ll, NKMAX)
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
CALL SET_LBX_ll('OPEN',1)
CALL SET_LBY_ll('OPEN', 1)
CALL SET_XRATIO_ll(1, 1)
CALL SET_YRATIO_ll(1, 1)
CALL SET_XOR_ll(1, 1)
CALL SET_XEND_ll(NIMAX_ll+2*JPHEXT, 1)
CALL SET_YOR_ll(1, 1)
CALL SET_YEND_ll(NJMAX_ll+2*JPHEXT, 1)
CALL SET_DAD_ll(0, 1)
!JUANZ
!CALL INI_PARA_ll(IINFO_ll)
CALL INI_PARAZ_ll(IINFO_ll)
!JUANZ
!
! sizes of arrays of the extended sub-domain
!
CALL GET_DIM_PHYS_ll('B',NIMAX,NJMAX)
!!$CALL GET_DIM_EXT_ll('B',NIU,NJU)
!!$CALL GET_INDICE_ll(NIB,NJB,NIE,NJE)
!!$CALL GET_OR_ll('B',IXOR,IYOR)
ENDIF
!JUAN REALZ
!
LDUMMY_REAL= .FALSE.
LFILTERING= .FALSE.
CFILTERING= 'UVT '
XLATGUESS= XUNDEF ; XLONGUESS= XUNDEF ; XBOXWIND=XUNDEF; XRADGUESS= XUNDEF
NK=50 ; XLAMBDA=0.2 ; NPHIL=24
NLEVELR0=15
NDIAG_FILT=-1
LBOGUSSING= .FALSE.
XLATBOG= XUNDEF ; XLONBOG= XUNDEF
XVTMAXSURF= XUNDEF ; XRADWINDSURF= XUNDEF
XMAX=16000. ; XC=0.7 ; XRHO_Z=-0.3 ; XRHO_ZZ=0.9
XB_0=1.65 ; XBETA_Z=-0.5 ; XBETA_ZZ=0.35
XANGCONV0=0. ; XANGCONV1000=0. ; XANGCONV2000=0.
CDADATMFILE=' ' ; CDADBOGFILE=' '
!
CALL INIT_NMLVAR
CALL POSNAM(IPRE_REAL1,'NAM_REAL_CONF',GFOUND,ILUOUT0)
IF (GFOUND) READ(IPRE_REAL1,NAM_REAL_CONF)
CALL POSNAM(IPRE_REAL1,'NAM_HURR_CONF',GFOUND,ILUOUT0)
IF (GFOUND) READ(IPRE_REAL1,NAM_HURR_CONF)
CALL POSNAM(IPRE_REAL1,'NAM_CH_CONF',GFOUND,ILUOUT0)
IF (GFOUND) READ(UNIT=IPRE_REAL1,NML=NAM_CH_CONF)
CALL UPDATE_MODD_FROM_NMLVAR
CALL POSNAM(IPRE_REAL1,'NAM_AERO_CONF',GFOUND,ILUOUT0)
IF (GFOUND) READ(IPRE_REAL1,NAM_AERO_CONF)
CALL POSNAM(IPRE_REAL1,'NAM_CONFZ',GFOUND,ILUOUT0)
IF (GFOUND) READ(UNIT=IPRE_REAL1,NML=NAM_CONFZ)

RODIER Quentin
committed
CALL POSNAM(IPRE_REAL1,'NAM_IBM_LSF' ,GFOUND,ILUOUT0)
IF (GFOUND) READ(UNIT=IPRE_REAL1,NML=NAM_IBM_LSF)

RODIER Quentin
committed
! Sea salt
CALL INIT_SALT
!
!* 4.3 set soil scheme to ISBA for initialization from GRIB
!
IF (YATMFILETYPE=='GRIBEX') THEN
CLBCX(:) ='OPEN'
CLBCY(:) ='OPEN'
END IF
!
CALL SECOND_MNH(ZTIME2)
ZMISC = ZTIME2 - ZTIME1
!-------------------------------------------------------------------------------
!
!* 5. READING OF THE INPUT DATA
! -------------------------
!
ZTIME1 = ZTIME2
!
IF (YATMFILETYPE=='MESONH') THEN

WAUTELET Philippe
committed
CALL READ_ALL_DATA_MESONH_CASE(TZPRE_REAL1FILE,YATMFILE,TPGDFILE,YDAD_NAME)
ELSE IF (YATMFILETYPE=='GRIBEX') THEN
IF(LEN_TRIM(YCHEMFILE)>0 .AND. YCHEMFILETYPE=='GRIBEX')THEN

WAUTELET Philippe
committed
CALL READ_ALL_DATA_GRIB_CASE('ATM1',TZPRE_REAL1FILE,YATMFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)

WAUTELET Philippe
committed
CALL READ_ALL_DATA_GRIB_CASE('ATM0',TZPRE_REAL1FILE,YATMFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
END IF
!
YDAD_NAME=' '
END IF
!
IF (NIMAX==1 .AND. NJMAX==1) THEN
L1D=.TRUE.
L2D=.FALSE.
ELSE IF (NJMAX==1) THEN
L1D=.FALSE.
L2D=.TRUE.
ELSE
L1D=.FALSE.
L2D=.FALSE.
END IF
!
! UPG*PT
!* 5.1 reading of the input chemical data
!
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
!IF(LEN_TRIM(YCHEMFILE)>0)THEN
! ! read again Nam_aero_conf
! CALL POSNAM(IPRE_REAL1,'NAM_AERO_CONF',GFOUND,ILUOUT0)
! IF (GFOUND) READ(IPRE_REAL1,NAM_AERO_CONF)
! IF(YCHEMFILETYPE=='GRIBEX') &
! CALL READ_ALL_DATA_GRIB_CASE('CHEM',TZPRE_REAL1FILE,YCHEMFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
! IF (YCHEMFILETYPE=='NETCDF') &
! CALL READ_CHEM_DATA_NETCDF_CASE(TZPRE_REAL1FILE,YCHEMFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
!END IF
!
!* 5.2 reading the input CAMS data
!
!IF(LEN_TRIM(YCAMSFILE)>0)THEN
! IF(YCAMSFILETYPE=='NETCDF') THEN
! CALL READ_CAMS_DATA_NETCDF_CASE(TZPRE_REAL1FILE,YCAMSFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
! ELSE
! CALL PRINT_MSG(NVERB_FATAL,'GEN','PREP_REAL_CASE','CANNOT READ CAMS GRIB FILES YET')
! END IF
!END IF
!* 5.1 reading CAMS or MACC files for init LIMA
!
IF(LEN_TRIM(YLIMAFILE)>0)THEN
IF(YLIMAFILETYPE=='NETCDF') THEN
CALL READ_LIMA_DATA_NETCDF_CASE(TZPRE_REAL1FILE,YLIMAFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
ELSE
WRITE(ILUOUT0,FMT=*)
!callabortstop
CALL PRINT_MSG(NVERB_FATAL,'GEN','PREP_REAL_CASE','Pb in MACC/CAMS file')
STOP
END IF
END IF
!
!* 5.2 reading of the input chemical data + dusts + salts if needed
!
IF(LEN_TRIM(YCHEMFILE)>0)THEN
! read again Nam_aero_conf
CALL POSNAM(IPRE_REAL1,'NAM_AERO_CONF',GFOUND,ILUOUT0)
IF (GFOUND) READ(IPRE_REAL1,NAM_AERO_CONF)
IF(YCHEMFILETYPE=='GRIBEX') &

WAUTELET Philippe
committed
CALL READ_ALL_DATA_GRIB_CASE('CHEM',TZPRE_REAL1FILE,YCHEMFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
IF (YCHEMFILETYPE=='MOZART') &
CALL READ_CHEM_DATA_MOZART_CASE(TZPRE_REAL1FILE,YCHEMFILE,TPGDFILE,ZHORI,NVERB,LDUMMY_REAL)
IF (YCHEMFILETYPE=='CAMSEU') &
CALL READ_CHEM_DATA_CAMS_CASE(TZPRE_REAL1FILE,YCHEMFILE,TPGDFILE,ZHORI,NVERB, &
LDUMMY_REAL,LUSECHEM)
!UPG*PT

WAUTELET Philippe
committed
CALL IO_File_close(TZPRE_REAL1FILE)
!
CALL SECOND_MNH(ZTIME2)
ZREAD = ZTIME2 - ZTIME1 - ZHORI
!-------------------------------------------------------------------------------
!

WAUTELET Philippe
committed
CALL IO_File_add2list(TINIFILE,CINIFILE,'MNH','WRITE',KLFITYPE=1,KLFIVERB=NVERB)
CALL IO_File_open(TINIFILE)
!
ZTIME1=ZTIME2
!
!* 6. CONFIGURATION VARIABLES
! -----------------------
!
!* 6.1 imposed values of some other configuration variables
!
CDCONV='NONE'
CSCONV='NONE'
CRAD='NONE'
CCONF='START'
NRIMX=6
NRIMY=6
LHORELAX_UVWTH=.TRUE.
LHORELAX_RV=LUSERV
LHORELAX_RC=LUSERC
LHORELAX_RR=LUSERR
LHORELAX_RI=LUSERI
LHORELAX_RS=LUSERS
LHORELAX_RG=LUSERG
LHORELAX_RH=LUSERH
LHORELAX_SV(:)=.FALSE.
LHORELAX_SVC2R2 = (NSV_C2R2 > 0)
LHORELAX_SVC1R3 = (NSV_C1R3 > 0)
LHORELAX_SVELEC = (NSV_ELEC > 0)
LHORELAX_SVCHEM = (NSV_CHEM > 0)
LHORELAX_SVCHIC = (NSV_CHIC > 0)
LHORELAX_SVDST = (NSV_DST > 0)
LHORELAX_SVSLT = (NSV_SLT > 0)
LHORELAX_SVAER = (NSV_AER > 0)
LHORELAX_SVPP = (NSV_PP > 0)
#ifdef MNH_FOREFIRE
LHORELAX_SVFF = (NSV_FF > 0)
#endif
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
LHORELAX_SVCS = (NSV_CS > 0)
LHORELAX_SVLG = .FALSE.
LHORELAX_SV(1:NSV)=.TRUE.
IF ( CTURB /= 'NONE') THEN
LHORELAX_TKE = .TRUE.
ELSE
LHORELAX_TKE = .FALSE.
END IF
!
!
CSTORAGE_TYPE='TT'
!-------------------------------------------------------------------------------
!
!* 8. COMPUTATION OF GEOMETRIC VARIABLES
! ----------------------------------
!
ZTIME1 = ZTIME2
!
ALLOCATE(XMAP(SIZE(XXHAT),SIZE(XYHAT)))
ALLOCATE(XLAT(SIZE(XXHAT),SIZE(XYHAT)))
ALLOCATE(XLON(SIZE(XXHAT),SIZE(XYHAT)))
ALLOCATE(XDXHAT(SIZE(XXHAT)))
ALLOCATE(XDYHAT(SIZE(XYHAT)))
ALLOCATE(XZZ(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
ALLOCATE(ZJ(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
!
IF (LCARTESIAN) THEN
CALL SM_GRIDCART(XXHAT,XYHAT,XZHAT,XZS,LSLEVE,XLEN1,XLEN2,XZSMT,XDXHAT,XDYHAT,XZZ,ZJ)
CALL SM_GRIDPROJ(XXHAT,XYHAT,XZHAT,XZS, &
LSLEVE,XLEN1,XLEN2,XZSMT,XLATORI,XLONORI, &
XMAP,XLAT,XLON,XDXHAT,XDYHAT,XZZ,ZJ )
END IF
!
CALL MPPDB_CHECK2D(XZS,"prep_real_case8:XZS",PRECISION)
CALL MPPDB_CHECK2D(XMAP,"prep_real_case8:XMAP",PRECISION)
CALL MPPDB_CHECK2D(XLAT,"prep_real_case8:XLAT",PRECISION)
CALL MPPDB_CHECK2D(XLON,"prep_real_case8:XLON",PRECISION)
CALL MPPDB_CHECK3D(XZZ,"prep_real_case8:XZZ",PRECISION)
CALL MPPDB_CHECK3D(ZJ,"prep_real_case8:ZJ",PRECISION)
!
ALLOCATE(XDXX(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
ALLOCATE(XDYY(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
ALLOCATE(XDZX(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
ALLOCATE(XDZY(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
ALLOCATE(XDZZ(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)))
!
!20131024 add update halo
!=> corrects on PDXX calculation in metrics and XDXX !!

WAUTELET Philippe
committed
CALL ADD3DFIELD_ll( TZFIELDS_ll, XZZ, 'PREP_REAL_CASE::XZZ' )
CALL UPDATE_HALO_ll(TZFIELDS_ll,IINFO_ll)
CALL CLEANLIST_ll(TZFIELDS_ll)
!
CALL METRICS(XMAP,XDXHAT,XDYHAT,XZZ,XDXX,XDYY,XDZX,XDZY,XDZZ)
!
CALL MPPDB_CHECK3D(XDXX,"prc8-beforeupdate_metrics:PDXX",PRECISION)
CALL MPPDB_CHECK3D(XDYY,"prc8-beforeupdate_metrics:PDYY",PRECISION)
CALL MPPDB_CHECK3D(XDZX,"prc8-beforeupdate_metrics:PDZX",PRECISION)
CALL MPPDB_CHECK3D(XDZY,"prc8-beforeupdate_metrics:PDZY",PRECISION)
!
CALL UPDATE_METRICS(CLBCX,CLBCY,XDXX,XDYY,XDZX,XDZY,XDZZ)
!
!20131112 add update_halo for XDYY and XDZY!!

WAUTELET Philippe
committed
CALL ADD3DFIELD_ll( TZFIELDS_ll, XDXX, 'PREP_REAL_CASE::XDXX' )
CALL ADD3DFIELD_ll( TZFIELDS_ll, XDZX, 'PREP_REAL_CASE::XDZX' )
CALL ADD3DFIELD_ll( TZFIELDS_ll, XDYY, 'PREP_REAL_CASE::XDYY' )
CALL ADD3DFIELD_ll( TZFIELDS_ll, XDZY, 'PREP_REAL_CASE::XDZY' )
CALL UPDATE_HALO_ll(TZFIELDS_ll,IINFO_ll)
CALL CLEANLIST_ll(TZFIELDS_ll)
!CALL EXTRAPOL('W',XDXX,XDZX)
!CALL EXTRAPOL('S',XDYY,XDZY)
CALL SECOND_MNH(ZTIME2)
ZMISC = ZMISC + ZTIME2 - ZTIME1
!-------------------------------------------------------------------------------
!
!* 9. PREPARATION OF THE VERTICAL SHIFT AND INTERPOLATION
! ---------------------------------------------------
!
ZTIME1 = ZTIME2
!
IF (YATMFILETYPE=='GRIBEX') THEN
CALL VER_PREP_GRIBEX_CASE('ATM ',ZDG)
ELSE IF (YATMFILETYPE=='MESONH') THEN
CALL VER_PREP_MESONH_CASE(ZDG)
END IF
!
IF (LEN_TRIM(YCHEMFILE)>0 .AND. YCHEMFILETYPE=='GRIBEX') THEN
CALL VER_PREP_GRIBEX_CASE('CHEM',ZDG)
END IF
!UPG*PT
!IF ((LEN_TRIM(YCHEMFILE)>0 .AND. YCHEMFILETYPE=='NETCDF') .OR. &
! (LEN_TRIM(YCAMSFILE)>0 .AND. YCAMSFILETYPE=='NETCDF')) THEN
! CALL VER_PREP_NETCDF_CASE(ZDG)
!END IF
IF (LEN_TRIM(YCHEMFILE)>0 .AND. ((YCHEMFILETYPE=='MOZART').OR. &
(YCHEMFILETYPE=='CAMSEU'))) THEN