source: trunk/Roms_agrif/scalars.h @ 3

Last change on this file since 3 was 3, checked in by pinsard, 17 years ago

add Roms_agrif level (forgot in changeset:2)

File size: 14.9 KB
Line 
1!
2! $Id: scalars.h,v 1.12 2005/10/10 13:40:18 pmarches Exp $
3!
4! This is include file "scalars.h"
5!---------------------------------
6!
7!  The following common block contains time variables and indices
8! for 2D (k-indices) and 3D (n-indices) computational engines. Since
9! they are changed together, they are placed into the same cache line
10! despite their mixed type, so that only one cachene is being
11! invalidated and has to be propagated accross the cluster.
12!
13! Note that the real values are placed first into the common block
14! before the integer variables. This is done to prevent the
15! possibility of misallignment of the 8-byte objects in the case
16! when an uneven number of 4-byte integers is placed before a 8-byte
17! real (in the case when default real size is set to 8bytes).
18! Thought misallignment is not formally a violation of fortran
19! standard, it may cause performance degradation and/or make compiler
20! issue a warning message (Sun, DEC Alpha) or even crash (Alpha).
21!
22! time        Time since initialization [seconds];
23! time_start  Initialization time [seconds];
24! tdays       Time since initialization [days];
25! dt          Time step for 3D primitive equations [seconds];
26! dtfast      Time step for 2D (barotropic) mode [seconds];
27!
28      real dt, dtfast, time, time_start, tdays
29      integer iic, kstp, krhs, knew, next_kstp
30#ifdef SOLVE3D
31     &      , iif, nstp, nrhs, nnew, nbstep3d
32#endif
33#ifdef FLOATS
34     &      , nfp1, nf, nfm1, nfm2, nfm3
35#endif
36      logical PREDICTOR_2D_STEP
37      common /time_indices/  dt,dtfast, time,time_start, tdays, 
38     &                       iic, kstp, krhs, knew, next_kstp,
39#ifdef SOLVE3D
40     &                       iif, nstp, nrhs, nnew, nbstep3d,
41#endif
42#ifdef FLOATS
43     &                       nfp1, nf, nfm1, nfm2, nfm3,
44#endif
45     &                       PREDICTOR_2D_STEP
46
47!
48! Slowly changing variables: these are typically set in the beginning
49! of the run and either remain unchanged, or are changing only in
50! association with the I/0. 
51!
52! xl, el   Physical size (m) of domain box in the XI-,ETA-directions.
53!
54! Tcline   Width (m) of surface or bottom boundary layer in which
55!          higher vertical resolution is required during stretching.
56! theta_s  S-coordinate surface control parameter, [0<theta_s<20].
57! theta_b  S-coordinate bottom control parameter, [0<theta_b<1].
58! hc       S-coordinate parameter, hc=min(hmin,Tcline).
59!
60! sc_r     S-coordinate independent variable, [-1 < sc < 0] at
61!             vertical RHO-points
62! sc_w     S-coordinate independent variable, [-1 < sc < 0] at
63!             vertical W-points.
64! Cs_r     Set of S-curves used to stretch the vertical coordinate
65!             lines that follow the topography at vertical RHO-points.
66! Cs_w     Set of S-curves used to stretch the vertical coordinate
67!             lines that follow the topography at vertical W-points.
68!
69! rho0     Boussinesque Approximation Mean density [kg/m^3].
70! R0       Background constant density anomaly [kg/m^3] used in
71!                                      linear equation of state.
72! T0,S0    Background temperature (Celsius) and salinity [PSU]
73!                          values used in analytical fields;
74! Tcoef    Thermal expansion coefficient in linear EOS;
75! Scoef    Saline contraction coefficient in linear EOS;
76!
77! rdrg     Linear bottom drag coefficient.
78! rdrg2    Quadratic bottom drag coefficient.
79! Cdb_max  Maximum bottom drag coefficient allowed.
80! Cdb_min  Minimum bottom drag coefficient to avoid the
81!                law-of-the-wall to extend indefinitely.
82! Zob      Bottom roughness (m).
83! 
84! gamma2   Slipperiness parameter, either 1. (free-slip)
85!
86! ntstart  Starting timestep in evolving the 3D primitive equations;
87!                              usually 1, if not a restart run.
88! ntimes   Number of timesteps for the 3D primitive equations in
89!                                                    the current run.
90! ndtfast  Number of timesteps for 2-D equations between each "dt".
91!
92! nrst     Number of timesteps between storage of restart fields.
93! nwrt     Number of timesteps between writing of fields into
94!                                                     history file.
95! ninfo    Number of timesteps between print of single line
96!                                   information to standard output.
97! nsta     Number of timesteps between storage of station data.
98! navg     Number of timesteps between storage of time-averaged
99!                                                           fields.
100! ntsavg   Starting timestep for accumulation of output time-
101!                                                 averaged fields.
102! nrrec    Counter of restart time records to read from disk,
103!                   the last is used as the initial conditions.
104!
105! ldefhis  Logical switch used to create the history file.
106!             If TRUE, a new history file is created. If FALSE,
107!             data is appended to an existing history file.
108! levsfrc  Deepest level to apply surface momentum stress as
109!                                                 bodyforce.
110! levbfrc  Shallowest level to apply bottom momentum stress as
111!                                                 bodyforce.
112! got_tini Logical switch used at initialisation
113!              If TRUE, the tracer is present in the initial file
114!              If FALSE, the tracer needs an analytical value 
115!
116! got_inised Logical switch used at initialisation  of sediments
117!              If TRUE, the sediment var. is in the initial file
118!              If FALSE, the sed. var. gets analytical value from file
119!
120! got_inibed Logical switch used at initialisation of ripple height, length
121!              If TRUE, the ripple var. is in the initial file
122!              If FALSE, the ripple var. is obtained from file (ifdef also SEDIMENT)
123!                        the ripple var. is set in ana_bsedim (ifndef SEDIMENT)
124!
125      real time_avg, rho0
126     &               , rdrg, rdrg2, Cdb_min, Cdb_max, Zob
127     &               , xl, el, visc2, visc4, gamma2
128#ifdef SOLVE3D
129      real  theta_s,   theta_b,   Tcline,  hc
130      real  sc_w(0:N), Cs_w(0:N), sc_r(N), Cs_r(N)
131      real  rx0, rx1
132      real  tnu2(NT),tnu4(NT)
133# ifdef MY25_MIXING
134      real Akq_bak, q2nu2, q2nu4
135# endif
136# ifndef NONLIN_EOS
137      real R0,T0,S0, Tcoef, Scoef
138# endif
139      real weight(6,0:NWEIGHT)
140
141#endif
142#if  defined SPONGE || \
143     defined TNUDGING   || defined M2NUDGING  || \
144     defined M3NUDGING  || defined ZNUDGING
145      real  x_sponge,   v_sponge
146#endif
147#if  defined T_FRC_BRY  || defined M2_FRC_BRY || \
148     defined M3_FRC_BRY || defined Z_FRC_BRY  || \
149     defined TNUDGING   || defined M2NUDGING  || \
150     defined M3NUDGING  || defined ZNUDGING
151       real  tauT_in, tauT_out, tauM_in, tauM_out
152#endif
153      integer numthreads,     ntstart,   ntimes,  ninfo
154     &      , ndtfast,nfast,  nrrec,     nrst,    nwrt
155#ifdef AVERAGES
156     &                                 , ntsavg,  navg
157#endif
158#ifdef BODYFORCE
159     &                      , levbfrc,   levsfrc
160#endif
161#ifdef FLOATS
162      integer nflt, nrpfflt
163#endif
164#if defined DIAGNOSTICS_TS
165      integer nwrtdia
166# ifdef AVERAGES
167      integer ntsdia_avg, nwrtdia_avg
168# endif
169#endif
170#if defined DIAGNOSTICS_UV
171      integer nwrtdiaM
172# ifdef AVERAGES
173      integer ntsdiaM_avg, nwrtdiaM_avg
174# endif
175#endif
176#ifdef DIAGNOSTICS_BIO
177      integer nwrtdiabio
178# ifdef AVERAGES
179      integer ntsdiabio_avg, nwrtdiabio_avg
180# endif
181#endif
182#ifdef STATIONS
183      integer nsta, nrpfsta
184#endif
185
186      logical ldefhis
187#ifdef SOLVE3D
188      logical got_tini(NT)
189#endif
190#ifdef SEDIMENT
191      logical got_inised(3)
192#endif
193#ifdef BBL
194      logical got_inibed(2)
195#endif
196#ifdef FLOATS
197      logical ldefflt
198#endif
199#if defined DIAGNOSTICS_TS
200      logical ldefdia
201# ifdef AVERAGES
202      logical ldefdia_avg
203# endif
204#endif
205#if defined DIAGNOSTICS_UV
206      logical ldefdiaM
207# ifdef AVERAGES
208      logical ldefdiaM_avg
209# endif
210#endif
211#ifdef DIAGNOSTICS_BIO
212      logical ldefdiabio
213# ifdef AVERAGES
214      logical ldefdiabio_avg
215# endif
216#endif
217#ifdef STATIONS
218      logical ldefsta
219#endif
220
221      common /scalars_main/
222     &             time_avg,  rho0,      rdrg,    rdrg2
223     &           , Zob,       Cdb_min,   Cdb_max
224     &           , xl, el,    visc2,     visc4,   gamma2
225#ifdef SOLVE3D
226     &           , theta_s,   theta_b,   Tcline,  hc
227     &           , sc_w,      Cs_w,      sc_r,    Cs_r
228     &           , rx0,       rx1,       tnu2,    tnu4
229# ifdef MY25_MIXING
230     &                      , Akq_bak,   q2nu2,   q2nu4
231# endif
232# ifndef NONLIN_EOS
233     &                      , R0,T0,S0,  Tcoef,   Scoef
234# endif
235     &                      , weight
236#endif
237#if  defined SPONGE || \
238     defined TNUDGING   || defined M2NUDGING  || \
239     defined M3NUDGING  || defined ZNUDGING
240     &                      , x_sponge,   v_sponge
241#endif
242#if  defined T_FRC_BRY  || defined M2_FRC_BRY || \
243     defined M3_FRC_BRY || defined Z_FRC_BRY  || \
244     defined TNUDGING   || defined M2NUDGING  || \
245     defined M3NUDGING  || defined ZNUDGING
246     &                      , tauT_in, tauT_out, tauM_in, tauM_out
247#endif
248     &      , numthreads,     ntstart,   ntimes,  ninfo
249     &      , ndtfast,nfast,  nrrec,     nrst,    nwrt
250#ifdef AVERAGES
251     &                                 , ntsavg,  navg
252#endif
253#ifdef BODYFORCE
254     &                      , levbfrc,   levsfrc
255#endif
256#ifdef FLOATS
257     &                      , nflt, nrpfflt
258#endif
259#ifdef STATIONS
260     &                      , nsta, nrpfsta
261#endif
262     &                      , ldefhis
263#ifdef SOLVE3D
264     &                      , got_tini
265#endif
266#ifdef SEDIMENT
267     &                      , got_inised
268#endif
269#ifdef BBL
270     &                      , got_inibed
271#endif
272#ifdef FLOATS
273     &                      , ldefflt
274#endif
275#if defined DIAGNOSTICS_TS
276     &                      , ldefdia, nwrtdia
277# ifdef AVERAGES
278     &                      , ldefdia_avg
279     &                      , nwrtdia_avg
280     &                      , ntsdia_avg
281# endif
282#endif
283#if defined DIAGNOSTICS_UV
284     &                      , ldefdiaM, nwrtdiaM
285# ifdef AVERAGES
286     &                      , ldefdiaM_avg
287     &                      , nwrtdiaM_avg
288     &                      , ntsdiaM_avg
289# endif
290#endif
291#ifdef DIAGNOSTICS_BIO
292     &                      , ldefdiabio, nwrtdiabio
293# ifdef AVERAGES
294     &                      , ldefdiabio_avg
295     &                      , nwrtdiabio_avg
296     &                      , ntsdiabio_avg
297# endif
298#endif
299#ifdef STATIONS
300     &                      , ldefsta
301#endif
302
303# if defined SOLVE3D     && !defined LMD_MIXING \
304  && !defined MY2_MIXING && !defined MY25_MIXING
305      real Akv_bak
306      real Akt_bak(NT)
307      common /scalars_akt/ Akv_bak, Akt_bak
308# endif
309!
310! This following common block contains a set of globally accessable
311! variables in order to allow information exchange between parallel
312! threads working on different subdomains.
313!
314! Global summation variables are declared with 16 byte precision
315! to avoid accumulation of roundoff errors, since roundoff  error
316! depends on the order of summation, which is undeterministic in
317! the case of summation between the parallel threads; not doing so
318! would make itimpossible to pass an ETALON CHECK test if there is
319! a feedback of these sums into the dynamics of the model, such as
320! in the case when global mass conservation is enforced. 
321!
322!  One sunny spring day, sometime in 1989 an american tourist, who
323! happened to be an attorney, was walking along a Moscow street.
324! Because it was the period of 'Perestroika' (which literally means
325! 'remodelling'), so that a lot of construction was going on in
326! Moscow, dozens of holes and trenches were open on the street. He
327! felt into one of them, broke his leg, ended up in a hospital and
328! complaining: In my country if a construction firm would not place
329! little red flags around the construction zone to warn passers-by
330! about the danger, I will sue em for their negligence! The doctor,
331! who was performing surgery on his leg replied to him: Did not you
332! see the one big red flag above the whole country in the first place?
333!
334! WARNING: FRAGILE ALIGNMENT SEQUENCE: In the following common block:
335! since real objects are grouped in pairs and integer*4 are grouped
336! in quartets, it is guaranteed that 16 Byte objects are aligned
337! in 16 Byte boundaries and 8 Byte objects are aligned in 8 Byte
338! boundaries. Removing or introduction of variables with violation
339! of parity, as well as changing the sequence of variables in the
340! common block may cause violation of alignment.
341!
342      logical synchro_flag
343      common /sync_flag/ synchro_flag
344
345      integer may_day_flag  ! This is a shared variable among nested grids
346      integer tile_count, first_time, bc_count
347#ifdef BIOLOGY
348     &      , bio_count
349#endif
350      common /communicators_i/
351     &        may_day_flag, tile_count, first_time, bc_count
352#ifdef BIOLOGY
353     &      , bio_count
354#endif
355
356      real hmin, hmax, grdmin, grdmax, Cu_min, Cu_max
357      common /communicators_r/
358     &     hmin, hmax, grdmin, grdmax, Cu_min, Cu_max
359
360      real*QUAD volume, avgke, avgpe, avgkp, bc_crss
361#ifdef OBC_VOLCONS
362     &        , bc_flux, ubar_xs
363#endif
364#ifdef BIOLOGY
365     &        , global_sum(0:2*NT+1)
366#endif
367      common /communicators_rq/
368     &          volume, avgke, avgpe, avgkp, bc_crss
369#ifdef OBC_VOLCONS
370     &        , bc_flux,  ubar_xs
371#endif
372#ifdef BIOLOGY
373     &        , global_sum
374#endif
375!
376!  The following common block contains process counters and model
377! timers. These are used to measure CPU time consumed by different
378! parallel threads during the whole run, as well as in various
379! parallel regions, if so is needed. These variables are used purely
380! for diagnostic/performance measurements purposes and do not affect
381! the model results.
382!
383      real*4 CPU_time(0:31,0:NPP)
384      integer proc(0:31,0:NPP),trd_count
385      common /timers/CPU_time,proc,trd_count
386
387#ifdef MPI
388!
389! MPI rlated variables
390! === ====== =========
391!
392      logical EAST_INTER, WEST_INTER, NORTH_INTER, SOUTH_INTER
393      integer mynode, ii,jj, p_W,p_E,p_S,p_N, p_SW,p_SE, p_NW,p_NE
394      common /comm_setup/ mynode, ii,jj, p_W,p_E,p_S,p_N, p_SW,p_SE,
395     &  p_NW,p_NE, EAST_INTER, WEST_INTER, NORTH_INTER, SOUTH_INTER
396         
397#endif
398
399!
400! Physical constants:
401! ======== ==========
402
403      real pi, deg2rad, rad2deg
404      parameter (pi=3.14159265358979323846, deg2rad=pi/180.,
405     &                                      rad2deg=180./pi)
406!
407! Earth radius [m]; Aceleration of gravity [m/s^2], duration
408! of the day in seconds and its inverse; Julian offset day.
409
410      real Eradius, g, day2sec,sec2day, jul_off,
411     &     year2day,day2year
412      parameter (Eradius=6371315.0,  day2sec=86400.,
413     &           sec2day=1./86400., jul_off=2440000.,
414     &           year2day=365.25, day2year=1./365.25)
415!
416! Acceleration of gravity (nondimensional for Soliton problem)
417!
418#ifdef SOLITON
419      parameter (g=1.)
420#else
421      parameter (g=9.81)
422#endif
423!
424!  Specific heat [Joules/kg/degC] for seawater, it is approximately
425!  4000, and varies only slightly (see Gill, 1982, Appendix 3).
426!
427      real Cp
428      parameter (Cp=3985.0)
429
430      real vonKar
431      parameter (vonKar=0.41)
432
433
Note: See TracBrowser for help on using the repository browser.