1 | MODULE dommsk |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE dommsk *** |
---|
4 | !! Ocean initialization : domain land/sea mask |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1987-07 (G. Madec) Original code |
---|
7 | !! 6.0 ! 1993-03 (M. Guyon) symetrical conditions (M. Guyon) |
---|
8 | !! 7.0 ! 1996-01 (G. Madec) suppression of common work arrays |
---|
9 | !! - ! 1996-05 (G. Madec) mask computed from tmask |
---|
10 | !! 8.0 ! 1997-02 (G. Madec) mesh information put in domhgr.F |
---|
11 | !! 8.1 ! 1997-07 (G. Madec) modification of kbat and fmask |
---|
12 | !! - ! 1998-05 (G. Roullet) free surface |
---|
13 | !! 8.2 ! 2000-03 (G. Madec) no slip accurate |
---|
14 | !! - ! 2001-09 (J.-M. Molines) Open boundaries |
---|
15 | !! NEMO 1.0 ! 2002-08 (G. Madec) F90: Free form and module |
---|
16 | !! - ! 2005-11 (V. Garnier) Surface pressure gradient organization |
---|
17 | !! 3.2 ! 2009-07 (R. Benshila) Suppression of rigid-lid option |
---|
18 | !! 3.6 ! 2015-05 (P. Mathiot) ISF: add wmask,wumask and wvmask |
---|
19 | !! 4.0 ! 2016-06 (G. Madec, S. Flavoni) domain configuration / user defined interface |
---|
20 | !!---------------------------------------------------------------------- |
---|
21 | |
---|
22 | !!---------------------------------------------------------------------- |
---|
23 | !! dom_msk : compute land/ocean mask |
---|
24 | !!---------------------------------------------------------------------- |
---|
25 | USE oce ! ocean dynamics and tracers |
---|
26 | USE dom_oce ! ocean space and time domain |
---|
27 | USE usrdef_fmask ! user defined fmask |
---|
28 | USE bdy_oce ! open boundary |
---|
29 | ! |
---|
30 | USE in_out_manager ! I/O manager |
---|
31 | USE iom ! IOM library |
---|
32 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
33 | USE lib_mpp ! Massively Parallel Processing library |
---|
34 | |
---|
35 | IMPLICIT NONE |
---|
36 | PRIVATE |
---|
37 | |
---|
38 | PUBLIC dom_msk ! routine called by inidom.F90 |
---|
39 | |
---|
40 | ! !!* Namelist namlbc : lateral boundary condition * |
---|
41 | REAL(wp) :: rn_shlat ! type of lateral boundary condition on velocity |
---|
42 | LOGICAL, PUBLIC :: ln_vorlat ! consistency of vorticity boundary condition |
---|
43 | ! with analytical eqs. |
---|
44 | |
---|
45 | !! * Substitutions |
---|
46 | # include "vectopt_loop_substitute.h90" |
---|
47 | !!---------------------------------------------------------------------- |
---|
48 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
49 | !! $Id$ |
---|
50 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | CONTAINS |
---|
53 | |
---|
54 | SUBROUTINE dom_msk( k_top, k_bot ) |
---|
55 | !!--------------------------------------------------------------------- |
---|
56 | !! *** ROUTINE dom_msk *** |
---|
57 | !! |
---|
58 | !! ** Purpose : Compute land/ocean mask arrays at tracer points, hori- |
---|
59 | !! zontal velocity points (u & v), vorticity points (f) points. |
---|
60 | !! |
---|
61 | !! ** Method : The ocean/land mask at t-point is deduced from ko_top |
---|
62 | !! and ko_bot, the indices of the fist and last ocean t-levels which |
---|
63 | !! are either defined in usrdef_zgr or read in zgr_read. |
---|
64 | !! The velocity masks (umask, vmask, wmask, wumask, wvmask) |
---|
65 | !! are deduced from a product of the two neighboring tmask. |
---|
66 | !! The vorticity mask (fmask) is deduced from tmask taking |
---|
67 | !! into account the choice of lateral boundary condition (rn_shlat) : |
---|
68 | !! rn_shlat = 0, free slip (no shear along the coast) |
---|
69 | !! rn_shlat = 2, no slip (specified zero velocity at the coast) |
---|
70 | !! 0 < rn_shlat < 2, partial slip | non-linear velocity profile |
---|
71 | !! 2 < rn_shlat, strong slip | in the lateral boundary layer |
---|
72 | !! |
---|
73 | !! tmask_i : interior ocean mask at t-point, i.e. excluding duplicated |
---|
74 | !! rows/lines due to cyclic or North Fold boundaries as well |
---|
75 | !! as MPP halos. |
---|
76 | !! tmask_h : halo mask at t-point, i.e. excluding duplicated rows/lines |
---|
77 | !! due to cyclic or North Fold boundaries as well as MPP halos. |
---|
78 | !! |
---|
79 | !! ** Action : tmask, umask, vmask, wmask, wumask, wvmask : land/ocean mask |
---|
80 | !! at t-, u-, v- w, wu-, and wv-points (=0. or 1.) |
---|
81 | !! fmask : land/ocean mask at f-point (=0., or =1., or |
---|
82 | !! =rn_shlat along lateral boundaries) |
---|
83 | !! tmask_i : interior ocean mask |
---|
84 | !! tmask_h : halo mask |
---|
85 | !! ssmask , ssumask, ssvmask, ssfmask : 2D ocean mask |
---|
86 | !!---------------------------------------------------------------------- |
---|
87 | INTEGER, DIMENSION(:,:), INTENT(in) :: k_top, k_bot ! first and last ocean level |
---|
88 | ! |
---|
89 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
90 | INTEGER :: iif, iil ! local integers |
---|
91 | INTEGER :: ijf, ijl ! - - |
---|
92 | INTEGER :: iktop, ikbot ! - - |
---|
93 | INTEGER :: ios, inum |
---|
94 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zwf ! 2D workspace |
---|
95 | !! |
---|
96 | NAMELIST/namlbc/ rn_shlat, ln_vorlat |
---|
97 | NAMELIST/nambdy/ ln_bdy ,nb_bdy, ln_coords_file, cn_coords_file, & |
---|
98 | & ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta, & |
---|
99 | & cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta, & |
---|
100 | & ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, rn_time_dmp_out, & |
---|
101 | & cn_ice, nn_ice_dta, & |
---|
102 | & rn_ice_tem, rn_ice_sal, rn_ice_age, & |
---|
103 | & ln_vol, nn_volctl, nn_rimwidth, nb_jpk_bdy |
---|
104 | !!--------------------------------------------------------------------- |
---|
105 | ! |
---|
106 | REWIND( numnam_ref ) ! Namelist namlbc in reference namelist : Lateral momentum boundary condition |
---|
107 | READ ( numnam_ref, namlbc, IOSTAT = ios, ERR = 901 ) |
---|
108 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlbc in reference namelist', lwp ) |
---|
109 | REWIND( numnam_cfg ) ! Namelist namlbc in configuration namelist : Lateral momentum boundary condition |
---|
110 | READ ( numnam_cfg, namlbc, IOSTAT = ios, ERR = 902 ) |
---|
111 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namlbc in configuration namelist', lwp ) |
---|
112 | IF(lwm) WRITE ( numond, namlbc ) |
---|
113 | |
---|
114 | IF(lwp) THEN ! control print |
---|
115 | WRITE(numout,*) |
---|
116 | WRITE(numout,*) 'dommsk : ocean mask ' |
---|
117 | WRITE(numout,*) '~~~~~~' |
---|
118 | WRITE(numout,*) ' Namelist namlbc' |
---|
119 | WRITE(numout,*) ' lateral momentum boundary cond. rn_shlat = ',rn_shlat |
---|
120 | WRITE(numout,*) ' consistency with analytical form ln_vorlat = ',ln_vorlat |
---|
121 | ENDIF |
---|
122 | ! |
---|
123 | IF(lwp) WRITE(numout,*) |
---|
124 | IF ( rn_shlat == 0. ) THEN ; IF(lwp) WRITE(numout,*) ' ==>>> ocean lateral free-slip' |
---|
125 | ELSEIF ( rn_shlat == 2. ) THEN ; IF(lwp) WRITE(numout,*) ' ==>>> ocean lateral no-slip' |
---|
126 | ELSEIF ( 0. < rn_shlat .AND. rn_shlat < 2. ) THEN ; IF(lwp) WRITE(numout,*) ' ==>>> ocean lateral partial-slip' |
---|
127 | ELSEIF ( 2. < rn_shlat ) THEN ; IF(lwp) WRITE(numout,*) ' ==>>> ocean lateral strong-slip' |
---|
128 | ELSE |
---|
129 | CALL ctl_stop( 'dom_msk: wrong value for rn_shlat (i.e. a negalive value). We stop.' ) |
---|
130 | ENDIF |
---|
131 | |
---|
132 | ! Ocean/land mask at t-point (computed from ko_top and ko_bot) |
---|
133 | ! ---------------------------- |
---|
134 | ! |
---|
135 | tmask(:,:,:) = 0._wp |
---|
136 | DO jj = 1, jpj |
---|
137 | DO ji = 1, jpi |
---|
138 | iktop = k_top(ji,jj) |
---|
139 | ikbot = k_bot(ji,jj) |
---|
140 | IF( iktop /= 0 ) THEN ! water in the column |
---|
141 | tmask(ji,jj,iktop:ikbot ) = 1._wp |
---|
142 | ENDIF |
---|
143 | END DO |
---|
144 | END DO |
---|
145 | ! |
---|
146 | ! the following call is mandatory |
---|
147 | ! it masks boundaries (bathy=0) where needed depending on the configuration (closed, periodic...) |
---|
148 | CALL lbc_lnk( 'dommsk', tmask , 'T', 1._wp ) ! Lateral boundary conditions |
---|
149 | |
---|
150 | ! Mask corrections for bdy (read in mppini2) |
---|
151 | REWIND( numnam_ref ) ! Namelist nambdy in reference namelist :Unstructured open boundaries |
---|
152 | READ ( numnam_ref, nambdy, IOSTAT = ios, ERR = 903) |
---|
153 | 903 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy in reference namelist', lwp ) |
---|
154 | REWIND( numnam_cfg ) ! Namelist nambdy in configuration namelist :Unstructured open boundaries |
---|
155 | READ ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 904 ) |
---|
156 | 904 IF( ios > 0 ) CALL ctl_nam ( ios , 'nambdy in configuration namelist', lwp ) |
---|
157 | ! ------------------------ |
---|
158 | IF ( ln_bdy .AND. ln_mask_file ) THEN |
---|
159 | CALL iom_open( cn_mask_file, inum ) |
---|
160 | CALL iom_get ( inum, jpdom_data, 'bdy_msk', bdytmask(:,:) ) |
---|
161 | CALL iom_close( inum ) |
---|
162 | DO jk = 1, jpkm1 |
---|
163 | DO jj = 1, jpj |
---|
164 | DO ji = 1, jpi |
---|
165 | tmask(ji,jj,jk) = tmask(ji,jj,jk) * bdytmask(ji,jj) |
---|
166 | END DO |
---|
167 | END DO |
---|
168 | END DO |
---|
169 | ENDIF |
---|
170 | |
---|
171 | ! Ocean/land mask at u-, v-, and f-points (computed from tmask) |
---|
172 | ! ---------------------------------------- |
---|
173 | ! NB: at this point, fmask is designed for free slip lateral boundary condition |
---|
174 | DO jk = 1, jpk |
---|
175 | DO jj = 1, jpjm1 |
---|
176 | DO ji = 1, fs_jpim1 ! vector loop |
---|
177 | umask(ji,jj,jk) = tmask(ji,jj ,jk) * tmask(ji+1,jj ,jk) |
---|
178 | vmask(ji,jj,jk) = tmask(ji,jj ,jk) * tmask(ji ,jj+1,jk) |
---|
179 | END DO |
---|
180 | DO ji = 1, jpim1 ! NO vector opt. |
---|
181 | fmask(ji,jj,jk) = tmask(ji,jj ,jk) * tmask(ji+1,jj ,jk) & |
---|
182 | & * tmask(ji,jj+1,jk) * tmask(ji+1,jj+1,jk) |
---|
183 | END DO |
---|
184 | END DO |
---|
185 | END DO |
---|
186 | CALL lbc_lnk_multi( 'dommsk', umask, 'U', 1., vmask, 'V', 1., fmask, 'F', 1. ) ! Lateral boundary conditions |
---|
187 | |
---|
188 | ! Ocean/land mask at wu-, wv- and w points (computed from tmask) |
---|
189 | !----------------------------------------- |
---|
190 | wmask (:,:,1) = tmask(:,:,1) ! surface |
---|
191 | wumask(:,:,1) = umask(:,:,1) |
---|
192 | wvmask(:,:,1) = vmask(:,:,1) |
---|
193 | DO jk = 2, jpk ! interior values |
---|
194 | wmask (:,:,jk) = tmask(:,:,jk) * tmask(:,:,jk-1) |
---|
195 | wumask(:,:,jk) = umask(:,:,jk) * umask(:,:,jk-1) |
---|
196 | wvmask(:,:,jk) = vmask(:,:,jk) * vmask(:,:,jk-1) |
---|
197 | END DO |
---|
198 | |
---|
199 | |
---|
200 | ! Ocean/land column mask at t-, u-, and v-points (i.e. at least 1 wet cell in the vertical) |
---|
201 | ! ---------------------------------------------- |
---|
202 | ssmask (:,:) = MAXVAL( tmask(:,:,:), DIM=3 ) |
---|
203 | ssumask(:,:) = MAXVAL( umask(:,:,:), DIM=3 ) |
---|
204 | ssvmask(:,:) = MAXVAL( vmask(:,:,:), DIM=3 ) |
---|
205 | |
---|
206 | |
---|
207 | ! Interior domain mask (used for global sum) |
---|
208 | ! -------------------- |
---|
209 | ! |
---|
210 | iif = nn_hls ; iil = nlci - nn_hls + 1 |
---|
211 | ijf = nn_hls ; ijl = nlcj - nn_hls + 1 |
---|
212 | ! |
---|
213 | ! ! halo mask : 0 on the halo and 1 elsewhere |
---|
214 | tmask_h(:,:) = 1._wp |
---|
215 | tmask_h( 1 :iif, : ) = 0._wp ! first columns |
---|
216 | tmask_h(iil:jpi, : ) = 0._wp ! last columns (including mpp extra columns) |
---|
217 | tmask_h( : , 1 :ijf) = 0._wp ! first rows |
---|
218 | tmask_h( : ,ijl:jpj) = 0._wp ! last rows (including mpp extra rows) |
---|
219 | ! |
---|
220 | ! ! north fold mask |
---|
221 | tpol(1:jpiglo) = 1._wp |
---|
222 | fpol(1:jpiglo) = 1._wp |
---|
223 | IF( jperio == 3 .OR. jperio == 4 ) THEN ! T-point pivot |
---|
224 | tpol(jpiglo/2+1:jpiglo) = 0._wp |
---|
225 | fpol( 1 :jpiglo) = 0._wp |
---|
226 | IF( mjg(nlej) == jpjglo ) THEN ! only half of the nlcj-1 row for tmask_h |
---|
227 | DO ji = iif+1, iil-1 |
---|
228 | tmask_h(ji,nlej-1) = tmask_h(ji,nlej-1) * tpol(mig(ji)) |
---|
229 | END DO |
---|
230 | ENDIF |
---|
231 | ENDIF |
---|
232 | ! |
---|
233 | IF( jperio == 5 .OR. jperio == 6 ) THEN ! F-point pivot |
---|
234 | tpol( 1 :jpiglo) = 0._wp |
---|
235 | fpol(jpiglo/2+1:jpiglo) = 0._wp |
---|
236 | ENDIF |
---|
237 | ! |
---|
238 | ! ! interior mask : 2D ocean mask x halo mask |
---|
239 | tmask_i(:,:) = ssmask(:,:) * tmask_h(:,:) |
---|
240 | |
---|
241 | |
---|
242 | ! Lateral boundary conditions on velocity (modify fmask) |
---|
243 | ! --------------------------------------- |
---|
244 | IF( rn_shlat /= 0 ) THEN ! Not free-slip lateral boundary condition |
---|
245 | ! |
---|
246 | ALLOCATE( zwf(jpi,jpj) ) |
---|
247 | ! |
---|
248 | DO jk = 1, jpk |
---|
249 | zwf(:,:) = fmask(:,:,jk) |
---|
250 | DO jj = 2, jpjm1 |
---|
251 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
252 | IF( fmask(ji,jj,jk) == 0._wp ) THEN |
---|
253 | fmask(ji,jj,jk) = rn_shlat * MIN( 1._wp , MAX( zwf(ji+1,jj), zwf(ji,jj+1), & |
---|
254 | & zwf(ji-1,jj), zwf(ji,jj-1) ) ) |
---|
255 | ENDIF |
---|
256 | END DO |
---|
257 | END DO |
---|
258 | DO jj = 2, jpjm1 |
---|
259 | IF( fmask(1,jj,jk) == 0._wp ) THEN |
---|
260 | fmask(1 ,jj,jk) = rn_shlat * MIN( 1._wp , MAX( zwf(2,jj), zwf(1,jj+1), zwf(1,jj-1) ) ) |
---|
261 | ENDIF |
---|
262 | IF( fmask(jpi,jj,jk) == 0._wp ) THEN |
---|
263 | fmask(jpi,jj,jk) = rn_shlat * MIN( 1._wp , MAX( zwf(jpi,jj+1), zwf(jpim1,jj), zwf(jpi,jj-1) ) ) |
---|
264 | ENDIF |
---|
265 | END DO |
---|
266 | DO ji = 2, jpim1 |
---|
267 | IF( fmask(ji,1,jk) == 0._wp ) THEN |
---|
268 | fmask(ji, 1 ,jk) = rn_shlat * MIN( 1._wp , MAX( zwf(ji+1,1), zwf(ji,2), zwf(ji-1,1) ) ) |
---|
269 | ENDIF |
---|
270 | IF( fmask(ji,jpj,jk) == 0._wp ) THEN |
---|
271 | fmask(ji,jpj,jk) = rn_shlat * MIN( 1._wp , MAX( zwf(ji+1,jpj), zwf(ji-1,jpj), zwf(ji,jpjm1) ) ) |
---|
272 | ENDIF |
---|
273 | END DO |
---|
274 | #if defined key_agrif |
---|
275 | IF( .NOT. AGRIF_Root() ) THEN |
---|
276 | IF ((nbondi == 1).OR.(nbondi == 2)) fmask(nlci-1 , : ,jk) = 0.e0 ! east |
---|
277 | IF ((nbondi == -1).OR.(nbondi == 2)) fmask(1 , : ,jk) = 0.e0 ! west |
---|
278 | IF ((nbondj == 1).OR.(nbondj == 2)) fmask(: ,nlcj-1 ,jk) = 0.e0 ! north |
---|
279 | IF ((nbondj == -1).OR.(nbondj == 2)) fmask(: ,1 ,jk) = 0.e0 ! south |
---|
280 | ENDIF |
---|
281 | #endif |
---|
282 | END DO |
---|
283 | ! |
---|
284 | DEALLOCATE( zwf ) |
---|
285 | ! |
---|
286 | CALL lbc_lnk( 'dommsk', fmask, 'F', 1._wp ) ! Lateral boundary conditions on fmask |
---|
287 | ! |
---|
288 | ! CAUTION : The fmask may be further modified in dyn_vor_init ( dynvor.F90 ) depending on ln_vorlat |
---|
289 | ! |
---|
290 | ENDIF |
---|
291 | |
---|
292 | ! User defined alteration of fmask (use to reduce ocean transport in specified straits) |
---|
293 | ! -------------------------------- |
---|
294 | ! |
---|
295 | CALL usr_def_fmask( cn_cfg, nn_cfg, fmask ) |
---|
296 | ! |
---|
297 | END SUBROUTINE dom_msk |
---|
298 | |
---|
299 | !!====================================================================== |
---|
300 | END MODULE dommsk |
---|