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 trunk/NEMO/OFF_SRC/DOM – NEMO

source: trunk/NEMO/OFF_SRC/DOM/dommsk.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

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