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

source: tags/start/NEMO/OFF_SRC/DOM/dommsk.F90 @ 8479

Last change on this file since 8479 was 325, checked in by opalod, 19 years ago

Initial revision

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