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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90 @ 3211

Last change on this file since 3211 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 22.4 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   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   Agrif_Root    : dummy function used when lk_agrif=F
14   !!   Agrif_CFixed  : dummy function used when lk_agrif=F
15   !!   dom_oce_alloc : dynamical allocation of dom_oce arrays
16   !!----------------------------------------------------------------------
17   USE par_oce        ! ocean parameters
18
19   IMPLICIT NONE
20   PUBLIC             ! allows the acces to par_oce when dom_oce is used
21   !                  ! exception to coding rules... to be suppressed ???
22
23   PUBLIC dom_oce_alloc  ! Called from nemogcm.F90
24
25   !!----------------------------------------------------------------------
26   !! time & space domain namelist
27   !! ----------------------------
28   !                                              !!* Namelist namdom : time & space domain *
29   INTEGER , PUBLIC ::   nn_bathy     =    0       !: = 0/1 ,compute/read the bathymetry file
30   REAL(wp), PUBLIC ::   rn_hmin      =   -3.0_wp  !: minimum ocean depth (>0) or minimum number of ocean levels (<0)
31   REAL(wp), PUBLIC ::   rn_e3zps_min =    5.0_wp  !: miminum thickness for partial steps (meters)
32   REAL(wp), PUBLIC ::   rn_e3zps_rat =    0.1_wp  !: minimum thickness ration for partial steps
33   INTEGER , PUBLIC ::   nn_msh       =    0       !: = 1 create a mesh-mask file
34   INTEGER , PUBLIC ::   nn_acc       =    0       !: = 0/1 use of the acceleration of convergence technique
35   REAL(wp), PUBLIC ::   rn_atfp      =    0.1_wp  !: asselin time filter parameter
36   REAL(wp), PUBLIC ::   rn_rdt       = 3600._wp   !: time step for the dynamics (and tracer if nacc=0)
37   REAL(wp), PUBLIC ::   rn_rdtmin    = 3600._wp   !: minimum time step on tracers
38   REAL(wp), PUBLIC ::   rn_rdtmax    = 3600._wp   !: maximum time step on tracers
39   REAL(wp), PUBLIC ::   rn_rdth      =  800._wp   !: depth variation of tracer step
40   INTEGER , PUBLIC ::   nn_baro      =   64       !: number of barotropic time steps (key_dynspg_ts)
41   INTEGER , PUBLIC ::   nn_closea    =    0       !: =0 suppress closed sea/lake from the ORCA domain or not (=1)
42
43   !                                    !! old non-DOCTOR names still used in the model
44   INTEGER , PUBLIC ::   ntopo           !: = 0/1 ,compute/read the bathymetry file
45   REAL(wp), PUBLIC ::   e3zps_min       !: miminum thickness for partial steps (meters)
46   REAL(wp), PUBLIC ::   e3zps_rat       !: minimum thickness ration for partial steps
47   INTEGER , PUBLIC ::   nmsh            !: = 1 create a mesh-mask file
48   INTEGER , PUBLIC ::   nacc            !: = 0/1 use of the acceleration of convergence technique
49   REAL(wp), PUBLIC ::   atfp            !: asselin time filter parameter
50   REAL(wp), PUBLIC ::   rdt             !: time step for the dynamics (and tracer if nacc=0)
51   REAL(wp), PUBLIC ::   rdtmin          !: minimum time step on tracers
52   REAL(wp), PUBLIC ::   rdtmax          !: maximum time step on tracers
53   REAL(wp), PUBLIC ::   rdth            !: depth variation of tracer step
54   INTEGER , PUBLIC ::   nclosea         !: =0 suppress closed sea/lake from the ORCA domain or not (=1)
55
56   !                                                  !!! associated variables
57   INTEGER , PUBLIC                 ::   neuler  = 0   !: restart euler forward option (0=Euler)
58   REAL(wp), PUBLIC                 ::   atfp1         !: asselin time filter coeff. (atfp1= 1-2*atfp)
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rdttra  !: vertical profile of tracer time step
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dtra  !: = 2*rdttra except at nit000 (=rdttra) if neuler=0
61
62   !                                         !!* Namelist namcla : cross land advection
63   INTEGER, PUBLIC ::   nn_cla = 0            !: =1 cross land advection for exchanges through some straits (ORCA2)
64
65   !!----------------------------------------------------------------------
66   !! space domain parameters
67   !!----------------------------------------------------------------------
68   LOGICAL, PUBLIC ::   lzoom      =  .FALSE.   !: zoom flag
69   LOGICAL, PUBLIC ::   lzoom_e    =  .FALSE.   !: East  zoom type flag
70   LOGICAL, PUBLIC ::   lzoom_w    =  .FALSE.   !: West  zoom type flag
71   LOGICAL, PUBLIC ::   lzoom_s    =  .FALSE.   !: South zoom type flag
72   LOGICAL, PUBLIC ::   lzoom_n    =  .FALSE.   !: North zoom type flag
73   LOGICAL, PUBLIC ::   lzoom_arct =  .FALSE.   !: ORCA    arctic zoom flag
74   LOGICAL, PUBLIC ::   lzoom_anta =  .FALSE.   !: ORCA antarctic zoom flag
75
76   !                                     !!! domain parameters linked to mpp
77   INTEGER, PUBLIC ::   nperio            !: type of lateral boundary condition
78   INTEGER, PUBLIC ::   nimpp, njmpp      !: i- & j-indexes for mpp-subdomain left bottom
79   INTEGER, PUBLIC ::   nreci, nrecj      !: overlap region in i and j
80   INTEGER, PUBLIC ::   nproc             !: number for local processor
81   INTEGER, PUBLIC ::   narea             !: number for local area
82   INTEGER, PUBLIC ::   nbondi, nbondj    !: mark of i- and j-direction local boundaries
83   INTEGER, PUBLIC ::   npolj             !: north fold mark (0, 3 or 4)
84   INTEGER, PUBLIC ::   nlci, nldi, nlei  !: i-dimensions of the local subdomain and its first and last indoor indices
85   INTEGER, PUBLIC ::   nlcj, nldj, nlej  !: j-dimensions of the local subdomain and its first and last indoor indices
86   INTEGER, PUBLIC ::   noea, nowe        !: index of the local neighboring processors in
87   INTEGER, PUBLIC ::   noso, nono        !: east, west, south and north directions
88   INTEGER, PUBLIC ::   npne, npnw        !: index of north east and north west processor
89   INTEGER, PUBLIC ::   npse, npsw        !: index of south east and south west processor
90   INTEGER, PUBLIC ::   nbne, nbnw        !: logical of north east & north west processor
91   INTEGER, PUBLIC ::   nbse, nbsw        !: logical of south east & south west processor
92   INTEGER, PUBLIC ::   nidom             !: ???
93
94   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mig        !: local  ==> global domain i-index
95   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mjg        !: local  ==> global domain j-index
96   INTEGER, PUBLIC,               DIMENSION(jpidta) ::   mi0, mi1   !: global ==> local  domain i-index
97   !                                                  !!bug ==> other solution?
98   !                                                  ! (mi0=1 and mi1=0 if the global index is not in the local domain)
99   INTEGER, PUBLIC,               DIMENSION(jpjdta) ::   mj0, mj1   !: global ==> local  domain j-index
100   !                                                  !!bug ==> other solution?
101   !                                                  ! (mi0=1 and mi1=0 if the global index is not in the local domain)
102   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nimppt, njmppt   !: i-, j-indexes for each processor
103   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ibonit, ibonjt   !: i-, j- processor neighbour existence
104   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nlcit , nlcjt    !: dimensions of every subdomain
105   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nldit , nldjt    !: first, last indoor index for each i-domain
106   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nleit , nlejt    !: first, last indoor index for each j-domain
107
108   !!----------------------------------------------------------------------
109   !! horizontal curvilinear coordinate and scale factors
110   !! ---------------------------------------------------------------------
111   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  glamt, glamu   !: longitude of t-, u-, v- and f-points (degre)
112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  glamv, glamf   !:
113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  gphit, gphiu   !: latitude  of t-, u-, v- and f-points (degre)
114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  gphiv, gphif   !:
115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  e1t, e2t       !: horizontal scale factors at t-point (m)
116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  e1u, e2u       !: horizontal scale factors at u-point (m)
117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  e1v, e2v       !: horizontal scale factors at v-point (m)
118   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  e1f, e2f       !: horizontal scale factors at f-point (m)
119   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  e1e2t          !: surface at t-point (m2)
120   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::  ff             !: coriolis factor (2.*omega*sin(yphi) ) (s-1)
121
122   !!----------------------------------------------------------------------
123   !! vertical coordinate and scale factors
124   !! ---------------------------------------------------------------------
125   !                                           !!* Namelist namzgr : vertical coordinate *
126   LOGICAL, PUBLIC ::   ln_zco     =  .TRUE.    !: z-coordinate - full step
127   LOGICAL, PUBLIC ::   ln_zps     =  .FALSE.   !: z-coordinate - partial step
128   LOGICAL, PUBLIC ::   ln_sco     =  .FALSE.   !: s-coordinate or hybrid z-s coordinate
129
130   !! All coordinates
131   !! ---------------
132   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdep3w          !: depth of T-points (sum of e3w) (m)
133   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdept , gdepw   !: analytical depth at T-W  points (m)
134   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
135             & e3v   , e3f     !: analytical vertical scale factors at  V--F
136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
137             & e3t   , e3u     !:                                       T--U  points (m)
138   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
139             & e3vw            !: analytical vertical scale factors at  VW--
140   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
141             & e3w   , e3uw    !:                                        W--UW  points (m)
142#if defined key_vvl
143   LOGICAL, PUBLIC, PARAMETER ::   lk_vvl = .TRUE.    !: variable grid flag
144
145   !! All coordinates
146   !! ---------------
147   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdep3w_1           !: depth of T-points (sum of e3w) (m)
148   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gdept_1, gdepw_1   !: analytical depth at T-W  points (m)
149   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3v_1  , e3f_1     !: analytical vertical scale factors at  V--F
150   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
151             & e3t_1  , e3u_1     !:                                       T--U  points (m)
152   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   e3vw_1             !: analytical vertical scale factors at  VW--
153   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
154             & e3w_1  , e3uw_1    !:                                       W--UW  points (m)
155   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
156             & e3t_b              !: before         -      -      -    -   T      points (m)
157   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   &
158             & e3u_b  , e3v_b     !:   -            -      -      -    -   U--V   points (m)
159#else
160   LOGICAL, PUBLIC, PARAMETER ::   lk_vvl = .FALSE.   !: fixed grid flag
161#endif
162   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hur  , hvr    !: inverse of u and v-points ocean depth (1/m)
163   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hu   , hv     !: depth at u- and v-points (meters)
164   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hu_0 , hv_0   !: refernce depth at u- and v-points (meters)
165
166   INTEGER, PUBLIC ::   nla10              !: deepest    W level Above  ~10m (nlb10 - 1)
167   INTEGER, PUBLIC ::   nlb10              !: shallowest W level Bellow ~10m (nla10 + 1)
168
169   !! z-coordinate with full steps (also used in the other cases as reference z-coordinate)
170   !! =-----------------====------
171   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   :: gdept_0, gdepw_0 !: reference depth of t- and w-points (m)
172   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   :: &
173             & e3t_0  , e3w_0   !: reference vertical scale factors at T- and W-pts (m)
174   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: e3tp   , e3wp    !: ocean bottom level thickness at T and W points
175
176   !! s-coordinate and hybrid z-s-coordinate
177   !! =----------------======---------------
178   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   &
179             & gsigt, gsigw   !: model level depth coefficient at t-, w-levels (analytic)
180   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   &
181             & gsi3w          !: model level depth coefficient at w-level (sum of gsigw)
182   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   &
183             & esigt, esigw   !: vertical scale factor coef. at t-, w-levels
184
185   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hbatv , hbatf    !: ocean depth at the vertical of  V--F
186   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   &
187             & hbatt , hbatu    !:                                 T--U  points (m)
188   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   scosrf, scobot   !: ocean surface and bottom topographies
189   !                                        !  (if deviating from coordinate surfaces in HYBRID)
190   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hifv  , hiff     !: interface depth between stretching at  V--F
191   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   &
192             & hift  , hifu     !: and quasi-uniform spacing              T--U  points (m)
193
194   !!----------------------------------------------------------------------
195   !! masks, bathymetry
196   !! ---------------------------------------------------------------------
197   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   mbathy       !: number of ocean level (=0, 1, ... , jpk-1)
198   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   mbkt         !: vertical index of the bottom last T- ocean level
199   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   &
200             & mbku, mbkv   !: vertical index of the bottom last U- and W- ocean level
201   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bathy        !: ocean depth (meters)
202   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tmask_i      !: interior domain T-point mask
203   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bmask        !: land/ocean mask of barotropic stream function
204
205   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tmask, umask, vmask, fmask   !: land/ocean masks
206   !                                                                                     !  at T-, U-, V- and F-pts
207#if defined key_z_first
208   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tmask_1, umask_1, vmask_1, fmask_1   !: as above, at sea surface only
209#endif
210
211   REAL(wp), PUBLIC, DIMENSION(jpiglo) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4)
212
213#if defined key_noslip_accurate
214   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:  ) :: npcoa        !: ???
215   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: nicoa, njcoa !: ???
216#endif
217
218   !!----------------------------------------------------------------------
219   !! calendar variables
220   !! ---------------------------------------------------------------------
221   INTEGER , PUBLIC ::   nyear         !: current year
222   INTEGER , PUBLIC ::   nmonth        !: current month
223   INTEGER , PUBLIC ::   nday          !: current day of the month
224   INTEGER , PUBLIC ::   ndastp        !: time step date in yyyymmdd format
225   INTEGER , PUBLIC ::   nday_year     !: current day counted from jan 1st of the current year
226   INTEGER , PUBLIC ::   nsec_year     !: current time step counted in second since 00h jan 1st of the current year
227   INTEGER , PUBLIC ::   nsec_month    !: current time step counted in second since 00h 1st day of the current month
228   INTEGER , PUBLIC ::   nsec_week     !: current time step counted in second since 00h of last monday
229   INTEGER , PUBLIC ::   nsec_day      !: current time step counted in second since 00h of the current day
230   REAL(wp), PUBLIC ::   fjulday       !: current julian day
231   REAL(wp), PUBLIC ::   fjulstartyear !: first day of the current year in julian days
232   REAL(wp), PUBLIC ::   adatrj        !: number of elapsed days since the begining of the whole simulation
233   !                                   !: (cumulative duration of previous runs that may have used different time-step size)
234   INTEGER , PUBLIC, DIMENSION(0: 1) ::   nyear_len     !: length in days of the previous/current year
235   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_len    !: length in days of the months of the current year
236   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_half   !: second since Jan 1st 0h of the current year and the half of the months
237   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_end    !: second since Jan 1st 0h of the current year and the end of the months
238   INTEGER , PUBLIC                  ::   nsec1jan000   !: second since Jan 1st 0h of nit000 year and Jan 1st 0h the current year
239
240   !!----------------------------------------------------------------------
241   !! mpp reproducibility
242   !!----------------------------------------------------------------------
243#if defined key_mpp_rep
244   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp_rep = .TRUE.    !: agrif flag
245#else
246   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp_rep = .FALSE.   !: agrif flag
247#endif
248
249   !!----------------------------------------------------------------------
250   !! agrif domain
251   !!----------------------------------------------------------------------
252#if defined key_agrif
253   LOGICAL, PUBLIC, PARAMETER ::   lk_agrif = .TRUE.    !: agrif flag
254#else
255   LOGICAL, PUBLIC, PARAMETER ::   lk_agrif = .FALSE.   !: agrif flag
256#endif
257
258   !! * Control permutation of array indices
259#  include "dom_oce_ftrans.h90"
260
261   !!----------------------------------------------------------------------
262   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
263   !! $Id$
264   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
265   !!----------------------------------------------------------------------
266CONTAINS
267
268#if ! defined key_agrif
269   !!----------------------------------------------------------------------
270   !! NOT 'key_agrif'      dummy function                     No AGRIF zoom
271   !!----------------------------------------------------------------------
272   LOGICAL FUNCTION Agrif_Root()
273      Agrif_Root = .TRUE.
274   END FUNCTION Agrif_Root
275
276   CHARACTER(len=3) FUNCTION Agrif_CFixed()
277      Agrif_CFixed = '0' 
278   END FUNCTION Agrif_CFixed
279#endif
280
281   INTEGER FUNCTION dom_oce_alloc()
282      !!----------------------------------------------------------------------
283      INTEGER, DIMENSION(12) :: ierr
284      !!----------------------------------------------------------------------
285      ierr(:) = 0
286      !
287      ALLOCATE( rdttra(jpk), r2dtra(jpk), mig(jpi), mjg(jpj), STAT=ierr(1) )
288         !
289      ALLOCATE( nimppt(jpnij) , ibonit(jpnij) , nlcit(jpnij) , nlcjt(jpnij) ,     &
290         &      njmppt(jpnij) , ibonjt(jpnij) , nldit(jpnij) , nldjt(jpnij) ,     &
291         &                                      nleit(jpnij) , nlejt(jpnij) , STAT=ierr(2) )
292         !
293      ALLOCATE( glamt(jpi,jpj) , gphit(jpi,jpj) , e1t(jpi,jpj) , e2t(jpi,jpj) ,                      & 
294         &      glamu(jpi,jpj) , gphiu(jpi,jpj) , e1u(jpi,jpj) , e2u(jpi,jpj) ,                      & 
295         &      glamv(jpi,jpj) , gphiv(jpi,jpj) , e1v(jpi,jpj) , e2v(jpi,jpj) , e1e2t(jpi,jpj) ,     & 
296         &      glamf(jpi,jpj) , gphif(jpi,jpj) , e1f(jpi,jpj) , e2f(jpi,jpj) , ff   (jpi,jpj) , STAT=ierr(3) )     
297         !
298      ALLOCATE( gdep3w(jpi,jpj,jpk) , e3v(jpi,jpj,jpk) , e3f (jpi,jpj,jpk) ,                         &
299         &      gdept (jpi,jpj,jpk) , e3t(jpi,jpj,jpk) , e3u (jpi,jpj,jpk) ,                         &
300         &      gdepw (jpi,jpj,jpk) , e3w(jpi,jpj,jpk) , e3vw(jpi,jpj,jpk) , e3uw(jpi,jpj,jpk) , STAT=ierr(4) )
301         !
302#if defined key_vvl
303      ALLOCATE( gdep3w_1(jpi,jpj,jpk) , e3v_1(jpi,jpj,jpk) , e3f_1 (jpi,jpj,jpk) ,                           &
304         &      gdept_1 (jpi,jpj,jpk) , e3t_1(jpi,jpj,jpk) , e3u_1 (jpi,jpj,jpk) ,                           &
305         &      gdepw_1 (jpi,jpj,jpk) , e3w_1(jpi,jpj,jpk) , e3vw_1(jpi,jpj,jpk) , e3uw_1(jpi,jpj,jpk) ,     &
306         &      e3t_b   (jpi,jpj,jpk) , e3u_b(jpi,jpj,jpk) , e3v_b (jpi,jpj,jpk)                       , STAT=ierr(5) )
307#endif
308         !
309      ALLOCATE( hu(jpi,jpj) , hur(jpi,jpj) , hu_0(jpi,jpj) ,     &
310         &      hv(jpi,jpj) , hvr(jpi,jpj) , hv_0(jpi,jpj) , STAT=ierr(6) )
311         !
312      ALLOCATE( gdept_0(jpk) , gdepw_0(jpk) ,                                     &
313         &      e3t_0  (jpk) , e3w_0  (jpk) , e3tp (jpi,jpj), e3wp(jpi,jpj) ,     &
314         &      gsigt  (jpk) , gsigw  (jpk) , gsi3w(jpk)    ,                     &
315         &      esigt  (jpk) , esigw  (jpk)                                 , STAT=ierr(7) )
316         !
317      ALLOCATE( hbatv (jpi,jpj) , hbatf (jpi,jpj) ,     &
318         &      hbatt (jpi,jpj) , hbatu (jpi,jpj) ,     &
319         &      scosrf(jpi,jpj) , scobot(jpi,jpj) ,     &
320         &      hifv  (jpi,jpj) , hiff  (jpi,jpj) ,     &
321         &      hift  (jpi,jpj) , hifu  (jpi,jpj) , STAT=ierr(8) )
322
323      ALLOCATE( mbathy(jpi,jpj) , bathy(jpi,jpj) ,                     &
324         &     tmask_i(jpi,jpj) , bmask(jpi,jpj) ,                     &
325         &     mbkt   (jpi,jpj) , mbku (jpi,jpj) , mbkv(jpi,jpj) , STAT=ierr(9) )
326
327      ALLOCATE( tmask(jpi,jpj,jpk) , umask(jpi,jpj,jpk),     & 
328         &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk), STAT=ierr(10) )
329
330#if defined key_noslip_accurate
331      ALLOCATE( npcoa(4,jpk), nicoa(2*(jpi+jpj),4,jpk), njcoa(2*(jpi+jpj),4,jpk), STAT=ierr(11) )
332#endif
333
334#if defined key_z_first
335      ALLOCATE( tmask_1(jpi,jpj) ,   umask_1(jpi,jpj),     & 
336         &      vmask_1(jpi,jpj) ,   fmask_1(jpi,jpj), STAT=ierr(12) )
337#endif
338
339      !
340      dom_oce_alloc = MAXVAL(ierr)
341      !
342   END FUNCTION dom_oce_alloc
343
344   !!======================================================================
345END MODULE dom_oce
Note: See TracBrowser for help on using the repository browser.