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

source: trunk/NEMOGCM/NEMO/OFF_SRC/dommsk.F90 @ 2571

Last change on this file since 2571 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

  • Property svn:keywords set to Id
File size: 4.3 KB
Line 
1MODULE dommsk
2   !!======================================================================
3   !!                       ***  MODULE dommsk   ***
4   !! Ocean initialization : domain land/sea masks, off-line case
5   !!======================================================================
6   !! History :  3.3  ! 2010-10  (C. Ethe)  adapted from OPA_SRC/DOM/dommsk
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   dom_msk        : compute land/ocean mask
11   !!----------------------------------------------------------------------
12   USE oce             ! ocean dynamics and tracers
13   USE dom_oce         ! ocean space and time domain
14   USE in_out_manager  ! I/O manager
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC   dom_msk    ! routine called by inidom.F90
20
21#if defined key_degrad
22   !! ------------------------------------------------
23   !! Degradation method
24   !! --------------------------------------------------
25   REAL(wp), PUBLIC, DIMENSION (jpi,jpj,jpk) ::   facvol  !! volume for degraded regions
26#endif
27
28   !! * Substitutions
29#  include "vectopt_loop_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/OFF 3.3 , NEMO Consortium (2010)
32   !! $Id$
33   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35CONTAINS
36   
37   SUBROUTINE dom_msk
38      !!---------------------------------------------------------------------
39      !!                 ***  ROUTINE dom_msk  ***
40      !!
41      !! ** Purpose :   Off-line case: defines the interior domain T-mask.
42      !!
43      !! ** Method  :   The interior ocean/land mask is computed from tmask
44      !!              setting to zero the duplicated row and lines due to
45      !!              MPP exchange halos, est-west cyclic and north fold
46      !!              boundary conditions.
47      !!
48      !! ** Action :   tmask_i  : interiorland/ocean mask at t-point
49      !!               tpol     : ???
50      !!----------------------------------------------------------------------
51      INTEGER  ::   ji, jk                   ! dummy loop indices
52      INTEGER  ::   iif, iil, ijf, ijl       ! local integers
53      INTEGER, DIMENSION(jpi,jpj) ::  imsk   ! 2D workspace
54      !!---------------------------------------------------------------------
55      !
56      ! Interior domain mask (used for global sum)
57      ! --------------------
58      tmask_i(:,:) = tmask(:,:,1)
59      iif = jpreci                        ! thickness of exchange halos in i-axis
60      iil = nlci - jpreci + 1
61      ijf = jprecj                        ! thickness of exchange halos in j-axis
62      ijl = nlcj - jprecj + 1
63      !
64      tmask_i( 1 :iif,   :   ) = 0._wp    ! first columns
65      tmask_i(iil:jpi,   :   ) = 0._wp    ! last  columns (including mpp extra columns)
66      tmask_i(   :   , 1 :ijf) = 0._wp    ! first rows
67      tmask_i(   :   ,ijl:jpj) = 0._wp    ! last  rows (including mpp extra rows)
68      !
69      !                                   ! north fold mask
70      tpol(1:jpiglo) = 1._wp
71      !                               
72      IF( jperio == 3 .OR. jperio == 4 )   tpol(jpiglo/2+1:jpiglo) = 0._wp    ! T-point pivot
73      IF( jperio == 5 .OR. jperio == 6 )   tpol(     1    :jpiglo) = 0._wp    ! F-point pivot
74      IF( jperio == 3 .OR. jperio == 4 ) THEN      ! T-point pivot: only half of the nlcj-1 row
75         IF( mjg(ijl-1) == jpjglo-1 ) THEN
76            DO ji = iif+1, iil-1
77               tmask_i(ji,ijl-1) = tmask_i(ji,ijl-1) * tpol(mig(ji))
78            END DO
79         ENDIF
80      ENDIF 
81      !
82      IF( nprint == 1 .AND. lwp ) THEN    ! Control print
83         imsk(:,:) = INT( tmask_i(:,:) )
84         WRITE(numout,*) ' tmask_i : '
85         CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1, 1, jpj, 1, 1, numout)
86         WRITE (numout,*)
87         WRITE (numout,*) ' dommsk: tmask for each level'
88         WRITE (numout,*) ' ----------------------------'
89         DO jk = 1, jpk
90            imsk(:,:) = INT( tmask(:,:,jk) )
91            WRITE(numout,*)
92            WRITE(numout,*) ' level = ',jk
93            CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1, 1, jpj, 1, 1, numout)
94         END DO
95      ENDIF
96      !
97   END SUBROUTINE dom_msk
98
99   !!======================================================================
100END MODULE dommsk
Note: See TracBrowser for help on using the repository browser.