ROMS
Loading...
Searching...
No Matches
mod_scalars.F
Go to the documentation of this file.
1#include "cppdefs.h"
3!
4!git $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2025 The ROMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.md !
9!=======================================================================
10!
11 USE mod_kinds
12#ifdef NO_4BYTE_REALS
13 USE netcdf
14#endif
15!
16 PUBLIC :: allocate_scalars
17 PUBLIC :: deallocate_scalars
18 PUBLIC :: initialize_scalars
19!
20!-----------------------------------------------------------------------
21! Multiple grid structure.
22!-----------------------------------------------------------------------
23!
24#if defined READ_WATER && defined MASKING && defined DISTRIBUTE
25! IJwater IJ-indices of water points.
26#endif
27! Fstate Logical switches to control computations of the
28! Forcing Singular Vectors or Stochastic Optimals.
29! Lstate Logical switches to control computations of the
30! model state.
31#ifdef STATIONS
32! Sflag Station extraction special flag:
33! Sflag = 0 => locations in terms of (I,J) pairs.
34! Sflag = 1 => locations in terms of (lon,lat) pairs.
35! SposX Longitude or frational I-coordinate station location.
36! SposY Latitude or frational J-coordinate station location.
37#endif
38! Cs_r Set of S-curves used to stretch the vertical grid
39! that follows the bathymetry at vertical RHO-points.
40! Cs_w Set of S-curves used to stretch the vertical grid
41! that follows the bathymetry at vertical W-points.
42! sc_r S-coordinate independent variable, [-1 < sc < 0] at
43! vertical RHO-points.
44! sc_w S-coordinate independent variable, [-1 < sc < 0] at
45! vertical W-points.
46!
48 logical, pointer :: fstate(:)
49 logical, pointer :: lstate(:)
50#if defined READ_WATER && defined MASKING && defined DISTRIBUTE
51 integer , pointer :: ijwater(:,:)
52#endif
53#ifdef STATIONS
54 integer, pointer :: sflag(:)
55
56 real(r8), pointer :: sposx(:)
57 real(r8), pointer :: sposy(:)
58#endif
59 real(dp), pointer :: cs_r(:)
60 real(dp), pointer :: cs_w(:)
61 real(dp), pointer :: sc_r(:)
62 real(dp), pointer :: sc_w(:)
63 END TYPE t_scalars
64!
65 TYPE (t_scalars), allocatable :: scalars(:)
66!
67!-----------------------------------------------------------------------
68! Time clock structure.
69!-----------------------------------------------------------------------
70!
71! Reference time (yyyymmdd.f) used to compute relative time. The
72! application date clock is measured ad elapsed time interval since
73! reference-time. This parameter also provides information about the
74! calendar used:
75!
76! If TIME_REF = -2, the model time and DSTART are in modified Julian
77! days units. The time "units" attribute is:
78!
79! 'time-units since 1968-05-23 00:00:00 GMT'
80!
81! If TIME_REF = -1, the model time and DSTART are in a calendar
82! with 360 days in every year (30 days each month).
83! The time "units" attribute is:
84!
85! 'time-units since 0001-01-01 00:00:00'
86!
87! If TIME_REF = 0, the model time and DSTART are in a common year
88! calendar with 365.2524 days. The "units" attribute
89! is:
90!
91! 'time-units since 0001-01-01 00:00:00'
92!
93! If TIME_REF > 0, the model time and DSTART are the elapsed time
94! units since specified reference time. For example,
95! TIME_REF=20020115.5 will yield the following
96! time "units" attribute:
97!
98! 'time-units since 2002-01-15 12:00:00'
99!
100 real(dp) :: time_ref = 0.0_dp ! YYYYMMDD.dd
101!
103 integer :: yday ! day of the year
104 integer :: year ! year including century (YYYY)
105 integer :: month ! month of the year (1,...,12)
106 integer :: day ! day of the month
107 integer :: hour ! hour of the day (1,...,23)
108 integer :: minutes ! minutes of the hour
109
110 real(dp) :: seconds ! frational seconds of the minute
111 real(dp) :: base ! reference date (YYYYMMDD.dd)
112 real(dp) :: datenumber(2) ! date number, [1]: days
113 ! [2]: seconds
114 real(dp) :: tide_datenumber(2) ! tide reference date number,
115 ! [1]: days [2]: seconds
116 character (len=22) :: string ! YYYY-MM-DD hh:mm:ss.ss
117 character (len=25) :: calendar ! date calendar
118 END TYPE t_clock
119!
120 TYPE (t_clock) :: rclock ! reference/base date
121!
122!-----------------------------------------------------------------------
123! Tracer identification indices.
124!-----------------------------------------------------------------------
125!
126 integer :: itemp ! Potential temperature
127 integer :: isalt ! Salinity
128#ifdef T_PASSIVE
129 integer, pointer :: inert(:) ! inert tracers
130#endif
131#ifdef DIAGNOSTICS
132!
133!-----------------------------------------------------------------------
134! Diagnostic fields identification indices.
135!-----------------------------------------------------------------------
136!
137# ifdef DIAGNOSTICS_TS
138 integer :: itrate ! Tracer, time rate of change
139 integer :: itvadv ! Tracer, vertical advection
140 integer :: ithadv ! Tracer, horizontal advection
141 integer :: itxadv ! Tracer, horizontal X-advection
142 integer :: ityadv ! Tracer, horizontal Y-advection
143 integer :: itvdif ! Tracer, vertical diffusion
144 integer :: ithdif ! Tracer, horizontal diffusion
145 integer :: itxdif ! Tracer, horizontal X-diffusion
146 integer :: itydif ! Tracer, horizontal Y-diffusion
147 integer :: itsdif ! Tracer, horizontal S-diffusion
148# endif
149# ifdef DIAGNOSTICS_UV
150 integer :: m2fcor ! 2D momentum, Coriolis
151 integer :: m2hadv ! 2D momentum, horizontal advection
152 integer :: m2xadv ! 2D momentum, horizontal X-advection
153 integer :: m2yadv ! 2D momentum, horizontal Y-advection
154# ifdef WEC_VF
155 integer :: m2hjvf ! 2D momentum, horizontal J vortex force
156 integer :: m2kvrf ! 2D momentum, K vortex force
157 integer :: m2fsco ! 2D momentum, coriolis-stokes
158 integer :: m2bstm ! 2D momentum, bottom streaming
159 integer :: m2sstm ! 2D momentum, surface streaming
160 integer :: m2wrol ! 2D momentum, wave roller accel
161 integer :: m2wbrk ! 2D momentum, wave breaking
162 integer :: m2zeta ! 2D momentum, Eulerian sea level adjustment
163 integer :: m2zetw ! 2D momentum, quasi-static sea level adjustment
164 integer :: m2zqsp ! 2D momentum, quasi-static pressure
165 integer :: m2zbeh ! 2D momentum, Bernoulli head
166# endif
167 integer :: m2pgrd ! 2D momentum, pressure gradient
168 integer :: m2hvis ! 2D momentum, horizontal viscosity
169 integer :: m2xvis ! 2D momentum, horizontal X-viscosity
170 integer :: m2yvis ! 2D momentum, horizontal Y-viscosity
171 integer :: m2sstr ! 2D momentum, surface stress
172 integer :: m2bstr ! 2D momentum, bottom stress
173 integer :: m2rate ! 2D momentum, time rate of change
174# ifdef SOLVE3D
175 integer :: m3fcor ! 3D momentum, Coriolis
176 integer :: m3vadv ! 3D momentum, vertical advection
177 integer :: m3hadv ! 3D momentum, horizontal advection
178 integer :: m3xadv ! 3D momentum, horizontal X-advection
179 integer :: m3yadv ! 3D momentum, horizontal Y-advection
180# ifdef WEC_VF
181 integer :: m3vjvf ! 3D momentum, vertical J vortex force
182 integer :: m3hjvf ! 3D momentum, horizontal J vortex force
183 integer :: m3kvrf ! 3D momentum, K vortex force
184 integer :: m3fsco ! 3D momentum, coriolis-stokes
185 integer :: m3bstm ! 3D momentum, bottom streaming
186 integer :: m3sstm ! 3D momentum, surface streaming
187 integer :: m3wrol ! 3D momentum, wave roller accel
188 integer :: m3wbrk ! 3D momentum, wave breaking
189# endif
190 integer :: m3pgrd ! 3D momentum, pressure gradient
191 integer :: m3vvis ! 3D momentum, vertical viscosity
192 integer :: m3hvis ! 3D momentum, horizontal viscosity
193 integer :: m3xvis ! 3D momentum, horizontal X-viscosity
194 integer :: m3yvis ! 3D momentum, horizontal Y-viscosity
195 integer :: m3rate ! 3D momentum, time rate of change
196# endif
197# endif
198#endif
199!
200!-----------------------------------------------------------------------
201! Time stepping indices, variables, and clocks.
202!-----------------------------------------------------------------------
203!
204! indx1 2D timestep rolling counter.
205! iic Timestep counter for 3D primitive equations.
206! iif Timestep counter for 2D primitive equations.
207#ifdef JEDI
208! jic Timestep counter for roms-jedi interface.
209#endif
210! ndtfast Number of barotropic timesteps between each
211! baroclinic timestep.
212! nfast Number of barotropic timesteps needed to compute
213! time-averaged barotropic variables centered at
214! time level n+1.
215! dt Size baroclinic timestep (s).
216! dtfast Size barotropic timestep (s).
217! run_time Total run time for all nested grids (s), it is
218! set in Masters/ocean.h
219! MyRunInterval Total run time for all nested grids (s), it is
220! set in Drivers/nl_ocean.h (coupling window)
221! io_time Current I/O time (s) processed in "get_state".
222! tdays Model time clock (days).
223! time Model time clock (s).
224#ifdef JEDI
225! time4jedi Model time clock (s) to pass to roms-jedi interface.
226#endif
227! time_code Model time clock (string, YYYY-MM-DD hh:mm:ss.ss)
228! AVGtime Model time clock for averages output (s).
229! DIAtime Model time clock for diagnostics output (s).
230! F_code Final time string for simulation
231! I_code Initial time string for simulation
232! INItime Nonlinear model initial conditions time (s).
233! INItimeS Saved nonlinear model initial conditions time (s).
234! IMPtime Impulse forcing time (s) to process.
235! ObsTime Observation time (s) to process.
236! FrcTime Adjoint or tangent linear Impulse forcing time (s).
237! dstart Time stamp assigned to model initialization (usually
238! a Calendar day, like modified Julian Day).
239#ifdef SP4DVAR
240! dstartS Saved original dstart for saddle-point 4D-Var.
241#endif
242! tide_start Reference time for tidal forcing (days).
243!
244 logical, allocatable :: perfectrst(:)
245 logical, allocatable :: predictor_2d_step(:)
246!$OMP THREADPRIVATE (PREDICTOR_2D_STEP)
247
248 integer, allocatable :: indx1(:)
249 integer, allocatable :: iic(:)
250 integer, allocatable :: iif(:)
251 integer, allocatable :: next_kstp(:)
252!$OMP THREADPRIVATE (indx1, iic, iif, next_kstp)
253
254#ifdef JEDI
255 integer, allocatable :: jic(:)
256#endif
257
258 integer, allocatable :: ndtfast(:)
259 integer, allocatable :: nfast(:)
260
261 real(dp), allocatable :: tdays(:) ! days
262 real(dp), allocatable :: time(:) ! seconds
263!$OMP THREADPRIVATE (tdays, time)
264
265#ifdef JEDI
266 real(dp), allocatable :: time4jedi(:) ! seconds
267#endif
268
269 real(dp), allocatable :: dt(:) ! seconds
270 real(dp), allocatable :: dtfast(:) ! seconds
271
272 real(dp), allocatable :: timeend(:) ! seconds
273 real(dp), allocatable :: avgtime(:) ! seconds
274 real(dp), allocatable :: diatime(:) ! seconds
275 real(dp), allocatable :: imptime(:) ! seconds
276 real(dp), allocatable :: initime(:) ! seconds
277 real(dp), allocatable :: initimes(:) ! seconds
278 real(dp), allocatable :: obstime(:) ! seconds
279 real(dp), allocatable :: frctime(:) ! seconds
280
281 real(dp) :: dstart = 0.0_dp ! days
282#ifdef SP4DVAR
283 real(dp) :: dstarts = 0.0_dp ! days
284#endif
285 real(dp) :: io_time = 0.0_dp ! seconds
286 real(dp) :: run_time = 0.0_dp ! seconds
287 real(dp) :: myruninterval = 0.0_dp ! seconds
288 real(dp) :: tide_start = 0.0_dp ! days
289
290 character (len=22) :: f_code, i_code
291
292 character (len=22), allocatable :: time_code(:) ! date string
293!$OMP THREADPRIVATE (time_code)
294
295#if defined POWER_LAW && defined SOLVE3D
296!
297! Power-law shape filter parameters for time-averaging of barotropic
298! Fields. The power-law shape filters are given by:
299!
300! F(xi)=xi^Falpha*(1-xi^Fbeta)-Fgamma*xi
301!
302! Possible settings of parameters to yield the second-order accuracy:
303!
304! Falpha Fbeta Fgamma
305! ------------------------------
306! 2.0 1.0 0.1181 0.169 The problem here is setting
307! 2.0 2.0 0.1576 0.234 Fgamma. Its value here is
308! 2.0 3.0 0.1772 0.266 understood as the MAXIMUM
309! 2.0 4.0 0.1892 0.284 allowed. It is computed using
310! 2.0 5.0 0.1976 0.296 a Newton iteration scheme.
311! 2.0 6.0 0.2039 0.304
312! 2.0 8.0 0.2129 0.314
313!
314! NOTE: Theoretical values of Fgamma presented in the table above are
315! derived assuming "exact" barotropic mode stepping. Consequently, it
316! does not account for effects caused by Forward-Euler (FE) startup
317! of the barotropic mode at every 3D time step. As the result, the
318! code may become unstable if the theoretical value of Fgamma is used
319! when mode splitting ratio "ndtfast" is small, thus yielding non-
320! negligible start up effects. To compensate this, the accepted
321! value of Fgamma is reduced relatively to theoretical one, depending
322! on splitting ratio "ndtfast". This measure is empirical. It is
323! shown to work with setting of "ndtfast" as low as 15, which is
324! more robust that the Hamming Window the squared cosine weights
325! options in "set_weights".
326!
327 real(dp) :: falpha = 2.0_dp
328 real(dp) :: fbeta = 4.0_dp
329 real(dp) :: fgamma = 0.284_dp
330#endif
331!
332! Total number timesteps in current run. In 3D configurations, "ntimes"
333! is the total of baroclinic timesteps. In 2D configuration, "ntimes"
334! is the total of barotropic timesteps.
335!
336 integer, allocatable :: ntimes(:)
337!
338! Time-step counter for current execution time-window.
339!
340 integer, allocatable :: step_counter(:)
341
342!$OMP THREADPRIVATE (step_counter)
343!
344! Number of time interval divisions for Stochastic Optimals. It must
345! a multiple of "ntimes".
346!
347 integer :: nintervals = 1
348!
349! Starting, current, and ending ensemble run parameters.
350!
351 integer :: erstr = 1 ! Starting value
352 integer :: erend = 1 ! Ending value
353 integer :: ninner = 1 ! number of inner loops
354 integer :: nouter = 1 ! number of outer loops
355 integer :: nrun = 1 ! Current counter
356#ifdef SENSITIVITY_4DVAR
357 integer :: nrunsave = 0 ! Loop counter
358#endif
359 integer :: outerloop = 0 ! split outer loop
360 integer :: inner = 0 ! inner loop counter
361 integer :: outer = 0 ! outer loop counter
362!
363! Set checksum algorithm: "adler32" or "crc32"
364!
365 character (len=*), parameter :: hashmethod = "bitsum"
366!
367! Split 4D-Var phase.
368!
369 character (len=20) :: phase4dvar
370!
371! Number of sadde point 4D-Var intervals.
372!
373 integer :: nsaddle = 1
374!
375! First, starting, and ending timestepping parameters
376!
377 integer, allocatable :: ntfirst(:) ! Forward-Euler step
378 integer, allocatable :: ntstart(:) ! Start step
379 integer, allocatable :: ntend(:) ! End step
380!!$OMP THREADPRIVATE (ntfirst, ntstart, ntend)
381!
382! Adjoint model or tangent linear model impulse forcing time record
383! counter and number of records available.
384!
385 integer, allocatable :: frcrec(:)
386!$OMP THREADPRIVATE (FrcRec)
387
388 integer, allocatable :: nrecfrc(:)
389!
390! HSIMT tracer advection coefficients for the TVD limiter (Wu and Zhu,
391! 2010).
392!
393 real(r8) :: cc1 = 0.25_r8
394 real(r8) :: cc2 = 0.5_r8
395 real(r8) :: cc3 = 1.0_r8/12.0_r8
396!
397!-----------------------------------------------------------------------
398! Control switches.
399!-----------------------------------------------------------------------
400!
401! Switch to use three ghost-points in the halo region.
402!
403 logical :: threeghostpoints = .false.
404!
405! Switch to set-up application grid, metrics, and associated variables
406! and parameters.
407!
408 logical, allocatable :: setgridconfig(:)
409!
410! Switch to procces (Get/Set) all input data in an application. It is
411! set to .TRUE. by default. It is manipulated by the ROMS-JEDI
412! interface during ROMS Phase 3 initialization that applies lateral
413! boundary condition to the initial state vector passed by OOPS. Some
414! applications requited input data for lateral boundary conditons.
415!
416 logical, allocatable :: processinputdata(:)
417!
418! Switch to proccess nudging coefficients for radiation open boundary
419! conditions.
420!
421 logical, allocatable :: nudgingcoeff(:)
422!
423! Switch to proccess input boundary data.
424!
425 logical, allocatable :: obcdata(:)
426!
427! These switches are designed to control computational options within
428! nested and/or multiple connected grids. They are .TRUE. by default.
429! They can turned off for a particular grind in input scripts.
430!
431 logical, allocatable :: lbiology(:)
432 logical, allocatable :: lfloats(:)
433 logical, allocatable :: lsediment(:)
434 logical, allocatable :: lstations(:)
435!
436! If equilibrium tides, switch to apply the 18.6-year lunar nodal
437! cycle correction.
438!
439 logical :: lnodal = .true.
440!
441!-----------------------------------------------------------------------
442! Physical constants.
443!-----------------------------------------------------------------------
444!
445! Cp Specific heat for seawater (Joules/Kg/degC).
446! Csolar Solar irradiantion constant (W/m2).
447! Eradius Earth equatorial radius (m).
448! Infinity Value resulting when dividing by zero.
449! StefBo Stefan-Boltzmann constant (W/m2/K4).
450! emmiss Infrared emissivity.
451! g Acceleration due to gravity (m/s2).
452! gorho0 gravity divided by mean density anomaly.
453! rhow fresh water density (kg/m3).
454! vonKar von Karman constant.
455!
456 real(dp) :: cp = 3985.0_dp ! Joules/kg/degC
457 real(dp) :: csolar = 1353.0_dp ! 1360-1380 W/m2
458 real(dp) :: infinity ! Infinity = 1.0/0.0
459 real(dp) :: eradius = 6371315.0_dp ! m
460 real(dp) :: stefbo = 5.67e-8_dp ! Watts/m2/K4
461 real(dp) :: emmiss = 0.97_dp ! non_dimensional
462 real(dp) :: rhow = 1000.0_dp ! kg/m3
463#ifdef SOLITON
464 real(dp) :: g = 1.0_dp ! non-dimensional
465#else
466 real(dp) :: g = 9.81_dp ! m/s2
467#endif
468 real(dp) :: gorho0 ! m4/s2/kg
469 real(dp) :: vonkar = 0.41_dp ! non-dimensional
470!
471!-----------------------------------------------------------------------
472! Various model parameters. Some of these parameters are overwritten
473! with the values provided from model standard input script.
474!-----------------------------------------------------------------------
475!
476! Switch for spherical grid (lon,lat) configurations.
477!
478 logical :: spherical = .false.
479!
480! Switch to indicate if ROMS kernel arrays have been allocated. It
481! used to skip memory reports during early termination.
482!
483 logical :: lallocatedmemory = .false.
484!$OMP THREADPRIVATE (LallocatedMemory)
485!
486! Switch to compute the grid stiffness.
487!
488 logical :: lstiffness = .true.
489!$OMP THREADPRIVATE (Lstiffness)
490!
491! Composite grid a refined grids switches. They are .FALSE. by default.
492!
493 logical, allocatable :: compositegrid(:,:)
494 logical, allocatable :: refinedgrid(:)
495!
496! Refinement grid scale factor from donor grid.
497!
498 integer, allocatable :: refinescale(:)
499!
500! Switch to extract donor grid (coarse) data at the refinement grid
501! contact point locations. The coarse data is extracted at the first
502! sub-refined time step. Recall that the finer grid time-step is
503! smaller than the coarser grid by a factor of RefineScale(:). This
504! switch is only relevant during refinement nesting.
505!
506 logical, allocatable :: getdonordata(:)
507!
508! Periodic boundary swiches for distributed-memory exchanges.
509!
510 logical, allocatable :: ewperiodic(:)
511 logical, allocatable :: nsperiodic(:)
512!
513! Lateral open boundary edges volume conservation switches.
514!
515 logical, allocatable :: volcons(:,:)
516#if defined ADJOINT || defined TANGENT || defined TL_IOMS
517 logical, allocatable :: ad_volcons(:,:)
518 logical, allocatable :: tl_volcons(:,:)
519#endif
520!
521! Switches to read and process climatology fields.
522!
523 logical, allocatable :: clm_file(:) ! Process NetCDF
524 logical, allocatable :: lclimatology(:) ! any field
525 logical, allocatable :: lsshclm(:) ! free-surface
526 logical, allocatable :: lm2clm(:) ! 2D momentum
527 logical, allocatable :: lm3clm(:) ! 3D momentum
528 logical, allocatable :: ltracerclm(:,:) ! tracers
529!
530! Switched to nudge to climatology fields.
531!
532 logical, allocatable :: lnudging(:) ! any field
533 logical, allocatable :: lnudgem2clm(:) ! 2D momentum
534 logical, allocatable :: lnudgem3clm(:) ! 3D momentum
535 logical, allocatable :: lnudgetclm(:,:) ! tracers
536!
537! Switches to activate point Source/Sinks in an application:
538! * Horizontal momentum transport (u or v)
539! * Vertical mass transport (w)
540! * Tracer transport
541!
542 logical, allocatable :: luvsrc(:) ! momentum
543 logical, allocatable :: lwsrc(:) ! mass
544 logical, allocatable :: ltracersrc(:,:) ! tracers
545!
546! Execution termination flag.
547!
548! exit_flag = 0 No error
549! exit_flag = 1 Blows up
550! exit_flag = 2 Input error
551! exit_flag = 3 Output error
552! exit_flag = 4 IO error
553! exit_flag = 5 Configuration error
554! exit_flag = 6 Partition error
555! exit_flag = 7 Illegal input parameter
556! exit_flag = 8 Fatal algorithm result
557! exit_flag = 9 coupling error
558!
559 integer :: exit_flag = 0
560 integer :: blowup = 0
561 integer :: noerror = 0
562!
563! Blow-up string.
564!
565 character (len=80) :: blowup_string
566!
567! Set threshold maximum speed (m/s) and density anomaly (kg/m3) to
568! test if the model is blowing-up.
569!
570 real(dp), allocatable :: maxspeed(:)
571 real(dp), allocatable :: maxrho(:)
572!
573 real(dp) :: max_speed = 20.0_dp ! m/s
574 real(dp) :: max_rho = 200.0_dp ! kg/m3
575!
576! Interpolation scheme.
577!
578 integer, parameter :: linear = 0 ! linear interpolation
579 integer, parameter :: cubic = 1 ! cubic interpolation
580!
581 integer :: interpflag = linear ! interpolation flag
582!
583! Shallowest and Deepest levels to apply bottom momentum stresses as
584! a bodyforce
585!
586 integer, allocatable :: levsfrc(:)
587 integer, allocatable :: levbfrc(:)
588!
589! Vertical coordinates transform. Currently, there are two vertical
590! transformation equations (see set_scoord.F for details):
591!
592! Original transform (Vtransform=1):
593!
594! z_r(x,y,s,t) = Zo_r + zeta(x,y,t) * [1.0 + Zo_r / h(x,y)]
595!
596! Zo_r = hc * [s(k) - C(k)] + C(k) * h(x,y)
597!
598! New transform (Vtransform=2):
599!
600! z_r(x,y,s,t) = zeta(x,y,t) + [zeta(x,y,t)+ h(x,y)] * Zo_r
601!
602! Zo_r = [hc * s(k) + C(k) * h(x,y)] / [hc + h(x,y)]
603!
604 integer, allocatable :: vtransform(:)
605!
606! Vertical grid stretching function flag:
607!
608! Vstretcing = 1 Original function (Song and Haidvogel, 1994)
609! = 2 A. Shchepetkin (ROMS-UCLA) function
610! = 3 R. Geyer BBL function
611!
612 integer, allocatable :: vstretching(:)
613!
614! Vertical grid stretching parameters.
615!
616! Tcline Width (m) of surface or bottom boundary layer in
617! which higher vertical resolution is required
618! during stretching.
619! hc S-coordinate critical depth, hc=MIN(hmin,Tcline).
620! theta_s S-coordinate surface control parameter.
621! theta_b S-coordinate bottom control parameter.
622!
623 real(dp), allocatable :: tcline(:) ! m, positive
624 real(dp), allocatable :: hc(:) ! m, positive
625 real(dp), allocatable :: theta_s(:) ! 0 < theta_s < 20
626 real(dp), allocatable :: theta_b(:) ! 0 < theta_b < 1
627!
628! Bathymetry range values.
629!
630 real(dp), allocatable :: hmin(:) ! m, positive
631 real(dp), allocatable :: hmax(:) ! m, positive
632!
633! Length (m) of domain box in the XI- and ETA-directions.
634!
635 real(r8), allocatable :: xl(:) ! m
636 real(r8), allocatable :: el(:) ! m
637!
638! Minimum and Maximum longitude and latitude at RHO-points
639!
640 real(r8), allocatable :: lonmin(:) ! degrees east
641 real(r8), allocatable :: lonmax(:) ! degrees east
642 real(r8), allocatable :: latmin(:) ! degrees north
643 real(r8), allocatable :: latmax(:) ! degrees north
644!
645! Constant used in the Shchepetkin boundary conditions for 2D momentum,
646! Co = 1.0_r8/(2.0_r8+SQRT(2.0_r8)).
647!
648 real(r8) :: co
649!
650! Number of digits in grid size for format statements.
651!
652 integer, allocatable :: idigits(:)
653 integer, allocatable :: jdigits(:)
654#ifdef SOLVE3D
655 integer, allocatable :: kdigits(:)
656#endif
657!
658! Diagnostic volume averaged variables.
659!
660 integer, allocatable :: first_time(:)
661
662 real(dp) :: avgke = 0.0_dp ! Kinetic energy
663 real(dp) :: avgpe = 0.0_dp ! Potential energy
664 real(dp) :: avgkp = 0.0_dp ! Total energy
665 real(dp) :: volume = 0.0_dp ! diagnostics volume
666 real(dp) :: ad_volume = 0.0_dp ! adjoint volume
667
668 real(dp), allocatable :: totvolume(:) ! Total volume
669 real(dp), allocatable :: minvolume(:) ! Minimum cell volume
670 real(dp), allocatable :: maxvolume(:) ! Maximum cell volume
671!
672! Minimun and maximum grid spacing
673!
674 real(dp), allocatable :: dxmin(:) ! all grid points
675 real(dp), allocatable :: dxmax(:)
676 real(dp), allocatable :: dymin(:)
677 real(dp), allocatable :: dymax(:)
678#ifdef MASKING
679 real(dp), allocatable :: dxminw(:) ! only water points
680 real(dp), allocatable :: dxmaxw(:)
681 real(dp), allocatable :: dyminw(:)
682 real(dp), allocatable :: dymaxw(:)
683#endif
684#ifdef SOLVE3D
685 real(dp), allocatable :: dzmin(:) ! all grid points
686 real(dp), allocatable :: dzmax(:)
687# ifdef MASKING
688 real(dp), allocatable :: dzminw(:) ! only water points
689 real(dp), allocatable :: dzmaxw(:)
690# endif
691#endif
692!
693! Maximum size of a grid node (m) over the whole curvilinear grid
694! application. Used for scaling horizontal mixing by the grid size.
695!
696 real(dp), allocatable :: grdmax(:)
697#ifdef DIFF_3DCOEF
698 real(dp), allocatable :: diffmin(:) ! Minimun diffusion
699 real(dp), allocatable :: diffmax(:) ! Maximum diffusion
700#endif
701#ifdef VISC_3DCOEF
702 real(dp), allocatable :: viscmin(:) ! Minimum viscosity
703 real(dp), allocatable :: viscmax(:) ! Maximum viscosity
704#endif
705!
706! Courant Numbers due to gravity wave speed limits.
707!
708 real(dp), allocatable :: cg_min(:) ! Minimun barotropic
709 real(dp), allocatable :: cg_max(:) ! Maximun barotropic
710 real(dp), allocatable :: cg_cor(:) ! Maximun Coriolis
711!
712! Time dependent Counrant Numbers due to velocity components and
713! indices location of maximum value.
714!
715 integer :: max_ci = 0 ! maximum I-location
716 integer :: max_cj = 0 ! maximum J-location
717 integer :: max_ck = 0 ! maximum K-location
718 real(r8) :: max_c = 0.0_r8 ! maximum total
719 real(r8) :: max_cu = 0.0_r8 ! maximum I-component
720 real(r8) :: max_cv = 0.0_r8 ! maximum J-component
721#ifdef SOLVE3D
722 real(r8) :: max_cw = 0.0_r8 ! maximum K-component
723#endif
724!
725! Linear equation of state parameters.
726!
727! R0 Background constant density anomaly (kg/m3).
728! Tcoef Thermal expansion coefficient (1/Celsius).
729! Scoef Saline contraction coefficient (1/PSU).
730!
731 real(r8), allocatable :: r0(:)
732 real(r8), allocatable :: tcoef(:)
733 real(r8), allocatable :: scoef(:)
734!
735! Background potential temperature (Celsius) and salinity (PSU) values
736! used in analytical initializations.
737!
738 real(r8), allocatable :: t0(:)
739 real(r8), allocatable :: s0(:)
740!
741! Slipperiness variable, either 1.0 (free slip) or -1.0 (no slip).
742!
743 real(r8), allocatable :: gamma2(:)
744!
745! Weighting coefficient for the newest (implicit) time step derivatives
746! using either a Crack-Nicolson implicit scheme (lambda=0.5) or a
747! backward implicit scheme (lambda=1.0).
748!
749#if defined SPLINES_VDIFF || defined SPLINES_VVISC
750 real(r8) :: lambda = 1.0_r8
751#else
752!! real(r8) :: lambda = 0.5_r8
753 real(r8) :: lambda = 1.0_r8
754#endif
755!
756! Jerlov water type to assign everywhere, range values: 1 - 5.
757!
758 integer, allocatable :: lmd_jwt(:)
759!
760! Grid r-factor (non-dimensional).
761!
762 real(dp), allocatable :: rx0(:) ! Beckmann and Haidvogel
763 real(dp), allocatable :: rx1(:) ! Haney
764!
765! Linear (m/s) and quadratic (nondimensional) bottom drag coefficients.
766!
767 real(r8), allocatable :: rdrg(:)
768 real(r8), allocatable :: rdrg2(:)
769!
770! Minimum and maximum threshold for transfer coefficient of momentum.
771!
772 real(dp) :: cdb_min = 0.000001_dp
773 real(dp) :: cdb_max = 0.5_dp
774!
775! Surface and bottom roughness (m)
776!
777 real(r8), allocatable :: zos(:)
778 real(r8), allocatable :: zob(:)
779!
780! Minimum depth for wetting and drying (m).
781!
782 real(r8), allocatable :: dcrit(:)
783!
784! Mean density (Kg/m3) used when the Boussinesq approximation is
785! inferred.
786!
787 real(dp) :: rho0 = 1025.0_dp
788!
789! Background Brunt-Vaisala frequency (1/s2).
790!
791 real(dp) :: bvf_bak = 0.00001_dp
792
793#ifdef PROPAGATOR
794!
795! Number of converged Ritz values and relative accuracy of computed
796! Ritz values.
797!
798 integer, allocatable :: nconv(:)
799 real(dp) :: ritz_tol = 1.0e-15_dp
800#endif
801!
802! Vector containing USER generic parameters.
803!
804 integer :: nuser
805 real(r8), allocatable :: user(:)
806!
807! Weights for the time average of 2D fields.
808!
809 real(dp), allocatable :: weight(:,:,:)
810!
811! Constants.
812!
813 real(dp), parameter :: pi = 3.14159265358979323846_dp
814 real(dp), parameter :: deg2rad = pi / 180.0_dp
815 real(dp), parameter :: rad2deg = 180.0_dp / pi
816 real(dp), parameter :: day2sec = 86400.0_dp
817 real(dp), parameter :: sec2day = 1.0_dp / 86400.0_dp
818#ifdef NO_4BYTE_REALS
819 real(dp), parameter :: spval = nf90_fill_double
820#else
821 real(dp), parameter :: spval = 1.0e+37_dp
822#endif
823 real(dp), parameter :: large = 1.0e+20_dp
824 real(dp), parameter :: jul_off = 2440000.0_dp
825!
826! Set special check value. Notice that a smaller value is assigned
827! to account for both NetCDF fill value and roundoff. There are
828! many Matlab scripts out there that do not inquire correctly
829! the spval from the _FillValue attribute in single/double
830! precision.
831!
832 real(dp), parameter :: spval_check = 1.0e+35_dp
833!
834!-----------------------------------------------------------------------
835! Horizontal and vertical constant mixing coefficients.
836!-----------------------------------------------------------------------
837!
838! Akk_bak Background vertical mixing coefficient (m2/s) for
839! turbulent energy.
840! Akp_bak Background vertical mixing coefficient (m2/s) for
841! generic statistical field "psi".
842! Akt_bak Background vertical mixing coefficient (m2/s) for
843! tracers.
844! Akv_bak Background vertical mixing coefficient (m2/s) for
845! momentum.
846! Akt_limit Upper threshold vertical mixing coefficient (m2/s)
847! for tracers.
848! Akv_limit Upper threshold vertical mixing coefficient (m2/s)
849! for momentum.
850! Kdiff Isopycnal mixing thickness diffusivity (m2/s) for
851! tracers.
852! ad_visc2 ADM lateral harmonic constant mixing coefficient
853! (m2/s) for momentum.
854! nl_visc2 NLM lateral harmonic constant mixing coefficient
855! (m2/s) for momentum.
856! tl_visc2 TLM lateral harmonic constant mixing coefficient
857! (m2/s) for momentum.
858! visc2 Current lateral harmonic constant mixing coefficient
859! (m2/s) for momentum.
860! ad_visc4 ADM lateral biharmonic (squared root) constant
861! mixing coefficient (m2 s^-1/2) for momentum.
862! nl_visc4 NLM lateral biharmonic (squared root) constant
863! mixing coefficient (m2 s^-1/2) for momentum.
864! tl_visc4 TLM lateral biharmonic (squared root) constant
865! mixing coefficient (m2 s^-1/2) for momentum.
866! visc4 Current lateral biharmonic (squared root) constant
867! mixing coefficient (m2 s^-1/2) for momentum.
868! ad_tnu2 ADM lateral harmonic constant mixing coefficient
869! (m2/s) for tracer type variables.
870! nl_tnu2 NLM lateral harmonic constant mixing coefficient
871! (m2/s) for tracer type variables.
872! tl_tnu2 TLM lateral harmonic constant mixing coefficient
873! (m2/s) for tracer type variables.
874! tnu2 Current lateral harmonic constant mixing coefficient
875! (m2/s) for tracer type variables.
876! ad_tnu4 ADM lateral biharmonic (squared root) constant
877! mixing coefficient (m2 s^-1/2) for tracers.
878! nl_tnu4 NLM lateral biharmonic (squared root) constant
879! mixing coefficient (m2 s^-1/2) for tracers.
880! tl_tnu4 TLM lateral biharmonic (squared root) constant
881! mixing coefficient (m2 s^-1/2) for tracers.
882! tnu4 Current lateral biharmonic (squared root) constant
883! mixing coefficient (m2 s^-1/2) for tracers.
884! tkenu2 Lateral harmonic constant mixing coefficient
885! (m2/s) for turbulent energy.
886! tkenu4 Lateral biharmonic (squared root) constant mixing
887! coefficient (m2 s^-1/2) for turbulent energy.
888!
889 real(r8), allocatable :: akk_bak(:) ! m2/s
890 real(r8), allocatable :: akp_bak(:) ! m2/s
891 real(r8), allocatable :: akv_bak(:) ! m2/s
892 real(r8), allocatable :: akv_limit(:) ! m2/s
893
894 real(r8), allocatable :: ad_visc2(:) ! m2/s
895 real(r8), allocatable :: nl_visc2(:) ! m2/s
896 real(r8), allocatable :: tl_visc2(:) ! m2/s
897 real(r8), allocatable :: visc2(:) ! m2/s
898
899 real(r8), allocatable :: ad_visc4(:) ! m2 s-1/2
900 real(r8), allocatable :: nl_visc4(:) ! m2 s-1/2
901 real(r8), allocatable :: tl_visc4(:) ! m2 s-1/2
902 real(r8), allocatable :: visc4(:) ! m2 s-1/2
903
904 real(r8), allocatable :: tkenu2(:) ! m2/s
905 real(r8), allocatable :: tkenu4(:) ! m2 s-1/2
906
907 real(r8), allocatable :: akt_bak(:,:) ! m2/s
908 real(r8), allocatable :: akt_limit(:,:) ! m2/s
909 real(r8), allocatable :: kdiff(:,:) ! m2/s
910
911 real(r8), allocatable :: ad_tnu2(:,:) ! m2/s
912 real(r8), allocatable :: nl_tnu2(:,:) ! m2/s
913 real(r8), allocatable :: tl_tnu2(:,:) ! m2/s
914 real(r8), allocatable :: tnu2(:,:) ! m2/s
915
916 real(r8), allocatable :: ad_tnu4(:,:) ! m2 s-1/2
917 real(r8), allocatable :: nl_tnu4(:,:) ! m2 s-1/2
918 real(r8), allocatable :: tl_tnu4(:,:) ! m2 s-1/2
919 real(r8), allocatable :: tnu4(:,:) ! m2 s-1/2
920!
921! Horizontal diffusive relaxation coefficients (m2/s) used to smooth
922! representer tangent linear solution during Picard iterations to
923! improve stability and convergence.
924!
925 real(r8), allocatable :: tl_m2diff(:) ! 2D momentum
926 real(r8), allocatable :: tl_m3diff(:) ! 3D momentum
927
928 real(r8), allocatable :: tl_tdiff(:,:) ! tracers
929!
930! Basic state vertical mixing coefficient scale factors for adjoint
931! based algorithms. In some applications, a smaller/larger values of
932! vertical mixing are necessary for stability.
933!
934 real(r8), allocatable :: ad_akv_fac(:) ! ADM momentum
935 real(r8), allocatable :: tl_akv_fac(:) ! TLM momentum
936
937 real(r8), allocatable :: ad_akt_fac(:,:) ! ADM tracers
938 real(r8), allocatable :: tl_akt_fac(:,:) ! TLM tracers
939
940!
941! Switches to increase/decrease horizontal viscosity and/or diffusion
942! in specific areas of the application domain (like sponge areas).
943!
944 logical, allocatable :: lsponge(:)
945 logical, allocatable :: luvsponge(:) ! viscosity
946 logical, allocatable :: ltracersponge(:,:) ! diffusion
947!
948!-----------------------------------------------------------------------
949! IO parameters.
950!-----------------------------------------------------------------------
951!
952! Switches to activate creation and writing of output NetCDF files.
953!
954 logical, allocatable :: ldefadj(:) ! Adjoint file
955 logical, allocatable :: ldefavg(:) ! Average file
956 logical, allocatable :: ldefdai(:) ! DA initial/restart
957 logical, allocatable :: ldefdia(:) ! Diagnostics file
958 logical, allocatable :: ldeferr(:) ! 4DVar error file
959 logical, allocatable :: ldefflt(:) ! Floats file
960 logical, allocatable :: ldefhis(:) ! History file
961 logical, allocatable :: ldefhss(:) ! Hessian file
962 logical, allocatable :: ldefini(:) ! Initial file
963 logical, allocatable :: ldefirp(:) ! Initial RPM file
964 logical, allocatable :: ldefitl(:) ! Initial TLM file
965 logical, allocatable :: ldeflcz(:) ! Lanczos Vectors file
966 logical, allocatable :: ldeflze(:) ! Evolved Lanczos file
967 logical, allocatable :: ldefmod(:) ! 4DVAR file
968 logical, allocatable :: ldefqck(:) ! Quicksave file
969 logical, allocatable :: ldefrst(:) ! Restart file
970#ifdef SP4DVAR
971 logical, allocatable :: ldefsca(:) ! AD scratch state file
972 logical, allocatable :: ldefsct(:) ! TL scratch state file
973 logical, allocatable :: ldefspa(:) ! AD Arnoldi state file
974 logical, allocatable :: ldefspt(:) ! TL Arnoldi state file
975#endif
976 logical, allocatable :: ldefsta(:) ! Stations file
977#ifdef STD_MODEL
978 logical, allocatable :: ldefstd(:) ! STD file
979#endif
980 logical, allocatable :: ldeftide(:) ! tide forcing file
981 logical, allocatable :: ldeftlm(:) ! Tangent linear file
982 logical, allocatable :: ldeftlf(:) ! TLM/RPM impulse file
983 logical, allocatable :: ldefxtr(:) ! TLM/RPM impulse file
984
985 logical, allocatable :: lreadadm(:) ! Read ADM multi-files
986 logical, allocatable :: lreadblk(:) ! Read NLM bulk fluxes
987 logical, allocatable :: lreadfrc(:) ! Read FRC files
988 logical, allocatable :: lreadfwd(:) ! Read FWD trajectory
989 logical, allocatable :: lreadqck(:) ! Read QCK trajectory
990 logical, allocatable :: lreadstd(:) ! Read STD file
991 logical, allocatable :: lreadtlm(:) ! Read TLM multi-files
992
993 logical, allocatable :: lwrtadj(:) ! Write adjoint file
994 logical, allocatable :: lwrtavg(:) ! Write average file
995 logical, allocatable :: lwrtdia(:) ! Write diagnostic file
996 logical, allocatable :: lwrthis(:) ! Write history file
997 logical, allocatable :: lwrtper(:) ! Write during ensemble
998 logical, allocatable :: lwrtqck(:) ! write quicksave file
999 logical, allocatable :: lwrtrst(:) ! Write restart file
1000#ifdef STD_MODEL
1001 logical, allocatable :: lwrtstd(:) ! Write STD file
1002#endif
1003 logical, allocatable :: lwrttlf(:) ! Write impulse file
1004 logical, allocatable :: lwrttlm(:) ! Write tangent file
1005 logical, allocatable :: lwrtxtr(:) ! Write extraction file
1006
1007 logical, allocatable :: ldefnrm(:,:) ! Norm file
1008 logical, allocatable :: lwrtnrm(:,:) ! Write norm file
1009!
1010! Switch to write out adjoint 2D state arrays instead of IO solution
1011! arrays and adjoint ocean time. This is used in 4DVAR for IO
1012! maniputations.
1013!
1014#ifdef AD_OUTPUT_STATE
1015 logical, allocatable :: lwrtstate3d(:)
1016#endif
1017#if defined STOCHASTIC_OPT && !defined STOCH_OPT_WHITE
1018 logical, allocatable :: soinitial(:)
1019#endif
1020 logical, allocatable :: lwrtstate2d(:)
1021 logical, allocatable :: lwrttime(:)
1022!
1023! Switch to write 4D-Var cost functions to DAV NetCDF.
1024!
1025 logical, allocatable :: lwrtcost(:)
1026!
1027! Switch to write out adjoint surface forcing fields adjusted by the
1028! 4DVAR algorithms.
1029!
1030 logical, allocatable :: ladjusted(:)
1031!
1032! Switch to append information to an existing ROMS standard output
1033! log file.
1034!
1035 logical :: lappend = .false.
1036!
1037! Switch to read input open boundary conditions data.
1038!
1039 logical, allocatable :: lprocessobc(:)
1040!
1041! Switch to read input tidal forcing data.
1042!
1043 logical, allocatable :: lprocesstides(:)
1044!
1045! Switch to write application set-up information to standard output.
1046!
1047 logical, allocatable :: lwrtinfo(:)
1048!
1049! Switch used to create new output NetCDF files. If TRUE, new output
1050! files are created. If FALSE, data is appended to an existing output
1051! files. Used only for history, average and station files.
1052!
1053 logical, allocatable :: ldefout(:) ! New output files
1054!
1055! Number of timesteps between creation of new output files.
1056!
1057 integer, allocatable :: ndefadj(:) ! Adjoint file
1058 integer, allocatable :: ndefavg(:) ! Average file
1059 integer, allocatable :: ndefdia(:) ! Diagnostics file
1060 integer, allocatable :: ndefhis(:) ! History file
1061 integer, allocatable :: ndefqck(:) ! Quicksave file
1062 integer, allocatable :: ndeftlm(:) ! Tangent linear file
1063 integer, allocatable :: ndefxtr(:) ! extraction file
1064!
1065! Starting timestep for accumulation of output.
1066!
1067 integer, allocatable :: ntsavg(:) ! Average file
1068 integer, allocatable :: ntsdia(:) ! Diagnostics file
1069!
1070! Number of timesteps between writing of output data.
1071!
1072 integer, allocatable :: nadj(:) ! Adjoint file
1073 integer, allocatable :: navg(:) ! Average file
1074 integer, allocatable :: ndia(:) ! Diagnostics file
1075 integer, allocatable :: nflt(:) ! Floats file
1076 integer, allocatable :: nhis(:) ! History file
1077 integer, allocatable :: nqck(:) ! Quicksave file
1078 integer, allocatable :: nrst(:) ! Restart file
1079 integer, allocatable :: nsta(:) ! Stations file
1080 integer, allocatable :: ntlm(:) ! Tangent linear file
1081 integer, allocatable :: nxtr(:) ! extraction file
1082#ifdef SP4DVAR
1083 integer, allocatable :: nsca(:) ! AD scratch state file
1084 integer, allocatable :: nsct(:) ! TL scratch state file
1085 integer, allocatable :: nspa(:) ! AD Arnoldi state file
1086 integer, allocatable :: nspt(:) ! TL Arnoldi state file
1087 integer, allocatable :: crec(:) ! Convolution records
1088#endif
1089!
1090! Field extraction flag to interpolate or decimate solution to the
1091! provided grid geometry.
1092! (For 4D-Var coarser inner loops use ExtractFlag = 2)
1093!
1094! ExtractFlag = 0 no extraction
1095! ExtractFlag = 1 extraction by interpolation
1096! ExtractFlag > 1 extraction by decimation
1097!
1098 integer, allocatable :: extractflag(:)
1099!
1100! Number of timesteps between print of single line information to
1101! standard output.
1102!
1103 integer, allocatable :: ninfo(:)
1104!
1105! Number of timesteps between 4DVAR adjustment of open boundaries.
1106! In strong constraint 4DVAR, it is possible to open bounadies at
1107! other intervals in addition to initial time. These parameters are
1108! used to store the appropriate number of open boundary records in
1109! output history NetCDF files.
1110!
1111! Nbrec(:) = 1 + ntimes(:) / nOBC(:)
1112!
1113! Here, it is assumed that nOBC is a multiple of NTIMES or greater
1114! than NTIMES. If nOBC > NTIMES, only one record is stored in the
1115! output history NetCDF files and the adjustment is for constant
1116! open boundaries with constant correction.
1117!
1118 integer, allocatable :: nobc(:) ! number of timesteps
1119 integer, allocatable :: nbrec(:) ! number of records
1120 integer, allocatable :: obccount(:) ! record counter
1121
1122#ifdef ADJUST_BOUNDARY
1123!
1124! Logical switches to process open boundary arrays during 4DVar
1125! adjustments.
1126!
1127 logical, allocatable :: lobc(:,:,:)
1128!
1129! Time (s) of surface forcing adjustment.
1130!
1131 real(dp), allocatable :: obc_time(:,:)
1132#endif
1133!
1134! Number of timesteps between adjustment of 4DVAR surface forcing
1135! fields. In strong constraint 4DVAR, it is possible to adjust surface
1136! forcing fields at other intervals in addition to initial time.
1137! These parameters are used to store the appropriate number of
1138! surface forcing records in output history NetCDF files.
1139!
1140! Nfrec(:) = 1 + ntimes(:) / nSFF(:)
1141!
1142! Here, it is assumed that nSFF is a multiple of NTIMES or greater
1143! than NTIMES. If nSFF > NTIMES, only one record is stored in the
1144! output history NetCDF files and the adjustment is for constant
1145! forcing with constant correction.
1146!
1147 integer, allocatable :: nsff(:) ! number of timesteps
1148 integer, allocatable :: nfrec(:) ! number of records
1149 integer, allocatable :: sfcount(:) ! record counter
1150
1151#ifdef ADJUST_STFLUX
1152!
1153! Logical switches to process surface tracer fluxes during 4DVar
1154! adjustments.
1155!
1156 logical, allocatable :: lstflux(:,:)
1157#endif
1158#if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
1159!
1160! Time (s) of surface forcing adjustment.
1161!
1162 real(dp), allocatable :: sf_time(:,:)
1163#endif
1164!
1165! Restart time record to read from disk and use as the initial
1166! conditions. Use nrrec=0 for new solutions. If nrrec is negative
1167! (say, nrrec=-1), the model will restart from the most recent
1168! time record. That is, the initialization record is assigned
1169! internally.
1170!
1171 integer, allocatable :: nrrec(:)
1172!
1173! Switch to activate processing of input data. This switch becomes
1174! very useful when reading input data serially in parallel
1175! applications.
1176!
1177 logical, allocatable :: synchro_flag(:)
1178!$OMP THREADPRIVATE (synchro_flag)
1179!
1180! Switch to inialize model with latest time record from initial
1181! (restart/history) NetCDF file.
1182!
1183 logical, allocatable :: lastrec(:)
1184!
1185! Generalized Statbility Theory (GST) parameters.
1186!
1187 logical :: lmultigst ! multiple eigenvector file switch
1188 logical :: lrstgst ! restart switch
1189 integer :: maxitergst ! Number of iterations
1190 integer :: ngst ! check pointing interval
1191!
1192! Switches used to recycle time records in some output file. If TRUE,
1193! only the latest two time records are maintained. If FALSE, all
1194! field records are saved.
1195!
1196 logical, allocatable :: lcycleadj(:)
1197 logical, allocatable :: lcyclerst(:)
1198 logical, allocatable :: lcycletlm(:)
1199
1200#if defined AVERAGES && defined AVERAGES_DETIDE && \
1201 (defined ssh_tides || defined uv_tides)
1202!
1203! Counter storing the number of accumulated harmonic records used
1204! for detiding.
1205!
1206 integer, allocatable :: hcount(:)
1207#endif
1208!
1209!-----------------------------------------------------------------------
1210! Adjoint sensitivity parameters.
1211!-----------------------------------------------------------------------
1212!
1213! Starting and ending vertical levels of the 3D adjoint state whose
1214! sensitivity is required.
1215!
1216 integer, allocatable :: kstrs(:) ! starting level
1217 integer, allocatable :: kends(:) ! ending level
1218!
1219! Starting and ending day for adjoint sensitivity forcing.
1220!
1221 real(r8), allocatable :: dstrs(:) ! starting day
1222 real(r8), allocatable :: dends(:) ! ending day
1223!
1224!-----------------------------------------------------------------------
1225! Stochastic optimals parameters.
1226!-----------------------------------------------------------------------
1227!
1228! Stochastic optimals forcing records counter.
1229!
1230 integer, allocatable :: sorec(:)
1231!$OMP THREADPRIVATE (SOrec)
1232!
1233! Trace of stochastic optimals matrix.
1234!
1235 real(r8), allocatable :: trnorm(:)
1236!
1237! Stochastic optimals time decorrelation scale (days) assumed for
1238! red noise processes.
1239!
1240 real(r8), allocatable :: so_decay(:)
1241!
1242! Stochastic optimals surface forcing standard deviation for
1243! dimensionalization.
1244!
1245 real(r8), allocatable :: so_sdev(:,:)
1246
1247#if defined FOUR_DVAR || defined VERIFICATION
1248!
1249!------------------------------------------------------------------------
1250! Background/model error covariance parameters.
1251!------------------------------------------------------------------------
1252!
1253! Maximum number of model state variables to process.
1254!
1255 integer :: mstatevar
1256!
1257! Logical switch to compute initial conditions, model and surface
1258! forcing error covariance normalization factors.
1259!
1260 logical, allocatable :: cnorm(:,:)
1261!
1262! Logical switch to compute boundary conditions error covariance
1263! normalization factors.
1264!
1265 logical, allocatable :: cnormb(:,:)
1266!
1267! Logical switches to process weak constraint forcing as intermittent
1268! or continuous impulses.
1269!
1270 logical, allocatable :: sporadicimpulse(:) ! intermittent
1271 logical, allocatable :: frequentimpulse(:) ! continuous
1272!
1273! Logical switch to control 4D-Var incremental analysis update forcing.
1274!
1275 logical, allocatable :: iauswitch(:)
1276!
1277! Duration of the 4D-Var incremental inalysis update (seconds).
1278!
1279 real(dp), allocatable :: timeiau(:)
1280!
1281! Stability and accuracy factor used to scale the time-step of the
1282! horizontal and vertical convolution operator below its theoretical
1283! (CFL) limit. Notice that four values are needed for these factors to
1284! facilitate the error covariance modeling for initial conditions (1),
1285! model (2), boundary conditions (3), and surface forcing (4).
1286!
1287 real(r8), dimension(4) :: hgamma
1288 real(r8), dimension(4) :: vgamma
1289!
1290! Parameters used to compute balanced salinity in terms of temperature
1291! using empirical T-S relationships in error covariance balance
1292! operator.
1293!
1294 real(r8), allocatable :: dtdz_min(:) ! minimum dT/ds (C/m)
1295 real(r8), allocatable :: ml_depth(:) ! mixed-layer depth (m)
1296!
1297! Balance operator level of no motion depth (m; positive) used when
1298! computing balanced free-surface contribution.
1299!
1300 real(r8), allocatable :: lnm_depth(:)
1301!
1302! Balance operator level of no motion flag used to compute balanced
1303! free-surface contribution:
1304!
1305! [0] Integrate from local bottom to the surface
1306! [1] Integrate from LNM_depth to surface or integrate from local bottom
1307! if shallower than LNM_depth
1308!
1309 integer :: lnm_flag
1310!
1311! Balance operator logical switches for state variables to consider in the
1312! error covariance multivariate constraints.
1313!
1314 logical, allocatable :: balance(:)
1315!
1316! Initial conditions, model and surface forcing error covariance
1317! horizontal decorrelation scales (m).
1318!
1319 real(r8), allocatable :: hdecay(:,:,:)
1320!
1321! Initial conditions, model and surface forcing error covariance
1322! temporal decorrelation scales (second).
1323!
1324 real(r8), allocatable :: tdecay(:,:)
1325!
1326! Initial conditions, model and surface forcing error covariance
1327! vertical decorrelation scales (m).
1328!
1329 real(r8), allocatable :: vdecay(:,:,:)
1330!
1331! Boundary conditions error covariance horizontal decorrelation
1332! scales (m).
1333!
1334 real(r8), allocatable :: hdecayb(:,:,:)
1335!
1336! Boundary conditions error covariance vertical decorrelation
1337! scales (m).
1338!
1339 real(r8), allocatable :: vdecayb(:,:,:)
1340!
1341! Method for background quality control of observations, [Ngrids].
1342!
1343! [1] Quality control in terms of state variable indices
1344! [2] Quality control in terms of observation provenance
1345!
1346 integer, allocatable :: bgqc_type(:)
1347!
1348! Background quality control standard deviation value for not
1349! rejection of observations.
1350!
1351 real(r8) :: bgqc_large = 1.0e+5_r8
1352!
1353! Number of observation provenances used in background quality control,
1354! [Ngrids]. Only used when bgqc_type(ng)=2.
1355!
1356 integer, allocatable :: nprovenance(:)
1357!
1358! Observation provenance indices to process during background quality
1359! control of observations, [MAXVAL(Nprovenance),Ngrids].
1360!
1361 integer, allocatable :: iprovenance(:,:)
1362!
1363! Background quality control threshold standard deviations in terms
1364! of observation provenance indices, [MAXVAL(Nprovenance),Ngrids].
1365!
1366 real(r8), allocatable :: p_bgqc(:,:)
1367!
1368! Background quality control threshold standard deviations in terms
1369! of state variable indices, [MstateVar,Ngrids]
1370!
1371 real(r8), allocatable :: s_bgqc(:,:)
1372
1373# ifdef STD_MODEL
1374!
1375! Background error covariance, standard deviation modeling parameters.
1376!
1377! This approach computes the standard deviation (STD) directly from
1378! the background (prior) field as an alternative to climatological
1379! values read from the input NetCDF files. It follows the work of
1380! Mogensen et al. (2012) by assuming the background errors are
1381! proportional to the vertical derivatives of the background field.
1382! The field error has a similar profile shape, but the difference
1383! with the actual error value is due to due to a vertical displacemnt.
1384! Thus, the parameters below, per state variable, are used to process
1385! the STD profile in terms od the location of the mixed layer where
1386! the error is larger.
1387!
1388 real(r8), allocatable :: sigma_max(:,:) ! Maximum value
1389 real(r8), allocatable :: sigma_ml(:,:) ! Minimum at mixed layer
1390 real(r8), allocatable :: sigma_do(:,:) ! Minimum in deep ocean
1391 real(r8), allocatable :: sigma_dz(:,:) ! vetical displacement
1392!
1393! The computation of the mixed-layer depth is computed using the
1394! approach of Kara et al. (2000), if activated. Otherwiae, a constant
1395! value is used.
1396!
1397 real(r8), allocatable :: mld_uniform(:) ! mixed layer depth
1398# endif
1399#endif
1400!
1401!-----------------------------------------------------------------------
1402! Nudging variables for passive (outflow) and active (inflow) oepn
1403! boundary conditions.
1404!-----------------------------------------------------------------------
1405!
1406! iwest West identification index in boundary arrays.
1407! isouth South identification index in boundary arrays.
1408! ieast East identification index in boundary arrays.
1409! inorth North identification index in boundary arrays.
1410! obcfac Factor between passive and active open boundary
1411! conditions (nondimensional and greater than one).
1412! The nudging time scales for the active conditions
1413! are obtained by multiplying the passive values by
1414! factor.
1415! FSobc_in Active and strong time-scale (1/sec) coefficients
1416! for nudging towards free-surface data at inflow.
1417! FSobc_out Passive and weak time-scale (1/sec) coefficients
1418! for nudging towards free-surface data at outflow.
1419! M2obc_in Active and strong time-scale (1/sec) coefficients
1420! for nudging towards 2D momentum data at inflow.
1421! M2obc_out Passive and weak time-scale (1/sec) coefficients
1422! for nudging towards 2D momentum data at outflow.
1423! M3obc_in Active and strong time-scale (1/sec) coefficients
1424! for nudging towards 3D momentum data at inflow.
1425! M3obc_out Passive and weak time-scale (1/sec) coefficients
1426! for nudging towards 3D momentum data at outflow.
1427! Tobc_in Active and strong time-scale (1/sec) coefficients
1428! for nudging towards tracer data at inflow.
1429! Tobc_out Passive and weak time-scale (1/sec) coefficients
1430! for nudging towards tracer data at outflow.
1431!
1432 integer, parameter :: iwest = 1
1433 integer, parameter :: isouth = 2
1434 integer, parameter :: ieast = 3
1435 integer, parameter :: inorth = 4
1436
1437 real(dp), allocatable :: obcfac(:)
1438 real(dp), allocatable :: fsobc_in(:,:)
1439 real(dp), allocatable :: fsobc_out(:,:)
1440 real(dp), allocatable :: m2obc_in(:,:)
1441 real(dp), allocatable :: m2obc_out(:,:)
1442#ifdef SOLVE3D
1443 real(dp), allocatable :: m3obc_in(:,:)
1444 real(dp), allocatable :: m3obc_out(:,:)
1445 real(dp), allocatable :: tobc_in(:,:,:)
1446 real(dp), allocatable :: tobc_out(:,:,:)
1447#endif
1448!
1449! Inverse time-scales (1/s) for nudging at open boundaries and sponge
1450! areas.
1451!
1452 real(dp), allocatable :: znudg(:) ! Free-surface
1453 real(dp), allocatable :: m2nudg(:) ! 2D momentum
1454 real(dp), allocatable :: m3nudg(:) ! 3D momentum
1455 real(dp), allocatable :: tnudg(:,:) ! Tracers
1456!
1457! Variables used to impose mass flux conservation in open boundary
1458! configurations.
1459!
1460 real(dp) :: bc_area = 0.0_dp
1461 real(dp) :: bc_flux = 0.0_dp
1462 real(dp) :: ubar_xs = 0.0_dp
1463#if defined TANGENT || defined TL_IOMS
1464 real(dp) :: tl_bc_area = 0.0_dp
1465 real(dp) :: tl_bc_flux = 0.0_dp
1466 real(dp) :: tl_ubar_xs = 0.0_dp
1467#endif
1468#ifdef ADJOINT
1469 real(dp) :: ad_bc_area = 0.0_dp
1470 real(dp) :: ad_bc_flux = 0.0_dp
1471 real(dp) :: ad_ubar_xs = 0.0_dp
1472#endif
1473#ifdef SP4DVAR
1474 real(r8) :: sp_sumdot = 0.0_r8
1475#endif
1476
1477#ifdef BULK_FLUXES
1478!
1479!-----------------------------------------------------------------------
1480! Constants used in surface fluxes bulk parameterization.
1481!-----------------------------------------------------------------------
1482!
1483! blk_Cpa Specific heat capacity for dry air (J/kg/K).
1484! blk_Cpw Specific heat capacity for seawater (J/kg/K).
1485! blk_Rgas Gas constant for dry air (J/kg/K).
1486! blk_Zabl Height (m) of atmospheric boundary layer.
1487! blk_ZQ Height (m) of surface air humidity measurement.
1488! blk_ZT Height (m) of surface air temperature measurement.
1489! blk_ZW Height (m) of surface winds measurement.
1490! blk_beta Beta parameter evaluated from Fairall low windspeed
1491! turbulence data.
1492! blk_dter Temperature change.
1493! blk_tcw Thermal conductivity of water (W/m/K).
1494! blk_visw Kinematic viscosity water (m2/s).
1495!
1496 real(dp) :: blk_cpa = 1004.67_dp ! (J/kg/K), Businger 1982
1497 real(dp) :: blk_cpw = 4000.0_dp ! (J/kg/K)
1498 real(dp) :: blk_rgas = 287.1_dp ! (J/kg/K)
1499 real(dp) :: blk_zabl = 600.0_dp ! (m)
1500 real(dp) :: blk_beta = 1.2_dp ! non-dimensional
1501 real(dp) :: blk_dter = 0.3_dp ! (K)
1502 real(dp) :: blk_tcw = 0.6_dp ! (W/m/K)
1503 real(dp) :: blk_visw = 0.000001_dp ! (m2/s)
1504
1505 real(r8), allocatable :: blk_zq(:) ! (m)
1506 real(r8), allocatable :: blk_zt(:) ! (m)
1507 real(r8), allocatable :: blk_zw(:) ! (m)
1508#endif
1509# if defined SG_BBL || defined SSW_BBL
1510!
1511!-----------------------------------------------------------------------
1512! Closure parameters associated with Styles and Glenn (1999) bottom
1513! currents and waves boundary layer.
1514!-----------------------------------------------------------------------
1515!
1516! sg_Cdmax Upper limit on bottom darg coefficient.
1517! sg_alpha Free parameter indicating the constant stress
1518! region of the wave boundary layer.
1519! sg_g Acceleration of gravity (m/s2).
1520! sg_kappa Von Karman constant.
1521! sg_mp Nondimensional closure constant.
1522! sg_n Maximum number of iterations for bisection method.
1523! sg_nu Kinematic viscosity of seawater (m2/s).
1524! sg_pi Ratio of circumference to diameter.
1525! sg_tol Convergence criterion.
1526! sg_ustarcdef Default bottom stress (m/s).
1527! sg_z100 Depth (m), 100 cm above bottom.
1528! sg_z1p Nondimensional closure constant.
1529! sg_zrmin Minimum allowed height (m) of current above bed.
1530! Otherwise, logarithmic interpolation is used.
1531! sg_znotcdef Default apparent hydraulic roughness (m).
1532! sg_znotdef Default hydraulic roughness (m).
1533!
1534 integer, parameter :: sg_n = 20
1535
1536 real(dp), parameter :: sg_pi = pi
1537
1538 real(dp) :: sg_cdmax = 0.01_dp ! non-dimensional
1539 real(dp) :: sg_alpha = 1.0_dp ! non-dimensional
1540 real(dp) :: sg_g = 9.81_dp ! (m/s2)
1541 real(dp) :: sg_kappa = 0.41_dp ! non-dimensional
1542 real(dp) :: sg_nu = 0.00000119_dp ! (m2/s)
1543 real(dp) :: sg_tol = 0.0001_dp ! non-dimensional
1544 real(dp) :: sg_ustarcdef = 0.01_dp ! (m/s)
1545 real(dp) :: sg_z100 = 1.0_dp ! (m)
1546 real(dp) :: sg_z1min = 0.20_dp ! (m)
1547 real(dp) :: sg_z1p ! non-dimensional
1548 real(dp) :: sg_znotcdef = 0.01_dp ! (m)
1549 real(dp) :: sg_znotdef ! (m)
1550
1551 complex(c8) :: sg_mp
1552# endif
1553#if defined LMD_SKPP || defined SOLAR_SOURCE
1554!
1555!-----------------------------------------------------------------------
1556! Water clarity parameters.
1557!-----------------------------------------------------------------------
1558!
1559! The water type classification is based on Jerlov water type using
1560! a double exponential function for light absorption:
1561!
1562! Array
1563! Index WaterType Examples
1564! ----- --------- --------
1565!
1566! 1 I Open Pacific
1567! 2 IA Eastern Mediterranean, Indian Ocean
1568! 3 IB Western Mediterranean, Open Atlantic
1569! 4 II Coastal waters, Azores
1570! 5 III Coastal waters, North Sea
1571! 6 1 Skagerrak Strait
1572! 7 3 Baltic
1573! 8 5 Black Sea
1574! 9 7 Dark coastal water
1575!
1576! lmd_mu1 Reciprocal of the absorption coefficient for solar
1577! wavelength band 1 as a function of the Jerlov
1578! water type.
1579! lmd_mu2 Reciprocal of the absorption coefficient for solar
1580! wavelength band 2 as a function of the Jerlov
1581! water type.
1582! lmd_r1 Fraction of total radiance for wavelength band 1 as
1583! a function of the Jerlov water type.
1584!
1585 real(r8), dimension(9) :: lmd_mu1 = &
1586 & (/ 0.35_r8, 0.6_r8, 1.0_r8, 1.5_r8, 1.4_r8, &
1587 & 0.42_r8, 0.37_r8, 0.33_r8, 0.00468592_r8 /)
1588
1589 real(r8), dimension(9) :: lmd_mu2 = &
1590 & (/ 23.0_r8, 20.0_r8, 17.0_r8, 14.0_r8, 7.9_r8, &
1591 & 5.13_r8, 3.54_r8, 2.34_r8, 1.51_r8 /)
1592
1593 real(r8), dimension(9) :: lmd_r1 = &
1594 & (/ 0.58_r8, 0.62_r8, 0.67_r8, 0.77_r8, 0.78_r8, &
1595 & 0.57_r8, 0.57_r8, 0.57_r8, 0.55_r8 /)
1596#endif
1597
1598#ifdef LMD_MIXING
1599!
1600!-----------------------------------------------------------------------
1601! Large et al. (1994) K-profile parameterization.
1602!-----------------------------------------------------------------------
1603!
1604! lmd_Ri0 Critical gradient Richardson number below which
1605! turbulent mixing occurs.
1606! lmd_Rrho0 Value of double-diffusive density ratio where
1607! mixing goes to zero in salt fingering.
1608! lmd_bvfcon Brunt-Vaisala frequency (1/s2) limit for convection.
1609! lmd_fdd Scaling factor for double diffusion of temperature
1610! in salt fingering case (lmd_fdd=0.7).
1611! lmd_nu Molecular viscosity (m2/s).
1612! lmd_nu0c Maximum interior convective viscosity and diffusivity
1613! due to shear instability.
1614! lmd_nu0m Maximum interior viscosity (m2/s) due shear
1615! instability.
1616! lmd_nu0s Maximum interior diffusivity (m2/s) due shear
1617! instability.
1618! lmd_nuf Scaling factor for double diffusion in salt
1619! fingering.
1620! lmd_nuwm Interior viscosity (m2/s) due to wave breaking.
1621! lmd_nuws Interior diffusivity (m2/s) due to wave breaking.
1622! lmd_sdd1 Double diffusion constant for salinity in diffusive
1623! convection case (lmd_sdd1=0.15).
1624! lmd_sdd2 Double diffusion constant for salinity in diffusive
1625! convection case (lmd_sdd2=1.85).
1626! lmd_sdd3 Double diffusion constant for salinity in diffusive
1627! convection case (lmd_sdd3=0.85).
1628! lmd_tdd1 Double diffusion constant for temperature
1629! in diffusive convection case (lmd_tdd1=0.909).
1630! lmd_tdd2 Double diffusion constant for temperature in
1631! diffusive convection case (lmd_tdd2=4.6).
1632! lmd_tdd3 Double diffusion constant for temperature in
1633! diffusive convection case (lmd_tdd3=0.54).
1634!
1635 real(r8) :: lmd_ri0 = 0.7_r8 ! non-dimensional
1636 real(r8) :: lmd_rrho0 = 1.9_r8 ! m2/s
1637 real(r8) :: lmd_bvfcon = -2.0e-5_r8 ! 1/s2
1638 real(r8) :: lmd_fdd = 0.7_r8 ! non-dimensional
1639 real(r8) :: lmd_nu = 1.5e-6_r8 ! m2/s
1640 real(r8) :: lmd_nu0c = 0.01_r8 ! m2/s
1641!! real(r8) :: lmd_nu0c = 0.1_r8 ! m2/s
1642!! real(r8) :: lmd_nu0c = 0.05_r8 ! m2/s
1643 real(r8) :: lmd_nu0m = 10.0e-4_r8 ! m2/s
1644 real(r8) :: lmd_nu0s = 10.0e-4_r8 ! m2/s
1645!! real(r8) :: lmd_nu0m = 50.0E-4_r8 ! m2/s
1646!! real(r8) :: lmd_nu0s = 50.0E-4_r8 ! m2/s
1647 real(r8) :: lmd_nuf = 10.0e-4_r8 ! m2/s
1648# ifdef DAMEE_4
1649 real(r8) :: lmd_nuwm = 1.0e-4_r8 ! m2/s
1650 real(r8) :: lmd_nuws = 1.0e-5_r8 ! m2/s
1651# else
1652 real(r8) :: lmd_nuwm = 1.0e-5_r8 ! m2/s
1653 real(r8) :: lmd_nuws = 1.0e-6_r8 ! m2/s
1654# endif
1655 real(r8) :: lmd_sdd1 = 0.15_r8 ! non-dimensional
1656 real(r8) :: lmd_sdd2 = 1.85_r8 ! non-dimensional
1657 real(r8) :: lmd_sdd3 = 0.85_r8 ! non-dimensional
1658 real(r8) :: lmd_tdd1 = 0.909_r8 ! non-dimensional
1659 real(r8) :: lmd_tdd2 = 4.6_r8 ! non-dimensional
1660 real(r8) :: lmd_tdd3 = 0.54_r8 ! non-dimensional
1661
1662# if defined LMD_SKPP || defined LMD_BKPP
1663!
1664!-----------------------------------------------------------------------
1665! Large et al. (1994) oceanic boundary layer parameters.
1666!-----------------------------------------------------------------------
1667!
1668! lmd_Cg Proportionality coefficient parameterizing nonlocal
1669! transport.
1670! lmd_Cstar Proportionality coefficient parameterizing nonlocal
1671! transport.
1672! lmd_Cv Ratio of interior Brunt-Vaisala frequency to that
1673! at entrainment depth "he".
1674! lmd_Ric Critical bulk Richardson number.
1675! lmd_am Coefficient of flux profile for momentum in their
1676! 1/3 power law regimes.
1677! lmd_as Coefficient of flux profile for tracers in their
1678! 1/3 power law regimes.
1679! lmd_betaT Ratio of entrainment flux to surface buoyancy flux.
1680! lmd_cekman Constant used in the computation of Ekman depth.
1681! lmd_cmonob Constant used in the computation of Monin-Obukhov
1682! depth.
1683! lmd_cm Coefficient of flux profile for momentum in their
1684! 1/3 power law regimes.
1685! lmd_cs Coefficient of flux profile for tracers in their
1686! 1/3 power law regimes.
1687! lmd_epsilon Non-dimensional extent of the surface layer.
1688! lmd_zetam Maximum stability parameter "zeta" value of the 1/3
1689! power law regime of flux profile for momentum.
1690! lmd_zetas Maximum stability parameter "zeta" value of the 1/3
1691! power law regime of flux profile for tracers.
1692!
1693 real(r8) :: lmd_cg
1694 real(r8) :: lmd_cstar = 10.0_r8
1695 real(r8) :: lmd_cv = 1.25_r8
1696!! real(r8) :: lmd_Cv = 1.4_r8
1697!! real(r8) :: lmd_Cv = 1.6_r8
1698!! real(r8) :: lmd_Cv = 1.8_r8
1699!! real(r8) :: lmd_Ric = 0.25_r8
1700 real(r8) :: lmd_ric = 0.3_r8
1701!! real(r8) :: lmd_Ric = 0.5_r8
1702!! real(r8) :: lmd_Ric = 0.75_r8
1703 real(r8) :: lmd_am = 1.257_r8
1704 real(r8) :: lmd_as = -28.86_r8
1705 real(r8) :: lmd_betat = -0.2_r8
1706 real(r8) :: lmd_cekman = 0.7_r8
1707 real(r8) :: lmd_cmonob = 1.0_r8
1708 real(r8) :: lmd_cm = 8.36_r8
1709 real(r8) :: lmd_cs = 98.96_r8
1710 real(r8) :: lmd_epsilon = 0.1_r8
1711 real(r8) :: lmd_zetam = -0.2_r8
1712 real(r8) :: lmd_zetas = -1.0_r8
1713# endif
1714#endif
1715!
1716!-----------------------------------------------------------------------
1717! Generic Length Scale parameters.
1718!-----------------------------------------------------------------------
1719!
1720! gls_Gh0
1721! gls_Ghcri
1722! gls_Ghmin
1723! gls_Kmin Minimum value of specific turbulent kinetic energy.
1724! gls_Pmin Minimum Value of dissipation.
1725! gls_cmu0 Stability coefficient (non-dimensional).
1726! gls_c1 Shear production coefficient (non-dimensional).
1727! gls_c2 Dissipation coefficient (non-dimensional).
1728! gls_c3m Buoyancy production coefficient (minus).
1729! gls_c3p Buoyancy production coefficient (plus).
1730! gls_E2
1731! gls_m Turbulent kinetic energy exponent (non-dimensional).
1732! gls_n Turbulent length scale exponent (non-dimensional).
1733! gls_p Stability exponent (non-dimensional).
1734! gls_sigk Constant Schmidt number (non-dimensional) for
1735! turbulent kinetic energy diffusivity.
1736! gls_sigp Constant Schmidt number (non-dimensional) for
1737! turbulent generic statistical field, "psi".
1738!
1739 real(r8), allocatable :: gls_m(:)
1740 real(r8), allocatable :: gls_n(:)
1741 real(r8), allocatable :: gls_p(:)
1742 real(r8), allocatable :: gls_sigk(:)
1743 real(r8), allocatable :: gls_sigp(:)
1744 real(r8), allocatable :: gls_cmu0(:)
1745 real(r8), allocatable :: gls_cmupr(:)
1746 real(r8), allocatable :: gls_c1(:)
1747 real(r8), allocatable :: gls_c2(:)
1748 real(r8), allocatable :: gls_c3m(:)
1749 real(r8), allocatable :: gls_c3p(:)
1750 real(r8), allocatable :: gls_kmin(:)
1751 real(r8), allocatable :: gls_pmin(:)
1752#ifdef GLS_MIXING
1753# if defined CANUTO_A || defined CANUTO_B
1754 real(r8) :: gls_s0
1755 real(r8) :: gls_s1
1756 real(r8) :: gls_s2
1757 real(r8) :: gls_s3
1758 real(r8) :: gls_s4
1759 real(r8) :: gls_s5
1760 real(r8) :: gls_s6
1761 real(r8) :: gls_b0
1762 real(r8) :: gls_b1
1763 real(r8) :: gls_b2
1764 real(r8) :: gls_b3
1765 real(r8) :: gls_b4
1766 real(r8) :: gls_b5
1767# endif
1768# ifdef CANUTO_A
1769 real(r8), parameter :: gls_gh0 = 0.0329_r8 ! 0.0329 GOTM, 0.0673 Burchard
1770 real(r8), parameter :: gls_ghcri = 0.03_r8
1771 real(r8), parameter :: gls_l1 = 0.107_r8
1772 real(r8), parameter :: gls_l2 = 0.0032_r8
1773 real(r8), parameter :: gls_l3 = 0.0864_r8
1774 real(r8), parameter :: gls_l4 = 0.12_r8
1775 real(r8), parameter :: gls_l5 = 11.9_r8
1776 real(r8), parameter :: gls_l6 = 0.4_r8
1777 real(r8), parameter :: gls_l7 = 0.0_r8
1778 real(r8), parameter :: gls_l8 = 0.48_r8
1779# elif defined CANUTO_B
1780 real(r8), parameter :: gls_gh0 = 0.0444_r8 ! 0.044 GOTM, 0.0673 Burchard
1781 real(r8), parameter :: gls_ghcri = 0.0414_r8
1782 real(r8), parameter :: gls_l1 = 0.127_r8
1783 real(r8), parameter :: gls_l2 = 0.00336_r8
1784 real(r8), parameter :: gls_l3 = 0.0906_r8
1785 real(r8), parameter :: gls_l4 = 0.101_r8
1786 real(r8), parameter :: gls_l5 = 11.2_r8
1787 real(r8), parameter :: gls_l6 = 0.4_r8
1788 real(r8), parameter :: gls_l7 = 0.0_r8
1789 real(r8), parameter :: gls_l8 = 0.318_r8
1790# else
1791 real(r8), parameter :: gls_gh0 = 0.028_r8
1792 real(r8), parameter :: gls_ghcri = 0.02_r8
1793# endif
1794 real(r8), parameter :: gls_ghmin = -0.28_r8
1795 real(r8), parameter :: gls_e2 = 1.33_r8
1796#endif
1797!
1798! Constants used in the various formulation of surface flux boundary
1799! conditions for the GLS vertical turbulence closure in terms of
1800! Charnock surface roughness (CHARNOK_ALPHA), roughness from wave
1801! amplitude (zos_hsig_alpha), wave dissipation (SZ_ALPHA), and
1802! Craig and Banner wave breaking (CRGBAN_CW).
1803!
1804 real(r8), allocatable :: charnok_alpha(:)
1805 real(r8), allocatable :: zos_hsig_alpha(:)
1806 real(r8), allocatable :: sz_alpha(:)
1807 real(r8), allocatable :: crgban_cw(:)
1808!
1809! Waves Effect on Currents dissipation energy partion scale:
1810!
1811! [0.0] All wave dissipation goes to breaking and none to roller
1812! [1.0] All wave dissipation goes to roller and none to breaking
1813!
1814 real(r8), allocatable :: wec_alpha(:)
1815
1816#if defined MY25_MIXING || defined GLS_MIXING
1817!
1818!-----------------------------------------------------------------------
1819! Mellor-Yamada (1982) Level 2.5 vertical mixing variables.
1820!-----------------------------------------------------------------------
1821!
1822! my_A1 Turbulent closure A1 constant.
1823! my_A2 Turbulent closure A2 constant.
1824! my_B1 Turbulent closure B1 constant.
1825! my_B1p2o3 B1**(2/3).
1826! my_B1pm1o3 B1**(-1/3).
1827! my_B2 Turbulent closure B2 constant.
1828! my_C1 Turbulent closure C1 constant.
1829! my_C2 Turbulent closure C2 constant.
1830! my_C3 Turbulent closure C3 constant.
1831! my_E1 Turbulent closure E1 constant.
1832! my_E1o2 0.5*E1
1833! my_E2 Turbulent closure E2 constant.
1834! my_Gh0 Lower bound on Galperin et al. stability function.
1835! my_Sh1 Tracers stability function constant factor.
1836! my_Sh2 Tracers stability function constant factor.
1837! my_Sm1 Momentum stability function constant factor.
1838! my_Sm2 Momentum stability function constant factor.
1839! my_Sm3 Momentum stability function constant factor.
1840! my_Sm4 Momentum stability function constant factor.
1841! my_Sq Scale for vertical mixing of turbulent energy.
1842! my_dtfac Asselin time filter coefficient.
1843! my_lmax Upper bound on the turbulent length scale.
1844! my_qmin Lower bound on turbulent energy "tke" and "gls".
1845!
1846 real(r8), parameter :: my_a1 = 0.92_r8
1847 real(r8), parameter :: my_a2 = 0.74_r8
1848 real(r8), parameter :: my_b1 = 16.6_r8
1849 real(r8), parameter :: my_b2 = 10.1_r8
1850 real(r8), parameter :: my_c1 = 0.08_r8
1851 real(r8), parameter :: my_c2 = 0.7_r8
1852 real(r8), parameter :: my_c3 = 0.2_r8
1853 real(r8), parameter :: my_e1 = 1.8_r8
1854 real(r8), parameter :: my_e2 = 1.33_r8
1855 real(r8), parameter :: my_gh0 = 0.0233_r8
1856 real(r8), parameter :: my_sq = 0.2_r8
1857 real(r8), parameter :: my_dtfac = 0.05_r8
1858 real(r8), parameter :: my_lmax = 0.53_r8
1859 real(r8), parameter :: my_qmin = 1.0e-8_r8
1860
1861 real(r8) :: my_b1p2o3
1863 real(r8) :: my_e1o2
1864 real(r8) :: my_sh1
1865 real(r8) :: my_sh2
1866 real(r8) :: my_sm1
1867 real(r8) :: my_sm2
1868 real(r8) :: my_sm3
1869 real(r8) :: my_sm4
1870#endif
1871#ifdef BVF_MIXING
1872!
1873!-----------------------------------------------------------------------
1874! Brunt-Vaisala frequency based vertical mixing variables.
1875!-----------------------------------------------------------------------
1876!
1877! bvf_numax Upper bound vertical diffusion (m2/s).
1878! bvf_numin Lower bound vertical diffusion (m2/s).
1879! bvf_nu0 Proportionality constant (m2/s2).
1880! bvf_nu0c Convective diffusion (m2/s) in static unstable
1881! regime.
1882!
1883 real(r8) :: bvf_numax = 4.0e-4_r8 ! m2/s
1884 real(r8) :: bvf_numin = 3.0e-5_r8 ! m2/s
1885 real(r8) :: bvf_nu0 = 1.0e-7_r8 ! m2/s2
1886 real(r8) :: bvf_nu0c = 1.0_r8 ! m2/s
1887#endif
1888!
1889!-----------------------------------------------------------------------
1890! Tangent linear and adjoint model parameters.
1891!-----------------------------------------------------------------------
1892!
1893! Tangent linear and adjoint model control switches.
1894!
1895 logical :: tlmodel = .false.
1896 logical :: admodel = .false.
1897!
1898 CONTAINS
1899!
1901!
1902!=======================================================================
1903! !
1904! This routine allocates structure and several variables in module !
1905! that depend on the number of nested grids. !
1906! !
1907!=======================================================================
1908!
1909 USE mod_param
1910!
1911! Local variable declarations.
1912!
1913 integer :: ng
1914
1915 real(r8), parameter :: inival = 0.0_r8
1916!
1917!-----------------------------------------------------------------------
1918! Allocate and initialize variables in module structure.
1919!-----------------------------------------------------------------------
1920!
1921 IF (.not.allocated(scalars)) THEN
1922 allocate ( scalars(ngrids) )
1923
1924 DO ng=1,ngrids
1925
1926#ifdef SOLVE3D
1927 allocate ( scalars(ng) % Fstate(9+2*mt) )
1928 dmem(ng)=dmem(ng)+real(9+2*mt,r8)
1929 scalars(ng) % Fstate = .false.
1930
1931 allocate ( scalars(ng) % Lstate(8+2*mt) )
1932 dmem(ng)=dmem(ng)+real(9+2*mt,r8)
1933 scalars(ng) % Lstate = .false.
1934#else
1935 allocate ( scalars(ng) % Fstate(5) )
1936 dmem(ng)=dmem(ng)+5.0_r8
1937 scalars(ng) % Fstate = .false.
1938
1939 allocate ( scalars(ng) % Lstate(3) )
1940 dmem(ng)=dmem(ng)+3.0_r8
1941 scalars(ng) % Lstate = .false.
1942#endif
1943
1944#if defined READ_WATER && defined MASKING && defined DISTRIBUTE
1945 allocate ( scalars(ng) % IJwater((lm(ng)+2)*(mm(ng)+2),4) )
1946 dmem(ng)=dmem(ng)+4.0_r8*real((lm(ng)+2)*(mm(ng)+2),r8)
1947 scalars(ng) % IJwater = 0
1948#endif
1949
1950 allocate ( scalars(ng) % Cs_r(n(ng)) )
1951 dmem(ng)=dmem(ng)+real(n(ng),r8)
1952 scalars(ng) % Cs_r = inival
1953
1954 allocate ( scalars(ng) % Cs_w(0:n(ng)) )
1955 dmem(ng)=dmem(ng)+real(n(ng)+1,r8)
1956 scalars(ng) % Cs_w = inival
1957
1958 allocate ( scalars(ng) % sc_r(n(ng)) )
1959 dmem(ng)=dmem(ng)+real(n(ng),r8)
1960 scalars(ng) % sc_r = inival
1961
1962 allocate ( scalars(ng) % sc_w(0:n(ng)) )
1963 dmem(ng)=dmem(ng)+real(n(ng)+1,r8)
1964 scalars(ng) % sc_w = inival
1965
1966 END DO
1967 END IF
1968!
1969! Allocate variables that require special treatment in shared-memory.
1970! These variables are private for each thread to avoid collisions.
1971!
1972!$OMP PARALLEL
1973 IF (.not.allocated(predictor_2d_step)) THEN
1974 allocate ( predictor_2d_step(ngrids) )
1975 dmem(1)=dmem(1)+real(ngrids,r8)
1976 END IF
1977
1978 IF (.not.allocated(indx1)) THEN
1979 allocate ( indx1(ngrids) )
1980 dmem(1)=dmem(1)+real(ngrids,r8)
1981 END IF
1982 IF (.not.allocated(iic)) THEN
1983 allocate ( iic(ngrids) )
1984 dmem(1)=dmem(1)+real(ngrids,r8)
1985 END IF
1986 IF (.not.allocated(iif)) THEN
1987 allocate ( iif(ngrids) )
1988 dmem(1)=dmem(1)+real(ngrids,r8)
1989 END IF
1990 IF (.not.allocated(next_kstp)) THEN
1991 allocate ( next_kstp(ngrids) )
1992 dmem(1)=dmem(1)+real(ngrids,r8)
1993 END IF
1994
1995 IF (.not.allocated(frcrec)) THEN
1996 allocate ( frcrec(ngrids) )
1997 dmem(1)=dmem(1)+real(ngrids,r8)
1998 END IF
1999 IF (.not.allocated(sorec)) THEN
2000 allocate ( sorec(ngrids) )
2001 dmem(1)=dmem(1)+real(ngrids,r8)
2002 END IF
2003!$OMP END PARALLEL
2004
2005#ifdef JEDI
2006 IF (.not.allocated(jic)) THEN
2007 allocate ( jic(ngrids) )
2008 jic=0
2009 dmem(1)=dmem(1)+real(ngrids,r8)
2010 END IF
2011#endif
2012!
2013!-----------------------------------------------------------------------
2014! Allocate variables.
2015!-----------------------------------------------------------------------
2016!
2017#if defined FOUR_DVAR || defined VERIFICATION
2018 mstatevar=6+mt
2019# if defined GLS_MIXING || defined MY25_MIXING
2021# endif
2022# ifdef WEC
2024# if defined SOLVE3D
2026# endif
2027# endif
2028# ifdef ADJUST_WSTRESS
2030# endif
2031# ifdef ADJUST_STFLUX
2033# endif
2034!
2035#endif
2036
2037#ifdef T_PASSIVE
2038 IF (.not.associated(inert)) THEN
2039 allocate ( inert(npt) )
2040 dmem(1)=dmem(1)+real(npt,r8)
2041 END IF
2042#endif
2043 IF (.not.allocated(perfectrst)) THEN
2044 allocate ( perfectrst(ngrids) )
2045 dmem(1)=dmem(1)+real(ngrids,r8)
2046 END IF
2047
2048 IF (.not.allocated(ndtfast)) THEN
2049 allocate ( ndtfast(ngrids) )
2050 dmem(1)=dmem(1)+real(ngrids,r8)
2051 END IF
2052 IF (.not.allocated(nfast)) THEN
2053 allocate ( nfast(ngrids) )
2054 dmem(1)=dmem(1)+real(ngrids,r8)
2055 END IF
2056
2057 IF (.not.allocated(dt)) THEN
2058 allocate ( dt(ngrids) )
2059 dmem(1)=dmem(1)+real(ngrids,r8)
2060 END IF
2061 IF (.not.allocated(dtfast)) THEN
2062 allocate ( dtfast(ngrids) )
2063 dmem(1)=dmem(1)+real(ngrids,r8)
2064 END IF
2065 IF (.not.allocated(timeend)) THEN
2066 allocate ( timeend(ngrids) )
2067 dmem(1)=dmem(1)+real(ngrids,r8)
2068 END IF
2069 IF (.not.allocated(avgtime)) THEN
2070 allocate ( avgtime(ngrids) )
2071 dmem(1)=dmem(1)+real(ngrids,r8)
2072 END IF
2073 IF (.not.allocated(diatime)) THEN
2074 allocate ( diatime(ngrids) )
2075 dmem(1)=dmem(1)+real(ngrids,r8)
2076 END IF
2077 IF (.not.allocated(imptime)) THEN
2078 allocate ( imptime(ngrids) )
2079 dmem(1)=dmem(1)+real(ngrids,r8)
2080 END IF
2081 IF (.not.allocated(initime)) THEN
2082 allocate ( initime(ngrids) )
2083 dmem(1)=dmem(1)+real(ngrids,r8)
2084 END IF
2085 IF (.not.allocated(initimes)) THEN
2086 allocate ( initimes(ngrids) )
2087 dmem(1)=dmem(1)+real(ngrids,r8)
2088 END IF
2089 IF (.not.allocated(obstime)) THEN
2090 allocate ( obstime(ngrids) )
2091 dmem(1)=dmem(1)+real(ngrids,r8)
2092 END IF
2093 IF (.not.allocated(frctime)) THEN
2094 allocate ( frctime(ngrids) )
2095 dmem(1)=dmem(1)+real(ngrids,r8)
2096 END IF
2097
2098 IF (.not.allocated(ntimes)) THEN
2099 allocate ( ntimes(ngrids) )
2100 dmem(1)=dmem(1)+real(ngrids,r8)
2101 END IF
2102 IF (.not.allocated(first_time)) THEN
2103 allocate ( first_time(ngrids) )
2104 dmem(1)=dmem(1)+real(ngrids,r8)
2105 END IF
2106
2107 IF (.not.allocated(ntfirst)) THEN
2108 allocate ( ntfirst(ngrids) )
2109 dmem(1)=dmem(1)+real(ngrids,r8)
2110 END IF
2111 IF (.not.allocated(ntstart)) THEN
2112 allocate ( ntstart(ngrids) )
2113 dmem(1)=dmem(1)+real(ngrids,r8)
2114 END IF
2115 IF (.not.allocated(ntend)) THEN
2116 allocate ( ntend(ngrids) )
2117 dmem(1)=dmem(1)+real(ngrids,r8)
2118 END IF
2119
2120!$OMP PARALLEL
2121 IF (.not.allocated(synchro_flag)) THEN
2122 allocate ( synchro_flag(ngrids) )
2123 dmem(1)=dmem(1)+real(ngrids,r8)
2124 END IF
2125 IF (.not.allocated(step_counter)) THEN
2126 allocate ( step_counter(ngrids) )
2127 dmem(1)=dmem(1)+real(ngrids,r8)
2128 END IF
2129 IF (.not.allocated(tdays)) THEN
2130 allocate ( tdays(ngrids) )
2131 tdays=0.0_dp
2132 dmem(1)=dmem(1)+real(ngrids,r8)
2133 END IF
2134 IF (.not.allocated(time)) THEN
2135 allocate ( time(ngrids) )
2136 time=0.0_dp
2137 dmem(1)=dmem(1)+real(ngrids,r8)
2138 END IF
2139 IF (.not.allocated(time_code)) THEN
2140 allocate ( time_code(ngrids) )
2141 dmem(1)=dmem(1)+real(ngrids,r8)
2142 END IF
2143!$OMP END PARALLEL
2144
2145#ifdef JEDI
2146 IF (.not.allocated(time4jedi)) THEN
2147 allocate ( time4jedi(ngrids) )
2148 time4jedi=0.0_dp
2149 dmem(1)=dmem(1)+real(ngrids,r8)
2150 END IF
2151#endif
2152
2153 IF (.not.allocated(nrecfrc)) THEN
2154 allocate ( nrecfrc(ngrids) )
2155 dmem(1)=dmem(1)+real(ngrids,r8)
2156 END IF
2157
2158 IF (.not.allocated(setgridconfig)) THEN
2159 allocate ( setgridconfig(ngrids) )
2160 dmem(1)=dmem(1)+real(ngrids,r8)
2161 END IF
2162
2163 IF (.not.allocated(processinputdata)) THEN
2164 allocate ( processinputdata(ngrids) )
2165 dmem(1)=dmem(1)+real(ngrids,r8)
2166 END IF
2167
2168 IF (.not.allocated(nudgingcoeff)) THEN
2169 allocate ( nudgingcoeff(ngrids) )
2170 dmem(1)=dmem(1)+real(ngrids,r8)
2171 END IF
2172
2173 IF (.not.allocated(obcdata)) THEN
2174 allocate ( obcdata(ngrids) )
2175 dmem(1)=dmem(1)+real(ngrids,r8)
2176 END IF
2177
2178 IF (.not.allocated(lbiology)) THEN
2179 allocate ( lbiology(ngrids) )
2180 dmem(1)=dmem(1)+real(ngrids,r8)
2181 END IF
2182 IF (.not.allocated(lfloats)) THEN
2183 allocate ( lfloats(ngrids) )
2184 dmem(1)=dmem(1)+real(ngrids,r8)
2185 END IF
2186 IF (.not.allocated(lsediment)) THEN
2187 allocate ( lsediment(ngrids) )
2188 dmem(1)=dmem(1)+real(ngrids,r8)
2189 END IF
2190 IF (.not.allocated(lstations)) THEN
2191 allocate ( lstations(ngrids) )
2192 dmem(1)=dmem(1)+real(ngrids,r8)
2193 END IF
2194
2195 IF (.not.allocated(compositegrid)) THEN
2196 allocate ( compositegrid(4,ngrids) )
2197 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
2198 END IF
2199 IF (.not.allocated(refinedgrid)) THEN
2200 allocate ( refinedgrid(ngrids) )
2201 dmem(1)=dmem(1)+real(ngrids,r8)
2202 END IF
2203 IF (.not.allocated(refinescale)) THEN
2204 allocate ( refinescale(ngrids) )
2205 dmem(1)=dmem(1)+real(ngrids,r8)
2206 END IF
2207 IF (.not.allocated(getdonordata)) THEN
2208 allocate ( getdonordata(ngrids) )
2209 dmem(1)=dmem(1)+real(ngrids,r8)
2210 END IF
2211
2212 IF (.not.allocated(ewperiodic)) THEN
2213 allocate ( ewperiodic(ngrids) )
2214 dmem(1)=dmem(1)+real(ngrids,r8)
2215 END IF
2216 IF (.not.allocated(nsperiodic)) THEN
2217 allocate ( nsperiodic(ngrids) )
2218 dmem(1)=dmem(1)+real(ngrids,r8)
2219 END IF
2220
2221 IF (.not.allocated(volcons)) THEN
2222 allocate ( volcons(4,ngrids) )
2223 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
2224 END IF
2225#if defined ADJOINT || defined TANGENT || defined TL_IOMS
2226 IF (.not.allocated(ad_volcons)) THEN
2227 allocate ( ad_volcons(4,ngrids) )
2228 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
2229 END IF
2230 IF (.not.allocated(tl_volcons)) THEN
2231 allocate ( tl_volcons(4,ngrids) )
2232 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
2233 END IF
2234#endif
2235
2236 IF (.not.allocated(lsponge)) THEN
2237 allocate ( lsponge(ngrids) )
2238 dmem(1)=dmem(1)+real(ngrids,r8)
2239 END IF
2240 IF (.not.allocated(luvsponge)) THEN
2241 allocate ( luvsponge(ngrids) )
2242 dmem(1)=dmem(1)+real(ngrids,r8)
2243 END IF
2244 IF (.not.allocated(ltracersponge)) THEN
2245 allocate ( ltracersponge(mt,ngrids) )
2246 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2247 END IF
2248
2249 IF (.not.allocated(clm_file)) THEN
2250 allocate ( clm_file(ngrids) )
2251 dmem(1)=dmem(1)+real(ngrids,r8)
2252 END IF
2253 IF (.not.allocated(lclimatology)) THEN
2254 allocate ( lclimatology(ngrids) )
2255 dmem(1)=dmem(1)+real(ngrids,r8)
2256 END IF
2257 IF (.not.allocated(lsshclm)) THEN
2258 allocate ( lsshclm(ngrids) )
2259 dmem(1)=dmem(1)+real(ngrids,r8)
2260 END IF
2261 IF (.not.allocated(lm2clm)) THEN
2262 allocate ( lm2clm(ngrids) )
2263 dmem(1)=dmem(1)+real(ngrids,r8)
2264 END IF
2265 IF (.not.allocated(lm3clm)) THEN
2266 allocate ( lm3clm(ngrids) )
2267 dmem(1)=dmem(1)+real(ngrids,r8)
2268 END IF
2269 IF (.not.allocated(ltracerclm)) THEN
2270 allocate ( ltracerclm(mt,ngrids) )
2271 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2272 END IF
2273
2274 IF (.not.allocated(lnudging)) THEN
2275 allocate ( lnudging(ngrids) )
2276 dmem(1)=dmem(1)+real(ngrids,r8)
2277 END IF
2278 IF (.not.allocated(lnudgem2clm)) THEN
2279 allocate ( lnudgem2clm(ngrids) )
2280 dmem(1)=dmem(1)+real(ngrids,r8)
2281 END IF
2282 IF (.not.allocated(lnudgem3clm)) THEN
2283 allocate ( lnudgem3clm(ngrids) )
2284 dmem(1)=dmem(1)+real(ngrids,r8)
2285 END IF
2286 IF (.not.allocated(lnudgetclm)) THEN
2287 allocate ( lnudgetclm(mt,ngrids) )
2288 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2289 END IF
2290
2291 IF (.not.allocated(luvsrc)) THEN
2292 allocate ( luvsrc(ngrids) )
2293 dmem(1)=dmem(1)+real(ngrids,r8)
2294 END IF
2295 IF (.not.allocated(lwsrc)) THEN
2296 allocate ( lwsrc(ngrids) )
2297 dmem(1)=dmem(1)+real(ngrids,r8)
2298 END IF
2299 IF (.not.allocated(ltracersrc)) THEN
2300 allocate ( ltracersrc(mt,ngrids) )
2301 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2302 END IF
2303
2304 IF (.not.allocated(maxspeed)) THEN
2305 allocate ( maxspeed(ngrids) )
2306 dmem(1)=dmem(1)+real(ngrids,r8)
2307 END IF
2308 IF (.not.allocated(maxrho)) THEN
2309 allocate ( maxrho(ngrids) )
2310 dmem(1)=dmem(1)+real(ngrids,r8)
2311 END IF
2312
2313 IF (.not.allocated(levsfrc)) THEN
2314 allocate ( levsfrc(ngrids) )
2315 dmem(1)=dmem(1)+real(ngrids,r8)
2316 END IF
2317 IF (.not.allocated(levbfrc)) THEN
2318 allocate ( levbfrc(ngrids) )
2319 dmem(1)=dmem(1)+real(ngrids,r8)
2320 END IF
2321
2322 IF (.not.allocated(vtransform)) THEN
2323 allocate ( vtransform(ngrids) )
2324 dmem(1)=dmem(1)+real(ngrids,r8)
2325 END IF
2326 IF (.not.allocated(vstretching)) THEN
2327 allocate ( vstretching(ngrids) )
2328 dmem(1)=dmem(1)+real(ngrids,r8)
2329 END IF
2330
2331 IF (.not.allocated(tcline)) THEN
2332 allocate ( tcline(ngrids) )
2333 dmem(1)=dmem(1)+real(ngrids,r8)
2334 END IF
2335 IF (.not.allocated(hc)) THEN
2336 allocate ( hc(ngrids) )
2337 dmem(1)=dmem(1)+real(ngrids,r8)
2338 END IF
2339 IF (.not.allocated(theta_s)) THEN
2340 allocate ( theta_s(ngrids) )
2341 dmem(1)=dmem(1)+real(ngrids,r8)
2342 END IF
2343 IF (.not.allocated(theta_b)) THEN
2344 allocate ( theta_b(ngrids) )
2345 dmem(1)=dmem(1)+real(ngrids,r8)
2346 END IF
2347
2348 IF (.not.allocated(hmin)) THEN
2349 allocate ( hmin(ngrids) )
2350 dmem(1)=dmem(1)+real(ngrids,r8)
2351 END IF
2352 IF (.not.allocated(hmax)) THEN
2353 allocate ( hmax(ngrids) )
2354 dmem(1)=dmem(1)+real(ngrids,r8)
2355 END IF
2356
2357 IF (.not.allocated(xl)) THEN
2358 allocate ( xl(ngrids) )
2359 dmem(1)=dmem(1)+real(ngrids,r8)
2360 END IF
2361 IF (.not.allocated(el)) THEN
2362 allocate ( el(ngrids) )
2363 dmem(1)=dmem(1)+real(ngrids,r8)
2364 END IF
2365
2366 IF (.not.allocated(lonmin)) THEN
2367 allocate ( lonmin(ngrids) )
2368 dmem(1)=dmem(1)+real(ngrids,r8)
2369 END IF
2370 IF (.not.allocated(lonmax)) THEN
2371 allocate ( lonmax(ngrids) )
2372 dmem(1)=dmem(1)+real(ngrids,r8)
2373 END IF
2374 IF (.not.allocated(latmin)) THEN
2375 allocate ( latmin(ngrids) )
2376 dmem(1)=dmem(1)+real(ngrids,r8)
2377 END IF
2378 IF (.not.allocated(latmax)) THEN
2379 allocate ( latmax(ngrids) )
2380 dmem(1)=dmem(1)+real(ngrids,r8)
2381 END IF
2382
2383 IF (.not.allocated(idigits)) THEN
2384 allocate ( idigits(ngrids) )
2385 dmem(1)=dmem(1)+real(ngrids,r8)
2386 END IF
2387 IF (.not.allocated(jdigits)) THEN
2388 allocate ( jdigits(ngrids) )
2389 dmem(1)=dmem(1)+real(ngrids,r8)
2390 END IF
2391#ifdef SOLVE3D
2392 IF (.not.allocated(kdigits)) THEN
2393 allocate ( kdigits(ngrids) )
2394 dmem(1)=dmem(1)+real(ngrids,r8)
2395 END IF
2396#endif
2397 IF (.not.allocated(totvolume)) THEN
2398 allocate ( totvolume(ngrids) )
2399 dmem(1)=dmem(1)+real(ngrids,r8)
2400 END IF
2401 IF (.not.allocated(minvolume)) THEN
2402 allocate ( minvolume(ngrids) )
2403 dmem(1)=dmem(1)+real(ngrids,r8)
2404 END IF
2405 IF (.not.allocated(maxvolume)) THEN
2406 allocate ( maxvolume(ngrids) )
2407 dmem(1)=dmem(1)+real(ngrids,r8)
2408 END IF
2409
2410 IF (.not.allocated(dxmin)) THEN
2411 allocate ( dxmin(ngrids) )
2412 dmem(1)=dmem(1)+real(ngrids,r8)
2413 END IF
2414 IF (.not.allocated(dxmax)) THEN
2415 allocate ( dxmax(ngrids) )
2416 dmem(1)=dmem(1)+real(ngrids,r8)
2417 END IF
2418 IF (.not.allocated(dymin)) THEN
2419 allocate ( dymin(ngrids) )
2420 dmem(1)=dmem(1)+real(ngrids,r8)
2421 END IF
2422 IF (.not.allocated(dymax)) THEN
2423 allocate ( dymax(ngrids) )
2424 dmem(1)=dmem(1)+real(ngrids,r8)
2425 END IF
2426
2427#ifdef MASKING
2428 IF (.not.allocated(dxminw)) THEN
2429 allocate ( dxminw(ngrids) )
2430 dmem(1)=dmem(1)+real(ngrids,r8)
2431 END IF
2432 IF (.not.allocated(dxmaxw)) THEN
2433 allocate ( dxmaxw(ngrids) )
2434 dmem(1)=dmem(1)+real(ngrids,r8)
2435 END IF
2436 IF (.not.allocated(dyminw)) THEN
2437 allocate ( dyminw(ngrids) )
2438 dmem(1)=dmem(1)+real(ngrids,r8)
2439 END IF
2440 IF (.not.allocated(dymaxw)) THEN
2441 allocate ( dymaxw(ngrids) )
2442 dmem(1)=dmem(1)+real(ngrids,r8)
2443 END IF
2444#endif
2445
2446
2447#ifdef SOLVE3D
2448 IF (.not.allocated(dzmin)) THEN
2449 allocate ( dzmin(ngrids) )
2450 dmem(1)=dmem(1)+real(ngrids,r8)
2451 END IF
2452 IF (.not.allocated(dzmax)) THEN
2453 allocate ( dzmax(ngrids) )
2454 dmem(1)=dmem(1)+real(ngrids,r8)
2455 END IF
2456# ifdef MASKING
2457 IF (.not.allocated(dzminw)) THEN
2458 allocate ( dzminw(ngrids) )
2459 dmem(1)=dmem(1)+real(ngrids,r8)
2460 END IF
2461 IF (.not.allocated(dzmaxw)) THEN
2462 allocate ( dzmaxw(ngrids) )
2463 dmem(1)=dmem(1)+real(ngrids,r8)
2464 END IF
2465# endif
2466#endif
2467
2468 IF (.not.allocated(grdmax)) THEN
2469 allocate ( grdmax(ngrids) )
2470 dmem(1)=dmem(1)+real(ngrids,r8)
2471 END IF
2472
2473#ifdef DIFF_3DCOEF
2474 IF (.not.allocated(diffmin)) THEN
2475 allocate ( diffmin(ngrids) )
2476 dmem(1)=dmem(1)+real(ngrids,r8)
2477 END IF
2478 IF (.not.allocated(diffmax)) THEN
2479 allocate ( diffmax(ngrids) )
2480 dmem(1)=dmem(1)+real(ngrids,r8)
2481 END IF
2482#endif
2483
2484 IF (.not.allocated(cg_min)) THEN
2485 allocate ( cg_min(ngrids) )
2486 dmem(1)=dmem(1)+real(ngrids,r8)
2487 END IF
2488 IF (.not.allocated(cg_max)) THEN
2489 allocate ( cg_max(ngrids) )
2490 dmem(1)=dmem(1)+real(ngrids,r8)
2491 END IF
2492 IF (.not.allocated(cg_cor)) THEN
2493 allocate ( cg_cor(ngrids) )
2494 dmem(1)=dmem(1)+real(ngrids,r8)
2495 END IF
2496
2497#ifdef VISC_3DCOEF
2498 IF (.not.allocated(viscmin)) THEN
2499 allocate ( viscmin(ngrids) )
2500 dmem(1)=dmem(1)+real(ngrids,r8)
2501 END IF
2502 IF (.not.allocated(viscmax)) THEN
2503 allocate ( viscmax(ngrids) )
2504 dmem(1)=dmem(1)+real(ngrids,r8)
2505 END IF
2506#endif
2507
2508 IF (.not.allocated(r0)) THEN
2509 allocate ( r0(ngrids) )
2510 dmem(1)=dmem(1)+real(ngrids,r8)
2511 END IF
2512 IF (.not.allocated(tcoef)) THEN
2513 allocate ( tcoef(ngrids) )
2514 dmem(1)=dmem(1)+real(ngrids,r8)
2515 END IF
2516 IF (.not.allocated(scoef)) THEN
2517 allocate ( scoef(ngrids) )
2518 dmem(1)=dmem(1)+real(ngrids,r8)
2519 END IF
2520
2521 IF (.not.allocated(t0)) THEN
2522 allocate ( t0(ngrids) )
2523 dmem(1)=dmem(1)+real(ngrids,r8)
2524 END IF
2525 IF (.not.allocated(s0)) THEN
2526 allocate ( s0(ngrids) )
2527 dmem(1)=dmem(1)+real(ngrids,r8)
2528 END IF
2529
2530 IF (.not.allocated(gamma2)) THEN
2531 allocate ( gamma2(ngrids) )
2532 dmem(1)=dmem(1)+real(ngrids,r8)
2533 END IF
2534
2535 IF (.not.allocated(lmd_jwt)) THEN
2536 allocate ( lmd_jwt(ngrids) )
2537 dmem(1)=dmem(1)+real(ngrids,r8)
2538 END IF
2539
2540 IF (.not.allocated(rx0)) THEN
2541 allocate ( rx0(ngrids) )
2542 dmem(1)=dmem(1)+real(ngrids,r8)
2543 END IF
2544 IF (.not.allocated(rx1)) THEN
2545 allocate ( rx1(ngrids) )
2546 dmem(1)=dmem(1)+real(ngrids,r8)
2547 END IF
2548
2549 IF (.not.allocated(rdrg)) THEN
2550 allocate ( rdrg(ngrids) )
2551 dmem(1)=dmem(1)+real(ngrids,r8)
2552 END IF
2553 IF (.not.allocated(rdrg2)) THEN
2554 allocate ( rdrg2(ngrids) )
2555 dmem(1)=dmem(1)+real(ngrids,r8)
2556 END IF
2557
2558 IF (.not.allocated(zos)) THEN
2559 allocate ( zos(ngrids) )
2560 dmem(1)=dmem(1)+real(ngrids,r8)
2561 END IF
2562 IF (.not.allocated(zob)) THEN
2563 allocate ( zob(ngrids) )
2564 dmem(1)=dmem(1)+real(ngrids,r8)
2565 END IF
2566
2567 IF (.not.allocated(dcrit)) THEN
2568 allocate ( dcrit(ngrids) )
2569 dmem(1)=dmem(1)+real(ngrids,r8)
2570 END IF
2571
2572#ifdef PROPAGATOR
2573 IF (.not.allocated(nconv)) THEN
2574 allocate ( nconv(ngrids) )
2575 dmem(1)=dmem(1)+real(ngrids,r8)
2576 END IF
2577#endif
2578
2579 IF (.not.allocated(weight)) THEN
2580 allocate ( weight(2,0:256,ngrids) )
2581 dmem(1)=dmem(1)+514.0_r8*real(ngrids,r8)
2582 END IF
2583
2584 IF (.not.allocated(akk_bak)) THEN
2585 allocate ( akk_bak(ngrids) )
2586 dmem(1)=dmem(1)+real(ngrids,r8)
2587 END IF
2588 IF (.not.allocated(akp_bak)) THEN
2589 allocate ( akp_bak(ngrids) )
2590 dmem(1)=dmem(1)+real(ngrids,r8)
2591 END IF
2592 IF (.not.allocated(akv_bak)) THEN
2593 allocate ( akv_bak(ngrids) )
2594 dmem(1)=dmem(1)+real(ngrids,r8)
2595 END IF
2596 IF (.not.allocated(akv_limit)) THEN
2597 allocate ( akv_limit(ngrids) )
2598 dmem(1)=dmem(1)+real(ngrids,r8)
2599 END IF
2600
2601 IF (.not.allocated(ad_visc2)) THEN
2602 allocate ( ad_visc2(ngrids) )
2603 dmem(1)=dmem(1)+real(ngrids,r8)
2604 END IF
2605 IF (.not.allocated(nl_visc2)) THEN
2606 allocate ( nl_visc2(ngrids) )
2607 dmem(1)=dmem(1)+real(ngrids,r8)
2608 END IF
2609 IF (.not.allocated(tl_visc2)) THEN
2610 allocate ( tl_visc2(ngrids) )
2611 dmem(1)=dmem(1)+real(ngrids,r8)
2612 END IF
2613 IF (.not.allocated(visc2)) THEN
2614 allocate ( visc2(ngrids) )
2615 dmem(1)=dmem(1)+real(ngrids,r8)
2616 END IF
2617
2618 IF (.not.allocated(ad_visc4)) THEN
2619 allocate ( ad_visc4(ngrids) )
2620 dmem(1)=dmem(1)+real(ngrids,r8)
2621 END IF
2622 IF (.not.allocated(nl_visc4)) THEN
2623 allocate ( nl_visc4(ngrids) )
2624 dmem(1)=dmem(1)+real(ngrids,r8)
2625 END IF
2626 IF (.not.allocated(tl_visc4)) THEN
2627 allocate ( tl_visc4(ngrids) )
2628 dmem(1)=dmem(1)+real(ngrids,r8)
2629 END IF
2630 IF (.not.allocated(visc4)) THEN
2631 allocate ( visc4(ngrids) )
2632 dmem(1)=dmem(1)+real(ngrids,r8)
2633 END IF
2634
2635 IF (.not.allocated(tkenu2)) THEN
2636 allocate ( tkenu2(ngrids) )
2637 dmem(1)=dmem(1)+real(ngrids,r8)
2638 END IF
2639 IF (.not.allocated(tkenu4)) THEN
2640 allocate ( tkenu4(ngrids) )
2641 dmem(1)=dmem(1)+real(ngrids,r8)
2642 END IF
2643
2644 IF (.not.allocated(akt_bak)) THEN
2645 allocate ( akt_bak(mt,ngrids) )
2646 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2647 END IF
2648 IF (.not.allocated(akt_limit)) THEN
2649 allocate ( akt_limit(nat,ngrids) )
2650 dmem(1)=dmem(1)+real(nat*ngrids,r8)
2651 END IF
2652 IF (.not.allocated(kdiff)) THEN
2653 allocate ( kdiff(mt,ngrids) )
2654 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2655 END IF
2656
2657 IF (.not.allocated(ad_tnu2)) THEN
2658 allocate ( ad_tnu2(mt,ngrids) )
2659 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2660 END IF
2661 IF (.not.allocated(nl_tnu2)) THEN
2662 allocate ( nl_tnu2(mt,ngrids) )
2663 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2664 END IF
2665 IF (.not.allocated(tl_tnu2)) THEN
2666 allocate ( tl_tnu2(mt,ngrids) )
2667 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2668 END IF
2669 IF (.not.allocated(tnu2)) THEN
2670 allocate ( tnu2(mt,ngrids) )
2671 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2672 END IF
2673
2674 IF (.not.allocated(ad_tnu4)) THEN
2675 allocate ( ad_tnu4(mt,ngrids) )
2676 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2677 END IF
2678 IF (.not.allocated(nl_tnu4)) THEN
2679 allocate ( nl_tnu4(mt,ngrids) )
2680 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2681 END IF
2682 IF (.not.allocated(tl_tnu4)) THEN
2683 allocate ( tl_tnu4(mt,ngrids) )
2684 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2685 END IF
2686 IF (.not.allocated(tnu4)) THEN
2687 allocate ( tnu4(mt,ngrids) )
2688 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2689 END IF
2690
2691 IF (.not.allocated(tl_m2diff)) THEN
2692 allocate ( tl_m2diff(ngrids) )
2693 dmem(1)=dmem(1)+real(ngrids,r8)
2694 END IF
2695 IF (.not.allocated(tl_m3diff)) THEN
2696 allocate ( tl_m3diff(ngrids) )
2697 dmem(1)=dmem(1)+real(ngrids,r8)
2698 END IF
2699 IF (.not.allocated(tl_tdiff)) THEN
2700 allocate ( tl_tdiff(mt,ngrids) )
2701 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2702 END IF
2703
2704 IF (.not.allocated(ad_akv_fac)) THEN
2705 allocate ( ad_akv_fac(ngrids) )
2706 dmem(1)=dmem(1)+real(ngrids,r8)
2707 END IF
2708 IF (.not.allocated(tl_akv_fac)) THEN
2709 allocate ( tl_akv_fac(ngrids) )
2710 dmem(1)=dmem(1)+real(ngrids,r8)
2711 END IF
2712
2713 IF (.not.allocated(ad_akt_fac)) THEN
2714 allocate ( ad_akt_fac(mt,ngrids) )
2715 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2716 END IF
2717 IF (.not.allocated(tl_akt_fac)) THEN
2718 allocate ( tl_akt_fac(mt,ngrids) )
2719 dmem(1)=dmem(1)+real(mt*ngrids,r8)
2720 END IF
2721
2722 IF (.not.allocated(ldefadj)) THEN
2723 allocate ( ldefadj(ngrids) )
2724 dmem(1)=dmem(1)+real(ngrids,r8)
2725 END IF
2726 IF (.not.allocated(ldefavg)) THEN
2727 allocate ( ldefavg(ngrids) )
2728 dmem(1)=dmem(1)+real(ngrids,r8)
2729 END IF
2730 IF (.not.allocated(ldefdai)) THEN
2731 allocate ( ldefdai(ngrids) )
2732 dmem(1)=dmem(1)+real(ngrids,r8)
2733 END IF
2734 IF (.not.allocated(ldefdia)) THEN
2735 allocate ( ldefdia(ngrids) )
2736 dmem(1)=dmem(1)+real(ngrids,r8)
2737 END IF
2738 IF (.not.allocated(ldeferr)) THEN
2739 allocate ( ldeferr(ngrids) )
2740 dmem(1)=dmem(1)+real(ngrids,r8)
2741 END IF
2742 IF (.not.allocated(ldefflt)) THEN
2743 allocate ( ldefflt(ngrids) )
2744 dmem(1)=dmem(1)+real(ngrids,r8)
2745 END IF
2746 IF (.not.allocated(ldefhis)) THEN
2747 allocate ( ldefhis(ngrids) )
2748 dmem(1)=dmem(1)+real(ngrids,r8)
2749 END IF
2750 IF (.not.allocated(ldefhss)) THEN
2751 allocate ( ldefhss(ngrids) )
2752 dmem(1)=dmem(1)+real(ngrids,r8)
2753 END IF
2754 IF (.not.allocated(ldefini)) THEN
2755 allocate ( ldefini(ngrids) )
2756 dmem(1)=dmem(1)+real(ngrids,r8)
2757 END IF
2758 IF (.not.allocated(ldefirp)) THEN
2759 allocate ( ldefirp(ngrids) )
2760 dmem(1)=dmem(1)+real(ngrids,r8)
2761 END IF
2762 IF (.not.allocated(ldefitl)) THEN
2763 allocate ( ldefitl(ngrids) )
2764 dmem(1)=dmem(1)+real(ngrids,r8)
2765 END IF
2766 IF (.not.allocated(ldeflcz)) THEN
2767 allocate ( ldeflcz(ngrids) )
2768 dmem(1)=dmem(1)+real(ngrids,r8)
2769 END IF
2770 IF (.not.allocated(ldeflze)) THEN
2771 allocate ( ldeflze(ngrids) )
2772 dmem(1)=dmem(1)+real(ngrids,r8)
2773 END IF
2774 IF (.not.allocated(ldefmod)) THEN
2775 allocate ( ldefmod(ngrids) )
2776 dmem(1)=dmem(1)+real(ngrids,r8)
2777 END IF
2778 IF (.not.allocated(ldefqck)) THEN
2779 allocate ( ldefqck(ngrids) )
2780 dmem(1)=dmem(1)+real(ngrids,r8)
2781 END IF
2782 IF (.not.allocated(ldefrst)) THEN
2783 allocate ( ldefrst(ngrids) )
2784 dmem(1)=dmem(1)+real(ngrids,r8)
2785 END IF
2786 IF (.not.allocated(ldefxtr)) THEN
2787 allocate ( ldefxtr(ngrids) )
2788 dmem(1)=dmem(1)+real(ngrids,r8)
2789 END IF
2790#ifdef SP4DVAR
2791 IF (.not.allocated(ldefsca)) THEN
2792 allocate ( ldefsca(ngrids) )
2793 dmem(1)=dmem(1)+real(ngrids,r8)
2794 END IF
2795 IF (.not.allocated(ldefsct)) THEN
2796 allocate ( ldefsct(ngrids) )
2797 dmem(1)=dmem(1)+real(ngrids,r8)
2798 END IF
2799 IF (.not.allocated(ldefspa)) THEN
2800 allocate ( ldefspa(ngrids) )
2801 dmem(1)=dmem(1)+real(ngrids,r8)
2802 END IF
2803 IF (.not.allocated(ldefspt)) THEN
2804 allocate ( ldefspt(ngrids) )
2805 dmem(1)=dmem(1)+real(ngrids,r8)
2806 END IF
2807#endif
2808 IF (.not.allocated(ldefsta)) THEN
2809 allocate ( ldefsta(ngrids) )
2810 dmem(1)=dmem(1)+real(ngrids,r8)
2811 END IF
2812 IF (.not.allocated(ldeftide)) THEN
2813 allocate ( ldeftide(ngrids) )
2814 dmem(1)=dmem(1)+real(ngrids,r8)
2815 END IF
2816 IF (.not.allocated(ldeftlm)) THEN
2817 allocate ( ldeftlm(ngrids) )
2818 dmem(1)=dmem(1)+real(ngrids,r8)
2819 END IF
2820 IF (.not.allocated(ldeftlf)) THEN
2821 allocate ( ldeftlf(ngrids) )
2822 dmem(1)=dmem(1)+real(ngrids,r8)
2823 END IF
2824
2825 IF (.not.allocated(lreadadm)) THEN
2826 allocate ( lreadadm(ngrids) )
2827 dmem(1)=dmem(1)+real(ngrids,r8)
2828 END IF
2829 IF (.not.allocated(lreadblk)) THEN
2830 allocate ( lreadblk(ngrids) )
2831 dmem(1)=dmem(1)+real(ngrids,r8)
2832 END IF
2833 IF (.not.allocated(lreadfrc)) THEN
2834 allocate ( lreadfrc(ngrids) )
2835 dmem(1)=dmem(1)+real(ngrids,r8)
2836 END IF
2837 IF (.not.allocated(lreadfwd)) THEN
2838 allocate ( lreadfwd(ngrids) )
2839 dmem(1)=dmem(1)+real(ngrids,r8)
2840 END IF
2841 IF (.not.allocated(lreadqck)) THEN
2842 allocate ( lreadqck(ngrids) )
2843 dmem(1)=dmem(1)+real(ngrids,r8)
2844 END IF
2845 IF (.not.allocated(lreadstd)) THEN
2846 allocate ( lreadstd(ngrids) )
2847 dmem(1)=dmem(1)+real(ngrids,r8)
2848 END IF
2849 IF (.not.allocated(lreadtlm)) THEN
2850 allocate ( lreadtlm(ngrids) )
2851 dmem(1)=dmem(1)+real(ngrids,r8)
2852 END IF
2853
2854 IF (.not.allocated(lwrtadj)) THEN
2855 allocate ( lwrtadj(ngrids) )
2856 dmem(1)=dmem(1)+real(ngrids,r8)
2857 END IF
2858 IF (.not.allocated(lwrtavg)) THEN
2859 allocate ( lwrtavg(ngrids) )
2860 dmem(1)=dmem(1)+real(ngrids,r8)
2861 END IF
2862 IF (.not.allocated(lwrtdia)) THEN
2863 allocate ( lwrtdia(ngrids) )
2864 dmem(1)=dmem(1)+real(ngrids,r8)
2865 END IF
2866 IF (.not.allocated(lwrthis)) THEN
2867 allocate ( lwrthis(ngrids) )
2868 dmem(1)=dmem(1)+real(ngrids,r8)
2869 END IF
2870 IF (.not.allocated(lwrtper)) THEN
2871 allocate ( lwrtper(ngrids) )
2872 dmem(1)=dmem(1)+real(ngrids,r8)
2873 END IF
2874 IF (.not.allocated(lwrtqck)) THEN
2875 allocate ( lwrtqck(ngrids) )
2876 dmem(1)=dmem(1)+real(ngrids,r8)
2877 END IF
2878 IF (.not.allocated(lwrtrst)) THEN
2879 allocate ( lwrtrst(ngrids) )
2880 dmem(1)=dmem(1)+real(ngrids,r8)
2881 END IF
2882 IF (.not.allocated(lwrttlf)) THEN
2883 allocate ( lwrttlf(ngrids) )
2884 dmem(1)=dmem(1)+real(ngrids,r8)
2885 END IF
2886 IF (.not.allocated(lwrttlm)) THEN
2887 allocate ( lwrttlm(ngrids) )
2888 dmem(1)=dmem(1)+real(ngrids,r8)
2889 END IF
2890 IF (.not.allocated(lwrtxtr)) THEN
2891 allocate ( lwrtxtr(ngrids) )
2892 dmem(1)=dmem(1)+real(ngrids,r8)
2893 END IF
2894
2895 IF (.not.allocated(ldefnrm)) THEN
2896 allocate ( ldefnrm(4,ngrids) )
2897 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
2898 END IF
2899 IF (.not.allocated(lwrtnrm)) THEN
2900 allocate ( lwrtnrm(4,ngrids) )
2901 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
2902 END IF
2903
2904#ifdef STD_MODEL
2905 IF (.not.allocated(ldefstd)) THEN
2906 allocate ( ldefstd(ngrids) )
2907 dmem(1)=dmem(1)+real(ngrids,r8)
2908 END IF
2909 IF (.not.allocated(lwrtstd)) THEN
2910 allocate ( lwrtstd(ngrids) )
2911 dmem(1)=dmem(1)+real(ngrids,r8)
2912 END IF
2913#endif
2914
2915#ifdef AD_OUTPUT_STATE
2916 IF (.not.allocated(lwrtstate3d)) THEN
2917 allocate ( lwrtstate3d(ngrids) )
2918 dmem(1)=dmem(1)+real(ngrids,r8)
2919 END IF
2920#endif
2921#if defined STOCHASTIC_OPT && !defined STOCH_OPT_WHITE
2922 IF (.not.allocated(soinitial)) THEN
2923 allocate ( soinitial(ngrids) )
2924 dmem(1)=dmem(1)+real(ngrids,r8)
2925 END IF
2926#endif
2927
2928 IF (.not.allocated(lwrtstate2d)) THEN
2929 allocate ( lwrtstate2d(ngrids) )
2930 dmem(1)=dmem(1)+real(ngrids,r8)
2931 END IF
2932 IF (.not.allocated(lwrttime)) THEN
2933 allocate ( lwrttime(ngrids) )
2934 dmem(1)=dmem(1)+real(ngrids,r8)
2935 END IF
2936 IF (.not.allocated(lwrtcost)) THEN
2937 allocate ( lwrtcost(ngrids) )
2938 dmem(1)=dmem(1)+real(ngrids,r8)
2939 END IF
2940
2941 IF (.not.allocated(ladjusted)) THEN
2942 allocate ( ladjusted(ngrids) )
2943 dmem(1)=dmem(1)+real(ngrids,r8)
2944 END IF
2945
2946 IF (.not.allocated(lprocessobc)) THEN
2947 allocate ( lprocessobc(ngrids) )
2948 dmem(1)=dmem(1)+real(ngrids,r8)
2949 END IF
2950 IF (.not.allocated(lprocesstides)) THEN
2951 allocate ( lprocesstides(ngrids) )
2952 dmem(1)=dmem(1)+real(ngrids,r8)
2953 END IF
2954
2955 IF (.not.allocated(lwrtinfo)) THEN
2956 allocate ( lwrtinfo(ngrids) )
2957 dmem(1)=dmem(1)+real(ngrids,r8)
2958 END IF
2959
2960 IF (.not.allocated(ldefout)) THEN
2961 allocate ( ldefout(ngrids) )
2962 dmem(1)=dmem(1)+real(ngrids,r8)
2963 END IF
2964
2965 IF (.not.allocated(ndefadj)) THEN
2966 allocate ( ndefadj(ngrids) )
2967 dmem(1)=dmem(1)+real(ngrids,r8)
2968 END IF
2969 IF (.not.allocated(ndefavg)) THEN
2970 allocate ( ndefavg(ngrids) )
2971 dmem(1)=dmem(1)+real(ngrids,r8)
2972 END IF
2973 IF (.not.allocated(ndefdia)) THEN
2974 allocate ( ndefdia(ngrids) )
2975 dmem(1)=dmem(1)+real(ngrids,r8)
2976 END IF
2977 IF (.not.allocated(ndefhis)) THEN
2978 allocate ( ndefhis(ngrids) )
2979 dmem(1)=dmem(1)+real(ngrids,r8)
2980 END IF
2981 IF (.not.allocated(ndefqck)) THEN
2982 allocate ( ndefqck(ngrids) )
2983 dmem(1)=dmem(1)+real(ngrids,r8)
2984 END IF
2985 IF (.not.allocated(ndeftlm)) THEN
2986 allocate ( ndeftlm(ngrids) )
2987 dmem(1)=dmem(1)+real(ngrids,r8)
2988 END IF
2989 IF (.not.allocated(ndefxtr)) THEN
2990 allocate ( ndefxtr(ngrids) )
2991 dmem(1)=dmem(1)+real(ngrids,r8)
2992 END IF
2993
2994 IF (.not.allocated(ntsavg)) THEN
2995 allocate ( ntsavg(ngrids) )
2996 dmem(1)=dmem(1)+real(ngrids,r8)
2997 END IF
2998 IF (.not.allocated(ntsdia)) THEN
2999 allocate ( ntsdia(ngrids) )
3000 dmem(1)=dmem(1)+real(ngrids,r8)
3001 END IF
3002
3003 IF (.not.allocated(nadj)) THEN
3004 allocate ( nadj(ngrids) )
3005 dmem(1)=dmem(1)+real(ngrids,r8)
3006 END IF
3007 IF (.not.allocated(navg)) THEN
3008 allocate ( navg(ngrids) )
3009 dmem(1)=dmem(1)+real(ngrids,r8)
3010 END IF
3011 IF (.not.allocated(ndia)) THEN
3012 allocate ( ndia(ngrids) )
3013 dmem(1)=dmem(1)+real(ngrids,r8)
3014 END IF
3015 IF (.not.allocated(nflt)) THEN
3016 allocate ( nflt(ngrids) )
3017 dmem(1)=dmem(1)+real(ngrids,r8)
3018 END IF
3019 IF (.not.allocated(nhis)) THEN
3020 allocate ( nhis(ngrids) )
3021 dmem(1)=dmem(1)+real(ngrids,r8)
3022 END IF
3023 IF (.not.allocated(nqck)) THEN
3024 allocate ( nqck(ngrids) )
3025 dmem(1)=dmem(1)+real(ngrids,r8)
3026 END IF
3027 IF (.not.allocated(nrst)) THEN
3028 allocate ( nrst(ngrids) )
3029 dmem(1)=dmem(1)+real(ngrids,r8)
3030 END IF
3031 IF (.not.allocated(nsta)) THEN
3032 allocate ( nsta(ngrids) )
3033 dmem(1)=dmem(1)+real(ngrids,r8)
3034 END IF
3035 IF (.not.allocated(ntlm)) THEN
3036 allocate ( ntlm(ngrids) )
3037 dmem(1)=dmem(1)+real(ngrids,r8)
3038 END IF
3039 IF (.not.allocated(nxtr)) THEN
3040 allocate ( nxtr(ngrids) )
3041 dmem(1)=dmem(1)+real(ngrids,r8)
3042 END IF
3043#ifdef SP4DVAR
3044 IF (.not.allocated(nsca)) THEN
3045 allocate ( nsca(ngrids) )
3046 dmem(1)=dmem(1)+real(ngrids,r8)
3047 END IF
3048 IF (.not.allocated(nsct)) THEN
3049 allocate ( nsct(ngrids) )
3050 dmem(1)=dmem(1)+real(ngrids,r8)
3051 END IF
3052 IF (.not.allocated(nspa)) THEN
3053 allocate ( nspa(ngrids) )
3054 dmem(1)=dmem(1)+real(ngrids,r8)
3055 END IF
3056 IF (.not.allocated(nspt)) THEN
3057 allocate ( nspt(ngrids) )
3058 dmem(1)=dmem(1)+real(ngrids,r8)
3059 END IF
3060 IF (.not.allocated(crec)) THEN
3061 allocate ( crec(ngrids) )
3062 dmem(1)=dmem(1)+real(ngrids,r8)
3063 END IF
3064#endif
3065
3066 IF (.not.allocated(extractflag)) THEN
3067 allocate ( extractflag(ngrids) )
3068 dmem(1)=dmem(1)+real(ngrids,r8)
3069 END IF
3070
3071 IF (.not.allocated(ninfo)) THEN
3072 allocate ( ninfo(ngrids) )
3073 dmem(1)=dmem(1)+real(ngrids,r8)
3074 END IF
3075
3076 IF (.not.allocated(nobc)) THEN
3077 allocate ( nobc(ngrids) )
3078 dmem(1)=dmem(1)+real(ngrids,r8)
3079 END IF
3080 IF (.not.allocated(nbrec)) THEN
3081 allocate ( nbrec(ngrids) )
3082 dmem(1)=dmem(1)+real(ngrids,r8)
3083 END IF
3084 IF (.not.allocated(obccount)) THEN
3085 allocate ( obccount(ngrids) )
3086 dmem(1)=dmem(1)+real(ngrids,r8)
3087 END IF
3088
3089#ifdef ADJUST_BOUNDARY
3090 IF (.not.allocated(lobc)) THEN
3091 allocate ( lobc(4,mstatevar,ngrids) )
3092 dmem(1)=dmem(1)+4.0_r8*real(mstatevar*ngrids,r8)
3093 END IF
3094#endif
3095
3096 IF (.not.allocated(nsff)) THEN
3097 allocate ( nsff(ngrids) )
3098 dmem(1)=dmem(1)+real(ngrids,r8)
3099 END IF
3100 IF (.not.allocated(nfrec)) THEN
3101 allocate ( nfrec(ngrids) )
3102 dmem(1)=dmem(1)+real(ngrids,r8)
3103 END IF
3104 IF (.not.allocated(sfcount)) THEN
3105 allocate ( sfcount(ngrids) )
3106 dmem(1)=dmem(1)+real(ngrids,r8)
3107 END IF
3108
3109#ifdef ADJUST_STFLUX
3110 IF (.not.allocated(lstflux)) THEN
3111 allocate ( lstflux(mt,ngrids) )
3112 dmem(1)=dmem(1)+real(mt*ngrids,r8)
3113 END IF
3114#endif
3115
3116 IF (.not.allocated(nrrec)) THEN
3117 allocate ( nrrec(ngrids) )
3118 dmem(1)=dmem(1)+real(ngrids,r8)
3119 END IF
3120
3121 IF (.not.allocated(lastrec)) THEN
3122 allocate ( lastrec(ngrids) )
3123 dmem(1)=dmem(1)+real(ngrids,r8)
3124 END IF
3125
3126 IF (.not.allocated(lcycleadj)) THEN
3127 allocate ( lcycleadj(ngrids) )
3128 dmem(1)=dmem(1)+real(ngrids,r8)
3129 END IF
3130 IF (.not.allocated(lcyclerst)) THEN
3131 allocate ( lcyclerst(ngrids) )
3132 dmem(1)=dmem(1)+real(ngrids,r8)
3133 END IF
3134 IF (.not.allocated(lcycletlm)) THEN
3135 allocate ( lcycletlm(ngrids) )
3136 dmem(1)=dmem(1)+real(ngrids,r8)
3137 END IF
3138
3139#if defined AVERAGES && defined AVERAGES_DETIDE && \
3140 (defined ssh_tides || defined uv_tides)
3141 IF (.not.allocated(hcount)) THEN
3142 allocate ( hcount(ngrids) )
3143 dmem(1)=dmem(1)+real(ngrids,r8)
3144 END IF
3145#endif
3146
3147 IF (.not.allocated(kstrs)) THEN
3148 allocate ( kstrs(ngrids) )
3149 dmem(1)=dmem(1)+real(ngrids,r8)
3150 END IF
3151 IF (.not.allocated(kends)) THEN
3152 allocate ( kends(ngrids) )
3153 dmem(1)=dmem(1)+real(ngrids,r8)
3154 END IF
3155
3156 IF (.not.allocated(dstrs)) THEN
3157 allocate ( dstrs(ngrids) )
3158 dmem(1)=dmem(1)+real(ngrids,r8)
3159 END IF
3160 IF (.not.allocated(dends)) THEN
3161 allocate ( dends(ngrids) )
3162 dmem(1)=dmem(1)+real(ngrids,r8)
3163 END IF
3164
3165 IF (.not.allocated(trnorm)) THEN
3166 allocate ( trnorm(ngrids) )
3167 dmem(1)=dmem(1)+real(ngrids,r8)
3168 END IF
3169
3170 IF (.not.allocated(so_decay)) THEN
3171 allocate ( so_decay(ngrids) )
3172 dmem(1)=dmem(1)+real(ngrids,r8)
3173 END IF
3174#ifdef SOLVE3D
3175 IF (.not.allocated(so_sdev)) THEN
3176 allocate ( so_sdev(7+2*mt,ngrids) )
3177 dmem(1)=dmem(1)+real((7+2*mt)*ngrids,r8)
3178 END IF
3179#else
3180 IF (.not.allocated(so_sdev)) THEN
3181 allocate ( so_sdev(5,ngrids) )
3182 dmem(1)=dmem(1)+5.0_r8*real(ngrids,r8)
3183 END IF
3184#endif
3185
3186#if defined FOUR_DVAR || defined VERIFICATION
3187 IF (.not.allocated(cnorm)) THEN
3188 allocate ( cnorm(2,mstatevar) )
3189 dmem(1)=dmem(1)+2.0_r8*real(mstatevar,r8)
3190 END IF
3191 IF (.not.allocated(cnormb)) THEN
3192 allocate ( cnormb(mstatevar,4) )
3193 dmem(1)=dmem(1)+4.0_r8*real(mstatevar,r8)
3194 END IF
3195
3196 IF (.not.allocated(sporadicimpulse)) THEN
3197 allocate ( sporadicimpulse(ngrids) )
3198 dmem(1)=dmem(1)+real(ngrids,r8)
3199 END IF
3200 IF (.not.allocated(frequentimpulse)) THEN
3201 allocate ( frequentimpulse(ngrids) )
3202 dmem(1)=dmem(1)+real(ngrids,r8)
3203 END IF
3204
3205 IF (.not.allocated(iauswitch)) THEN
3206 allocate ( iauswitch(ngrids) )
3207 dmem(1)=dmem(1)+real(ngrids,r8)
3208 END IF
3209
3210 IF (.not.allocated(timeiau)) THEN
3211 allocate ( timeiau(ngrids) )
3212 timeiau=0.0_dp
3213 dmem(1)=dmem(1)+real(ngrids,r8)
3214 END IF
3215
3216 IF (.not.allocated(dtdz_min)) THEN
3217 allocate ( dtdz_min(ngrids) )
3218 dmem(1)=dmem(1)+real(ngrids,r8)
3219 END IF
3220 IF (.not.allocated(ml_depth)) THEN
3221 allocate ( ml_depth(ngrids) )
3222 dmem(1)=dmem(1)+real(ngrids,r8)
3223 END IF
3224
3225 IF (.not.allocated(lnm_depth)) THEN
3226 allocate ( lnm_depth(ngrids) )
3227 dmem(1)=dmem(1)+real(ngrids,r8)
3228 END IF
3229
3230 IF (.not.allocated(balance)) THEN
3231 allocate ( balance(mstatevar) )
3232 dmem(1)=dmem(1)+real(mstatevar,r8)
3233 END IF
3234
3235 IF (.not.allocated(hdecay)) THEN
3236 allocate ( hdecay(2,mstatevar,ngrids) )
3237 dmem(1)=dmem(1)+2.0_r8*real(mstatevar*ngrids,r8)
3238 END IF
3239 IF (.not.allocated(vdecay)) THEN
3240 allocate ( vdecay(2,mstatevar,ngrids) )
3241 dmem(1)=dmem(1)+2.0_r8*real(mstatevar*ngrids,r8)
3242 END IF
3243
3244 IF (.not.allocated(tdecay)) THEN
3245 allocate ( tdecay(mstatevar,ngrids) )
3246 dmem(1)=dmem(1)+real(mstatevar*ngrids,r8)
3247 END IF
3248
3249 IF (.not.allocated(hdecayb)) THEN
3250 allocate ( hdecayb(mstatevar,4,ngrids) )
3251 dmem(1)=dmem(1)+4.0_r8*real(mstatevar*ngrids,r8)
3252 END IF
3253 IF (.not.allocated(vdecayb)) THEN
3254 allocate ( vdecayb(mstatevar,4,ngrids) )
3255 dmem(1)=dmem(1)+4.0_r8*real(mstatevar*ngrids,r8)
3256 END IF
3257
3258 IF (.not.allocated(bgqc_type)) THEN
3259 allocate ( bgqc_type(ngrids) )
3260 dmem(1)=dmem(1)+real(ngrids,r8)
3261 END IF
3262 IF (.not.allocated(nprovenance)) THEN
3263 allocate ( nprovenance(ngrids) )
3264 dmem(1)=dmem(1)+real(ngrids,r8)
3265 END IF
3266 IF (.not.allocated(s_bgqc)) THEN
3267 allocate ( s_bgqc(mstatevar,ngrids) )
3268 dmem(1)=dmem(1)+real(mstatevar*ngrids,r8)
3269 END IF
3270
3271# ifdef STD_MODEL
3272 IF (.not.allocated(sigma_max)) THEN
3273 allocate ( sigma_max(mstatevar,ngrids) )
3274 dmem(1)=dmem(1)+real(mstatevar*ngrids,r8)
3275 END IF
3276 IF (.not.allocated(sigma_ml)) THEN
3277 allocate ( sigma_ml(mstatevar,ngrids) )
3278 dmem(1)=dmem(1)+real(mstatevar*ngrids,r8)
3279 END IF
3280 IF (.not.allocated(sigma_do)) THEN
3281 allocate ( sigma_do(mstatevar,ngrids) )
3282 dmem(1)=dmem(1)+real(mstatevar*ngrids,r8)
3283 END IF
3284 IF (.not.allocated(sigma_dz)) THEN
3285 allocate ( sigma_dz(mstatevar,ngrids) )
3286 dmem(1)=dmem(1)+real(mstatevar*ngrids,r8)
3287 END IF
3288
3289 IF (.not.allocated(mld_uniform)) THEN
3290 allocate ( mld_uniform(ngrids) )
3291 dmem(1)=dmem(1)+real(ngrids,r8)
3292 END IF
3293# endif
3294#endif
3295
3296 IF (.not.allocated(obcfac)) THEN
3297 allocate ( obcfac(ngrids) )
3298 dmem(1)=dmem(1)+real(ngrids,r8)
3299 END IF
3300 IF (.not.allocated(fsobc_in)) THEN
3301 allocate ( fsobc_in(ngrids,4) )
3302 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
3303 END IF
3304 IF (.not.allocated(fsobc_out)) THEN
3305 allocate ( fsobc_out(ngrids,4) )
3306 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
3307 END IF
3308 IF (.not.allocated(m2obc_in)) THEN
3309 allocate ( m2obc_in(ngrids,4) )
3310 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
3311 END IF
3312 IF (.not.allocated(m2obc_out)) THEN
3313 allocate ( m2obc_out(ngrids,4) )
3314 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
3315 END IF
3316
3317#ifdef SOLVE3D
3318 IF (.not.allocated(m3obc_in)) THEN
3319 allocate ( m3obc_in(ngrids,4) )
3320 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
3321 END IF
3322 IF (.not.allocated(m3obc_out)) THEN
3323 allocate ( m3obc_out(ngrids,4) )
3324 dmem(1)=dmem(1)+4.0_r8*real(ngrids,r8)
3325 END IF
3326 IF (.not.allocated(tobc_in)) THEN
3327 allocate ( tobc_in(mt,ngrids,4) )
3328 dmem(1)=dmem(1)+4.0_r8*real(mt*ngrids,r8)
3329 END IF
3330 IF (.not.allocated(tobc_out)) THEN
3331 allocate ( tobc_out(mt,ngrids,4) )
3332 dmem(1)=dmem(1)+4.0_r8*real(mt*ngrids,r8)
3333 END IF
3334#endif
3335
3336 IF (.not.allocated(znudg)) THEN
3337 allocate ( znudg(ngrids) )
3338 dmem(1)=dmem(1)+real(ngrids,r8)
3339 END IF
3340 IF (.not.allocated(m2nudg)) THEN
3341 allocate ( m2nudg(ngrids) )
3342 dmem(1)=dmem(1)+real(ngrids,r8)
3343 END IF
3344 IF (.not.allocated(m3nudg)) THEN
3345 allocate ( m3nudg(ngrids) )
3346 dmem(1)=dmem(1)+real(ngrids,r8)
3347 END IF
3348 IF (.not.allocated(tnudg)) THEN
3349 allocate ( tnudg(mt,ngrids) )
3350 dmem(1)=dmem(1)+real(ngrids,r8)
3351 END IF
3352
3353#ifdef BULK_FLUXES
3354 IF (.not.allocated(blk_zq)) THEN
3355 allocate ( blk_zq(ngrids) )
3356 dmem(1)=dmem(1)+real(ngrids,r8)
3357 END IF
3358 IF (.not.allocated(blk_zt)) THEN
3359 allocate ( blk_zt(ngrids) )
3360 dmem(1)=dmem(1)+real(ngrids,r8)
3361 END IF
3362 IF (.not.allocated(blk_zw)) THEN
3363 allocate ( blk_zw(ngrids) )
3364 dmem(1)=dmem(1)+real(ngrids,r8)
3365 END IF
3366#endif
3367
3368 IF (.not.allocated(gls_m)) THEN
3369 allocate ( gls_m(ngrids) )
3370 dmem(1)=dmem(1)+real(ngrids,r8)
3371 END IF
3372 IF (.not.allocated(gls_n)) THEN
3373 allocate ( gls_n(ngrids) )
3374 dmem(1)=dmem(1)+real(ngrids,r8)
3375 END IF
3376 IF (.not.allocated(gls_p)) THEN
3377 allocate ( gls_p(ngrids) )
3378 dmem(1)=dmem(1)+real(ngrids,r8)
3379 END IF
3380 IF (.not.allocated(gls_sigk)) THEN
3381 allocate ( gls_sigk(ngrids) )
3382 dmem(1)=dmem(1)+real(ngrids,r8)
3383 END IF
3384 IF (.not.allocated(gls_sigp)) THEN
3385 allocate ( gls_sigp(ngrids) )
3386 dmem(1)=dmem(1)+real(ngrids,r8)
3387 END IF
3388 IF (.not.allocated(gls_cmu0)) THEN
3389 allocate ( gls_cmu0(ngrids) )
3390 dmem(1)=dmem(1)+real(ngrids,r8)
3391 END IF
3392 IF (.not.allocated(gls_cmupr)) THEN
3393 allocate ( gls_cmupr(ngrids) )
3394 dmem(1)=dmem(1)+real(ngrids,r8)
3395 END IF
3396 IF (.not.allocated(gls_c1)) THEN
3397 allocate ( gls_c1(ngrids) )
3398 dmem(1)=dmem(1)+real(ngrids,r8)
3399 END IF
3400 IF (.not.allocated(gls_c2)) THEN
3401 allocate ( gls_c2(ngrids) )
3402 dmem(1)=dmem(1)+real(ngrids,r8)
3403 END IF
3404 IF (.not.allocated(gls_c3m)) THEN
3405 allocate ( gls_c3m(ngrids) )
3406 dmem(1)=dmem(1)+real(ngrids,r8)
3407 END IF
3408 IF (.not.allocated(gls_c3p)) THEN
3409 allocate ( gls_c3p(ngrids) )
3410 dmem(1)=dmem(1)+real(ngrids,r8)
3411 END IF
3412 IF (.not.allocated(gls_kmin)) THEN
3413 allocate ( gls_kmin(ngrids) )
3414 dmem(1)=dmem(1)+real(ngrids,r8)
3415 END IF
3416 IF (.not.allocated(gls_pmin)) THEN
3417 allocate ( gls_pmin(ngrids) )
3418 dmem(1)=dmem(1)+real(ngrids,r8)
3419 END IF
3420
3421 IF (.not.allocated(charnok_alpha)) THEN
3422 allocate ( charnok_alpha(ngrids) )
3423 dmem(1)=dmem(1)+real(ngrids,r8)
3424 END IF
3425 IF (.not.allocated(zos_hsig_alpha)) THEN
3426 allocate ( zos_hsig_alpha(ngrids) )
3427 dmem(1)=dmem(1)+real(ngrids,r8)
3428 END IF
3429 IF (.not.allocated(sz_alpha)) THEN
3430 allocate ( sz_alpha(ngrids) )
3431 dmem(1)=dmem(1)+real(ngrids,r8)
3432 END IF
3433 IF (.not.allocated(crgban_cw)) THEN
3434 allocate ( crgban_cw(ngrids) )
3435 dmem(1)=dmem(1)+real(ngrids,r8)
3436 END IF
3437 IF (.not.allocated(wec_alpha)) THEN
3438 allocate ( wec_alpha(ngrids) )
3439 dmem(1)=dmem(1)+real(ngrids,r8)
3440 END IF
3441!
3442 RETURN
3443 END SUBROUTINE allocate_scalars
3444!
3445 SUBROUTINE deallocate_scalars (ng)
3446!
3447!=======================================================================
3448! !
3449! This routine deallocates structures variables and module variables. !
3450! Notice that "destroy" cannot be use to deallocate pointer variables !
3451! because of cyclic dependencies. !
3452! !
3453!=======================================================================
3454!
3455! Imported variable declarations.
3456!
3457 integer :: ng
3458
3459#ifdef SUBOBJECT_DEALLOCATION
3460!
3461!-----------------------------------------------------------------------
3462! Deallocate each variable in the derived-type T_SCALARS structure
3463! separately.
3464!-----------------------------------------------------------------------
3465!
3466# ifdef SOLVE3D
3467 IF (associated(scalars(ng)%Fstate)) THEN
3468 deallocate ( scalars(ng)%Fstate )
3469 END IF
3470
3471 IF (associated(scalars(ng)%Lstate)) THEN
3472 deallocate ( scalars(ng)%Lstate )
3473 END IF
3474# else
3475 IF (associated(scalars(ng)%Fstate)) THEN
3476 deallocate ( scalars(ng)%Fstate )
3477 END IF
3478
3479 IF (associated(scalars(ng)%Lstate)) THEN
3480 deallocate ( scalars(ng)%Lstate )
3481 END IF
3482# endif
3483
3484# if defined READ_WATER && defined MASKING && defined DISTRIBUTE
3485 IF (associated(scalars(ng)%IJwater)) THEN
3486 deallocate ( scalars(ng)%IJwater )
3487 END IF
3488# endif
3489 IF (associated(scalars(ng)%Cs_r)) THEN
3490 deallocate ( scalars(ng)%Cs_r )
3491 END IF
3492
3493 IF (associated(scalars(ng)%Cs_w)) THEN
3494 deallocate ( scalars(ng)%Cs_w )
3495 END IF
3496
3497 IF (associated(scalars(ng)%sc_r)) THEN
3498 deallocate ( scalars(ng)%sc_r )
3499 END IF
3500
3501 IF (associated(scalars(ng)%sc_w)) THEN
3502 deallocate ( scalars(ng)%sc_w )
3503 END IF
3504#endif
3505!
3506!-----------------------------------------------------------------------
3507! Deallocate derived-type SCALARS structure.
3508!-----------------------------------------------------------------------
3509!
3510 IF (ng.eq.ngrids) THEN
3511 IF (allocated(scalars)) deallocate ( scalars )
3512 END IF
3513!
3514!-----------------------------------------------------------------------
3515! Deallocate variables in modules.
3516!-----------------------------------------------------------------------
3517!
3518! Deallocate variables that require special treatment in shared-memory.
3519! These variables are private for each thread to avoid collisions.
3520!
3521!$OMP PARALLEL
3522 IF (allocated(predictor_2d_step)) deallocate ( predictor_2d_step )
3523
3524 IF (allocated(indx1)) deallocate ( indx1 )
3525
3526 IF (allocated(iic)) deallocate ( iic )
3527
3528 IF (allocated(iif)) deallocate ( iif )
3529
3530 IF (allocated(next_kstp)) deallocate ( next_kstp )
3531
3532 IF (allocated(frcrec)) deallocate ( frcrec )
3533
3534 IF (allocated(sorec)) deallocate ( sorec )
3535
3536 IF (allocated(synchro_flag)) deallocate ( synchro_flag )
3537
3538 IF (allocated(step_counter)) deallocate ( step_counter )
3539
3540 IF (allocated(tdays)) deallocate ( tdays )
3541
3542 IF (allocated(time)) deallocate ( time )
3543
3544 IF (allocated(time_code)) deallocate ( time_code )
3545!$OMP END PARALLEL
3546!
3547! Deallocate regular variables
3548!
3549#ifdef T_PASSIVE
3550 IF (associated(inert)) deallocate ( inert )
3551#endif
3552 IF (allocated(perfectrst)) deallocate ( perfectrst )
3553
3554 IF (allocated(ndtfast)) deallocate ( ndtfast )
3555
3556 IF (allocated(nfast)) deallocate ( nfast )
3557
3558 IF (allocated(dt)) deallocate ( dt )
3559
3560 IF (allocated(dtfast)) deallocate ( dtfast )
3561
3562 IF (allocated(timeend)) deallocate ( timeend )
3563
3564 IF (allocated(avgtime)) deallocate ( avgtime )
3565
3566 IF (allocated(diatime)) deallocate ( diatime )
3567
3568 IF (allocated(imptime)) deallocate ( imptime )
3569
3570 IF (allocated(initime)) deallocate ( initime )
3571
3572 IF (allocated(initimes)) deallocate ( initimes )
3573
3574 IF (allocated(obstime)) deallocate ( obstime )
3575
3576 IF (allocated(frctime)) deallocate ( frctime )
3577
3578 IF (allocated(ntimes)) deallocate ( ntimes )
3579
3580 IF (allocated(first_time)) deallocate ( first_time )
3581
3582 IF (allocated(ntfirst)) deallocate ( ntfirst )
3583
3584 IF (allocated(ntstart)) deallocate ( ntstart )
3585
3586 IF (allocated(ntend)) deallocate ( ntend )
3587
3588 IF (allocated(nrecfrc)) deallocate ( nrecfrc )
3589
3590 IF (allocated(setgridconfig)) deallocate ( setgridconfig )
3591
3592 IF (allocated(processinputdata)) deallocate ( processinputdata )
3593
3594 IF (allocated(nudgingcoeff)) deallocate ( nudgingcoeff )
3595
3596 IF (allocated(obcdata)) deallocate ( obcdata )
3597
3598 IF (allocated(lbiology)) deallocate ( lbiology )
3599
3600 IF (allocated(lfloats)) deallocate ( lfloats )
3601
3602 IF (allocated(lsediment)) deallocate ( lsediment )
3603
3604 IF (allocated(lstations)) deallocate ( lstations )
3605
3606 IF (allocated(compositegrid)) deallocate ( compositegrid )
3607
3608 IF (allocated(refinedgrid)) deallocate ( refinedgrid )
3609
3610 IF (allocated(refinescale)) deallocate ( refinescale )
3611
3612 IF (allocated(getdonordata)) deallocate ( getdonordata )
3613
3614 IF (allocated(ewperiodic)) deallocate ( ewperiodic )
3615
3616 IF (allocated(nsperiodic)) deallocate ( nsperiodic )
3617
3618 IF (allocated(volcons)) deallocate ( volcons )
3619
3620#if defined ADJOINT || defined TANGENT || defined TL_IOMS
3621 IF (allocated(ad_volcons)) deallocate ( ad_volcons )
3622
3623 IF (allocated(tl_volcons)) deallocate ( tl_volcons )
3624#endif
3625
3626 IF (allocated(lsponge)) deallocate ( lsponge )
3627
3628 IF (allocated(luvsponge)) deallocate ( luvsponge )
3629
3630 IF (allocated(ltracersponge)) deallocate ( ltracersponge )
3631
3632 IF (allocated(clm_file)) deallocate ( clm_file )
3633
3634 IF (allocated(lclimatology)) deallocate ( lclimatology )
3635
3636 IF (allocated(lsshclm)) deallocate ( lsshclm )
3637
3638 IF (allocated(lm2clm)) deallocate ( lm2clm )
3639
3640 IF (allocated(lm3clm)) deallocate ( lm3clm )
3641
3642 IF (allocated(ltracerclm)) deallocate ( ltracerclm )
3643
3644 IF (allocated(lnudging)) deallocate ( lnudging )
3645
3646 IF (allocated(lnudgem2clm)) deallocate ( lnudgem2clm )
3647
3648 IF (allocated(lnudgem3clm)) deallocate ( lnudgem3clm )
3649
3650 IF (allocated(lnudgetclm)) deallocate ( lnudgetclm )
3651
3652 IF (allocated(luvsrc)) deallocate ( luvsrc )
3653
3654 IF (allocated(lwsrc)) deallocate ( lwsrc )
3655
3656 IF (allocated(ltracersrc)) deallocate ( ltracersrc )
3657
3658 IF (allocated(maxspeed)) deallocate ( maxspeed )
3659
3660 IF (allocated(maxrho)) deallocate ( maxrho )
3661
3662 IF (allocated(levsfrc)) deallocate ( levsfrc )
3663
3664 IF (allocated(levbfrc)) deallocate ( levbfrc )
3665
3666 IF (allocated(vtransform)) deallocate ( vtransform )
3667
3668 IF (allocated(vstretching)) deallocate ( vstretching )
3669
3670 IF (allocated(tcline)) deallocate ( tcline )
3671
3672 IF (allocated(hc)) deallocate ( hc )
3673
3674 IF (allocated(theta_s)) deallocate ( theta_s )
3675
3676 IF (allocated(theta_b)) deallocate ( theta_b )
3677
3678 IF (allocated(hmin)) deallocate ( hmin )
3679
3680 IF (allocated(hmax)) deallocate ( hmax )
3681
3682 IF (allocated(xl)) deallocate ( xl )
3683
3684 IF (allocated(el)) deallocate ( el )
3685
3686 IF (allocated(lonmin)) deallocate ( lonmin )
3687
3688 IF (allocated(lonmax)) deallocate ( lonmax )
3689
3690 IF (allocated(latmin)) deallocate ( latmin )
3691
3692 IF (allocated(latmax)) deallocate ( latmax )
3693
3694 IF (allocated(idigits)) deallocate ( idigits )
3695
3696 IF (allocated(jdigits)) deallocate ( jdigits )
3697
3698#ifdef SOLVE3D
3699 IF (allocated(kdigits)) deallocate ( kdigits )
3700#endif
3701
3702 IF (allocated(totvolume)) deallocate ( totvolume )
3703
3704 IF (allocated(minvolume)) deallocate ( minvolume )
3705
3706 IF (allocated(maxvolume)) deallocate ( maxvolume )
3707
3708 IF (allocated(dxmin)) deallocate ( dxmin )
3709
3710 IF (allocated(dxmax)) deallocate ( dxmax )
3711
3712 IF (allocated(dymin)) deallocate ( dymin )
3713
3714 IF (allocated(dymax)) deallocate ( dymax )
3715
3716#ifdef MASKING
3717 IF (allocated(dxminw)) deallocate ( dxminw )
3718
3719 IF (allocated(dxmaxw)) deallocate ( dxmaxw )
3720
3721 IF (allocated(dyminw)) deallocate ( dyminw )
3722
3723 IF (allocated(dymaxw)) deallocate ( dymaxw )
3724
3725#endif
3726
3727#ifdef SOLVE3D
3728 IF (allocated(dzmin)) deallocate ( dzmin )
3729
3730 IF (allocated(dzmax)) deallocate ( dzmax )
3731
3732# ifdef MASKING
3733 IF (allocated(dzminw)) deallocate ( dzminw )
3734
3735 IF (allocated(dzmaxw)) deallocate ( dzmaxw )
3736# endif
3737#endif
3738
3739 IF (allocated(grdmax)) deallocate ( grdmax )
3740
3741#ifdef DIFF_3DCOEF
3742 IF (allocated(diffmin)) deallocate ( diffmin )
3743
3744 IF (allocated(diffmax)) deallocate ( diffmax )
3745#endif
3746
3747 IF (allocated(cg_min)) deallocate ( cg_min )
3748
3749 IF (allocated(cg_max)) deallocate ( cg_max )
3750
3751 IF (allocated(cg_cor)) deallocate ( cg_cor )
3752
3753#ifdef VISC_3DCOEF
3754 IF (allocated(viscmin)) deallocate ( viscmin )
3755
3756 IF (allocated(viscmax)) deallocate ( viscmax )
3757#endif
3758
3759 IF (allocated(r0)) deallocate ( r0 )
3760
3761 IF (allocated(tcoef)) deallocate ( tcoef )
3762
3763 IF (allocated(scoef)) deallocate ( scoef )
3764
3765 IF (allocated(t0)) deallocate ( t0 )
3766
3767 IF (allocated(s0)) deallocate ( s0 )
3768
3769 IF (allocated(gamma2)) deallocate ( gamma2 )
3770
3771 IF (allocated(lmd_jwt)) deallocate ( lmd_jwt )
3772
3773 IF (allocated(rx0)) deallocate ( rx0 )
3774
3775 IF (allocated(rx1)) deallocate ( rx1 )
3776
3777 IF (allocated(rdrg)) deallocate ( rdrg )
3778
3779 IF (allocated(rdrg2)) deallocate ( rdrg2 )
3780
3781 IF (allocated(zos)) deallocate ( zos )
3782
3783 IF (allocated(zob)) deallocate ( zob )
3784
3785 IF (allocated(dcrit)) deallocate ( dcrit )
3786
3787#ifdef PROPAGATOR
3788 IF (allocated(nconv)) deallocate ( nconv )
3789#endif
3790
3791 IF (allocated(weight)) deallocate ( weight )
3792
3793 IF (allocated(akk_bak)) deallocate ( akk_bak )
3794
3795 IF (allocated(akp_bak)) deallocate ( akp_bak )
3796
3797 IF (allocated(akv_bak)) deallocate ( akv_bak )
3798
3799 IF (allocated(akv_limit)) deallocate ( akv_limit )
3800
3801 IF (allocated(ad_visc2)) deallocate ( ad_visc2 )
3802
3803 IF (allocated(nl_visc2)) deallocate ( nl_visc2 )
3804
3805 IF (allocated(tl_visc2)) deallocate ( tl_visc2 )
3806
3807 IF (allocated(visc2)) deallocate ( visc2 )
3808
3809 IF (allocated(ad_visc4)) deallocate ( ad_visc4 )
3810
3811 IF (allocated(nl_visc4)) deallocate ( nl_visc4 )
3812
3813 IF (allocated(tl_visc4)) deallocate ( tl_visc4 )
3814
3815 IF (allocated(visc4)) deallocate ( visc4 )
3816
3817 IF (allocated(tkenu2)) deallocate ( tkenu2 )
3818
3819 IF (allocated(tkenu4)) deallocate ( tkenu4 )
3820
3821 IF (allocated(akt_bak)) deallocate ( akt_bak )
3822
3823 IF (allocated(akt_limit)) deallocate ( akt_limit )
3824
3825 IF (allocated(kdiff)) deallocate ( kdiff )
3826
3827 IF (allocated(ad_tnu2)) deallocate ( ad_tnu2 )
3828
3829 IF (allocated(nl_tnu2)) deallocate ( nl_tnu2 )
3830
3831 IF (allocated(tl_tnu2)) deallocate ( tl_tnu2 )
3832
3833 IF (allocated(tnu2)) deallocate ( tnu2 )
3834
3835 IF (allocated(ad_tnu4)) deallocate ( ad_tnu4 )
3836
3837 IF (allocated(nl_tnu4)) deallocate ( nl_tnu4 )
3838
3839 IF (allocated(tl_tnu4)) deallocate ( tl_tnu4 )
3840
3841 IF (allocated(tnu4)) deallocate ( tnu4 )
3842
3843 IF (allocated(tl_m2diff)) deallocate ( tl_m2diff )
3844
3845 IF (allocated(tl_m3diff)) deallocate ( tl_m3diff )
3846
3847 IF (allocated(tl_tdiff)) deallocate ( tl_tdiff )
3848
3849 IF (allocated(ad_akv_fac)) deallocate ( ad_akv_fac )
3850
3851 IF (allocated(tl_akv_fac)) deallocate ( tl_akv_fac )
3852
3853 IF (allocated(ad_akt_fac)) deallocate ( ad_akt_fac )
3854
3855 IF (allocated(tl_akt_fac)) deallocate ( tl_akt_fac )
3856
3857 IF (allocated(ldefadj)) deallocate ( ldefadj )
3858
3859 IF (allocated(ldefavg)) deallocate ( ldefavg )
3860
3861 IF (allocated(ldefdai)) deallocate ( ldefdai )
3862
3863 IF (allocated(ldefdia)) deallocate ( ldefdia )
3864
3865 IF (allocated(ldeferr)) deallocate ( ldeferr )
3866
3867 IF (allocated(ldefflt)) deallocate ( ldefflt )
3868
3869 IF (allocated(ldefhis)) deallocate ( ldefhis )
3870
3871 IF (allocated(ldefhss)) deallocate ( ldefhss )
3872
3873 IF (allocated(ldefini)) deallocate ( ldefini )
3874
3875 IF (allocated(ldefirp)) deallocate ( ldefirp )
3876
3877 IF (allocated(ldefitl)) deallocate ( ldefitl )
3878
3879 IF (allocated(ldeflcz)) deallocate ( ldeflcz )
3880
3881 IF (allocated(ldeflze)) deallocate ( ldeflze )
3882
3883 IF (allocated(ldefmod)) deallocate ( ldefmod )
3884
3885 IF (allocated(ldefqck)) deallocate ( ldefqck )
3886
3887 IF (allocated(ldefrst)) deallocate ( ldefrst )
3888
3889#ifdef STD_MODEL
3890 IF (allocated(ldefstd)) deallocate ( ldefstd )
3891#endif
3892
3893#ifdef SP4DVAR
3894 IF (allocated(ldefsca)) deallocate ( ldefsca )
3895
3896 IF (allocated(ldefsct)) deallocate ( ldefsct )
3897
3898 IF (allocated(ldefspa)) deallocate ( ldefspa )
3899
3900 IF (allocated(ldefspt)) deallocate ( ldefspt )
3901#endif
3902
3903 IF (allocated(ldefsta)) deallocate ( ldefsta )
3904
3905 IF (allocated(ldeftide)) deallocate ( ldeftide )
3906
3907 IF (allocated(ldeftlf)) deallocate ( ldeftlf )
3908
3909 IF (allocated(ldeftlm)) deallocate ( ldeftlm )
3910
3911 IF (allocated(ldefxtr)) deallocate ( ldefxtr )
3912
3913 IF (allocated(lreadadm)) deallocate ( lreadadm )
3914
3915 IF (allocated(lreadblk)) deallocate ( lreadblk )
3916
3917 IF (allocated(lreadfrc)) deallocate ( lreadfrc )
3918
3919 IF (allocated(lreadfwd)) deallocate ( lreadfwd )
3920
3921 IF (allocated(lreadqck)) deallocate ( lreadqck )
3922
3923 IF (allocated(lreadstd)) deallocate ( lreadstd )
3924
3925 IF (allocated(lreadtlm)) deallocate ( lreadtlm )
3926
3927 IF (allocated(lwrtadj)) deallocate ( lwrtadj )
3928
3929 IF (allocated(lwrtavg)) deallocate ( lwrtavg )
3930
3931 IF (allocated(lwrtdia)) deallocate ( lwrtdia )
3932
3933 IF (allocated(lwrthis)) deallocate ( lwrthis )
3934
3935 IF (allocated(lwrtper)) deallocate ( lwrtper )
3936
3937 IF (allocated(lwrtqck)) deallocate ( lwrtqck )
3938
3939 IF (allocated(lwrtrst)) deallocate ( lwrtrst )
3940
3941#ifdef STD_MODEL
3942 IF (allocated(lwrtstd)) deallocate ( lwrtstd )
3943#endif
3944
3945 IF (allocated(lwrttlf)) deallocate ( lwrttlf )
3946
3947 IF (allocated(lwrttlm)) deallocate ( lwrttlm )
3948
3949 IF (allocated(lwrtxtr)) deallocate ( lwrtxtr )
3950
3951
3952 IF (allocated(ldefnrm)) deallocate ( ldefnrm )
3953
3954 IF (allocated(lwrtnrm)) deallocate ( lwrtnrm )
3955
3956#ifdef AD_OUTPUT_STATE
3957 IF (allocated(lwrtstate3d)) deallocate ( lwrtstate3d )
3958#endif
3959
3960#if defined STOCHASTIC_OPT && !defined STOCH_OPT_WHITE
3961 IF (allocated(soinitial)) deallocate ( soinitial )
3962#endif
3963
3964 IF (allocated(lwrtstate2d)) deallocate ( lwrtstate2d )
3965
3966 IF (allocated(lwrttime)) deallocate ( lwrttime )
3967
3968 IF (allocated(lwrtcost)) deallocate ( lwrtcost )
3969
3970 IF (allocated(ladjusted)) deallocate ( ladjusted )
3971
3972 IF (allocated(lprocessobc)) deallocate ( lprocessobc )
3973
3974 IF (allocated(lprocesstides)) deallocate ( lprocesstides )
3975
3976 IF (allocated(lwrtinfo)) deallocate ( lwrtinfo )
3977
3978 IF (allocated(ldefout)) deallocate ( ldefout )
3979
3980 IF (allocated(ndefadj)) deallocate ( ndefadj )
3981
3982 IF (allocated(ndefavg)) deallocate ( ndefavg )
3983
3984 IF (allocated(ndefdia)) deallocate ( ndefdia )
3985
3986 IF (allocated(ndefhis)) deallocate ( ndefhis )
3987
3988 IF (allocated(ndefqck)) deallocate ( ndefqck )
3989
3990 IF (allocated(ndeftlm)) deallocate ( ndeftlm )
3991
3992 IF (allocated(ndeftlm)) deallocate ( ndefxtr )
3993
3994 IF (allocated(ntsavg)) deallocate ( ntsavg )
3995
3996 IF (allocated(ntsdia)) deallocate ( ntsdia )
3997
3998 IF (allocated(nadj)) deallocate ( nadj )
3999
4000 IF (allocated(navg)) deallocate ( navg )
4001
4002 IF (allocated(ndia)) deallocate ( ndia )
4003
4004 IF (allocated(nflt)) deallocate ( nflt )
4005
4006 IF (allocated(nhis)) deallocate ( nhis )
4007
4008 IF (allocated(nqck)) deallocate ( nqck )
4009
4010 IF (allocated(nrst)) deallocate ( nrst )
4011
4012 IF (allocated(nsta)) deallocate ( nsta )
4013
4014 IF (allocated(ntlm)) deallocate ( ntlm )
4015
4016#ifdef SP4DVAR
4017 IF (allocated(nsca)) deallocate ( nsca )
4018
4019 IF (allocated(nsct)) deallocate ( nsct )
4020
4021 IF (allocated(nspa)) deallocate ( nspa )
4022
4023 IF (allocated(nspt)) deallocate ( nspt )
4024
4025 IF (allocated(crec)) deallocate ( crec )
4026#endif
4027
4028 IF (allocated(extractflag)) deallocate ( extractflag )
4029
4030 IF (allocated(ninfo)) deallocate ( ninfo )
4031
4032 IF (allocated(nobc)) deallocate ( nobc )
4033
4034 IF (allocated(nbrec)) deallocate ( nbrec )
4035
4036 IF (allocated(obccount)) deallocate ( obccount )
4037
4038#ifdef ADJUST_BOUNDARY
4039 IF (allocated(lobc)) deallocate ( lobc )
4040#endif
4041
4042 IF (allocated(nsff)) deallocate ( nsff )
4043
4044 IF (allocated(nfrec)) deallocate ( nfrec )
4045
4046 IF (allocated(sfcount)) deallocate ( sfcount )
4047
4048#ifdef ADJUST_STFLUX
4049 IF (allocated(lstflux)) deallocate ( lstflux )
4050#endif
4051
4052 IF (allocated(nrrec)) deallocate ( nrrec )
4053
4054 IF (allocated(lastrec)) deallocate ( lastrec )
4055
4056 IF (allocated(lcycleadj)) deallocate ( lcycleadj )
4057
4058 IF (allocated(lcyclerst)) deallocate ( lcyclerst )
4059
4060 IF (allocated(lcycletlm)) deallocate ( lcycletlm )
4061
4062#if defined AVERAGES && defined AVERAGES_DETIDE && \
4063 (defined ssh_tides || defined uv_tides)
4064 IF (allocated(hcount)) deallocate ( hcount )
4065#endif
4066
4067 IF (allocated(kstrs)) deallocate ( kstrs )
4068
4069 IF (allocated(kends)) deallocate ( kends )
4070
4071 IF (allocated(dstrs)) deallocate ( dstrs )
4072
4073 IF (allocated(dends)) deallocate ( dends )
4074
4075 IF (allocated(trnorm)) deallocate ( trnorm )
4076
4077 IF (allocated(so_decay)) deallocate ( so_decay )
4078
4079 IF (allocated(so_sdev)) deallocate ( so_sdev )
4080
4081#if defined FOUR_DVAR || defined VERIFICATION
4082 IF (allocated(cnorm)) deallocate ( cnorm )
4083
4084 IF (allocated(cnormb)) deallocate ( cnormb )
4085
4086 IF (allocated(sporadicimpulse)) deallocate ( sporadicimpulse )
4087
4088 IF (allocated(frequentimpulse)) deallocate ( frequentimpulse )
4089
4090 IF (allocated(dtdz_min)) deallocate ( dtdz_min )
4091
4092 IF (allocated(ml_depth)) deallocate ( ml_depth )
4093
4094 IF (allocated(lnm_depth)) deallocate ( lnm_depth )
4095
4096 IF (allocated(balance)) deallocate ( balance )
4097
4098 IF (allocated(hdecay)) deallocate ( hdecay )
4099
4100 IF (allocated(vdecay)) deallocate ( vdecay )
4101
4102 IF (allocated(tdecay)) deallocate ( tdecay )
4103
4104 IF (allocated(hdecayb)) deallocate ( hdecayb )
4105
4106 IF (allocated(vdecayb)) deallocate ( vdecayb )
4107
4108 IF (allocated(bgqc_type)) deallocate ( bgqc_type )
4109
4110 IF (allocated(nprovenance)) deallocate ( nprovenance )
4111
4112 IF (allocated(s_bgqc)) deallocate ( s_bgqc )
4113
4114# ifdef STD_MODEL
4115 IF (allocated(sigma_max)) deallocate ( sigma_max )
4116
4117 IF (allocated(sigma_ml)) deallocate ( sigma_ml )
4118
4119 IF (allocated(sigma_do)) deallocate ( sigma_do )
4120
4121 IF (allocated(sigma_dz)) deallocate ( sigma_dz )
4122
4123 IF (allocated(mld_uniform)) deallocate ( mld_uniform )
4124# endif
4125#endif
4126
4127 IF (allocated(obcfac)) deallocate ( obcfac )
4128
4129 IF (allocated(fsobc_in)) deallocate ( fsobc_in )
4130
4131 IF (allocated(fsobc_out)) deallocate ( fsobc_out )
4132
4133 IF (allocated(m2obc_in)) deallocate ( m2obc_in )
4134
4135 IF (allocated(m2obc_out)) deallocate ( m2obc_out )
4136
4137#ifdef SOLVE3D
4138 IF (allocated(m3obc_in)) deallocate ( m3obc_in )
4139
4140 IF (allocated(m3obc_out)) deallocate ( m3obc_out )
4141
4142 IF (allocated(tobc_in)) deallocate ( tobc_in )
4143
4144 IF (allocated(tobc_out)) deallocate ( tobc_out )
4145#endif
4146
4147 IF (allocated(znudg)) deallocate ( znudg )
4148
4149 IF (allocated(m2nudg)) deallocate ( m2nudg )
4150
4151 IF (allocated(m3nudg)) deallocate ( m3nudg )
4152
4153 IF (allocated(tnudg)) deallocate ( tnudg )
4154
4155#ifdef BULK_FLUXES
4156 IF (allocated(blk_zq)) deallocate ( blk_zq )
4157
4158 IF (allocated(blk_zt)) deallocate ( blk_zt )
4159
4160 IF (allocated(blk_zw)) deallocate ( blk_zw )
4161#endif
4162
4163 IF (allocated(gls_m)) deallocate ( gls_m )
4164
4165 IF (allocated(gls_n)) deallocate ( gls_n )
4166
4167 IF (allocated(gls_p)) deallocate ( gls_p )
4168
4169 IF (allocated(gls_sigk)) deallocate ( gls_sigk )
4170
4171 IF (allocated(gls_sigp)) deallocate ( gls_sigp )
4172
4173 IF (allocated(gls_cmu0)) deallocate ( gls_cmu0 )
4174
4175 IF (allocated(gls_cmupr)) deallocate ( gls_cmupr )
4176
4177 IF (allocated(gls_c1)) deallocate ( gls_c1 )
4178
4179 IF (allocated(gls_c2)) deallocate ( gls_c2 )
4180
4181 IF (allocated(gls_c3m)) deallocate ( gls_c3m )
4182
4183 IF (allocated(gls_c3p)) deallocate ( gls_c3p )
4184
4185 IF (allocated(gls_kmin)) deallocate ( gls_kmin )
4186
4187 IF (allocated(gls_pmin)) deallocate ( gls_pmin )
4188
4189 IF (allocated(charnok_alpha)) deallocate ( charnok_alpha )
4190
4191 IF (allocated(zos_hsig_alpha)) deallocate ( zos_hsig_alpha )
4192
4193 IF (allocated(sz_alpha)) deallocate ( sz_alpha )
4194
4195 IF (allocated(crgban_cw)) deallocate ( crgban_cw )
4196!
4197 RETURN
4198 END SUBROUTINE deallocate_scalars
4199!
4201!
4202!=======================================================================
4203! !
4204! This routine initializes several variables in module for all nested !
4205! grids. !
4206! !
4207!=======================================================================
4208!
4209 USE mod_param
4210!
4211! Local variable declarations.
4212!
4213 integer :: i, ic, j, ng, itrc
4214
4215 real(r8) :: one, zero
4216 real(r8), parameter :: inival = 0.0_r8
4217!
4218!---------------------------------------------------------------------
4219! Set tracer identification indices.
4220!---------------------------------------------------------------------
4221!
4222 itemp=1
4223 isalt=2
4224 ic=nat
4225
4226#ifdef T_PASSIVE
4227!
4228! Indices for inert passive tracers to advect and diffuse.
4229!
4230 DO i=1,npt
4231 ic=ic+1
4232 inert(i)=ic
4233 END DO
4234#endif
4235
4236#ifdef DIAGNOSTICS
4237!
4238!---------------------------------------------------------------------
4239! Set diagnostic fields identification indices.
4240!---------------------------------------------------------------------
4241
4242# ifdef DIAGNOSTICS_TS
4243!
4244! Indices for tracer diagnostic variables.
4245!
4246 ithadv=1
4247 itxadv=2
4248 ityadv=3
4249 itvadv=4
4250 ic=4
4251# if defined TS_DIF2 || defined TS_DIF4
4252 ithdif=ic+1
4253 itxdif=ic+2
4254 itydif=ic+3
4255 ic=ic+3
4256# if defined MIX_GEO_TS || defined MIX_ISO_TS
4257 itsdif=ic+1
4258 ic=ic+1
4259# endif
4260# endif
4261 itvdif=ic+1
4262 itrate=ic+2
4263# endif
4264# ifdef DIAGNOSTICS_UV
4265!
4266! Indices for 2D momentum diagnostic variables. In some places in
4267! the code a compact DO-loop (idiag=1:M2pgrd) is used to improve
4268! flexibility. Therefore, the order of indices is very important.
4269! Only those fields that require special treatment are set below
4270! the M2pgrd index.
4271!
4272 ic=0
4273# if defined UV_COR
4274 m2fcor=ic+1
4275 ic=ic+1
4276# endif
4277# if defined UV_ADV
4278 m2hadv=ic+1
4279 m2xadv=ic+2
4280 m2yadv=ic+3
4281 ic=ic+3
4282# endif
4283# if defined WEC_VF
4284# if defined UV_COR
4285 m2fsco=ic+1
4286 ic=ic+1
4287# endif
4288# ifdef BOTTOM_STREAMING
4289 m2bstm=ic+1
4290 ic=ic+1
4291# endif
4292# ifdef SURFACE_STREAMING
4293 m2sstm=ic+1
4294 ic=ic+1
4295# endif
4296 m2hjvf=ic+1
4297 m2kvrf=ic+2
4298 m2wrol=ic+3
4299 m2wbrk=ic+4
4300 ic=ic+4
4301# endif
4302# if defined VEGETATION && defined VEG_DRAG
4303 m2fveg=ic+1
4304 ic=ic+1
4305# endif
4306# if defined UV_VIS2 || defined UV_VIS4
4307 m2hvis=ic+1
4308 m2xvis=ic+2
4309 m2yvis=ic+3
4310 ic=ic+3
4311# endif
4312 m2pgrd=ic+1
4313 m2sstr=ic+2 ! These indices need to be
4314 m2bstr=ic+3 ! specified last to allow a
4315# if defined WEC_VF
4316 m2zeta=ic+4
4317 m2zetw=ic+5
4318 m2zqsp=ic+6
4319 m2zbeh=ic+7
4320# endif
4321 m2rate=ndm2d ! compact DO-loop structure
4322# ifdef SOLVE3D
4323!
4324! Indices for 3D momentum diagnostic variables. In some places in
4325! the code a compact DO-loop (idiag=1:M3pgrd) is used to improve
4326! flexibility. Therefore, the order of indices is very important.
4327! Only those fields that require special treatment are set below
4328! the M3pgrd index.
4329!
4330 ic=0
4331# if defined UV_COR
4332 m3fcor=ic+1
4333 ic=ic+1
4334# endif
4335# if defined UV_ADV
4336 m3vadv=ic+1
4337 m3hadv=ic+2
4338 m3xadv=ic+3
4339 m3yadv=ic+4
4340 ic=ic+4
4341# endif
4342# if defined WEC_VF
4343# if defined UV_COR
4344 m3fsco=ic+1
4345 ic=ic+1
4346# endif
4347# ifdef BOTTOM_STREAMING
4348 m3bstm=ic+1
4349 ic=ic+1
4350# endif
4351# ifdef SURFACE_STREAMING
4352 m3sstm=ic+1
4353 ic=ic+1
4354# endif
4355 m3vjvf=ic+1
4356 m3hjvf=ic+2
4357 m3kvrf=ic+3
4358 m3wrol=ic+4
4359 m3wbrk=ic+5
4360 ic=ic+5
4361# endif
4362# if defined VEGETATION && defined VEG_DRAG
4363 m3fveg=ic+1
4364 ic=ic+1
4365# endif
4366 m3pgrd=ic+1 ! needs to be here, indices below
4367 m3vvis=ic+2 ! require special treatment
4368# if defined UV_VIS2 || defined UV_VIS4
4369 m3hvis=ic+3
4370 m3xvis=ic+4
4371 m3yvis=ic+5
4372# endif
4374# endif
4375# endif
4376#endif
4377!
4378!-----------------------------------------------------------------------
4379! Activate all computation control switches.
4380!-----------------------------------------------------------------------
4381!
4382 DO ng=1,ngrids
4383 lastrec(ng)=.false.
4384 compositegrid(1:4,ng)=.false.
4385 refinedgrid(ng)=.false.
4386 getdonordata(ng)=.false.
4387 lbiology(ng)=.true.
4388 lcycleadj(ng)=.false.
4389 lcyclerst(ng)=.false.
4390 lcycletlm(ng)=.false.
4391 lfloats(ng)=.true.
4392 lsediment(ng)=.true.
4393 lstations(ng)=.true.
4394#if defined FOUR_DVAR || defined VERIFICATION
4395 frequentimpulse(ng)=.false.
4396 sporadicimpulse(ng)=.false.
4397#endif
4398 END DO
4399
4400#ifdef ADJUST_BOUNDARY
4401!
4402!-----------------------------------------------------------------------
4403! Initilize switches to process open boundary arrays for 4DVar
4404! adjustments.
4405!-----------------------------------------------------------------------
4406!
4407 DO ng=1,ngrids
4408 DO j=1,mstatevar
4409 DO i=1,4
4410 lobc(i,j,ng)=.false.
4411 END DO
4412 END DO
4413 END DO
4414#endif
4415#ifdef ADJUST_STFLUX
4416!
4417!-----------------------------------------------------------------------
4418! Initilize switches to process surface tracer fluexes for 4DVar
4419! adjustments.
4420!-----------------------------------------------------------------------
4421!
4422 DO ng=1,ngrids
4423 DO i=1,mt
4424 lstflux(i,ng)=.false.
4425 END DO
4426 END DO
4427#endif
4428!
4429!-----------------------------------------------------------------------
4430! Initialize several scalar variables.
4431!-----------------------------------------------------------------------
4432!
4433 one=1.0_r8
4434 zero=0.0_r8
4435 co=1.0_r8/(2.0_r8+sqrt(2.0_r8))
4436 gorho0=g/rho0
4437 DO ng=1,ngrids
4438 ewperiodic(ng)=.false.
4439 nsperiodic(ng)=.false.
4440 nudgingcoeff(ng)=.false.
4441 obcdata(ng)=.false.
4442 setgridconfig(ng)=.true.
4443 processinputdata(ng)=.true.
4444 extractflag(ng)=0
4445 refinescale(ng)=0
4446 gamma2(ng)=-1.0_r8
4447 vtransform(ng)=1
4448 vstretching(ng)=1
4449#if defined AVERAGES && defined AVERAGES_DETIDE && \
4450 (defined ssh_tides || defined uv_tides)
4451 hcount(ng)=0
4452#endif
4453#ifdef ADJUST_BOUNDARY
4454 obccount(ng)=0
4455#endif
4456#if defined ADJUST_STFLUX || defined ADJUST_WSTRESS
4457 sfcount(ng)=0
4458#endif
4459 first_time(ng)=0
4460 idigits(ng)=int(log10(real(lm(ng),r8)))+1
4461 jdigits(ng)=int(log10(real(mm(ng),r8)))+1
4462#ifdef SOLVE3D
4463 kdigits(ng)=int(log10(real(n(ng),r8)))+1
4464#endif
4465 maxspeed(ng)=-large
4466 maxrho(ng)=-large
4467 totvolume(ng)=0.0_dp
4468 minvolume(ng)= large
4469 maxvolume(ng)=-large
4470 dxmin(ng)= large
4471 dxmax(ng)=-large
4472 dymin(ng)= large
4473 dymax(ng)=-large
4474#ifdef MASKING
4475 dxminw(ng)= large
4476 dxmaxw(ng)=-large
4477 dyminw(ng)= large
4478 dymaxw(ng)=-large
4479#endif
4480#ifdef SOLVE3D
4481 dzmin(ng)= large
4482 dzmax(ng)=-large
4483# ifdef MASKING
4484 dzminw(ng)= large
4485 dzmaxw(ng)=-large
4486# endif
4487#endif
4488 grdmax(ng)=-large
4489#ifdef DIFF_3DCOEF
4490 diffmin(ng)= large
4491 diffmax(ng)=-large
4492#endif
4493 cg_min(ng)= large
4494 cg_max(ng)=-large
4495 cg_cor(ng)=-large
4496#ifdef VISC_3DCOEF
4497 viscmin(ng)= large
4498 viscmax(ng)=-large
4499#endif
4500 rx0(ng)=-large
4501 rx1(ng)=-large
4502 clm_file(ng)=.false.
4503 lnudging(ng)=.false.
4504 lnudgem2clm(ng)=.false.
4505 lnudgem3clm(ng)=.false.
4506 lclimatology(ng)=.false.
4507 lm2clm(ng)=.false.
4508 lm3clm(ng)=.false.
4509 lsshclm(ng)=.false.
4510 lsponge(ng)=.false.
4511 luvsponge(ng)=.false.
4512 luvsrc(ng)=.false.
4513 lwsrc(ng)=.false.
4514 DO itrc=1,mt
4515 lnudgetclm(itrc,ng)=.false.
4516 ltracerclm(itrc,ng)=.false.
4517 ltracersrc(itrc,ng)=.false.
4518 ltracersponge(itrc,ng)=.false.
4519 ad_akt_fac(itrc,ng)=1.0_r8
4520 tl_akt_fac(itrc,ng)=1.0_r8
4521 ad_tnu2(itrc,ng)=inival
4522 nl_tnu2(itrc,ng)=inival
4523 tl_tnu2(itrc,ng)=inival
4524 tnu2(itrc,ng)=inival
4525 ad_tnu4(itrc,ng)=inival
4526 nl_tnu4(itrc,ng)=inival
4527 tl_tnu4(itrc,ng)=inival
4528 tnu4(itrc,ng)=inival
4529 END DO
4530 DO itrc=1,nat
4531 akt_limit(itrc,ng)=1.0e-3_r8
4532 END DO
4533 akv_limit(ng)=1.0e-3_r8
4534 ad_akv_fac(ng)=1.0_r8
4535 tl_akv_fac(ng)=1.0_r8
4536 ad_visc2(ng)=inival
4537 nl_visc2(ng)=inival
4538 tl_visc2(ng)=inival
4539 visc2(ng)=inival
4540 ad_visc4(ng)=inival
4541 nl_visc4(ng)=inival
4542 tl_visc4(ng)=inival
4543 visc4(ng)=inival
4544#ifdef BULK_FLUXES
4545 blk_zq(ng)=10.0_r8
4546 blk_zt(ng)=10.0_r8
4547 blk_zw(ng)=10.0_r8
4548#endif
4549 DO i=1,4
4550 volcons(i,ng)=.false.
4551#if defined ADJOINT || defined TANGENT || defined TL_IOMS
4552 ad_volcons(i,ng)=.false.
4553 tl_volcons(i,ng)=.false.
4554#endif
4555 fsobc_in(ng,i)=0.0_dp
4556 fsobc_out(ng,i)=0.0_dp
4557 m2obc_in(ng,i)=0.0_dp
4558 m2obc_out(ng,i)=0.0_dp
4559#ifdef SOLVE3D
4560 m3obc_in(ng,i)=0.0_dp
4561 m3obc_out(ng,i)=0.0_dp
4562#endif
4563 END DO
4564 END DO
4565#ifdef SOLVE3D
4566 tobc_in = 0.0_dp
4567 tobc_out = 0.0_dp
4568#endif
4569!
4570! Initialize blowup string.
4571!
4572 DO i=1,len(blowup_string)
4573 blowup_string(i:i)=' '
4574 END DO
4575!
4576! Initialize thread private variables.
4577!
4578!$OMP PARALLEL
4579 synchro_flag=.false.
4580
4581 ntfirst=1
4582 ntstart=1
4583 ntend=0
4584 step_counter=0
4585!$OMP END PARALLEL
4586
4587#if defined LMD_SKPP || defined LMD_BKPP
4588!
4589! Proportionality coefficient parameterizing boundary layer
4590! nonlocal transport.
4591!
4592 lmd_cg=lmd_cstar* &
4593 & vonkar*(lmd_cs*vonkar*lmd_epsilon)**(1.0_r8/3.0_r8)
4594#endif
4595
4596#if defined FOUR_DVAR || defined VERIFICATION
4597!
4598! Initialize error covariace variables.
4599!
4600 balance=.false.
4601
4602 cnorm=.false.
4603 hdecay=inival
4604 tdecay=inival
4605 vdecay=inival
4606
4607 cnormb=.false.
4608 hdecayb=inival
4609 vdecayb=inival
4610
4611# ifdef STD_MODEL
4612 sigma_max=inival
4613 sigma_ml=inival
4614 sigma_do=inival
4615 sigma_dz=inival
4616 mld_uniform=inival
4617# endif
4618#endif
4619!
4620! Initialize several IO flags.
4621!
4622 lmultigst=.false.
4623 lrstgst=.false.
4624
4625 DO ng=1,ngrids
4626
4627 perfectrst(ng)=.false.
4628
4629 ladjusted(ng)=.false.
4630
4631 lprocessobc(ng)=.false.
4632 lprocesstides(ng)=.false.
4633
4634 ldefadj(ng)=.false.
4635 ldefavg(ng)=.true.
4636 ldefdai(ng)=.false.
4637 ldefdia(ng)=.true.
4638 ldeferr(ng)=.false.
4639#ifdef FLOATS
4640 ldefflt(ng)=.true.
4641#endif
4642 ldefhis(ng)=.true.
4643#ifdef FOUR_DVAR
4644 ldefini(ng)=.true.
4645#else
4646 ldefini(ng)=.false.
4647#endif
4648 ldefirp(ng)=.false.
4649 ldefitl(ng)=.false.
4650 ldefmod(ng)=.false.
4651 ldefqck(ng)=.false.
4652 ldefrst(ng)=.true.
4653 ldefsta(ng)=.true.
4654#ifdef STD_MODEL
4655 ldefstd(ng)=.false.
4656#endif
4657 ldeftlm(ng)=.false.
4658#if defined AVERAGES && defined AVERAGES_DETIDE && \
4659 (defined ssh_tides || defined uv_tides)
4660 ldeftide(ng)=.true.
4661#else
4662 ldeftide(ng)=.false.
4663#endif
4664 lreadadm(ng)=.false.
4665 lreadblk(ng)=.false.
4666#ifdef FRC_FILE
4667 lreadfrc(ng)=.true.
4668#else
4669 lreadfrc(ng)=.false.
4670#endif
4671 lreadfwd(ng)=.false.
4672 lreadqck(ng)=.false.
4673 lreadstd(ng)=.false.
4674 lreadtlm(ng)=.false.
4675 lwrtadj(ng)=.false.
4676 lwrtavg(ng)=.false.
4677 lwrtdia(ng)=.false.
4678 lwrthis(ng)=.false.
4679 lwrtper(ng)=.false.
4680 lwrtqck(ng)=.false.
4681 lwrtrst(ng)=.false.
4682#ifdef STD_MODEL
4683 lwrtstd(ng)=.false.
4684#endif
4685 lwrttlm(ng)=.false.
4686 lwrtxtr(ng)=.false.
4687 lwrtinfo(ng)=.true.
4688 lwrtstate2d(ng)=.false.
4689#ifdef AD_OUTPUT_STATE
4690 lwrtstate3d(ng)=.false.
4691#endif
4692#if defined STOCHASTIC_OPT && !defined STOCH_OPT_WHITE
4693 soinitial(ng)=.false.
4694#endif
4695 lwrttime(ng)=.true.
4696 lwrtcost(ng)=.false.
4697 ldefout(ng)=.false.
4698
4699 END DO
4700!
4701! Initialize the NLM initial conditions time to a negative number to
4702! check if its value was assigned elsewhere. It can be used during
4703! the initialization of the adjoint model when DSTART is not the
4704! same as the start of the simulation.
4705!
4706 DO ng=1,ngrids
4707 initime(ng)=-1.0_dp
4708 initimes(ng)=-1.0_dp
4709 END DO
4710
4711# if defined SG_BBL || defined SSW_BBL
4712!
4713! Nondimensional closure parameters associated with Styles and Glenn
4714! (1999) bottom currents and waves boundary layer.
4715!
4717 sg_mp=cmplx(sqrt(1.0_r8/(2.0_r8*sg_z1p)), &
4718 & sqrt(1.0_r8/(2.0_r8*sg_z1p)))
4719#endif
4720#if defined GLS_MIXING || defined MY25_MIXING
4721# if defined CANUTO_A || defined CANUTO_B
4722!
4723! Compute parameters for Canuto et al. (2001) stability functions.
4724! (Canuto, V.M., Cheng, H.Y., and Dubovikov, M.S., 2001: Ocean
4725! turbulence. Part I: One-point closure model - momentum and
4726! heat vertical diffusivities, JPO, 1413-1426).
4727!
4728 gls_s0=3.0_r8/2.0_r8*gls_l1*gls_l5**2
4729 gls_s1=-gls_l4*(gls_l6+gls_l7)+2.0_r8*gls_l4*gls_l5* &
4730 & (gls_l1-1.0_r8/3.0_r8*gls_l2-gls_l3)+3.0_r8/2.0_r8* &
4732 gls_s2=-3.0_r8/8.0_r8*gls_l1*(gls_l6**2-gls_l7**2)
4733 gls_s4=2.0_r8*gls_l5
4734 gls_s5=2.0_r8*gls_l4
4735 gls_s6=2.0_r8/3.0_r8*gls_l5*(3.0_r8*gls_l3**2-gls_l2**2)- &
4736 & 1.0_r8/2.0_r8*gls_l5*gls_l1*(3.0_r8*gls_l3-gls_l2)+ &
4737 & 3.0_r8/4.0_r8*gls_l1*(gls_l6-gls_l7)
4738 gls_b0=3.0_r8*gls_l5**2
4739 gls_b1=gls_l5*(7.0_r8*gls_l4+3.0_r8*gls_l8)
4740 gls_b2=gls_l5**2*(3.0_r8*gls_l3**2-gls_l2**2)- &
4741 & 3.0_r8/4.0_r8*(gls_l6**2-gls_l7**2)
4742 gls_b3=gls_l4*(4.0_r8*gls_l4+3.0_r8*gls_l8)
4743 gls_b5=1.0_r8/4.0_r8*(gls_l2**2-3.0_r8*gls_l3**2)* &
4744 & (gls_l6**2-gls_l7**2)
4746 & gls_l5*(gls_l2**2-gls_l3**2))+gls_l5*gls_l8* &
4747 & (3.0_r8*gls_l3**2-gls_l2**2)
4748# endif
4749!
4750! Coefficients used to compute stability functions for tracer and
4751! momentum.
4752!
4753 my_b1p2o3=my_b1**(2.0_r8/3.0_r8)
4754 my_b1pm1o3=1.0_r8/(my_b1**(1.0_r8/3.0_r8))
4755 my_e1o2=0.5_r8*my_e1
4756 my_sm1=my_a1*my_a2*((my_b2-3.0_r8*my_a2)* &
4757 & (1.0_r8-6.0_r8*my_a1/my_b1)- &
4758 & 3.0_r8*my_c1*(my_b2+6.0_r8*my_a1))
4759 my_sm2=9.0_r8*my_a1*my_a2
4760 my_sh1=my_a2*(1.0_r8-6.0_r8*my_a1/my_b1)
4761# ifdef KANTHA_CLAYSON
4762 my_sh2=3.0_r8*my_a2*(6.0_r8*my_a1+my_b2*(1.0_r8-my_c3))
4763 my_sm4=18.0_r8*my_a1*my_a1+9.0_r8*my_a1*my_a2*(1.0_r8-my_c2)
4764# else
4765 my_sh2=3.0_r8*my_a2*(6.0_r8*my_a1+my_b2)
4766 my_sm3=my_a1*(1.0_r8-3.0_r8*my_c1-6.0_r8*my_a1/my_b1)
4767 my_sm4=18.0_r8*my_a1*my_a1+9.0_r8*my_a1*my_a2
4768# endif
4769#endif
4770
4771 RETURN
4772 END SUBROUTINE initialize_scalars
4773!
4774 END MODULE mod_scalars
integer, parameter r8
Definition mod_kinds.F:28
integer, parameter dp
Definition mod_kinds.F:25
integer nat
Definition mod_param.F:499
integer, dimension(:), allocatable n
Definition mod_param.F:479
real(r8), dimension(:), allocatable dmem
Definition mod_param.F:137
integer, dimension(:), allocatable lm
Definition mod_param.F:455
integer ndm3d
Definition mod_param.F:579
integer ngrids
Definition mod_param.F:113
integer mt
Definition mod_param.F:490
integer, dimension(:), allocatable mm
Definition mod_param.F:456
integer npt
Definition mod_param.F:505
integer ndm2d
Definition mod_param.F:578
real(dp) blk_dter
real(dp), dimension(:), allocatable cg_min
real(r8) my_sh2
real(r8) my_sh1
real(dp) fbeta
real(r8), dimension(:), allocatable tkenu4
real(dp) bc_flux
real(r8), parameter my_gh0
real(dp) sg_kappa
real(r8), dimension(:), allocatable blk_zt
logical spherical
integer ninner
integer m3vvis
real(r8), dimension(:,:), allocatable tdecay
real(dp) ad_bc_flux
real(r8) my_b1pm1o3
real(dp) sg_g
logical, dimension(:), allocatable clm_file
logical, dimension(:), allocatable luvsrc
integer, dimension(:), allocatable crec
real(dp), dimension(:), allocatable dzmaxw
real(r8) gls_b5
logical, dimension(:,:), allocatable lwrtnrm
real(dp) sg_z100
integer, dimension(:), allocatable kends
integer m2fcor
real(r8), dimension(:), allocatable ad_akv_fac
real(r8) lmd_betat
real(dp), dimension(:), allocatable dxmaxw
real(r8), parameter my_sq
logical, dimension(:), allocatable lwrtqck
real(r8), dimension(:), allocatable gls_p
real(r8), dimension(:), allocatable gls_n
real(r8) cc3
real(r8) gls_b3
real(r8) bvf_numax
real(dp), dimension(:,:), allocatable m3obc_out
real(r8) lmd_tdd2
logical, dimension(:), allocatable lfloats
logical, dimension(:), allocatable lwrtdia
real(r8) lmd_tdd1
real(dp), parameter day2sec
integer, dimension(:), allocatable obccount
real(r8) lmd_epsilon
real(r8), dimension(:,:), allocatable tl_tnu2
integer ityadv
complex(c8) sg_mp
real(dp), dimension(:), allocatable dzmin
logical, dimension(:), allocatable lreadqck
integer, dimension(:), allocatable nrrec
real(dp), dimension(:), allocatable totvolume
real(r8), dimension(:,:), allocatable tnu2
real(dp) cdb_min
logical, dimension(:), allocatable luvsponge
real(r8), parameter my_c3
subroutine, public allocate_scalars
logical lnodal
integer, dimension(:), allocatable ninfo
real(r8) co
integer nouter
integer nrunsave
real(dp), parameter spval
real(dp), dimension(:), allocatable hmin
integer, dimension(:), allocatable nspa
logical, dimension(:,:), allocatable ltracersrc
logical, dimension(:), allocatable lnudgem2clm
real(r8), dimension(:), allocatable tl_m2diff
logical, dimension(:), allocatable ladjusted
real(r8), parameter my_lmax
integer, dimension(:), allocatable ntimes
real(r8), dimension(:), allocatable gls_m
real(dp), dimension(:), allocatable obstime
real(r8) gls_s2
real(dp) falpha
logical, dimension(:), allocatable ldefitl
real(r8), dimension(:), allocatable blk_zw
real(r8), parameter gls_l5
integer m3hadv
integer mstatevar
integer, dimension(:), allocatable nxtr
real(r8), dimension(:), allocatable gls_cmupr
real(r8), dimension(:), allocatable zos_hsig_alpha
integer, dimension(:), allocatable iic
real(r8) gls_s4
integer, dimension(:), allocatable ndefhis
logical, dimension(:), allocatable ldeferr
real(dp), dimension(:), allocatable dzminw
integer m3xadv
real(dp) vonkar
real(r8), dimension(:), allocatable ml_depth
real(r8), dimension(:,:), allocatable tl_tdiff
real(r8), parameter gls_ghcri
integer, dimension(:), allocatable ntlm
real(r8), dimension(:), allocatable t0
real(r8), dimension(:), allocatable el
real(dp), dimension(:), allocatable theta_s
logical, dimension(:), allocatable lreadstd
real(dp), dimension(:), allocatable dt
real(r8), parameter my_qmin
real(r8), dimension(:), allocatable dtdz_min
real(r8), parameter gls_l2
real(r8) lmd_sdd2
integer, parameter sg_n
logical, dimension(:), allocatable ldefhss
subroutine, public initialize_scalars
logical lappend
real(dp), parameter spval_check
integer, dimension(:), allocatable nobc
logical tlmodel
real(r8), parameter gls_l7
logical, dimension(:,:), allocatable ad_volcons
logical lmultigst
logical, dimension(:), allocatable lsponge
real(r8), parameter gls_l3
logical, dimension(:), allocatable setgridconfig
logical lallocatedmemory
real(r8), dimension(:), allocatable latmax
logical, dimension(:), allocatable lwrtxtr
real(r8), parameter gls_l4
real(r8) lambda
real(dp) ubar_xs
real(r8) lmd_nu0c
real(r8) gls_b0
real(dp) ad_volume
real(r8) lmd_cg
real(r8) cc1
real(r8), dimension(:), allocatable dcrit
real(dp) blk_cpw
integer nsaddle
real(r8), dimension(:), allocatable sz_alpha
real(dp), dimension(:), allocatable timeiau
logical, dimension(:), allocatable lprocessobc
integer, dimension(:), allocatable levbfrc
real(dp) tl_bc_area
real(r8) lmd_ri0
integer interpflag
logical, dimension(:,:,:), allocatable lobc
logical lstiffness
integer m2pgrd
logical, dimension(:), allocatable ewperiodic
integer, parameter iwest
real(r8), dimension(:,:), allocatable so_sdev
real(r8) lmd_cm
logical, dimension(:), allocatable nsperiodic
real(dp) sg_znotdef
real(dp), dimension(:), allocatable maxrho
real(r8) lmd_cv
integer m2xadv
real(dp), dimension(:), allocatable minvolume
logical, dimension(:), allocatable lwrttlf
real(r8) lmd_bvfcon
integer m2yadv
logical, dimension(:), allocatable lnudging
integer, dimension(:), allocatable sorec
integer, dimension(:), allocatable nconv
real(dp), parameter large
integer blowup
real(dp), dimension(:), allocatable znudg
real(dp) avgke
logical threeghostpoints
logical, dimension(:), allocatable lm3clm
logical, dimension(:,:), allocatable lstflux
real(dp) bc_area
real(dp) avgpe
logical, dimension(:), allocatable ldefflt
real(r8), dimension(:), allocatable tl_akv_fac
integer, dimension(:), allocatable next_kstp
real(r8) bvf_numin
integer, parameter linear
integer itxdif
integer ithadv
logical, dimension(:), allocatable balance
logical, dimension(:), allocatable ldefdia
real(r8) gls_b2
integer outerloop
real(dp), dimension(:,:,:), allocatable tobc_out
real(r8) bvf_nu0c
logical, dimension(:), allocatable lsshclm
real(dp), dimension(:), allocatable avgtime
logical, dimension(:), allocatable ldeftlf
real(r8), dimension(:), allocatable user
integer, dimension(:), allocatable nrst
integer erend
real(r8), dimension(:,:), allocatable nl_tnu2
real(r8) lmd_nu0s
integer, dimension(:), allocatable nqck
real(dp) sg_cdmax
logical, dimension(:), allocatable synchro_flag
integer, dimension(:), allocatable frcrec
real(dp) sg_znotcdef
real(r8), dimension(9) lmd_mu1
logical, dimension(:), allocatable lreadfrc
real(dp), dimension(:), allocatable m2nudg
logical, dimension(:), allocatable predictor_2d_step
logical, dimension(:), allocatable lastrec
character(len= *), parameter hashmethod
real(r8), dimension(:), allocatable latmin
real(r8), dimension(:), allocatable gls_c2
real(dp), dimension(:,:), allocatable fsobc_out
logical, dimension(:), allocatable lprocesstides
real(r8) lmd_sdd1
integer, dimension(:), allocatable nfrec
real(r8), dimension(:), allocatable charnok_alpha
integer, dimension(:), allocatable ndeftlm
real(dp), dimension(:), allocatable dxmin
real(r8) gls_b4
logical, dimension(:), allocatable ldefini
real(r8), dimension(:), allocatable zos
real(dp), dimension(:,:,:), allocatable tobc_in
real(dp), dimension(:,:), allocatable tnudg
real(r8), dimension(:,:), allocatable s_bgqc
real(dp) sg_tol
real(r8), parameter my_c2
real(r8) lmd_nuwm
integer max_cj
real(dp) cp
logical, dimension(:), allocatable ldeftide
real(r8), dimension(:), allocatable rdrg
logical, dimension(:), allocatable ldefspt
logical, dimension(:), allocatable ldefavg
real(dp), dimension(:,:,:), allocatable weight
logical, dimension(:,:), allocatable ltracersponge
integer itvadv
real(r8), dimension(:), allocatable lnm_depth
logical, dimension(:), allocatable ldeflze
logical admodel
real(dp) bvf_bak
logical, dimension(:), allocatable ldefqck
integer m3vadv
real(r8), parameter my_e1
integer, dimension(:), allocatable jic
real(r8), dimension(:,:), allocatable tl_tnu4
integer, dimension(:), allocatable nflt
real(dp) time_ref
integer, dimension(:), allocatable navg
real(r8), dimension(:,:), allocatable p_bgqc
real(r8), dimension(:), allocatable s0
real(dp), dimension(:), allocatable tdays
real(dp), parameter sg_pi
logical, dimension(:,:), allocatable volcons
real(r8), parameter my_b1
real(dp) tl_ubar_xs
integer, dimension(:), allocatable lmd_jwt
integer nuser
logical, dimension(:), allocatable lwrtavg
real(r8), dimension(:), allocatable dends
real(dp), dimension(:), allocatable frctime
real(dp) eradius
real(r8), parameter gls_l8
integer, dimension(:), allocatable kstrs
real(r8), dimension(:), allocatable tcoef
integer, dimension(:), allocatable idigits
logical, dimension(:), allocatable ldefadj
real(dp), dimension(:), allocatable dymax
real(dp) dstart
real(r8), dimension(:), allocatable akk_bak
real(r8), dimension(:), allocatable gls_cmu0
logical, dimension(:), allocatable frequentimpulse
real(r8), dimension(:), allocatable visc2
logical, dimension(:), allocatable lcycleadj
logical, dimension(:), allocatable getdonordata
type(t_clock) rclock
integer, dimension(:), allocatable nfast
real(r8) lmd_zetam
real(dp), dimension(:), allocatable dymaxw
real(dp), dimension(:), allocatable tcline
integer, dimension(:), allocatable ndtfast
logical, dimension(:), allocatable ldefhis
real(r8), dimension(:,:), allocatable ad_akt_fac
logical, dimension(:), allocatable ldefsct
real(r8), dimension(:), allocatable lonmax
real(r8), parameter gls_ghmin
real(dp), parameter deg2rad
logical, dimension(:), allocatable lwrtadj
logical, dimension(:), allocatable ldefspa
logical, dimension(:), allocatable lwsrc
real(r8), dimension(:), allocatable ad_visc4
real(dp), dimension(:), allocatable obcfac
real(r8), dimension(:), allocatable visc4
real(dp) ad_bc_area
character(len=22) i_code
logical lrstgst
real(dp), parameter sec2day
real(dp), dimension(:), allocatable cg_max
integer, dimension(:), allocatable ntend
real(r8) max_cu
integer max_ci
logical, dimension(:), allocatable lcycletlm
subroutine, public deallocate_scalars(ng)
real(r8), dimension(:), allocatable gls_sigk
integer m3xvis
real(dp) csolar
logical, dimension(:), allocatable ldefmod
real(dp) blk_zabl
real(r8), dimension(:), allocatable tl_visc4
real(r8), parameter my_c1
real(r8) my_sm3
logical, dimension(:), allocatable ldefirp
real(r8), parameter my_a1
real(r8), dimension(:), allocatable crgban_cw
logical, dimension(:), allocatable obcdata
real(r8), dimension(9) lmd_mu2
logical, dimension(:,:), allocatable ldefnrm
real(dp), dimension(:), allocatable theta_b
real(r8) my_sm4
real(dp) sg_alpha
integer, parameter cubic
real(dp) ad_ubar_xs
real(dp) gorho0
real(dp) volume
integer, dimension(:), allocatable first_time
character(len=22), dimension(:), allocatable time_code
real(r8) lmd_zetas
real(r8) sp_sumdot
logical, dimension(:), allocatable lsediment
real(dp) blk_visw
logical, dimension(:), allocatable lwrtcost
real(dp), dimension(:), allocatable dxminw
integer, dimension(:), allocatable hcount
real(r8), dimension(:,:,:), allocatable vdecay
real(dp) blk_tcw
real(r8) my_sm2
real(r8), dimension(:), allocatable gamma2
integer exit_flag
real(dp) ritz_tol
real(dp), dimension(:), allocatable maxvolume
integer, dimension(:), allocatable extractflag
integer itrate
integer, dimension(:), allocatable ndefqck
logical, dimension(:), allocatable lwrtinfo
logical, dimension(:), allocatable nudgingcoeff
real(r8), parameter my_a2
real(dp) blk_rgas
real(dp), dimension(:), allocatable grdmax
integer isalt
real(dp), dimension(:), allocatable rx1
integer, dimension(:), allocatable nsta
integer, dimension(:), allocatable nrecfrc
real(r8), dimension(:,:), allocatable ad_tnu2
real(r8), dimension(:,:), allocatable akt_bak
logical, dimension(:), allocatable lnudgem3clm
logical, dimension(:), allocatable iauswitch
logical, dimension(:), allocatable lwrtstate2d
integer m2hvis
real(dp), dimension(:), allocatable hc
real(dp), dimension(:), allocatable time4jedi
real(dp), dimension(:), allocatable initimes
real(dp), parameter jul_off
integer, dimension(:), allocatable nhis
real(dp), dimension(:), allocatable diatime
real(r8), dimension(:), allocatable akv_bak
real(r8), dimension(:), allocatable gls_pmin
integer, dimension(:), allocatable ndefavg
logical, dimension(:), allocatable lreadtlm
real(r8), parameter gls_e2
real(dp) sg_nu
logical, dimension(:), allocatable lwrtper
integer, dimension(:), allocatable indx1
integer m3hvis
logical, dimension(:,:), allocatable compositegrid
real(r8), dimension(:), allocatable nl_visc4
integer, dimension(:), allocatable kdigits
real(r8), dimension(:), allocatable lonmin
real(r8) my_e1o2
real(r8) gls_s1
logical, dimension(:), allocatable lclimatology
integer itemp
real(r8) lmd_ric
real(dp) stefbo
real(r8), dimension(:), allocatable ad_visc2
integer m3rate
logical, dimension(:,:), allocatable cnorm
integer, dimension(:), allocatable sfcount
real(r8), dimension(:,:), allocatable ad_tnu4
real(r8), parameter gls_l6
integer, dimension(:), allocatable bgqc_type
real(r8) bvf_nu0
real(r8), dimension(:), allocatable tl_visc2
logical, dimension(:), allocatable ldefxtr
real(r8) max_cw
real(r8), dimension(4) hgamma
integer, dimension(:), allocatable nsca
real(r8) lmd_cmonob
real(r8) lmd_cstar
real(r8), dimension(:,:), allocatable nl_tnu4
real(dp) rhow
real(dp), dimension(:), allocatable dzmax
real(dp), dimension(:,:), allocatable obc_time
real(r8) lmd_fdd
integer, parameter isouth
real(r8), dimension(:), allocatable nl_visc2
integer, dimension(:), allocatable ndefxtr
real(r8), dimension(:), allocatable akp_bak
integer m3yadv
integer nintervals
real(r8) my_b1p2o3
real(r8) my_sm1
logical, dimension(:), allocatable sporadicimpulse
real(dp) myruninterval
real(r8), dimension(:,:), allocatable akt_limit
real(r8), parameter my_b2
type(t_scalars), dimension(:), allocatable scalars
Definition mod_scalars.F:65
real(r8), dimension(:), allocatable blk_zq
integer maxitergst
integer erstr
real(dp) fgamma
real(r8), dimension(:), allocatable gls_c1
integer itsdif
integer, dimension(:), allocatable nspt
integer m3yvis
real(r8) cc2
real(r8), dimension(:), allocatable dstrs
integer m2rate
logical, dimension(:), allocatable lm2clm
real(r8), dimension(9) lmd_r1
real(dp) blk_beta
integer max_ck
real(r8), dimension(:), allocatable akv_limit
logical, dimension(:), allocatable perfectrst
real(dp), dimension(:), allocatable timeend
real(r8), dimension(:), allocatable zob
real(dp) sg_ustarcdef
real(dp), dimension(:), allocatable m3nudg
real(r8), dimension(:), allocatable rdrg2
real(r8) gls_s6
real(dp) avgkp
integer itvdif
integer, dimension(:), pointer inert
real(r8), dimension(:,:,:), allocatable hdecayb
real(r8), parameter gls_gh0
logical, dimension(:), allocatable lwrttime
real(dp), dimension(:), allocatable dxmax
real(r8) max_cv
real(r8), dimension(:), allocatable tl_m3diff
logical, dimension(:), allocatable ldefsca
logical, dimension(:), allocatable lwrthis
logical, dimension(:,:), allocatable tl_volcons
integer m2yvis
real(r8), dimension(:,:), allocatable kdiff
logical, dimension(:), allocatable lreadadm
integer lnm_flag
real(r8) lmd_rrho0
real(r8) lmd_as
character(len=20) phase4dvar
real(dp), dimension(:), allocatable dtfast
integer, dimension(:), allocatable ntfirst
real(dp), dimension(:,:), allocatable m2obc_out
real(dp) max_rho
integer m3fcor
real(dp) tl_bc_flux
logical, dimension(:), allocatable ldefrst
integer m2sstr
real(dp), dimension(:), allocatable imptime
logical, dimension(:), allocatable lbiology
logical, dimension(:), allocatable lwrttlm
logical, dimension(:), allocatable ldefout
logical, dimension(:), allocatable lwrtrst
real(dp), parameter rad2deg
integer, parameter ieast
real(dp) g
real(r8), dimension(:), allocatable xl
integer m2hadv
integer itydif
real(dp), dimension(:), allocatable time
real(r8), parameter gls_l1
real(r8), parameter my_e2
integer, dimension(:), allocatable nsct
real(dp) cdb_max
real(dp) dstarts
real(r8) lmd_am
logical, dimension(:), allocatable ldefsta
real(dp) sg_z1p
logical, dimension(:), allocatable refinedgrid
logical, dimension(:), allocatable lstations
real(r8) lmd_cs
real(r8) lmd_nu
logical, dimension(:), allocatable ldeftlm
logical, dimension(:,:), allocatable ltracerclm
real(r8) max_c
integer, dimension(:), allocatable nsff
real(dp) infinity
integer, dimension(:), allocatable refinescale
real(r8), dimension(:), allocatable gls_sigp
character(len=80) blowup_string
real(r8) gls_s5
real(dp) rho0
integer, dimension(:), allocatable ntstart
real(r8), dimension(:), allocatable tkenu2
integer nrun
integer, dimension(:), allocatable step_counter
real(r8) gls_s0
real(dp), dimension(:,:), allocatable sf_time
real(r8), dimension(:,:), allocatable tnu4
real(r8), dimension(:), allocatable gls_kmin
logical, dimension(:), allocatable processinputdata
integer, parameter inorth
integer, dimension(:), allocatable ndefadj
integer, dimension(:), allocatable levsfrc
integer, dimension(:), allocatable nbrec
logical, dimension(:), allocatable ldeflcz
real(r8), dimension(:), allocatable trnorm
integer m3pgrd
real(dp), dimension(:), allocatable hmax
logical, dimension(:,:), allocatable cnormb
integer, dimension(:), allocatable nadj
real(dp), dimension(:), allocatable rx0
logical, dimension(:), allocatable ldefdai
integer, dimension(:), allocatable jdigits
real(r8) lmd_sdd3
integer, dimension(:), allocatable ndia
real(r8), dimension(:), allocatable r0
integer m2xvis
integer, dimension(:), allocatable vstretching
real(dp) blk_cpa
logical, dimension(:,:), allocatable lnudgetclm
integer, dimension(:), allocatable nprovenance
real(r8), dimension(:), allocatable so_decay
logical, dimension(:), allocatable lreadfwd
integer inner
integer m2bstr
integer itxadv
real(r8) gls_b1
integer, dimension(:), allocatable iif
real(dp), dimension(:), allocatable dymin
real(dp), dimension(:,:), allocatable m2obc_in
real(dp) io_time
real(dp) run_time
real(r8) lmd_nu0m
integer, dimension(:), allocatable ntsdia
real(dp), dimension(:), allocatable cg_cor
real(dp) sg_z1min
real(r8), dimension(:,:,:), allocatable vdecayb
integer, dimension(:,:), allocatable iprovenance
real(dp), dimension(:), allocatable initime
integer, dimension(:), allocatable ntsavg
integer noerror
real(dp) emmiss
real(r8) lmd_nuws
real(dp) max_speed
real(r8) gls_s3
integer, dimension(:), allocatable ndefdia
logical, dimension(:), allocatable lcyclerst
real(r8), dimension(:,:,:), allocatable hdecay
real(r8), dimension(:), allocatable gls_c3m
real(dp), dimension(:,:), allocatable fsobc_in
real(r8) lmd_nuf
real(r8), dimension(:), allocatable scoef
real(dp), dimension(:), allocatable maxspeed
real(r8) lmd_cekman
real(dp) tide_start
real(dp), parameter pi
integer outer
real(r8), dimension(:,:), allocatable tl_akt_fac
real(r8), parameter my_dtfac
real(r8), dimension(:), allocatable wec_alpha
real(r8), dimension(4) vgamma
logical, dimension(:), allocatable lreadblk
real(dp), dimension(:), allocatable dyminw
integer ithdif
real(dp), dimension(:,:), allocatable m3obc_in
integer, dimension(:), allocatable vtransform
real(r8) bgqc_large
character(len=22) f_code
real(r8), dimension(:), allocatable gls_c3p
real(r8) lmd_tdd3