Ticket #12: mod_param.F

File mod_param.F, 18.7 KB (added by m.hadfield, 17 years ago)
Line 
1#include "cppdefs.h"
2 MODULE mod_param
3!
4!svn $Id: mod_param.F 48 2007-05-09 16:15:44Z arango $
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2007 The ROMS/TOMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.txt !
9!=======================================================================
10! !
11! Grid parameters: !
12! !
13! Im Number of global grid points in the XI-direction !
14! for each nested grid. !
15! Jm Number of global grid points in the ETA-direction !
16! for each nested grid. !
17! Lm Number of interior grid points in the XI-direction !
18! for each nested grid. !
19! Mm Number of internal grid points in the ETA-direction. !
20! for each nested grid. !
21! N Number of vertical levels for each nested grid. !
22! Ngrids Number of nested and/or connected grids to solve. !
23! NtileI Number of XI-direction tiles or domain partitions for !
24! each nested grid. Values used to compute tile ranges. !
25! NtileJ Number of ETA-direction tiles or domain partitions for !
26! each nested grid. Values used to compute tile ranges. !
27! NtileX Number of XI-direction tiles or domain partitions for !
28! each nested grid. Values used in parallel loops. !
29! NtileE Number of ETA-direction tiles or domain partitions for !
30! each nested grid. Values used in parallel loops. !
31! HaloSizeI Maximum halo size, in grid points, in XI-direction. !
32! HaloSizeJ Maximum halo size, in grid points, in ETA-direction. !
33! TileSide Maximun tile side length in XI- or ETA-directions. !
34! TileSize Maximum tile size. !
35! !
36! Configuration parameters: !
37! !
38! Nfloats Number of floats tracjectories. !
39! Nstation Number of output stations. !
40! MTC Maximum number of tidal components. !
41! NSV Number of model state variables. !
42! !
43! Tracer parameters: !
44! !
45! NAT Number of active tracer type variables (usually, !
46! NAT=2 for potential temperature and salinity). !
47! NBT Number of biological tracer type variables. !
48! NST Number of sediment tracer type variables (NCS+NNS). !
49! NPT Number of extra passive tracer type variables to !
50! advect and diffuse only (dyes, etc). !
51! NT Total number of tracer type variables. !
52! MT Maximum number of tracer type variables. !
53! !
54! Nbed Number of sediment bed layers. !
55! NCS Number of cohesive (mud) sediment tracers. !
56! NNS Number of non-cohesive (sand) sediment tracers. !
57! !
58! NBands Number of spectral irradiance bands in EcoSim. !
59! Nbac Number of bacteria constituents in EcoSim. !
60! Ndom Number of dissolved matter constituents in EcoSim. !
61! Nfec Number of fecal matter constituents in EcoSim. !
62! Nphy Number of phytoplankton constituents in EcoSim. !
63! Npig Number of pigment constituents in EcoSim. !
64! PHY EcoSim indices of phytoplankton species considered. !
65! PIG EcoSim phytoplankton-pigment matrix. !
66! !
67! Diagnostic fields parameters: !
68! !
69! NDbio2d Number of diagnostic 2D biology fields. !
70! NDbio3d Number of diagnostic 3D biology fields. !
71! NDT Number of diagnostic tracer fields. !
72! NDM2d Number of diagnostic 2D momentum fields. !
73! NDM3d Number of diagnostic 3D momentum fields. !
74! NDrhs Number of diagnostic 3D right-hand-side fields. !
75! !
76!=======================================================================
77!
78 USE mod_kinds
79!
80 implicit none
81!
82!-----------------------------------------------------------------------
83! Model grid(s) parameters.
84!-----------------------------------------------------------------------
85!
86! Number of nested and/or connected grids to solve.
87!
88 integer, parameter :: Ngrids = NestedGrids
89!
90! Number of interior RHO-points in the XI- and ETA-directions. The
91! size of models state variables (C-grid) at input and output are:
92!
93! RH0-type variables: [0:Lm+1, 0:Mm+1] ----v(i,j+1)----
94! PSI-type variables: [1:Lm+1, 1:Mm+1] | |
95! U-type variables: [1:Lm+1, 0:Mm+1] u(i,j) r(i,j) u(i+1,j)
96! V-type variables: [0:Lm+1, 1:Mm+1] | |
97! -----v(i,j)-----
98 integer, dimension(Ngrids) :: Lm
99 integer, dimension(Ngrids) :: Mm
100!
101! Global horizontal size of model arrays including padding. All the
102! model state arrays are of same size to facilitate parallelization.
103!
104 integer, dimension(Ngrids) :: Im
105 integer, dimension(Ngrids) :: Jm
106!
107! Number of vertical levels. The vertical ranges of model state
108! variables are:
109! -----W(i,j,k)-----
110! RHO-, U-, V-type variables: [1:N] | |
111! W-type variables: [0:N] | r(i,j,k) |
112! | |
113! ----W(i,j,k-1)----
114 integer, dimension(Ngrids) :: N
115!
116!-----------------------------------------------------------------------
117! Tracers parameters.
118!-----------------------------------------------------------------------
119!
120! Total number of tracer type variables, NT(:) = NAT + NBT + NPT + NST.
121! The MT corresponds to the maximum number of tracers between all
122! nested grids.
123!
124 integer, dimension(Ngrids) :: NT
125 integer :: MT
126!
127! Number of active tracers. Usually, NAT=2 for potential temperature
128! and salinity.
129!
130 integer :: NAT = 0
131!
132! Total number of inert passive tracers to advect and diffuse only
133! (like dyes, etc). This parameter is independent of the number of
134! biological and/or sediment tracers.
135!
136 integer :: NPT = 0
137!
138!-----------------------------------------------------------------------
139! Sediment tracers parameters.
140!-----------------------------------------------------------------------
141!
142! Number of sediment bed layes.
143!
144 integer :: Nbed = 0
145!
146! Total number of sediment tracers, NST = NCS + NNS.
147!
148 integer :: NST = 0
149!
150! Number of cohesive (mud) sediments.
151!
152 integer :: NCS
153!
154! Number of non-cohesive (sand) sediments.
155!
156 integer :: NNS
157
158#ifdef BIOLOGY
159!
160!-----------------------------------------------------------------------
161! Biological tracers parameters.
162!-----------------------------------------------------------------------
163
164# if defined BIO_FASHAM
165!
166! Number of tracers for Fasham-type, Nitrogen-based biological model.
167!
168# ifdef CARBON
169# ifdef OXYGEN
170 integer, parameter :: NBT = 12
171# else
172 integer, parameter :: NBT = 11
173# endif
174# else
175# ifdef OXYGEN
176 integer, parameter :: NBT = 8
177# else
178 integer, parameter :: NBT = 7
179# endif
180# endif
181# elif defined BIO_LIMADONEY
182!
183! Number of tracers for Lima and Doney (2004) ecological model.
184!
185 integer, parameter :: NBT = 14
186# elif defined NPZD_FRANKS || defined NPZD_POWELL
187!
188! Number of tracers for NPZD model.
189!
190 integer, parameter :: NBT = 4
191# elif defined ECOSIM
192!
193! Bio-optical EcoSim parameters.
194!
195 integer, parameter :: NBands = 60 ! spectral bands
196 integer, parameter :: Nbac = 1 ! bacteria constituents
197 integer, parameter :: Ndom = 2 ! DOM constituents
198 integer, parameter :: Nfec = 2 ! Fecal constituents
199 integer, parameter :: Nphy = 4 ! Phytoplankton groups
200 integer, parameter :: Npig = 7 ! Pigments
201!
202! Determine number of EcoSim biological tracer. Currently, there is a
203! maximum of seven phytoplankton species and seven different pigments:
204!
205! [1] small diatom [1] chlorophyll-a
206! [2] large diatom [2] chlorophyll-b
207! [3] small dinoflagellate [3] chlorophyll-c
208! [4] large dinoflagellate [4] photosythetic carotenoids
209! [5] synechococcus [5] photoprotective carotenoids
210! [6] small prochlorococcus [6] low urobilin phycoeurythin carotenoids
211! [7] large prochlorococcus [7] high urobilin phycoeurythin carotenoids
212!
213! The phytoplankton/pigment matrix is as follows:
214!
215! P h y t o p l a n k t o n
216! [1] [2] [3] [4] [5] [6] [7]
217!
218! t [7] 0 0 0 0 1 0 0
219! n [6] 0 0 0 0 0 0 0
220! e [5] 1 1 1 1 1 1 1
221! m [4] 1 1 1 1 0 0 0
222! g [3] 1 1 1 1 0 0 0
223! i [2] 0 0 0 0 0 1 1
224! P [1] 1 1 1 1 1 1 1
225!
226 integer, parameter, dimension(7,7) :: PIG = reshape ( &
227 & (/ 1, 1, 1, 1, 1, 1, 1, &
228 & 0, 0, 0, 0, 0, 1, 1, &
229 & 1, 1, 1, 1, 0, 0, 0, &
230 & 1, 1, 1, 1, 0, 0, 0, &
231 & 1, 1, 1, 1, 1, 1, 1, &
232 & 0, 0, 0, 0, 0, 0, 0, &
233 & 0, 0, 0, 0, 1, 0, 0 /), &
234 & (/ 7, 7 /) )
235!
236! Set phytoplankton species to consider (see above classification):
237!
238 integer, parameter, dimension(Nphy) :: PHY = (/ 1, 2, 4, 5 /)
239!
240! Number of biological tracer type variables is set at run time
241!
242 integer :: NBT
243# endif
244#else
245 integer, parameter :: NBT = 0
246#endif
247#ifdef FLOATS
248!
249!-----------------------------------------------------------------------
250! Floats tracjectories parameters.
251!-----------------------------------------------------------------------
252!
253! Number of trajectory time-stepping levels, [0:NFT].
254!
255 integer, parameter :: NFT = 4
256!
257! Total number of floats to track.
258!
259 integer, dimension(Ngrids) :: Nfloats
260!
261! Total number of float variables to process and output.
262!
263 integer, dimension(Ngrids) :: NFV
264#endif
265#ifdef STATIONS
266!
267!-----------------------------------------------------------------------
268! Stations parameters.
269!-----------------------------------------------------------------------
270!
271! Number of output stations.
272!
273 integer, dimension(Ngrids) :: Nstation
274#endif
275!
276!-----------------------------------------------------------------------
277! Maximum number of tidal constituents to process.
278!-----------------------------------------------------------------------
279!
280 integer :: MTC
281
282#ifdef DIAGNOSTICS
283!
284!-----------------------------------------------------------------------
285! Diagnostic fields parameters.
286!-----------------------------------------------------------------------
287!
288! Number of diagnostic tracer fields.
289!
290 integer :: NDT
291!
292! Number of diagnostic momentum fields.
293!
294 integer :: NDM2d ! 2D momentum
295 integer :: NDM3d ! 3D momentum
296!
297! Number of diagnostic biology fields. Currenly, only available for
298! the Fasham model.
299!
300 integer :: NDbio2d ! 2D fields
301 integer :: NDbio3d ! 3D fields
302!
303! Number of diagnostic 3D right-hand-side fields.
304!
305 integer :: NDrhs
306#endif
307!
308!-----------------------------------------------------------------------
309! Model state parameters.
310!-----------------------------------------------------------------------
311!
312! Number of model state variables.
313!
314 integer, dimension(Ngrids) :: NSV
315!
316! Set nonlinear, tangent linear, and adjoint models identifiers.
317!
318 integer :: iNLM = 1
319 integer :: iTLM = 2
320 integer :: iRPM = 3
321 integer :: iADM = 4
322!
323!-----------------------------------------------------------------------
324! Domain partition parameters.
325!-----------------------------------------------------------------------
326!
327! Number of tiles or domain partitions in the XI- and ETA-directions.
328! These values are used to compute tile ranges [Istr:Iend, Jstr:Jend].
329!
330 integer, dimension(Ngrids) :: NtileI
331 integer, dimension(Ngrids) :: NtileJ
332!
333! Number of tiles or domain partitions in the XI- and ETA-directions.
334! These values are used to parallel loops to differentiate between
335! shared-memory and distributed-memory. Notice that in distributed
336! memory both values are set to one.
337!
338 integer, dimension(Ngrids) :: NtileX
339 integer, dimension(Ngrids) :: NtileE
340!
341! Maximum number of points in the halo region in the XI- and
342! ETA-directions.
343!
344 integer, dimension(Ngrids) :: HaloSizeI
345 integer, dimension(Ngrids) :: HaloSizeJ
346!
347! Maximum tile side length in XI- or ETA-directions.
348!
349 integer, dimension(Ngrids) :: TileSide
350!
351! Maximum number of points in a tile partition.
352!
353 integer, dimension(Ngrids) :: TileSize
354!
355! Set number of ghost-points in the halo region. It is only used
356! in distributed-memory applications.
357!
358 integer :: NghostPoints = GHOST_POINTS
359
360 CONTAINS
361
362 SUBROUTINE initialize_param
363!
364!=======================================================================
365! !
366! This routine initializes several parameters in module "mod_param" !
367! for all nested grids. !
368! !
369!=======================================================================
370!
371! Local variable declarations
372!
373 integer :: I_padd, J_padd, ng
374#ifdef ECOSIM
375 integer :: i, j
376!
377!-----------------------------------------------------------------------
378! Determine number of EcoSim total bio-optical constituents:
379!-----------------------------------------------------------------------
380!
381! Nutrients: NO3, NO4, PO4, FeO, SiO, DIC (6)
382! Bacteria: C, Fe, N, P (Nbac*4)
383! DOM: CDM, C, N, P (Ndom*4)
384! Fecal: C, Fe, N, P, Si (Nfec*5)
385! Phytoplakton: C, Fe, N, P (Nfec*4 + Si)
386! Pigments: look table
387!
388 NBT=6+(Nbac*4)+(Ndom*4)+(Nfec*5)+(Nphy*4)
389!
390! Add phytoplankton silica constituents.
391!
392 DO i=1,Nphy
393 IF (PHY(i).le.2) NBT=NBT+1
394 END DO
395!
396! Add pigments. Check phytoplankton-pigment table for values greater
397! than zero.
398!
399 DO j=1,Npig
400 DO i=1,Nphy
401 IF (PIG(PHY(i),j).eq.1) NBT=NBT+1
402 END DO
403 END DO
404#endif
405
406#ifdef DIAGNOSTICS
407!
408!-----------------------------------------------------------------------
409! Determine number of diagnostic variables.
410!-----------------------------------------------------------------------
411
412# ifdef DIAGNOSTICS_TS
413!
414! Tracer diagnostics.
415!
416 NDT=4 ! Acceleration, advection, vertical diffusion
417# if defined TS_DIF2 || defined TS_DIF4
418 NDT=NDT+1 ! Horizontal diffusion
419# endif
420# else
421 NDT=0 ! No tracer diagnostics
422# endif
423# ifdef DIAGNOSTICS_UV
424!
425! 2D Momentum diagnostics.
426!
427 NDM2d=4 ! Acceleration, 2D P-Gradient, stresses
428# ifdef UV_ADV
429 NDM2d=NDM2d+1 ! Horizontal advection
430# endif
431# ifdef NEARSHORE_MELLOR
432 NDM2d=NDM2d+1 ! Horizontal radiation stresses
433# endif
434# ifdef UV_COR
435 NDM2d=NDM2d+1 ! Coriolis
436# endif
437# if defined UV_VIS2 || defined UV_VIS4
438 NDM2d=NDM2d+1 ! Horizontal viscosity
439# endif
440# ifdef SOLVE3D
441!
442! 3D Momentum diagnostics and right-hand-side terms.
443!
444 NDM3d=3 ! Acceleration, 3D P-Gradient, vertical viscosity
445 NDrhs=1 ! 3D P-Gradient
446# ifdef UV_ADV
447 NDM3d=NDM3d+2 ! Horizontal and vertical advection
448 NDrhs=NDrhs+2
449# endif
450# ifdef NEARSHORE_MELLOR
451 NDM3d=NDM3d+2 ! Horizontal and vertical radiation stresses
452 NDrhs=NDrhs+2
453# endif
454# ifdef UV_COR
455 NDM3d=NDM3d+1 ! Coriolis
456 NDrhs=NDrhs+1
457# endif
458# if defined UV_VIS2 || defined UV_VIS4
459 NDM3d=NDM3d+1 ! Horizontal viscosity
460# endif
461# ifdef BODYFORCE
462 NDrhs=NDrhs+1 ! Vertical viscosity
463# endif
464# else
465 NDM3d=0 ! No 3D momentum diagnostics
466 NDrhs=0
467# endif
468# endif
469# if defined BIO_FASHAM && defined DIAGNOSTICS_BIO
470!
471! Source and sink biology diagnostic terms.
472!
473 NDbio3d=2
474 NDbio2d=0
475# ifdef DENITRIFICATION
476 NDbio2d=NDbio2d+1
477# endif
478# ifdef CARBON
479 NDbio2d=NDbio2d+2
480# endif
481# ifdef OXYGEN
482 NDbio2d=NDbio2d+1
483# endif
484# endif
485#endif
486!
487!-----------------------------------------------------------------------
488! Derived dimension parameters.
489!-----------------------------------------------------------------------
490!
491 DO ng=1,Ngrids
492 I_padd=(Lm(ng)+2)/2-(Lm(ng)+1)/2
493 J_padd=(Mm(ng)+2)/2-(Mm(ng)+1)/2
494 Im(ng)=Lm(ng)+I_padd
495 Jm(ng)=Mm(ng)+J_padd
496 NT(ng)=NAT+NBT+NST+NPT
497#ifdef FLOATS
498# ifdef FLOAT_VWALK
499 NFV(ng)=NT(ng)+12
500# else
501 NFV(ng)=NT(ng)+10
502# endif
503#endif
504 NSV(ng)=NT(ng)+5
505 END DO
506!
507! Set maximum number of tracer between all nested grids.
508!
509 MT=MAX(2,MAXVAL(NT))
510
511 RETURN
512 END SUBROUTINE initialize_param
513
514 END MODULE mod_param