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.
dommsk.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC/dommsk.F90 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 14 years ago

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 8.3 KB
Line 
1MODULE dommsk
2   !!==============================================================================
3   !!                       ***  MODULE dommsk   ***
4   !! Ocean initialization : domain land/sea mask
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   dom_msk        : compute land/ocean mask
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce             ! ocean dynamics and tracers
12   USE dom_oce         ! ocean space and time domain
13   USE in_out_manager  ! I/O manager
14   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
15   USE lib_mpp
16
17   IMPLICIT NONE
18   PRIVATE
19
20   !! * Routine accessibility
21   PUBLIC dom_msk        ! routine called by inidom.F90
22
23   !! * Module variables
24#if defined key_degrad
25   !! ------------------------------------------------
26   !! Degradation method
27   !! --------------------------------------------------
28   REAL(wp), PUBLIC, DIMENSION (jpi,jpj,jpk) :: &
29      facvol  !! volume for degraded regions
30#endif
31   !! * Substitutions
32#  include "vectopt_loop_substitute.h90"
33   !!----------------------------------------------------------------------
34   !!   OPA 9.0 , LOCEAN-IPSL  (2005)
35   !!   $Id$
36   !!   This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
37   !!----------------------------------------------------------------------
38
39CONTAINS
40   
41   SUBROUTINE dom_msk
42      !!---------------------------------------------------------------------
43      !!                 ***  ROUTINE dom_msk  ***
44      !!
45      !! ** Purpose :   Compute land/ocean mask arrays at tracer points, hori-
46      !!      zontal velocity points (u & v), vorticity points (f) and baro-
47      !!      tropic stream function  points (b).
48      !!        Set mbathy to the number of non-zero w-levels of a water column
49      !!      (if island in the domain (lk_isl=T), this is done latter in
50      !!      routine solver_init)
51      !!
52      !! ** Method  :   The ocean/land mask is computed from the basin bathy-
53      !!      metry in level (mbathy) which is defined or read in dommba.
54      !!      mbathy equals 0 over continental T-point, -n over the nth
55      !!      island T-point, and the number of ocean level over the ocean.
56      !!
57      !!      At a given position (ji,jj,jk) the ocean/land mask is given by:
58      !!      t-point : 0. IF mbathy( ji ,jj) =< 0
59      !!                1. IF mbathy( ji ,jj) >= jk
60      !!      u-point : 0. IF mbathy( ji ,jj)  or mbathy(ji+1, jj ) =< 0
61      !!                1. IF mbathy( ji ,jj) and mbathy(ji+1, jj ) >= jk.
62      !!      v-point : 0. IF mbathy( ji ,jj)  or mbathy( ji ,jj+1) =< 0
63      !!                1. IF mbathy( ji ,jj) and mbathy( ji ,jj+1) >= jk.
64      !!      f-point : 0. IF mbathy( ji ,jj)  or mbathy( ji ,jj+1)
65      !!                   or mbathy(ji+1,jj)  or mbathy(ji+1,jj+1) =< 0
66      !!                1. IF mbathy( ji ,jj) and mbathy( ji ,jj+1)
67      !!                and mbathy(ji+1,jj) and mbathy(ji+1,jj+1) >= jk.
68      !!      b-point : the same definition as for f-point of the first ocean
69      !!                level (surface level) but with 0 along coastlines.
70      !!
71      !!        The lateral friction is set through the value of fmask along
72      !!      the coast and topography. This value is defined by shlat, a
73      !!      namelist parameter:
74      !!         shlat = 0, free slip  (no shear along the coast)
75      !!         shlat = 2, no slip  (specified zero velocity at the coast)
76      !!         0 < shlat < 2, partial slip   | non-linear velocity profile
77      !!         2 < shlat, strong slip        | in the lateral boundary layer
78      !!
79      !!      N.B. If nperio not equal to 0, the land/ocean mask arrays
80      !!      are defined with the proper value at lateral domain boundaries,
81      !!      but bmask. indeed, bmask defined the domain over which the
82      !!      barotropic stream function is computed. this domain cannot
83      !!      contain identical columns because the matrix associated with
84      !!      the barotropic stream function equation is then no more inverti-
85      !!      ble. therefore bmask is set to 0 along lateral domain boundaries
86      !!      even IF nperio is not zero.
87      !!
88      !!      In case of open boundaries (lk_obc=T):
89      !!        - tmask is set to 1 on the points to be computed bay the open
90      !!          boundaries routines.
91      !!        - bmask is  set to 0 on the open boundaries.
92      !!
93      !!      Set mbathy to the number of non-zero w-levels of a water column
94      !!                  mbathy = min( mbathy, 1 ) + 1
95      !!      (note that the minimum value of mbathy is 2).
96      !!
97      !! ** Action :
98      !!                     tmask    : land/ocean mask at t-point (=0. or 1.)
99      !!                     umask    : land/ocean mask at u-point (=0. or 1.)
100      !!                     vmask    : land/ocean mask at v-point (=0. or 1.)
101      !!                     fmask    : land/ocean mask at f-point (=0. or 1.)
102      !!                          =shlat along lateral boundaries
103      !!                     bmask    : land/ocean mask at barotropic stream
104      !!                          function point (=0. or 1.) and set to
105      !!                          0 along lateral boundaries
106      !!                   mbathy   : number of non-zero w-levels
107      !!
108      !! History :
109      !!        !  87-07  (G. Madec)  Original code
110      !!        !  91-12  (G. Madec)
111      !!        !  92-06  (M. Imbard)
112      !!        !  93-03  (M. Guyon)  symetrical conditions (M. Guyon)
113      !!        !  96-01  (G. Madec)  suppression of common work arrays
114      !!        !  96-05  (G. Madec)  mask computed from tmask and sup-
115      !!                 pression of the double computation of bmask
116      !!        !  97-02  (G. Madec)  mesh information put in domhgr.F
117      !!        !  97-07  (G. Madec)  modification of mbathy and fmask
118      !!        !  98-05  (G. Roullet)  free surface
119      !!        !  00-03  (G. Madec)  no slip accurate
120      !!        !  01-09  (J.-M. Molines)  Open boundaries
121      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
122      !!----------------------------------------------------------------------
123      !! *Local declarations
124      INTEGER  ::   ji, jk     ! dummy loop indices
125      INTEGER  ::   iif, iil, ijf, ijl
126      INTEGER, DIMENSION(jpi,jpj) ::  imsk
127
128      !!---------------------------------------------------------------------
129     
130
131
132      ! Interior domain mask (used for global sum)
133      ! --------------------
134
135      tmask_i(:,:) = tmask(:,:,1)
136      iif = jpreci                         ! ???
137      iil = nlci - jpreci + 1
138      ijf = jprecj                         ! ???
139      ijl = nlcj - jprecj + 1
140
141      tmask_i( 1 :iif,   :   ) = 0.e0      ! first columns
142      tmask_i(iil:jpi,   :   ) = 0.e0      ! last  columns (including mpp extra columns)
143      tmask_i(   :   , 1 :ijf) = 0.e0      ! first rows
144      tmask_i(   :   ,ijl:jpj) = 0.e0      ! last  rows (including mpp extra rows)
145
146
147      ! north fold mask
148      tpol(1:jpiglo) = 1.e0 
149      IF( jperio == 3 .OR. jperio == 4 ) THEN      ! T-point pivot
150         tpol(jpiglo/2+1:jpiglo) = 0.e0
151      ENDIF
152      IF( jperio == 5 .OR. jperio == 6 ) THEN      ! F-point pivot
153         tpol(     1    :jpiglo) = 0.e0
154      ENDIF
155
156      IF( jperio == 3 .OR. jperio == 4 ) THEN      ! T-point pivot: only half of the nlcj-1 row
157         if (mjg(ijl-1) == jpjglo-1) then
158         DO ji = iif+1, iil-1
159            tmask_i(ji,ijl-1) = tmask_i(ji,ijl-1) * tpol(mig(ji))
160         END DO
161         endif
162      ENDIF 
163
164      ! Control print
165      ! -------------
166      IF( nprint == 1 .AND. lwp ) THEN
167         imsk(:,:) = INT( tmask_i(:,:) )
168         WRITE(numout,*) ' tmask_i : '
169         CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1,   &
170               &                           1, jpj, 1, 1, numout)
171         WRITE (numout,*)
172         WRITE (numout,*) ' dommsk: tmask for each level'
173         WRITE (numout,*) ' ----------------------------'
174         DO jk = 1, jpk
175            imsk(:,:) = INT( tmask(:,:,jk) )
176
177            WRITE(numout,*)
178            WRITE(numout,*) ' level = ',jk
179            CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1,   &
180               &                              1, jpj, 1, 1, numout)
181         END DO
182      ENDIF
183
184   END SUBROUTINE dom_msk
185
186END MODULE dommsk
Note: See TracBrowser for help on using the repository browser.