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 @ 5131

Last change on this file since 5131 was 5131, checked in by cetlod, 9 years ago

bugfix:define wmask and rn2b for offline configuration, see ticket#1480

  • Property svn:keywords set to Id
File size: 5.7 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 lib_mpp         ! MPP library
15   USE in_out_manager  ! I/O manager
16   USE wrk_nemo 
17   USE lbclnk 
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   dom_msk    ! routine called by inidom.F90
23
24   REAL(wp)        :: rn_shlat   = 2.   ! type of lateral boundary condition on velocity
25   LOGICAL, PUBLIC :: ln_vorlat  = .false.   !  consistency of vorticity boundary condition
26
27   !! * Substitutions
28#  include "vectopt_loop_substitute.h90"
29   !!----------------------------------------------------------------------
30   !! NEMO/OFF 3.3 , NEMO Consortium (2010)
31   !! $Id$
32   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34CONTAINS
35
36   SUBROUTINE dom_msk
37      !!---------------------------------------------------------------------
38      !!                 ***  ROUTINE dom_msk  ***
39      !!
40      !! ** Purpose :   Off-line case: defines the interior domain T-mask.
41      !!
42      !! ** Method  :   The interior ocean/land mask is computed from tmask
43      !!              setting to zero the duplicated row and lines due to
44      !!              MPP exchange halos, est-west cyclic and north fold
45      !!              boundary conditions.
46      !!
47      !! ** Action :   tmask_i  : interiorland/ocean mask at t-point
48      !!               tpol     : ???
49      !!----------------------------------------------------------------------
50      !
51      INTEGER  ::   ji, jj, jk                   ! dummy loop indices
52      INTEGER  ::   iif, iil, ijf, ijl       ! local integers
53      INTEGER, POINTER, DIMENSION(:,:) ::  imsk 
54      !
55      !!---------------------------------------------------------------------
56     
57      CALL wrk_alloc( jpi, jpj, imsk )
58      !
59      ! Interior domain mask (used for global sum)
60      ! --------------------
61      ssmask(:,:)  = tmask(:,:,1)
62      tmask_i(:,:) = tmask(:,:,1)
63      iif = jpreci                        ! thickness of exchange halos in i-axis
64      iil = nlci - jpreci + 1
65      ijf = jprecj                        ! thickness of exchange halos in j-axis
66      ijl = nlcj - jprecj + 1
67      !
68      tmask_i( 1 :iif,   :   ) = 0._wp    ! first columns
69      tmask_i(iil:jpi,   :   ) = 0._wp    ! last  columns (including mpp extra columns)
70      tmask_i(   :   , 1 :ijf) = 0._wp    ! first rows
71      tmask_i(   :   ,ijl:jpj) = 0._wp    ! last  rows (including mpp extra rows)
72      !
73      !                                   ! north fold mask
74      tpol(1:jpiglo) = 1._wp
75      !                               
76      IF( jperio == 3 .OR. jperio == 4 )   tpol(jpiglo/2+1:jpiglo) = 0._wp    ! T-point pivot
77      IF( jperio == 5 .OR. jperio == 6 )   tpol(     1    :jpiglo) = 0._wp    ! F-point pivot
78      IF( jperio == 3 .OR. jperio == 4 ) THEN      ! T-point pivot: only half of the nlcj-1 row
79         IF( mjg(ijl-1) == jpjglo-1 ) THEN
80            DO ji = iif+1, iil-1
81               tmask_i(ji,ijl-1) = tmask_i(ji,ijl-1) * tpol(mig(ji))
82            END DO
83         ENDIF
84      ENDIF 
85      !
86      ! (ISF) MIN(1,SUM(umask)) is here to check if you have effectively at
87      ! least 1 wet u point
88      DO jj = 1, jpjm1
89         DO ji = 1, fs_jpim1   ! vector loop
90            umask_i(ji,jj)  = ssmask(ji,jj) * ssmask(ji+1,jj  )  * MIN(1._wp,SUM(umask(ji,jj,:)))
91            vmask_i(ji,jj)  = ssmask(ji,jj) * ssmask(ji  ,jj+1)  * MIN(1._wp,SUM(vmask(ji,jj,:)))
92         END DO
93         DO ji = 1, jpim1      ! NO vector opt.
94            fmask_i(ji,jj) =  ssmask(ji,jj  ) * ssmask(ji+1,jj  )   &
95               &            * ssmask(ji,jj+1) * ssmask(ji+1,jj+1) * MIN(1._wp,SUM(fmask(ji,jj,:)))
96         END DO
97      END DO
98      CALL lbc_lnk( umask_i, 'U', 1._wp )      ! Lateral boundary conditions
99      CALL lbc_lnk( vmask_i, 'V', 1._wp )
100      CALL lbc_lnk( fmask_i, 'F', 1._wp )
101
102      ! 3. Ocean/land mask at wu-, wv- and w points
103      !----------------------------------------------
104      wmask (:,:,1) = tmask(:,:,1) ! ????????
105      wumask(:,:,1) = umask(:,:,1) ! ????????
106      wvmask(:,:,1) = vmask(:,:,1) ! ????????
107      DO jk=2,jpk
108         wmask (:,:,jk)=tmask(:,:,jk) * tmask(:,:,jk-1)
109         wumask(:,:,jk)=umask(:,:,jk) * umask(:,:,jk-1)   
110         wvmask(:,:,jk)=vmask(:,:,jk) * vmask(:,:,jk-1)
111      END DO
112      !
113      IF( nprint == 1 .AND. lwp ) THEN    ! Control print
114         imsk(:,:) = INT( tmask_i(:,:) )
115         WRITE(numout,*) ' tmask_i : '
116         CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1, 1, jpj, 1, 1, numout)
117         WRITE (numout,*)
118         WRITE (numout,*) ' dommsk: tmask for each level'
119         WRITE (numout,*) ' ----------------------------'
120         DO jk = 1, jpk
121            imsk(:,:) = INT( tmask(:,:,jk) )
122            WRITE(numout,*)
123            WRITE(numout,*) ' level = ',jk
124            CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1, 1, jpj, 1, 1, numout)
125         END DO
126      ENDIF
127      !
128      CALL wrk_dealloc( jpi, jpj, imsk )
129      !
130   END SUBROUTINE dom_msk
131   !!======================================================================
132END MODULE dommsk
Note: See TracBrowser for help on using the repository browser.