New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
dom_oce.F90 in branches/UKMO/2014_Surge_Modelling/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/UKMO/2014_Surge_Modelling/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90 @ 5066

Last change on this file since 5066 was 5066, checked in by rfurner, 9 years ago

added current state of wetting and drying code to test...note it does not work

  • Property svn:keywords set to Id
File size: 29.6 KB
Line 
1MODULE dom_oce
2   !!======================================================================
3   !!                       ***  MODULE dom_oce  ***
4   !!       
5   !! ** Purpose :   Define in memory all the ocean space domain variables
6   !!======================================================================
7   !! History :  1.0  ! 2005-10  (A. Beckmann, G. Madec)  reactivate s-coordinate
8   !!            3.3  ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level
9   !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation
10   !!            3.5  ! 2012     (S. Mocavero, I. Epicoco) Add arrays associated
11   !!                             to the optimization of BDY communications
12   !!            3.6.?! 2014     (H. Liu) Add arrays associated with Wetting and Drying
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   Agrif_Root    : dummy function used when lk_agrif=F
17   !!   Agrif_CFixed  : dummy function used when lk_agrif=F
18   !!   dom_oce_alloc : dynamical allocation of dom_oce arrays
19   !!----------------------------------------------------------------------
20   USE par_oce        ! ocean parameters
21
22   IMPLICIT NONE
23   PUBLIC             ! allows the acces to par_oce when dom_oce is used
24   !                  ! exception to coding rules... to be suppressed ???
25
26   PUBLIC dom_oce_alloc  ! Called from nemogcm.F90
27
28   !!----------------------------------------------------------------------
29   !! time & space domain namelist
30   !! ----------------------------
31   !                                    !!* Namelist namdom : time & space domain *
32   INTEGER , PUBLIC ::   nn_bathy        !: = 0/1 ,compute/read the bathymetry file
33   REAL(wp), PUBLIC ::   rn_bathy        !: depth of flat bottom (active if nn_bathy=0; if =0 depth=jpkm1)
34   REAL(wp), PUBLIC ::   rn_hmin         !: minimum ocean depth (>0) or minimum number of ocean levels (<0)
35   REAL(wp), PUBLIC ::   rn_e3zps_min    !: miminum thickness for partial steps (meters)
36   REAL(wp), PUBLIC ::   rn_e3zps_rat    !: minimum thickness ration for partial steps
37   INTEGER , PUBLIC ::   nn_msh          !: = 1 create a mesh-mask file
38   INTEGER , PUBLIC ::   nn_acc          !: = 0/1 use of the acceleration of convergence technique
39   REAL(wp), PUBLIC ::   rn_atfp         !: asselin time filter parameter
40   REAL(wp), PUBLIC ::   rn_rdt          !: time step for the dynamics (and tracer if nacc=0)
41   REAL(wp), PUBLIC ::   rn_rdtmin       !: minimum time step on tracers
42   REAL(wp), PUBLIC ::   rn_rdtmax       !: maximum time step on tracers
43   REAL(wp), PUBLIC ::   rn_rdth         !: depth variation of tracer step
44   INTEGER , PUBLIC ::   nn_closea       !: =0 suppress closed sea/lake from the ORCA domain or not (=1)
45   INTEGER , PUBLIC ::   nn_euler        !: =0 start with forward time step or not (=1)
46   LOGICAL , PUBLIC ::   ln_crs          !: Apply grid coarsening to dynamical model output or online passive tracers
47
48   !! Time splitting parameters
49   !! =========================
50   LOGICAL,  PUBLIC :: ln_bt_fw          !: Forward integration of barotropic sub-stepping
51   LOGICAL,  PUBLIC :: ln_bt_av          !: Time averaging of barotropic variables
52   LOGICAL,  PUBLIC :: ln_bt_nn_auto     !: Set number of barotropic iterations automatically
53   INTEGER,  PUBLIC :: nn_bt_flt         !: Filter choice
54   INTEGER,  PUBLIC :: nn_baro           !: Number of barotropic iterations during one baroclinic step (rdt)
55   REAL(wp), PUBLIC :: rn_bt_cmax        !: Maximum allowed courant number (used if ln_bt_nn_auto=T)
56
57   !! Horizontal grid parameters for domhgr
58   !! =====================================
59   INTEGER       ::   jphgr_msh        !: type of horizontal mesh
60   !                                       !  = 0 curvilinear coordinate on the sphere read in coordinate.nc
61   !                                       !  = 1 geographical mesh on the sphere with regular grid-spacing
62   !                                       !  = 2 f-plane with regular grid-spacing
63   !                                       !  = 3 beta-plane with regular grid-spacing
64   !                                       !  = 4 Mercator grid with T/U point at the equator
65
66   REAL(wp)      ::   ppglam0              !: longitude of first raw and column T-point (jphgr_msh = 1)
67   REAL(wp)      ::   ppgphi0              !: latitude  of first raw and column T-point (jphgr_msh = 1)
68   !                                                        !  used for Coriolis & Beta parameters (jphgr_msh = 2 or 3)
69   REAL(wp)      ::   ppe1_deg             !: zonal      grid-spacing (degrees)
70   REAL(wp)      ::   ppe2_deg             !: meridional grid-spacing (degrees)
71   REAL(wp)      ::   ppe1_m               !: zonal      grid-spacing (degrees)
72   REAL(wp)      ::   ppe2_m               !: meridional grid-spacing (degrees)
73
74   !! Vertical grid parameter for domzgr
75   !! ==================================
76   REAL(wp)      ::   ppsur                !: ORCA r4, r2 and r05 coefficients
77   REAL(wp)      ::   ppa0                 !: (default coefficients)
78   REAL(wp)      ::   ppa1                 !:
79   REAL(wp)      ::   ppkth                !:
80   REAL(wp)      ::   ppacr                !:
81   !
82   !  If both ppa0 ppa1 and ppsur are specified to 0, then
83   !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr
84   REAL(wp)      ::   ppdzmin              !: Minimum vertical spacing
85   REAL(wp)      ::   pphmax               !: Maximum depth
86   !
87   LOGICAL       ::   ldbletanh            !: Use/do not use double tanf function for vertical coordinates
88   REAL(wp)      ::   ppa2                 !: Double tanh function parameters
89   REAL(wp)      ::   ppkth2               !:
90   REAL(wp)      ::   ppacr2               !:
91
92   !                                    !! old non-DOCTOR names still used in the model
93   INTEGER , PUBLIC ::   ntopo           !: = 0/1 ,compute/read the bathymetry file
94   REAL(wp), PUBLIC ::   e3zps_min       !: miminum thickness for partial steps (meters)
95   REAL(wp), PUBLIC ::   e3zps_rat       !: minimum thickness ration for partial steps
96   INTEGER , PUBLIC ::   nmsh            !: = 1 create a mesh-mask file
97   INTEGER , PUBLIC ::   nacc            !: = 0/1 use of the acceleration of convergence technique
98   REAL(wp), PUBLIC ::   atfp            !: asselin time filter parameter
99   REAL(wp), PUBLIC ::   rdt             !: time step for the dynamics (and tracer if nacc=0)
100   REAL(wp), PUBLIC ::   rdtmin          !: minimum time step on tracers
101   REAL(wp), PUBLIC ::   rdtmax          !: maximum time step on tracers
102   REAL(wp), PUBLIC ::   rdth            !: depth variation of tracer step
103
104   !                                                  !!! associated variables
105   INTEGER , PUBLIC                 ::   neuler        !: restart euler forward option (0=Euler)
106   REAL(wp), PUBLIC                 ::   atfp1         !: asselin time filter coeff. (atfp1= 1-2*atfp)
107   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rdttra  !: vertical profile of tracer time step
108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dtra  !: = 2*rdttra except at nit000 (=rdttra) if neuler=0
109
110   !                                         !!* Namelist namcla : cross land advection
111   INTEGER, PUBLIC ::   nn_cla               !: =1 cross land advection for exchanges through some straits (ORCA2)
112
113   !!----------------------------------------------------------------------
114   !! space domain parameters
115   !!----------------------------------------------------------------------
116   LOGICAL, PUBLIC ::   lzoom      =  .FALSE.   !: zoom flag
117   LOGICAL, PUBLIC ::   lzoom_e    =  .FALSE.   !: East  zoom type flag
118   LOGICAL, PUBLIC ::   lzoom_w    =  .FALSE.   !: West  zoom type flag
119   LOGICAL, PUBLIC ::   lzoom_s    =  .FALSE.   !: South zoom type flag
120   LOGICAL, PUBLIC ::   lzoom_n    =  .FALSE.   !: North zoom type flag
121
122   !                                     !!! domain parameters linked to mpp
123   INTEGER, PUBLIC ::   nperio            !: type of lateral boundary condition
124   INTEGER, PUBLIC ::   nimpp, njmpp      !: i- & j-indexes for mpp-subdomain left bottom
125   INTEGER, PUBLIC ::   nreci, nrecj      !: overlap region in i and j
126   INTEGER, PUBLIC ::   nproc             !: number for local processor
127   INTEGER, PUBLIC ::   narea             !: number for local area
128   INTEGER, PUBLIC ::   nbondi, nbondj    !: mark of i- and j-direction local boundaries
129   INTEGER, ALLOCATABLE, PUBLIC ::   nbondi_bdy(:)    !: mark i-direction local boundaries for BDY open boundaries
130   INTEGER, ALLOCATABLE, PUBLIC ::   nbondj_bdy(:)    !: mark j-direction local boundaries for BDY open boundaries
131   INTEGER, ALLOCATABLE, PUBLIC ::   nbondi_bdy_b(:)  !: mark i-direction of neighbours local boundaries for BDY open boundaries 
132   INTEGER, ALLOCATABLE, PUBLIC ::   nbondj_bdy_b(:)  !: mark j-direction of neighbours local boundaries for BDY open boundaries 
133
134   INTEGER, PUBLIC ::   npolj             !: north fold mark (0, 3 or 4)
135   INTEGER, PUBLIC ::   nlci, nldi, nlei  !: i-dimensions of the local subdomain and its first and last indoor indices
136   INTEGER, PUBLIC ::   nlcj, nldj, nlej  !: i-dimensions of the local subdomain and its first and last indoor indices
137   INTEGER, PUBLIC ::   noea, nowe        !: index of the local neighboring processors in
138   INTEGER, PUBLIC ::   noso, nono        !: east, west, south and north directions
139   INTEGER, PUBLIC ::   npne, npnw        !: index of north east and north west processor
140   INTEGER, PUBLIC ::   npse, npsw        !: index of south east and south west processor
141   INTEGER, PUBLIC ::   nbne, nbnw        !: logical of north east & north west processor
142   INTEGER, PUBLIC ::   nbse, nbsw        !: logical of south east & south west processor
143   INTEGER, PUBLIC ::   nidom             !: ???
144
145   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mig        !: local  ==> global domain i-index
146   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mjg        !: local  ==> global domain j-index
147   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mi0, mi1   !: global ==> local  domain i-index    !!bug ==> other solution?
148   !                                                  ! (mi0=1 and mi1=0 if the global index is not in the local domain)
149   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mj0, mj1   !: global ==> local  domain j-index     !!bug ==> other solution?
150   !                                                  ! (mi0=1 and mi1=0 if the global index is not in the local domain)
151   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nimppt, njmppt   !: i-, j-indexes for each processor
152   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ibonit, ibonjt   !: i-, j- processor neighbour existence
153   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nlcit , nlcjt    !: dimensions of every subdomain
154   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nldit , nldjt    !: first, last indoor index for each i-domain
155   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nleit , nlejt    !: first, last indoor index for each j-domain
156
157   !!----------------------------------------------------------------------
158   !! horizontal curvilinear coordinate and scale factors
159   !! ---------------------------------------------------------------------
160   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  glamt, glamu   !: longitude of t-, u-, v- and f-points (degre)
161   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  glamv, glamf   !:
162   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  gphit, gphiu   !: latitude  of t-, u-, v- and f-points (degre)
163   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  gphiv, gphif   !:
164   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, TARGET, DIMENSION(:,:) ::  e1t, e2t       !: horizontal scale factors at t-point (m)
165   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, TARGET, DIMENSION(:,:) ::  e1u, e2u       !: horizontal scale factors at u-point (m)
166   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, TARGET, DIMENSION(:,:) ::  e1v, e2v       !: horizontal scale factors at v-point (m)
167   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, TARGET, DIMENSION(:,:) ::  e1f, e2f       !: horizontal scale factors at f-point (m)
168   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  e1e2t          !: surface at t-point (m2)
169   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ff             !: coriolis factor (2.*omega*sin(yphi) ) (s-1)
170
171   !!----------------------------------------------------------------------
172   !! vertical coordinate and scale factors
173   !! ---------------------------------------------------------------------
174   !                                 !!* Namelist namzgr : vertical coordinate *
175   LOGICAL, PUBLIC ::   ln_zco        !: z-coordinate - full step
176   LOGICAL, PUBLIC ::   ln_zps        !: z-coordinate - partial step
177   LOGICAL, PUBLIC ::   ln_sco        !: s-coordinate or hybrid z-s coordinate
178
179   !! All coordinates
180   !! ---------------
181   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdep3w_0           !: depth of t-points (sum of e3w) (m)
182   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdept_0, gdepw_0   !: analytical (time invariant) depth at t-w  points (m)
183   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3v_0  , e3f_0     !: analytical (time invariant) vertical scale factors at  v-f
184   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3t_0  , e3u_0     !:                                      t-u  points (m)
185   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3vw_0             !: analytical (time invariant) vertical scale factors at  vw
186   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3w_0  , e3uw_0    !:                                      w-uw points (m)
187#if defined key_vvl
188   LOGICAL, PUBLIC, PARAMETER ::   lk_vvl = .TRUE.    !: variable grid flag
189
190   !! All coordinates
191   !! ---------------
192   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdep3w_n           !: now depth of T-points (sum of e3w) (m)
193   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdept_n, gdepw_n   !: now depth at T-W  points (m)
194   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdept_b, gdepw_b   !: before depth at T-W  points (m)
195   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3t_n              !: now    vertical scale factors at  t       point  (m)
196   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3u_n  , e3v_n     !:            -      -      -    -   u --v   points (m)
197   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3w_n  , e3f_n     !:            -      -      -    -   w --f   points (m)
198   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3uw_n , e3vw_n    !:            -      -      -    -   uw--vw  points (m)
199   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3t_b              !: before     -      -      -    -   t       points (m)
200   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3w_b              !: before     -      -      -    -   t       points (m)
201   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3u_b  , e3v_b     !:   -        -      -      -    -   u --v   points (m)
202   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3uw_b , e3vw_b    !:   -        -      -      -    -   uw--vw  points (m)
203   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3t_a              !: after      -      -      -    -   t       point  (m)
204   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3u_a  , e3v_a     !:   -        -      -      -    -   u --v   points (m)
205#else
206   LOGICAL, PUBLIC, PARAMETER ::   lk_vvl = .FALSE.   !: fixed grid flag
207#endif
208   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hur  , hvr     !: Now    inverse of u and v-points ocean depth (1/m)
209   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hu   , hv      !:        depth at u- and v-points (meters)
210   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ht             !:        depth at t-points (meters)
211   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ehur_a, ehvr_a !: After  inverse of u and v-points ocean depth (1/m)
212   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ehu_a , ehv_a  !:        depth at u- and v-points (meters)
213   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ehur_b, ehvr_b !: Before inverse of u and v-points ocean depth (1/m)
214   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ehu_b , ehv_b  !:        depth at u- and v-points (meters)
215   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ht_0           !: reference depth at t-       points (meters)
216   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hu_0 , hv_0    !: reference depth at u- and v-points (meters)
217   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   re2u_e1u       !: scale factor coeffs at u points (e2u/e1u)
218   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   re1v_e2v       !: scale factor coeffs at v points (e1v/e2v)
219   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e12t , r1_e12t !: horizontal cell surface and inverse at t points
220   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e12u , r1_e12u !: horizontal cell surface and inverse at u points
221   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e12v , r1_e12v !: horizontal cell surface and inverse at v points
222   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e12f , r1_e12f !: horizontal cell surface and inverse at f points
223
224   INTEGER, PUBLIC ::   nla10              !: deepest    W level Above  ~10m (nlb10 - 1)
225   INTEGER, PUBLIC ::   nlb10              !: shallowest W level Bellow ~10m (nla10 + 1)
226
227   !! z-coordinate with full steps (also used in the other cases as reference z-coordinate)
228   !! =-----------------====------
229   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   gdept_1d, gdepw_1d !: reference depth of t- and w-points (m)
230   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   e3t_1d  , e3w_1d   !: reference vertical scale factors at T- and W-pts (m)
231   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e3tp    , e3wp     !: ocean bottom level thickness at T and W points
232
233   !! s-coordinate and hybrid z-s-coordinate
234   !! =----------------======---------------
235   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   gsigt, gsigw       !: model level depth coefficient at t-, w-levels (analytic)
236   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   gsi3w              !: model level depth coefficient at w-level (sum of gsigw)
237   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   esigt, esigw       !: vertical scale factor coef. at t-, w-levels
238
239   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hbatv , hbatf      !: ocean depth at the vertical of  v--f
240   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hbatt , hbatu      !:                                 t--u points (m)
241   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   scosrf, scobot     !: ocean surface and bottom topographies
242   !                                                                           !  (if deviating from coordinate surfaces in HYBRID)
243   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hifv  , hiff       !: interface depth between stretching at v--f
244   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hift  , hifu       !: and quasi-uniform spacing             t--u points (m)
245   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rx1                !: Maximum grid stiffness ratio
246
247   !!----------------------------------------------------------------------
248   !! masks, bathymetry
249   !! ---------------------------------------------------------------------
250   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   mbathy             !: number of ocean level (=0, 1, ... , jpk-1)
251   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   mbkt               !: vertical index of the bottom last T- ocean level
252   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   mbku, mbkv         !: vertical index of the bottom last U- and W- ocean level
253   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bathy              !: ocean depth (meters)
254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tmask_i            !: interior domain T-point mask
255   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bmask              !: land/ocean mask of barotropic stream function
256
257   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:), TARGET :: tmask, umask, vmask, fmask   !: land/ocean mask at T-, U-, V- and F-pts
258
259   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4)
260
261#if defined key_noslip_accurate
262   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:  )  :: npcoa              !: ???
263   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  :: nicoa, njcoa       !: ???
264#endif
265
266   !!----------------------------------------------------------------------
267   !! critical depths,limiters,and masks for  Wetting and Drying
268   !! ---------------------------------------------------------------------
269
270   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wdmask             !: u- and v- limiter
271
272   LOGICAL,  PUBLIC, SAVE ::   ln_wd       !: key to turn on/off wetting/drying (T: on, F: off)
273   REAL(wp), PUBLIC, SAVE ::   rn_wdmin1   !: minimum water depth on dried cells
274   REAL(wp), PUBLIC, SAVE ::   rn_wdmin2   !: tolerrance of minimum water depth on dried cells
275   REAL(wp), PUBLIC, SAVE ::   rn_wdld     !: land elevation below which wetting/drying will be considered
276   INTEGER , PUBLIC, SAVE ::   nn_wdit     !: maximum number of iteration for W/D limiter
277
278   !!----------------------------------------------------------------------
279   !! calendar variables
280   !! ---------------------------------------------------------------------
281   INTEGER , PUBLIC ::   nyear         !: current year
282   INTEGER , PUBLIC ::   nmonth        !: current month
283   INTEGER , PUBLIC ::   nday          !: current day of the month
284   INTEGER , PUBLIC ::   ndastp        !: time step date in yyyymmdd format
285   INTEGER , PUBLIC ::   nday_year     !: current day counted from jan 1st of the current year
286   INTEGER , PUBLIC ::   nsec_year     !: current time step counted in second since 00h jan 1st of the current year
287   INTEGER , PUBLIC ::   nsec_month    !: current time step counted in second since 00h 1st day of the current month
288   INTEGER , PUBLIC ::   nsec_week     !: current time step counted in second since 00h of last monday
289   INTEGER , PUBLIC ::   nsec_day      !: current time step counted in second since 00h of the current day
290   REAL(wp), PUBLIC ::   fjulday       !: current julian day
291   REAL(wp), PUBLIC ::   fjulstartyear !: first day of the current year in julian days
292   REAL(wp), PUBLIC ::   adatrj        !: number of elapsed days since the begining of the whole simulation
293   !                                   !: (cumulative duration of previous runs that may have used different time-step size)
294   INTEGER , PUBLIC, DIMENSION(0: 2) ::   nyear_len     !: length in days of the previous/current/next year
295   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_len    !: length in days of the months of the current year
296   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_half   !: second since Jan 1st 0h of the current year and the half of the months
297   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_end    !: second since Jan 1st 0h of the current year and the end of the months
298   INTEGER , PUBLIC                  ::   nsec1jan000   !: second since Jan 1st 0h of nit000 year and Jan 1st 0h the current year
299
300   !!----------------------------------------------------------------------
301   !! mpp reproducibility
302   !!----------------------------------------------------------------------
303#if defined key_mpp_rep
304   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp_rep = .TRUE.    !: agrif flag
305#else
306   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp_rep = .FALSE.   !: agrif flag
307#endif
308
309   !!----------------------------------------------------------------------
310   !! agrif domain
311   !!----------------------------------------------------------------------
312#if defined key_agrif
313   LOGICAL, PUBLIC, PARAMETER ::   lk_agrif = .TRUE.    !: agrif flag
314#else
315   LOGICAL, PUBLIC, PARAMETER ::   lk_agrif = .FALSE.   !: agrif flag
316#endif
317
318   !!----------------------------------------------------------------------
319   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
320   !! $Id$
321   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
322   !!----------------------------------------------------------------------
323CONTAINS
324
325#if ! defined key_agrif
326   !!----------------------------------------------------------------------
327   !! NOT 'key_agrif'      dummy function                     No AGRIF zoom
328   !!----------------------------------------------------------------------
329   LOGICAL FUNCTION Agrif_Root()
330      Agrif_Root = .TRUE.
331   END FUNCTION Agrif_Root
332
333   CHARACTER(len=3) FUNCTION Agrif_CFixed()
334      Agrif_CFixed = '0' 
335   END FUNCTION Agrif_CFixed
336#endif
337
338   INTEGER FUNCTION dom_oce_alloc()
339      !!----------------------------------------------------------------------
340      INTEGER, DIMENSION(12) :: ierr
341      !!----------------------------------------------------------------------
342      ierr(:) = 0
343      !
344      ALLOCATE( rdttra(jpk), r2dtra(jpk), mig(jpi), mjg(jpj), STAT=ierr(1) )
345         !
346      ALLOCATE( nimppt(jpnij) , ibonit(jpnij) , nlcit(jpnij) , nlcjt(jpnij) ,     &
347         &      njmppt(jpnij) , ibonjt(jpnij) , nldit(jpnij) , nldjt(jpnij) ,     &
348         &                                      nleit(jpnij) , nlejt(jpnij) ,     &
349         &      mi0(jpidta)   , mi1 (jpidta),  mj0(jpjdta)   , mj1 (jpjdta),      &
350         &      tpol(jpiglo)  , fpol(jpiglo)                               , STAT=ierr(2) )
351         !
352      ALLOCATE( glamt(jpi,jpj) , gphit(jpi,jpj) , e1t(jpi,jpj) , e2t(jpi,jpj) ,                      & 
353         &      glamu(jpi,jpj) , gphiu(jpi,jpj) , e1u(jpi,jpj) , e2u(jpi,jpj) ,                      & 
354         &      glamv(jpi,jpj) , gphiv(jpi,jpj) , e1v(jpi,jpj) , e2v(jpi,jpj) , e1e2t(jpi,jpj) ,     & 
355         &      glamf(jpi,jpj) , gphif(jpi,jpj) , e1f(jpi,jpj) , e2f(jpi,jpj) , ff   (jpi,jpj) , STAT=ierr(3) )     
356         !
357      ALLOCATE( gdep3w_0(jpi,jpj,jpk) , e3v_0(jpi,jpj,jpk) , e3f_0 (jpi,jpj,jpk) ,                         &
358         &      gdept_0 (jpi,jpj,jpk) , e3t_0(jpi,jpj,jpk) , e3u_0 (jpi,jpj,jpk) ,                         &
359         &      gdepw_0 (jpi,jpj,jpk) , e3w_0(jpi,jpj,jpk) , e3vw_0(jpi,jpj,jpk) , e3uw_0(jpi,jpj,jpk) , STAT=ierr(4) )
360         !
361#if defined key_vvl
362      ALLOCATE( gdep3w_n(jpi,jpj,jpk) , e3t_n (jpi,jpj,jpk) , e3u_n (jpi,jpj,jpk) ,                           &
363         &      gdept_n (jpi,jpj,jpk) , e3v_n (jpi,jpj,jpk) , e3w_n (jpi,jpj,jpk) ,                           &
364         &      gdepw_n (jpi,jpj,jpk) , e3f_n (jpi,jpj,jpk) , e3vw_n(jpi,jpj,jpk) , e3uw_n(jpi,jpj,jpk) ,     &
365         &      e3t_b   (jpi,jpj,jpk) , e3u_b (jpi,jpj,jpk) , e3v_b (jpi,jpj,jpk) ,                           &
366         &      e3uw_b  (jpi,jpj,jpk) , e3vw_b(jpi,jpj,jpk) ,                                                 &
367         &      gdept_b (jpi,jpj,jpk) ,gdepw_b(jpi,jpj,jpk) , e3w_b (jpi,jpj,jpk) ,                           &
368         &      e3t_a   (jpi,jpj,jpk) , e3u_a (jpi,jpj,jpk) , e3v_a (jpi,jpj,jpk) ,                           &
369         &      ehu_a    (jpi,jpj)    , ehv_a  (jpi,jpj),                                                     &
370         &      ehur_a   (jpi,jpj)    , ehvr_a (jpi,jpj),                                                     &
371         &      ehu_b    (jpi,jpj)    , ehv_b  (jpi,jpj),                                                     &
372         &      ehur_b   (jpi,jpj)    , ehvr_b (jpi,jpj),                                  STAT=ierr(5) )                         
373#endif
374         !
375      ALLOCATE( hu      (jpi,jpj) , hur     (jpi,jpj) , hu_0(jpi,jpj) , ht_0  (jpi,jpj) ,     &
376         &      hv      (jpi,jpj) , hvr     (jpi,jpj) , hv_0(jpi,jpj) , ht    (jpi,jpj) ,     &
377         &      re2u_e1u(jpi,jpj) , re1v_e2v(jpi,jpj) ,                                       &
378         &      e12t    (jpi,jpj) , r1_e12t (jpi,jpj) ,                                       &
379         &      e12u    (jpi,jpj) , r1_e12u (jpi,jpj) ,                                       &
380         &      e12v    (jpi,jpj) , r1_e12v (jpi,jpj) ,                                       &
381         &      e12f    (jpi,jpj) , r1_e12f (jpi,jpj) ,                                   STAT=ierr(6)  )
382         !
383      ALLOCATE( gdept_1d(jpk) , gdepw_1d(jpk) ,                                     &
384         &      e3t_1d  (jpk) , e3w_1d  (jpk) , e3tp (jpi,jpj), e3wp(jpi,jpj) ,     &
385         &      gsigt   (jpk) , gsigw   (jpk) , gsi3w(jpk)    ,                     &
386         &      esigt   (jpk) , esigw   (jpk)                                 , STAT=ierr(7) )
387         !
388      ALLOCATE( hbatv (jpi,jpj) , hbatf (jpi,jpj) ,     &
389         &      hbatt (jpi,jpj) , hbatu (jpi,jpj) ,     &
390         &      scosrf(jpi,jpj) , scobot(jpi,jpj) ,     &
391         &      hifv  (jpi,jpj) , hiff  (jpi,jpj) ,     &
392         &      hift  (jpi,jpj) , hifu  (jpi,jpj) , rx1 (jpi,jpj) , STAT=ierr(8) )
393
394      ALLOCATE( mbathy(jpi,jpj) , bathy(jpi,jpj) ,                     &
395         &     tmask_i(jpi,jpj) , bmask(jpi,jpj) ,                     &
396         &     mbkt   (jpi,jpj) , mbku (jpi,jpj) , mbkv(jpi,jpj) , STAT=ierr(9) )
397
398      ALLOCATE( tmask(jpi,jpj,jpk) , umask(jpi,jpj,jpk),     & 
399         &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk), STAT=ierr(10) )
400
401#if defined key_noslip_accurate
402      ALLOCATE( npcoa(4,jpk), nicoa(2*(jpi+jpj),4,jpk), njcoa(2*(jpi+jpj),4,jpk), STAT=ierr(11) )
403#endif
404      !
405      IF(ln_wd) &
406      ALLOCATE( wdmask(jpi,jpj), STAT=ierr(12) )
407      !
408      dom_oce_alloc = MAXVAL(ierr)
409      !
410   END FUNCTION dom_oce_alloc
411
412   !!======================================================================
413END MODULE dom_oce
414
Note: See TracBrowser for help on using the repository browser.