Newer
Older
1
2
3
4
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
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
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
!MNH_LIC Copyright 1994-2021 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.
!-----------------------------------------------------------------
! #######################
PROGRAM PREP_IDEAL_CASE
! #######################
!
!!**** *PREP_IDEAL_CASE* - program to write an initial FM-file
!!
!! PURPOSE
!! -------
! The purpose of this program is to prepare an initial meso-NH file
! (LFIFM and DESFM files) filled with some idealized fields.
!
! ---- The present version can provide two types of fields:
!
! 1) CIDEAL = 'CSTN' : 3D fields derived from a vertical profile with
! --------------- n levels of constant moist Brunt Vaisala frequency
! The vertical profile is read in EXPRE file.
! These fields can be used for model runs
!
! 2) CIDEAL = 'RSOU' : 3D fields derived from a radiosounding.
! ---------------
! The radiosounding is read in EXPRE file.
! The following kind of data is permitted :
! YKIND = 'STANDARD' : Zsol, Psol, Tsol, TDsol
! (Pressure, dd, ff) ,
! (Pressure, T, Td)
! YKIND = 'PUVTHVMR' : zsol, Psol, Thvsol, Rsol
! (Pressure, U, V) ,
! (Pressure, THv, R)
! YKIND = 'PUVTHVHU' : zsol, Psol, Thvsol, Husol
! (Pressure, U, V) ,
! (Pressure, THv, Hu)
! YKIND = 'ZUVTHVHU' : zsol, Psol, Thvsol, Husol
! (height, U, V) ,
! (height, THv, Hu)
! YKIND = 'ZUVTHVMR' : zsol, Psol, Thvsol, Rsol
! (height, U, V) ,
! (height, THv, R)
! YKIND = 'PUVTHDMR' : zsol, Psol, Thdsol, Rsol
! (Pressure, U, V) ,
! (Pressure, THd, R)
! YKIND = 'PUVTHDHU' : zsol, Psol, Thdsol, Husol
! (Pressure, U, V) ,
! (Pressure, THd, Hu)
! YKIND = 'ZUVTHDMR' : zsol, Psol, Thdsol, Rsol
! (height, U, V) ,
! (height, THd, R)
! YKIND = 'ZUVTHLMR' : zsol, Psol, Thdsol, Rsol
! (height, U, V) ,
! (height, THl, Rt)
!
! These fields can be used for model runs
!
! Cases (1) and (2) can be balanced
! (geostrophic, hydrostatic and anelastic balances) if desired.
!
! ---- The orography can be flat (YZS='FLAT'), but also
! sine-shaped (YZS='SINE') or bell-shaped (YZS='BELL')
!
! ---- The U(z) profile given in the RSOU and CSTN cases can
! be multiplied (CUFUN="Y*Z") by a function of y (function FUNUY)
! The V(z) profile given in the RSOU and CSTN cases can
! be multiplied (CVFUN="X*Z") by a function of x (function FUNVX).
! If it is not the case, i.e. U(y,z)=U(z) then CUFUN="ZZZ" and
! CVFUN="ZZZ" for V(y,z)=V(z). Instead of these separable forms,
! non-separables functions FUNUYZ (CUFUN="Y,Z") and FUNVXZ (CVFUN="X,Z")
! can be used to specify the wind components.
!
!!** METHOD
!! ------
!! The directives and data to perform the preparation of the initial FM
!! file are stored in EXPRE file. This file is composed of two parts :
!! - a namelists-format part which is present in all cases
!! - a free-format part which contains data in cases
!! of discretised orography (CZS='DATA')
!! of radiosounding (CIDEAL='RSOU') or Nv=cste profile (CIDEAL='CSTN')
!! of forced version (LFORCING=.TRUE.)
!!
!!
!! The following PREP_IDEAL_CASE program :
!!
!! - initializes physical constants by calling INI_CST
!!
!! - sets default values for global variables which will be
!! written in DESFM file and for variables in EXPRE file (namelists part)
!! which will be written in LFIFM file.
!!
!! - reads the namelists part of EXPRE file which gives
!! informations about the preinitialization to perform,
!!
!! - allocates memory for arrays,
!!
!! - initializes fields depending on the
!! directives (CIDEAL in namelist NAM_CONF_PRE) :
!!
!! * grid variables :
!! The gridpoints are regularly spaced by XDELTAX, XDELTAY.
!! The grid is stretched along the z direction, the mesh varies
!! from XDZGRD near the ground to XDZTOP near the top and the
!! weigthing function is a TANH function characterized by its
!! center and width above and under this center
!! The orography is initialized following the kind of orography
!! (YZS in namelist NAM_CONF_PRE) and the degrees of freedom :
!! sine-shape ---> ZHMAX, IEXPX,IEXPY
!! bell-shape ---> ZHMAX, ZAX,ZAY,IIZS,IJZS
!! The horizontal grid variables are initialized following
!! the kind of geometry (LCARTESIAN in namelist NAM_CONF_PRE)
!! and the grid parameters XLAT0,XLON0,XBETA in both geometries
!! and XRPK,XLONORI,XLATORI in conformal projection.
!! In the case of initialization from a radiosounding, the
!! date and time is read in free-part of the EXPRE file. In other
!! cases year, month and day are set to NUNDEF and time to 0.
!!
!! * prognostic fields :
!!
!! U,V,W, Theta and r. are first determined. They are
!! multiplied by rhoj after the anelastic reference state
!! computation.
!! For the CSTN and RSOU cases, the determination of
!! Theta and rv is performed respectively by SET_RSOU
!! and by SET_CSTN which call the common routine SET_MASS.
!! These three routines have the following actions :
!! --- The input vertical profile is converted in
!! variables (U,V,thetav,r) and interpolated
!! on a mixed grid (with VERT_COORD) as in PREP_REAL_CASE
!! --- A variation of the u-wind component( x-model axis component)
!! is possible in y direction, a variation of the v-wind component
!! (y-model axis component) is possible in x direction.
!! --- Thetav could be computed with thermal wind balance
!! (LGEOSBAL=.TRUE. with call of SET_GEOSBAL)
!! --- The mass fields (theta and r ) and the wind components are
!! then interpolated on the model grid with orography as in
!! PREP_REAL_CASE with the option LSHIFT
!! --- An anelastic correction is applied in PRESSURE_IN_PREP in
!! the case of non-vanishing orography.
!!
!! * anelastic reference state variables :
!!
!! 1D reference state :
!! RSOU and CSTN cases : rhorefz and thvrefz are computed
!! by SET_REFZ (called by SET_MASS).
!! They are deduced from thetav and r on the model grid
!! without orography.
!! The 3D reference state is computed by SET_REF
!!
!! * The total mass of dry air is computed by TOTAL_DMASS
!!
!! - writes the DESFM file,
!!
!! - writes the LFIFM file .
!!
!! EXTERNAL
!! --------
!! DEFAULT_DESFM : to set default values for variables which can be
!! contained in DESFM file
!! DEFAULT_EXPRE : to set default values for other global variables
!! which can be contained in namelist-part of EXPRE 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_RSOU : to initialize mass fields from a radiosounding
!! SET_CSTN : to initialize mass fields from a vertical profile of
!! n layers of Nv=cste
!! SET_REF : to compute rhoJ
!! RESSURE_IN_PREP : to apply an anelastic correction in the case of
!! non-vanishing orography
!! IO_File_open : to open a FM-file (DESFM + LFIFM)
!! WRITE_DESFM : to write the DESFM file
!! WRI_LFIFM : to write the LFIFM file
!! IO_File_close : to close a FM-file (DESFM + LFIFM)
!!
!! MXM,MYM,MZM : Shuman operators
!! WGUESS : to compute W with the continuity equation from
!! the U,V values
!!
!!
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! Module MODD_PARAMETERS : contains parameters
!! Module MODD_DIM1 : contains dimensions
!! Module MODD_CONF : contains configuration variables for
!! all models
!! Module MODD_CST : contains physical constants
!! Module MODD_GRID : contains grid variables for all models
!! Module MODD_GRID1 : contains grid variables
!! Module MODD_TIME : contains time variables for all models
!! Module MODD_TIME1 : contains time variables
!! Module MODD_REF : contains reference state variables for
!! all models
!! Module MODD_REF1 : contains reference state variables
!! Module MODD_LUNIT : contains variables which concern names
!! and logical unit numbers of files for all models
!! Module MODD_FIELD1 : contains prognostics variables
!! Module MODD_GR_FIELD1 : contains the surface prognostic variables
!! Module MODD_LSFIELD1 : contains Larger Scale fields
!! Module MODD_DYN1 : contains dynamic control variables for model 1
!! Module MODD_LBC1 : contains lbc control variables for model 1
!!
!!
!! Module MODN_CONF1 : contains configuration variables for model 1
!! and the NAMELIST list
!! Module MODN_LUNIT1 : contains variables which concern names
!! and logical unit numbers of files and
!! the NAMELIST list
!!
!!
!! REFERENCE
!! ---------
!! Book2 of MESO-NH documentation (program PREP_IDEAL_CASE)
!!
!! AUTHOR
!! ------
!! V. Ducrocq *Meteo France*
!!
!! MODIFICATIONS
!! -------------
!! Original 05/05/94
!! updated V. Ducrocq 27/06/94
!! updated P.M. 27/07/94
!! updated V. Ducrocq 23/08/94
!! updated V. Ducrocq 01/09/94
!! namelist changes J. Stein 26/10/94
!! namelist changes J. Stein 04/11/94
!! remove the second step of the geostrophic balance 14/11/94 (J.Stein)
!! add grid stretching in the z direction + Larger scale fields +
!! cleaning 6/12/94 (J.Stein)
!! periodize the orography and the grid sizes in the periodic case
!! 19/12/94 (J.Stein)
!! correct a bug in the Larger Scale Fields initialization
!! 19/12/94 (J.Stein)
!! add the vertical grid stretching 02/01/95 (J. Stein)
!! Total mass of dry air computation 02/01/95 (J.P.Lafore)
!! add the 1D switch 13/01/95 (J. Stein)
!! enforce a regular vertical grid if desired 18/01/95 (J. Stein)
!! add the tdtcur initialization 26/01/95 (J. Stein)
!! bug in the test of the type of RS localization 25/02/95 (J. Stein)
!! remove R from the historical variables 16/03/95 (J. Stein)
!! error on the grid stretching 30/06/95 (J. Stein)
!! add the soil fields 01/09/95 (S.Belair)
!! change the streching function and the wind guess
!! (J. Stein and V.Masson) 21/09/95
!! reset to FALSE LUSERC,..,LUSERH 12/12/95 (J. Stein)
!! enforce the RS localization in 1D and 2D config.
!! + add the 'TSZ0' option for the soil variables 28/01/96 (J. Stein)
!! initialization of domain from center point 31/01/96 (V. Masson)
!! add the constant file reading 05/02/96 (J. Stein)
!! enter vertical model levels values 20/10/95 (T.Montmerle)
!! add LFORCING option 19/02/96 (K. Suhre)
!! modify structure of NAM_CONF_PRE 20/02/96 (J.-P. Pinty)
!! default of the domain center when use of pgd file 12/03/96 (V. Masson)
!! change the surface initialization 20/03/96 ( Stein,
!! Bougeault, Kastendeutsch )
!! change the DEFAULT_DESFMN CALL 17/04/96 ( Lafore )
!! set the STORAGE_TYPE to 'TT' (a single instant) 30/04/96 (Stein,
!! Jabouille)
!! new wguess to spread the divergence 15/05/96 (Stein)
!! set LTHINSHELL to TRUE + return to the old wguess 29/08/96 (Stein)
!! MY_NAME and DAD_NAME writing for nesting 30/07/96 (Lafore)
!! MY_NAME and DAD_NAME reading in pgd file 26/09/96 (Masson)
!! and reading of pgd grid in a new routine
!! XXHAT and XYHAT are set to 0. at origine point 02/10/96 (Masson)
!! add LTHINSHELL in namelist NAM_CONF_PRE 08/10/96 (Masson)
!! restores use of TS and T2 26/11/96 (Masson)
!! value XUNDEF for soil and vegetation fields on sea 27/11/96 (Masson)
!! use of HUG and HU2 in both ISBA and TSZ0 cases 04/12/96 (Masson)
!! add initialization of chemical variables 06/08/96 (K. Suhre)
!! add MANUAL option for the terrain elevation 12/12/96 (J.-P. Pinty)
!! set DATA instead of MANUAL for the terrain
!! elevation option
!! add new anelastic equations' systems 29/06/97 (Stein)
!! split mode_lfifm_pgd 29/07/97 (Masson)
!! add directional z0 and subgrid scale orography 31/07/97 (Masson)
!! separates surface treatment in PREP_IDEAL_SURF 15/03/99 (Masson)
!! new PGD fields allocations 15/03/99 (Masson)
!! iterative call to pressure solver 15/03/99 (Masson)
!! removes TSZ0 case 04/01/00 (Masson)
!! parallelization 18/06/00 (Pinty)
!! adaptation for patch approach 02/07/00 (Solmon/Masson)
!! bug in W LB field on Y direction 05/03/01 (Stein)
!! add module MODD_NSV for NSV variable 01/02/01 (D. Gazen)
!! allow namelists in different orders 15/10/01 (I. Mallet)
!! allow LUSERC and LUSERI in 1D configuration 05/06/02 (P. Jabouille)
!! add ZUVTHLMR case (move in set_rsou latter) 05/12/02 Jabouille/Masson
!! move LHORELAX_SV (after INI_NSV) 30/04/04 (Pinty)
!! Correction Parallel bug IBEG & IDEND evalution 13/11/08 J.Escobar
!! add the option LSHIFT for interpolation of 26/10/10 (G.Tanguy)
!! correction for XHAT & parallelizarion of ZSDATA 23/09/11 J.Escobar
!! the vertical profile (as in PREP_REAL_CASE)
!! add use MODI of SURFEX routines 10/10/111 J.Escobar
!!
!! For 2D modeling:
!! Initialization of ADVFRC profiles (SET_ADVFRC) 06/2010 (P.Peyrille)
!! when LDUMMY(2)=T in PRE_IDEA1.nam
!! USE MODDB_ADVFRC_n for grid-nesting 02*2012 (M. Tomasini)
!! LBOUSS in MODD_REF 07/2013 (C.Lac)
!! Correction for ZS in PGD file 04/2014 (G. TANGUY)
!! Bug : remove NC WRITE_HGRID 05/2014 (S. Bielli via J.Escobar )
!! BUG if ZFRC and ZFRC_ADV or ZFRC_REL are used together 11/2014 (G. Delautier)
!! Bug : detected with cray compiler ,
!! missing '&' in continuation string 3/12/2014 J.Escobar
!! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1
!! 06/2016 (G.Delautier) phasage surfex 8
!! P.Wautelet : 08/07/2016 : removed MNH_NCWRIT define
!! 01/2018 (G.Delautier) SURFEX 8.1
! P. Wautelet: 05/2016-04/2018: new data structures and calls for I/O
! P. Wautelet 07/02/2019: force TYPE to a known value for IO_File_add2list
! P. Wautelet 14/02/2019: remove CLUOUT/CLUOUT0 and associated variables
! P. Wautelet 28/03/2019: use MNHTIME for time measurement variables
! P. Wautelet 28/03/2019: use TFILE instead of unit number for set_iluout_timing
! P. Wautelet 19/04/2019: removed unused dummy arguments and variables
! P. Wautelet 26/04/2019: replace non-standard FLOAT function by REAL function
! P. Wautelet 20/05/2019: add name argument to ADDnFIELD_ll + new ADD4DFIELD_ll subroutine
! F. Auguste 02/2021: add IBM
! P. Wautelet 09/03/2021: move some chemistry initializations to ini_nsv
! Jean-Luc Redelsperger 03/2021: ocean LES case
! P. Wautelet 06/07/2021: use FINALIZE_MNH
!-------------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------
!
USE MODD_PARAMETERS ! Declarative modules
USE MODD_ARGSLIST_ll, ONLY : LIST_ll
USE MODD_DIM_n
USE MODD_CONF
USE MODD_CST
USE MODD_GRID
USE MODD_GRID_n
USE MODD_IBM_LSF, ONLY: CIBM_TYPE, LIBM_LSF, NIBM_SMOOTH, XIBM_SMOOTH
USE MODD_IBM_PARAM_n, ONLY: XIBM_LS
USE MODD_METRICS_n
USE MODD_PGDDIM
USE MODD_PGDGRID
USE MODD_TIME
USE MODD_TIME_n
USE MODD_PARAM_ICE, ONLY: PARAM_ICE_ASSOCIATE
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
USE MODD_REF
USE MODD_REF_n
USE MODD_LUNIT
USE MODD_FIELD_n
USE MODD_DYN_n
USE MODD_LBC_n
USE MODD_LSFIELD_n
USE MODD_PARAM_n
USE MODD_CH_MNHC_n, ONLY: LUSECHEM, LUSECHAQ, LUSECHIC, LCH_PH, LCH_INIT_FIELD
USE MODD_CH_AEROSOL,ONLY: LORILAM, CORGANIC, LVARSIGI, LVARSIGJ, LINITPM, XINIRADIUSI, &
XINIRADIUSJ, XINISIGI, XINISIGJ, XN0IMIN, XN0JMIN, CRGUNIT
USE MODD_DUST, ONLY: LDUST, NMODE_DST, CRGUNITD, XINISIG, XINIRADIUS, XN0MIN
USE MODD_SALT, ONLY: LSALT, NMODE_SLT, CRGUNITS, XINISIG_SLT, XINIRADIUS_SLT, XN0MIN_SLT
USE MODD_VAR_ll, ONLY: NPROC
USE MODD_LUNIT, ONLY: TLUOUT0, TOUTDATAFILE
USE MODD_LUNIT_n
USE MODD_IO, ONLY: TFILE_DUMMY, TFILE_OUTPUTLISTING
USE MODD_CONF_n
USE MODD_NSV, ONLY: NSV
use modd_precision, only: LFIINT, MNHREAL_MPI, MNHTIME
!
USE MODN_BLANK_n
!
USE MODE_FINALIZE_MNH, only: FINALIZE_MNH
USE MODE_THERMO
USE MODE_POS
USE MODE_GRIDCART ! Executive modules
USE MODE_GRIDPROJ
USE MODE_GATHER_ll
USE MODE_IO, only: IO_Config_set, IO_Init, IO_Pack_set
USE MODE_IO_FIELD_READ, only: IO_Field_read
USE MODE_IO_FIELD_WRITE, only: IO_Field_write, IO_Header_write
USE MODE_IO_FILE, only: IO_File_close, IO_File_open
USE MODE_IO_MANAGE_STRUCT, only: IO_File_add2list
USE MODE_ll
USE MODE_MODELN_HANDLER
use mode_field, only: Alloc_field_scalars, Ini_field_list, Ini_field_scalars
USE MODE_MSG
!
USE MODI_DEFAULT_DESFM_n ! Interface modules
USE MODI_DEFAULT_EXPRE
USE MODI_IBM_INIT_LS
USE MODI_READ_HGRID
USE MODI_SHUMAN
USE MODI_SET_RSOU
USE MODI_SET_CSTN
USE MODI_SET_FRC
USE MODI_PRESSURE_IN_PREP
USE MODI_WRITE_DESFM_n
USE MODI_WRITE_LFIFM_n
USE MODI_METRICS
USE MODI_UPDATE_METRICS
USE MODI_SET_REF
USE MODI_SET_PERTURB
USE MODI_TOTAL_DMASS
USE MODI_CH_INIT_FIELD_n
USE MODI_INI_NSV
USE MODI_READ_PRE_IDEA_NAM_n
USE MODI_ZSMT_PIC
USE MODI_ZSMT_PGD
USE MODI_READ_VER_GRID
USE MODI_READ_ALL_NAMELISTS
USE MODI_PGD_GRID_SURF_ATM
USE MODI_SPLIT_GRID
USE MODI_PGD_SURF_ATM
USE MODI_ICE_ADJUST_BIS
USE MODI_WRITE_PGD_SURF_ATM_n
USE MODI_PREP_SURF_MNH
USE MODI_INIT_SALT
USE MODI_AER2LIMA
USE MODD_PARAM_LIMA
!
!JUAN
USE MODE_SPLITTINGZ_ll
USE MODD_SUB_MODEL_n
USE MODE_MNH_TIMING
USE MODN_CONFZ
!JUAN
!
USE MODI_VERSION
USE MODI_INIT_PGD_SURF_ATM
USE MODI_WRITE_SURF_ATM_N
USE MODD_MNH_SURFEX_n
! Modif ADVFRC
USE MODD_2D_FRC
USE MODD_ADVFRC_n ! Modif for grid-nesting
USE MODI_SETADVFRC
USE MODD_RELFRC_n ! Modif for grid-nesting
USE MODI_SET_RELFRC
!
USE MODI_INI_CST
USE MODI_INI_NEB
USE MODD_NEB, ONLY: NEB
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
USE MODI_WRITE_HGRID
USE MODD_MPIF
USE MODD_VAR_ll
USE MODD_IO, ONLY: TFILEDATA,TFILE_SURFEX
!
USE MODE_MPPDB
!
USE MODD_GET_n
!
USE MODN_CONFIO, ONLY : NAM_CONFIO
!
IMPLICIT NONE
!
!* 0.1 Declarations of global variables not declared in the modules
!
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XJ ! Jacobian
REAL :: XLATCEN=XUNDEF, XLONCEN=XUNDEF ! latitude and longitude of the center of
! the domain for initialization. This
! point is vertical vorticity point
! ------------------------
REAL :: XDELTAX=0.5E4, XDELTAY=0.5E4 ! horizontal mesh lengths
! used to determine XXHAT,XYHAT
!
INTEGER :: NLUPRE,NLUOUT ! Logical unit numbers for EXPRE file
! and for output_listing file
INTEGER :: NRESP ! return code in FM routines
INTEGER :: NTYPE ! type of file (cpio or not)
INTEGER(KIND=LFIINT) :: NNPRAR ! number of articles predicted in the LFIFM file
LOGICAL :: GFOUND ! Return code when searching namelist
!
INTEGER :: JLOOP,JILOOP,JJLOOP ! Loop indexes
!
INTEGER :: NIB,NJB,NKB ! Begining useful area in x,y,z directions
INTEGER :: NIE,NJE ! Ending useful area in x,y directions
INTEGER :: NIU,NJU,NKU ! Upper bounds in x,y,z directions
CHARACTER(LEN=4) :: CIDEAL ='CSTN' ! kind of idealized fields
! 'CSTN' : Nv=cste case
! 'RSOU' : radiosounding case
CHARACTER(LEN=4) :: CZS ='FLAT' ! orography selector
! 'FLAT' : zero orography
! 'SINE' : sine-shaped orography
! 'BELL' : bell-shaped orography
REAL :: XHMAX=XUNDEF ! Maximum height for orography
REAL :: NEXPX=3,NEXPY=1 ! Exponents for orography in case of CZS='SINE'
REAL :: XAX= 1.E4, XAY=1.E4 ! Widths for orography in case CZS='BELL'
! along x and y
INTEGER :: NIZS = 5, NJZS = 5 ! Localization of the center in
! case CZS ='BELL'
!
!* 0.1.1 Declarations of local variables for N=cste and
! radiosounding cases :
!
INTEGER :: NYEAR,NMONTH,NDAY ! year, month and day in EXPRE file
REAL :: XTIME ! time in EXPRE file
LOGICAL :: LPERTURB =.FALSE. ! Logical to add a perturbation to
! a basic state
LOGICAL :: LGEOSBAL =.FALSE. ! Logical to satisfy the geostrophic
! balance
! .TRUE. for geostrophic balance
! .FALSE. to ignore this balance
LOGICAL :: LSHIFT =.FALSE. ! flag to perform vertical shift or not.
CHARACTER(LEN=3) :: CFUNU ='ZZZ' ! CHARACTER STRING for variation of
! U in y direction
! 'ZZZ' : U = U(Z)
! 'Y*Z' : U = F(Y) * U(Z)
! 'Y,Z' : U = G(Y,Z)
CHARACTER(LEN=3) :: CFUNV ='ZZZ' ! CHARACTER STRING for variation of
! V in x direction
! 'ZZZ' : V = V(Z)
! 'Y*Z' : V = F(X) * V(Z)
! 'Y,Z' : V = G(X,Z)
CHARACTER(LEN=6) :: CTYPELOC='IJGRID' ! Type of informations used to give the
! localization of vertical profile
! 'IJGRID' for (i,j) point on index space
! 'XYHATM' for (x,y) coordinates on
! conformal or cartesian plane
! 'LATLON' for (latitude,longitude) on
! spherical earth
REAL :: XLATLOC= 45., XLONLOC=0.
! Latitude and longitude of the vertical
! profile localization (used in case
! CTYPELOC='LATLON')
REAL :: XXHATLOC=2.E4, XYHATLOC=2.E4
! (x,y) of the vertical profile
! localization (used in cases
! CTYPELOC='LATLON' and 'XYHATM')
INTEGER, DIMENSION(1) :: NILOC=4, NJLOC=4
! (i,j) of the vertical profile
! localization
!
!
REAL,DIMENSION(:,:,:),ALLOCATABLE :: XCORIOZ ! Coriolis parameter (this
! is exceptionnaly a 3D array
! for computing needs)
!
!
!* 0.1.2 Declarations of local variables used when a PhysioGraphic Data
! file is used :
!
INTEGER :: JSV ! loop index on scalar var.
CHARACTER(LEN=28) :: CPGD_FILE=' ' ! Physio-Graphic Data file name
LOGICAL :: LREAD_ZS = .TRUE., & ! switch to use orography
! coming from the PGD file
LREAD_GROUND_PARAM = .TRUE. ! switch to use soil parameters
! useful for the soil scheme
! coming from the PGD file
INTEGER :: NSLEVE =12 ! number of iteration for smooth orography
REAL :: XSMOOTH_ZS = XUNDEF ! optional uniform smooth orography for SLEVE coordinate
CHARACTER(LEN=28) :: YPGD_NAME, YPGD_DAD_NAME ! general information
CHARACTER(LEN=2) :: YPGD_TYPE
!
INTEGER :: IINFO_ll ! return code of // routines
TYPE(LIST_ll), POINTER :: TZ_FIELDS_ll ! list of metric coefficient fields
!
INTEGER :: IISIZEXF,IJSIZEXF,IISIZEXFU,IJSIZEXFU ! dimensions of the
INTEGER :: IISIZEX4,IJSIZEX4,IISIZEX2,IJSIZEX2 ! West-east LB arrays
INTEGER :: IISIZEYF,IJSIZEYF,IISIZEYFV,IJSIZEYFV ! dimensions of the
INTEGER :: IISIZEY4,IJSIZEY4,IISIZEY2,IJSIZEY2 ! North-south LB arrays
INTEGER :: IBEG,IEND,IXOR,IXDIM,IYOR,IYDIM,ILBX,ILBY
REAL, DIMENSION(:), ALLOCATABLE :: ZXHAT_ll, ZYHAT_ll
!
REAL, DIMENSION(:,:,:), ALLOCATABLE ::ZTHL,ZT,ZRT,ZFRAC_ICE,&
ZEXN,ZLVOCPEXN,ZLSOCPEXN,ZCPH, &
ZRSATW, ZRSATI
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZBUF
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
! variables for adjustement
REAL :: ZDIST
!
!JUAN TIMING
REAL(kind=MNHTIME), DIMENSION(2) :: ZTIME1, ZTIME2, ZEND, ZTOT
CHARACTER :: YMI
INTEGER :: IMI
!JUAN TIMING
!
REAL, DIMENSION(:), ALLOCATABLE :: ZZS_ll
INTEGER :: IJ
!
REAL :: ZZS_MAX, ZZS_MAX_ll
INTEGER :: IJPHEXT
!
TYPE(TFILEDATA),POINTER :: TZEXPREFILE => NULL()
!
!
!* 0.2 Namelist declarations
!
NAMELIST/NAM_CONF_PRE/ LTHINSHELL,LCARTESIAN, &! Declarations in MODD_CONF
LPACK, &!
NVERB,CIDEAL,CZS, &!+global variables initialized
LBOUSS,LOCEAN,LPERTURB, &! at their declarations
LFORCING,CEQNSYS, &! at their declarations
LSHIFT,L2D_ADV_FRC,L2D_REL_FRC, &
NHALO , JPHEXT
NAMELIST/NAM_GRID_PRE/ XLON0,XLAT0, & ! Declarations in MODD_GRID
XBETA,XRPK, &
XLONORI,XLATORI
NAMELIST/NAM_GRIDH_PRE/ XLATCEN,XLONCEN, & ! local variables initialized
XDELTAX,XDELTAY, & ! at their declarations
XHMAX,NEXPX,NEXPY, &
XAX,XAY,NIZS,NJZS
NAMELIST/NAM_VPROF_PRE/LGEOSBAL, CFUNU,CFUNV, &! global variables initialized
CTYPELOC,XLATLOC,XLONLOC, &! at their declarations
XXHATLOC,XYHATLOC,NILOC,NJLOC
NAMELIST/NAM_REAL_PGD/CPGD_FILE, & ! Physio-Graphic Data file
! name
LREAD_ZS, & ! switch to use orography
! coming from the PGD file
LREAD_GROUND_PARAM
NAMELIST/NAM_SLEVE/NSLEVE, XSMOOTH_ZS
!
!* 0.3 Auxillary Namelist declarations
!
NAMELIST/NAM_AERO_PRE/ LORILAM, LINITPM, XINIRADIUSI, XINIRADIUSJ, &
XINISIGI, XINISIGJ, XN0IMIN, XN0JMIN, CRGUNIT, &
LDUST, LSALT, CRGUNITD, CRGUNITS,&
NMODE_DST, XINISIG, XINIRADIUS, XN0MIN,&
XINISIG_SLT, XINIRADIUS_SLT, XN0MIN_SLT, &
NMODE_SLT
!
NAMELIST/NAM_IBM_LSF/ LIBM_LSF, CIBM_TYPE, NIBM_SMOOTH, XIBM_SMOOTH
!
!-------------------------------------------------------------------------------
!
!* 0. PROLOGUE
! --------
CALL MPPDB_INIT()
!
CALL GOTO_MODEL(1)
!
CALL IO_Init()
NULLIFY(TZ_FIELDS_ll)
CALL VERSION
CPROGRAM='IDEAL '
!
!JUAN TIMING
XT_START = 0.0_MNHTIME
XT_STORE = 0.0_MNHTIME
!
CALL SECOND_MNH2(ZEND)
!
!JUAN TIMING
!
!* 1. INITIALIZE PHYSICAL CONSTANTS :
! ------------------------------
!
NVERB = 5
CALL INI_CST
CALL INI_NEB
!
!-------------------------------------------------------------------------------
!
!
!* 2. SET DEFAULT VALUES :
! --------------------
!
!
!* 2.1 For variables in DESFM file
!
CALL ALLOC_FIELD_SCALARS()
CALL PARAM_ICE_ASSOCIATE()
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
CALL DEFAULT_DESFM_n(1)
!
CSURF = "NONE"
!
!
!* 2.2 For other global variables in EXPRE file
!
CALL DEFAULT_EXPRE
!-------------------------------------------------------------------------------
!
!* 3. READ THE EXPRE FILE :
! --------------------
!
!* 3.1 initialize logical unit numbers (EXPRE and output-listing files)
! and open these files :
!
!
CALL IO_File_add2list(TLUOUT0,'OUTPUT_LISTING1','OUTPUTLISTING','WRITE')
CALL IO_File_open(TLUOUT0)
NLUOUT = TLUOUT0%NLU
!Set output files for PRINT_MSG
TLUOUT => TLUOUT0
TFILE_OUTPUTLISTING => TLUOUT0
!
CALL IO_File_add2list(TZEXPREFILE,'PRE_IDEA1.nam','NML','READ')
CALL IO_File_open(TZEXPREFILE)
NLUPRE=TZEXPREFILE%NLU
!
!* 3.2 read in NLUPRE the namelist informations
!
WRITE(NLUOUT,FMT=*) 'attempt to read ',TRIM(TZEXPREFILE%CNAME),' file'
CALL POSNAM(NLUPRE,'NAM_REAL_PGD',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_REAL_PGD)
!
!
CALL POSNAM(NLUPRE,'NAM_CONF_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_CONF_PRE)
!JUANZ
CALL POSNAM(NLUPRE,'NAM_CONFZ',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_CONFZ)
!JUANZ
CALL POSNAM(NLUPRE,'NAM_CONFIO',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_CONFIO)
CALL IO_Config_set()
CALL POSNAM(NLUPRE,'NAM_GRID_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_GRID_PRE)
CALL POSNAM(NLUPRE,'NAM_GRIDH_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_GRIDH_PRE)
CALL POSNAM(NLUPRE,'NAM_VPROF_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_VPROF_PRE)
CALL POSNAM(NLUPRE,'NAM_BLANKN',GFOUND,NLUOUT)
CALL INIT_NAM_BLANKn
IF (GFOUND) THEN
READ(UNIT=NLUPRE,NML=NAM_BLANKn)
CALL UPDATE_NAM_BLANKn
END IF
CALL READ_PRE_IDEA_NAM_n(NLUPRE,NLUOUT)
CALL POSNAM(NLUPRE,'NAM_AERO_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_AERO_PRE)
CALL POSNAM(NLUPRE,'NAM_IBM_LSF' ,GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_IBM_LSF )
!
CALL INI_FIELD_LIST(1)
!
CALL INI_FIELD_SCALARS()
! Sea salt
CALL INIT_SALT
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
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
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
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
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
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
!
IF( LEN_TRIM(CPGD_FILE) /= 0 ) THEN
! open the PGD_FILE
CALL IO_File_add2list(TPGDFILE,TRIM(CPGD_FILE),'PGD','READ',KLFINPRAR=NNPRAR,KLFITYPE=2,KLFIVERB=NVERB)
CALL IO_File_open(TPGDFILE)
! read the grid in the PGD file
CALL IO_Field_read(TPGDFILE,'IMAX', NIMAX)
CALL IO_Field_read(TPGDFILE,'JMAX', NJMAX)
CALL IO_Field_read(TPGDFILE,'JPHEXT',IJPHEXT)
IF ( CPGD_FILE /= CINIFILEPGD) THEN
WRITE(NLUOUT,FMT=*) ' WARNING : in PRE_IDEA1.nam, in NAM_LUNITn you&
& have CINIFILEPGD= ',CINIFILEPGD
WRITE(NLUOUT,FMT=*) ' whereas in NAM_REAL_PGD you have CPGD_FILE = '&
,CPGD_FILE
WRITE(NLUOUT,FMT=*) ' '
WRITE(NLUOUT,FMT=*) ' CINIFILEPGD HAS BEEN SET TO ',CPGD_FILE
CINIFILEPGD=CPGD_FILE
END IF
IF ( IJPHEXT .NE. JPHEXT ) THEN
WRITE(NLUOUT,FMT=*) ' PREP_IDEAL_CASE : JPHEXT in PRE_IDEA1.nam/NAM_CONF_PRE ( or default value )&
& JPHEXT=',JPHEXT
WRITE(NLUOUT,FMT=*) ' different from PGD files=', CINIFILEPGD,' value JPHEXT=',IJPHEXT
WRITE(NLUOUT,FMT=*) '-> JOB ABORTED'
CALL PRINT_MSG(NVERB_FATAL,'GEN','PREP_IDEAL_CASE','')
!WRITE(NLUOUT,FMT=*) ' JPHEXT HAS BEEN SET TO ', IJPHEXT
!IJPHEXT = JPHEXT
END IF
END IF
!
NIMAX_ll=NIMAX !! _ll variables are global variables
NJMAX_ll=NJMAX !! but the old names are kept in PRE_IDEA1.nam file
!
!* 3.3 check some parameters:
!
L1D=.FALSE. ; L2D=.FALSE.
!
IF ((NIMAX == 1).OR.(NJMAX == 1)) THEN
L2D=.TRUE.
NJMAX_ll=1
NIMAX_ll=MAX(NIMAX,NJMAX)
WRITE(NLUOUT,FMT=*) ' NJMAX HAS BEEN SET TO 1 SINCE 2D INITIAL FILE IS REQUIRED &
& (L2D=TRUE) )'
END IF
!
IF ((NIMAX == 1).AND.(NJMAX == 1)) THEN
L1D=.TRUE.
NIMAX_ll = 1
NJMAX_ll = 1
WRITE(NLUOUT,FMT=*) ' 1D INITIAL FILE IS REQUIRED (L1D=TRUE) '
END IF
!
IF(.NOT. L1D) THEN
LHORELAX_UVWTH=.TRUE.
LHORELAX_RV=.TRUE.
ENDIF
!
NRIMX= MIN(JPRIMMAX,NIMAX_ll/2)
!
IF (L2D) THEN
NRIMY=0
ELSE
NRIMY= MIN(JPRIMMAX,NJMAX_ll/2)
END IF
!
IF (L1D) THEN
NRIMX=0
NRIMY=0
END IF
!
IF (L1D .AND. ( LPERTURB .OR. LGEOSBAL .OR. &
(.NOT. LCARTESIAN ) .OR. (.NOT. LTHINSHELL) ))THEN
LGEOSBAL = .FALSE.
LPERTURB = .FALSE.
LCARTESIAN = .TRUE.
LTHINSHELL = .TRUE.
WRITE(NLUOUT,FMT=*) ' LGEOSBAL AND LPERTURB HAVE BEEN SET TO FALSE &
& AND LCARTESIAN AND LTHINSHELL TO TRUE &
& SINCE 1D INITIAL FILE IS REQUIRED (L1D=TRUE)'
END IF
!
IF (LGEOSBAL .AND. LSHIFT ) THEN
LSHIFT=.FALSE.
WRITE(NLUOUT,FMT=*) ' LSHIFT HAS BEEN SET TO FALSE SINCE &
& LGEOSBAL=.TRUE. IS REQUIRED '
END IF
!
!* 3.4 compute the number of moist variables :
!
IF (.NOT.LUSERV) THEN
LUSERV = .TRUE.
WRITE(NLUOUT,FMT=*) ' LUSERV HAS BEEN RESET TO TRUE, SINCE A MOIST VARIABLE &
& IS PRESENT IN EXPRE FILE (CIDEAL = RSOU OR CSTN)'
END IF
!
IF((LUSERI .OR. LUSERC).AND. (CIDEAL /= 'RSOU')) THEN
!callabortstop
CALL PRINT_MSG(NVERB_FATAL,'GEN','PREP_IDEAL_CASE','use of hydrometeors is only allowed in RSOU case')
ENDIF
IF (LUSERI) THEN
LUSERC =.TRUE.
LUSERR =.TRUE.
LUSERI =.TRUE.
LUSERS =.TRUE.
LUSERG =.TRUE.
LUSERH =.FALSE.
CCLOUD='ICE3'
ELSEIF(LUSERC) THEN
LUSERR =.FALSE.
LUSERI =.FALSE.
LUSERS =.FALSE.
LUSERG =.FALSE.
LUSERH =.FALSE.
CCLOUD='REVE'
ELSE
LUSERC =.FALSE.
LUSERR =.FALSE.
LUSERI =.FALSE.
LUSERS =.FALSE.
LUSERG =.FALSE.
LUSERH =.FALSE.
LHORELAX_RC=.FALSE.
LHORELAX_RR=.FALSE.
LHORELAX_RI=.FALSE.
LHORELAX_RS=.FALSE.
LHORELAX_RG=.FALSE.
LHORELAX_RH=.FALSE.
CCLOUD='NONE'
!
END IF
!
NRR=0
IF (LUSERV) THEN
NRR=NRR+1
IDX_RVT = NRR
END IF
IF (LUSERC) THEN
NRR=NRR+1
IDX_RCT = NRR
END IF
IF (LUSERR) THEN
NRR=NRR+1
IDX_RRT = NRR
END IF
IF (LUSERI) THEN
NRR=NRR+1
IDX_RIT = NRR
END IF
IF (LUSERS) THEN
NRR=NRR+1
IDX_RST = NRR
END IF
IF (LUSERG) THEN
NRR=NRR+1
IDX_RGT = NRR
END IF
IF (LUSERH) THEN
NRR=NRR+1
IDX_RHT = NRR
END IF
!
! NRR=4 for RSOU case because RI and Rc always computed
IF (CIDEAL == 'RSOU' .AND. NRR < 4 ) NRR=4
!
!
!* 3.5 Chemistry
!
IF (LORILAM .OR. LCH_INIT_FIELD) THEN
LUSECHEM = .TRUE.
IF (LORILAM) THEN
CORGANIC = "MPMPO"
LVARSIGI = .TRUE.
LVARSIGJ = .TRUE.
END IF
END IF
! initialise NSV_* variables
CALL INI_NSV(1)
LHORELAX_SV(:)=.FALSE.
IF(.NOT. L1D) LHORELAX_SV(1:NSV)=.TRUE.
!
!-------------------------------------------------------------------------------
!
!* 4. ALLOCATE MEMORY FOR ARRAYS :
! ----------------------------
!
!* 4.1 Vertical Spatial grid
!
CALL READ_VER_GRID(TZEXPREFILE)
!
!* 4.2 Initialize parallel variables and compute array's dimensions
!
!
IF(LGEOSBAL) THEN
CALL SET_SPLITTING_ll('XSPLITTING') ! required for integration of thermal wind balance
ELSE
CALL SET_SPLITTING_ll('BSPLITTING')
ENDIF
CALL SET_JP_ll(1,JPHEXT,JPVEXT,JPHEXT)
CALL SET_DAD0_ll()
CALL SET_DIM_ll(NIMAX_ll, NJMAX_ll, NKMAX)
CALL IO_Pack_set(L1D,L2D,LPACK)
CALL SET_LBX_ll(CLBCX(1), 1)
CALL SET_LBY_ll(CLBCY(1), 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)
CALL INI_PARAZ_ll(IINFO_ll)
!
! sizes of arrays of the extended sub-domain
!
CALL GET_DIM_EXT_ll('B',NIU,NJU)
CALL GET_DIM_PHYS_ll('B',NIMAX,NJMAX)
CALL GET_INDICE_ll(NIB,NJB,NIE,NJE)
CALL GET_OR_ll('B',IXOR,IYOR)
NKB=1+JPVEXT
NKU=NKMAX+2*JPVEXT
!
!* 4.3 Global variables absent from the modules :
!
ALLOCATE(XJ(NIU,NJU,NKU))
SELECT CASE(CIDEAL)
CASE('RSOU','CSTN')
IF (LGEOSBAL) ALLOCATE(XCORIOZ(NIU,NJU,NKU)) ! exceptionally a 3D array
CASE DEFAULT ! undefined preinitialization
!callabortstop
CALL PRINT_MSG(NVERB_FATAL,'GEN','PREP_IDEAL_CASE','CIDEAL is not correctly defined')
END SELECT
!
!* 4.4 Prognostic variables at M instant (module MODD_FIELD1):
!
ALLOCATE(XUT(NIU,NJU,NKU))
ALLOCATE(XVT(NIU,NJU,NKU))
ALLOCATE(XWT(NIU,NJU,NKU))
ALLOCATE(XTHT(NIU,NJU,NKU))
ALLOCATE(XPABST(NIU,NJU,NKU))
ALLOCATE(XRT(NIU,NJU,NKU,NRR))
ALLOCATE(XSVT(NIU,NJU,NKU,NSV))
!
!* 4.5 Grid variables (module MODD_GRID1 and MODD_METRICS1):
!
ALLOCATE(XMAP(NIU,NJU))
ALLOCATE(XLAT(NIU,NJU))
ALLOCATE(XLON(NIU,NJU))
ALLOCATE(XDXHAT(NIU),XDYHAT(NJU))
IF (LEN_TRIM(CPGD_FILE)==0) ALLOCATE(XZS(NIU,NJU))
IF (LEN_TRIM(CPGD_FILE)==0) ALLOCATE(ZZS_ll(NIMAX_ll))
IF (LEN_TRIM(CPGD_FILE)==0) ALLOCATE(XZSMT(NIU,NJU))
ALLOCATE(XZZ(NIU,NJU,NKU))
!
ALLOCATE(XDXX(NIU,NJU,NKU))
ALLOCATE(XDYY(NIU,NJU,NKU))
ALLOCATE(XDZX(NIU,NJU,NKU))
ALLOCATE(XDZY(NIU,NJU,NKU))
ALLOCATE(XDZZ(NIU,NJU,NKU))
!
!* 4.6 Reference state variables (modules MODD_REF and MODD_REF1):
!
ALLOCATE(XRHODREFZ(NKU),XTHVREFZ(NKU))
XTHVREFZ(:)=0.0
IF (LCOUPLES) THEN
! Arrays for reference state different in ocean and atmosphere
ALLOCATE(XRHODREFZO(NKU),XTHVREFZO(NKU))
XTHVREFZO(:)=0.0
END IF
IF(CEQNSYS == 'DUR') THEN
ALLOCATE(XRVREF(NIU,NJU,NKU))
ELSE
ALLOCATE(XRVREF(0,0,0))
END IF
ALLOCATE(XRHODREF(NIU,NJU,NKU),XTHVREF(NIU,NJU,NKU),XEXNREF(NIU,NJU,NKU))
ALLOCATE(XRHODJ(NIU,NJU,NKU))