1 | MODULE bdyini |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE bdyini *** |
---|
4 | !! Unstructured open boundaries : initialisation |
---|
5 | !!====================================================================== |
---|
6 | !! History : 1.0 ! 2005-01 (J. Chanut, A. Sellar) Original code |
---|
7 | !! - ! 2007-01 (D. Storkey) Update to use IOM module |
---|
8 | !! - ! 2007-01 (D. Storkey) Tidal forcing |
---|
9 | !! 3.0 ! 2008-04 (NEMO team) add in the reference version |
---|
10 | !! 3.3 ! 2010-09 (E.O'Dea) updates for Shelf configurations |
---|
11 | !! 3.3 ! 2010-09 (D.Storkey) add ice boundary conditions |
---|
12 | !! 3.4 ! 2011 (D. Storkey) rewrite in preparation for OBC-BDY merge |
---|
13 | !! 3.4 ! 2012 (J. Chanut) straight open boundary case update |
---|
14 | !! 3.5 ! 2012 (S. Mocavero, I. Epicoco) Updates for the |
---|
15 | !! optimization of BDY communications |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | #if defined key_bdy |
---|
18 | !!---------------------------------------------------------------------- |
---|
19 | !! 'key_bdy' Unstructured Open Boundary Conditions |
---|
20 | !!---------------------------------------------------------------------- |
---|
21 | !! bdy_init : Initialization of unstructured open boundaries |
---|
22 | !!---------------------------------------------------------------------- |
---|
23 | USE timing ! Timing |
---|
24 | USE oce ! ocean dynamics and tracers variables |
---|
25 | USE dom_oce ! ocean space and time domain |
---|
26 | USE bdy_oce ! unstructured open boundary conditions |
---|
27 | USE in_out_manager ! I/O units |
---|
28 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
29 | USE lib_mpp ! for mpp_sum |
---|
30 | USE iom ! I/O |
---|
31 | USE sbctide, ONLY: lk_tide ! Tidal forcing or not |
---|
32 | USE phycst, ONLY: rday |
---|
33 | |
---|
34 | IMPLICIT NONE |
---|
35 | PRIVATE |
---|
36 | |
---|
37 | PUBLIC bdy_init ! routine called in nemo_init |
---|
38 | |
---|
39 | INTEGER, PARAMETER :: jp_nseg = 100 |
---|
40 | INTEGER, PARAMETER :: nrimmax = 20 ! maximum rimwidth in structured |
---|
41 | ! open boundary data files |
---|
42 | ! Straight open boundary segment parameters: |
---|
43 | INTEGER :: nbdysege, nbdysegw, nbdysegn, nbdysegs |
---|
44 | INTEGER, DIMENSION(jp_nseg) :: jpieob, jpjedt, jpjeft, npckge |
---|
45 | INTEGER, DIMENSION(jp_nseg) :: jpiwob, jpjwdt, jpjwft, npckgw |
---|
46 | INTEGER, DIMENSION(jp_nseg) :: jpjnob, jpindt, jpinft, npckgn |
---|
47 | INTEGER, DIMENSION(jp_nseg) :: jpjsob, jpisdt, jpisft, npckgs |
---|
48 | !!---------------------------------------------------------------------- |
---|
49 | !! NEMO/OPA 4.0 , NEMO Consortium (2011) |
---|
50 | !! $Id$ |
---|
51 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
52 | !!---------------------------------------------------------------------- |
---|
53 | CONTAINS |
---|
54 | |
---|
55 | SUBROUTINE bdy_init |
---|
56 | !!---------------------------------------------------------------------- |
---|
57 | !! *** ROUTINE bdy_init *** |
---|
58 | !! |
---|
59 | !! ** Purpose : Initialization of the dynamics and tracer fields with |
---|
60 | !! unstructured open boundaries. |
---|
61 | !! |
---|
62 | !! ** Method : Read initialization arrays (mask, indices) to identify |
---|
63 | !! an unstructured open boundary |
---|
64 | !! |
---|
65 | !! ** Input : bdy_init.nc, input file for unstructured open boundaries |
---|
66 | !!---------------------------------------------------------------------- |
---|
67 | ! namelist variables |
---|
68 | !------------------- |
---|
69 | CHARACTER(LEN=80),DIMENSION(jpbgrd) :: clfile |
---|
70 | CHARACTER(LEN=1) :: ctypebdy |
---|
71 | INTEGER :: nbdyind, nbdybeg, nbdyend |
---|
72 | |
---|
73 | ! local variables |
---|
74 | !------------------- |
---|
75 | INTEGER :: ib_bdy, ii, ij, ik, igrd, ib, ir, iseg ! dummy loop indices |
---|
76 | INTEGER :: icount, icountr, ibr_max, ilen1, ibm1 ! local integers |
---|
77 | INTEGER :: iw, ie, is, in, inum, id_dummy ! - - |
---|
78 | INTEGER :: igrd_start, igrd_end, jpbdta ! - - |
---|
79 | INTEGER :: jpbdtau, jpbdtas ! - - |
---|
80 | INTEGER :: ib_bdy1, ib_bdy2, ib1, ib2 ! - - |
---|
81 | INTEGER, POINTER :: nbi, nbj, nbr ! short cuts |
---|
82 | REAL , POINTER :: flagu, flagv ! - - |
---|
83 | REAL(wp) :: zefl, zwfl, znfl, zsfl ! local scalars |
---|
84 | INTEGER, DIMENSION (2) :: kdimsz |
---|
85 | INTEGER, DIMENSION(jpbgrd,jp_bdy) :: nblendta ! Length of index arrays |
---|
86 | INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: nbidta, nbjdta ! Index arrays: i and j indices of bdy dta |
---|
87 | INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: nbrdta ! Discrete distance from rim points |
---|
88 | CHARACTER(LEN=1),DIMENSION(jpbgrd) :: cgrid |
---|
89 | INTEGER :: com_east, com_west, com_south, com_north ! Flags for boundaries sending |
---|
90 | INTEGER :: com_east_b, com_west_b, com_south_b, com_north_b ! Flags for boundaries receiving |
---|
91 | INTEGER :: iw_b(4), ie_b(4), is_b(4), in_b(4) ! Arrays for neighbours coordinates |
---|
92 | |
---|
93 | !! |
---|
94 | NAMELIST/nambdy/ nb_bdy, ln_coords_file, cn_coords_file, & |
---|
95 | & ln_mask_file, cn_mask_file, nn_dyn2d, nn_dyn2d_dta, & |
---|
96 | & nn_dyn3d, nn_dyn3d_dta, nn_tra, nn_tra_dta, & |
---|
97 | & ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, & |
---|
98 | #if defined key_lim2 |
---|
99 | & nn_ice_lim2, nn_ice_lim2_dta, & |
---|
100 | #endif |
---|
101 | & ln_vol, nn_volctl, nn_rimwidth |
---|
102 | !! |
---|
103 | NAMELIST/nambdy_index/ ctypebdy, nbdyind, nbdybeg, nbdyend |
---|
104 | |
---|
105 | !!---------------------------------------------------------------------- |
---|
106 | |
---|
107 | IF( nn_timing == 1 ) CALL timing_start('bdy_init') |
---|
108 | |
---|
109 | IF( bdy_oce_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'bdy_init : unable to allocate oce arrays' ) |
---|
110 | |
---|
111 | IF(lwp) WRITE(numout,*) |
---|
112 | IF(lwp) WRITE(numout,*) 'bdy_init : initialization of open boundaries' |
---|
113 | IF(lwp) WRITE(numout,*) '~~~~~~~~' |
---|
114 | ! |
---|
115 | |
---|
116 | IF( jperio /= 0 ) CALL ctl_stop( 'Cyclic or symmetric,', & |
---|
117 | & ' and general open boundary condition are not compatible' ) |
---|
118 | |
---|
119 | cgrid= (/'t','u','v'/) |
---|
120 | |
---|
121 | ! ----------------------------------------- |
---|
122 | ! Initialise and read namelist parameters |
---|
123 | ! ----------------------------------------- |
---|
124 | |
---|
125 | nb_bdy = 0 |
---|
126 | ln_coords_file(:) = .false. |
---|
127 | cn_coords_file(:) = '' |
---|
128 | ln_mask_file = .false. |
---|
129 | cn_mask_file(:) = '' |
---|
130 | nn_dyn2d(:) = 0 |
---|
131 | nn_dyn2d_dta(:) = -1 ! uninitialised flag |
---|
132 | nn_dyn3d(:) = 0 |
---|
133 | nn_dyn3d_dta(:) = -1 ! uninitialised flag |
---|
134 | nn_tra(:) = 0 |
---|
135 | nn_tra_dta(:) = -1 ! uninitialised flag |
---|
136 | ln_tra_dmp(:) = .false. |
---|
137 | ln_dyn3d_dmp(:) = .false. |
---|
138 | rn_time_dmp(:) = 1. |
---|
139 | #if defined key_lim2 |
---|
140 | nn_ice_lim2(:) = 0 |
---|
141 | nn_ice_lim2_dta(:)= -1 ! uninitialised flag |
---|
142 | #endif |
---|
143 | ln_vol = .false. |
---|
144 | nn_volctl = -1 ! uninitialised flag |
---|
145 | nn_rimwidth(:) = -1 ! uninitialised flag |
---|
146 | |
---|
147 | REWIND( numnam ) |
---|
148 | READ ( numnam, nambdy ) |
---|
149 | |
---|
150 | ! ----------------------------------------- |
---|
151 | ! Check and write out namelist parameters |
---|
152 | ! ----------------------------------------- |
---|
153 | ! ! control prints |
---|
154 | IF(lwp) WRITE(numout,*) ' nambdy' |
---|
155 | |
---|
156 | IF( nb_bdy .eq. 0 ) THEN |
---|
157 | IF(lwp) WRITE(numout,*) 'nb_bdy = 0, NO OPEN BOUNDARIES APPLIED.' |
---|
158 | ELSE |
---|
159 | IF(lwp) WRITE(numout,*) 'Number of open boundary sets : ',nb_bdy |
---|
160 | ENDIF |
---|
161 | |
---|
162 | DO ib_bdy = 1,nb_bdy |
---|
163 | IF(lwp) WRITE(numout,*) ' ' |
---|
164 | IF(lwp) WRITE(numout,*) '------ Open boundary data set ',ib_bdy,'------' |
---|
165 | |
---|
166 | IF( ln_coords_file(ib_bdy) ) THEN |
---|
167 | IF(lwp) WRITE(numout,*) 'Boundary definition read from file '//TRIM(cn_coords_file(ib_bdy)) |
---|
168 | ELSE |
---|
169 | IF(lwp) WRITE(numout,*) 'Boundary defined in namelist.' |
---|
170 | ENDIF |
---|
171 | IF(lwp) WRITE(numout,*) |
---|
172 | |
---|
173 | IF(lwp) WRITE(numout,*) 'Boundary conditions for barotropic solution: ' |
---|
174 | SELECT CASE( nn_dyn2d(ib_bdy) ) |
---|
175 | CASE(jp_none) ; IF(lwp) WRITE(numout,*) ' no open boundary condition' |
---|
176 | CASE(jp_frs) ; IF(lwp) WRITE(numout,*) ' Flow Relaxation Scheme' |
---|
177 | CASE(jp_flather) ; IF(lwp) WRITE(numout,*) ' Flather radiation condition' |
---|
178 | CASE DEFAULT ; CALL ctl_stop( 'unrecognised value for nn_dyn2d' ) |
---|
179 | END SELECT |
---|
180 | IF( nn_dyn2d(ib_bdy) .gt. 0 ) THEN |
---|
181 | SELECT CASE( nn_dyn2d_dta(ib_bdy) ) ! |
---|
182 | CASE( 0 ) ; IF(lwp) WRITE(numout,*) ' initial state used for bdy data' |
---|
183 | CASE( 1 ) ; IF(lwp) WRITE(numout,*) ' boundary data taken from file' |
---|
184 | CASE( 2 ) ; IF(lwp) WRITE(numout,*) ' tidal harmonic forcing taken from file' |
---|
185 | CASE( 3 ) ; IF(lwp) WRITE(numout,*) ' boundary data AND tidal harmonic forcing taken from files' |
---|
186 | CASE DEFAULT ; CALL ctl_stop( 'nn_dyn2d_dta must be between 0 and 3' ) |
---|
187 | END SELECT |
---|
188 | IF (( nn_dyn2d_dta(ib_bdy) .ge. 2 ).AND.(.NOT.lk_tide)) THEN |
---|
189 | CALL ctl_stop( 'You must activate key_tide to add tidal forcing at open boundaries' ) |
---|
190 | ENDIF |
---|
191 | ENDIF |
---|
192 | IF(lwp) WRITE(numout,*) |
---|
193 | |
---|
194 | IF(lwp) WRITE(numout,*) 'Boundary conditions for baroclinic velocities: ' |
---|
195 | SELECT CASE( nn_dyn3d(ib_bdy) ) |
---|
196 | CASE(jp_none) ; IF(lwp) WRITE(numout,*) ' no open boundary condition' |
---|
197 | CASE(jp_frs) ; IF(lwp) WRITE(numout,*) ' Flow Relaxation Scheme' |
---|
198 | CASE( 2 ) ; IF(lwp) WRITE(numout,*) ' Specified value' |
---|
199 | CASE( 3 ) ; IF(lwp) WRITE(numout,*) ' Zero baroclinic velocities (runoff case)' |
---|
200 | CASE DEFAULT ; CALL ctl_stop( 'unrecognised value for nn_dyn3d' ) |
---|
201 | END SELECT |
---|
202 | IF( nn_dyn3d(ib_bdy) .gt. 0 ) THEN |
---|
203 | SELECT CASE( nn_dyn3d_dta(ib_bdy) ) ! |
---|
204 | CASE( 0 ) ; IF(lwp) WRITE(numout,*) ' initial state used for bdy data' |
---|
205 | CASE( 1 ) ; IF(lwp) WRITE(numout,*) ' boundary data taken from file' |
---|
206 | CASE DEFAULT ; CALL ctl_stop( 'nn_dyn3d_dta must be 0 or 1' ) |
---|
207 | END SELECT |
---|
208 | ENDIF |
---|
209 | |
---|
210 | IF ( ln_dyn3d_dmp(ib_bdy) ) THEN |
---|
211 | IF ( nn_dyn3d(ib_bdy).EQ.0 ) THEN |
---|
212 | IF(lwp) WRITE(numout,*) 'No open boundary condition for baroclinic velocities: ln_dyn3d_dmp is set to .false.' |
---|
213 | ln_dyn3d_dmp(ib_bdy)=.false. |
---|
214 | ELSEIF ( nn_dyn3d(ib_bdy).EQ.1 ) THEN |
---|
215 | CALL ctl_stop( 'Use FRS OR relaxation' ) |
---|
216 | ELSE |
---|
217 | IF(lwp) WRITE(numout,*) ' + baroclinic velocities relaxation zone' |
---|
218 | IF(lwp) WRITE(numout,*) ' Damping time scale: ',rn_time_dmp(ib_bdy),' days' |
---|
219 | IF((lwp).AND.rn_time_dmp(ib_bdy)<0) CALL ctl_stop( 'Time scale must be positive' ) |
---|
220 | ENDIF |
---|
221 | ELSE |
---|
222 | IF(lwp) WRITE(numout,*) ' NO relaxation on baroclinic velocities' |
---|
223 | ENDIF |
---|
224 | IF(lwp) WRITE(numout,*) |
---|
225 | |
---|
226 | IF(lwp) WRITE(numout,*) 'Boundary conditions for temperature and salinity: ' |
---|
227 | SELECT CASE( nn_tra(ib_bdy) ) |
---|
228 | CASE(jp_none) ; IF(lwp) WRITE(numout,*) ' no open boundary condition' |
---|
229 | CASE(jp_frs) ; IF(lwp) WRITE(numout,*) ' Flow Relaxation Scheme' |
---|
230 | CASE( 2 ) ; IF(lwp) WRITE(numout,*) ' Specified value' |
---|
231 | CASE( 3 ) ; IF(lwp) WRITE(numout,*) ' Neumann conditions' |
---|
232 | CASE( 4 ) ; IF(lwp) WRITE(numout,*) ' Runoff conditions : Neumann for T and specified to 0.1 for salinity' |
---|
233 | CASE DEFAULT ; CALL ctl_stop( 'unrecognised value for nn_tra' ) |
---|
234 | END SELECT |
---|
235 | IF( nn_tra(ib_bdy) .gt. 0 ) THEN |
---|
236 | SELECT CASE( nn_tra_dta(ib_bdy) ) ! |
---|
237 | CASE( 0 ) ; IF(lwp) WRITE(numout,*) ' initial state used for bdy data' |
---|
238 | CASE( 1 ) ; IF(lwp) WRITE(numout,*) ' boundary data taken from file' |
---|
239 | CASE DEFAULT ; CALL ctl_stop( 'nn_tra_dta must be 0 or 1' ) |
---|
240 | END SELECT |
---|
241 | ENDIF |
---|
242 | |
---|
243 | IF ( ln_tra_dmp(ib_bdy) ) THEN |
---|
244 | IF ( nn_tra(ib_bdy).EQ.0 ) THEN |
---|
245 | IF(lwp) WRITE(numout,*) 'No open boundary condition for tracers: ln_tra_dmp is set to .false.' |
---|
246 | ln_tra_dmp(ib_bdy)=.false. |
---|
247 | ELSEIF ( nn_tra(ib_bdy).EQ.1 ) THEN |
---|
248 | CALL ctl_stop( 'Use FRS OR relaxation' ) |
---|
249 | ELSE |
---|
250 | IF(lwp) WRITE(numout,*) ' + T/S relaxation zone' |
---|
251 | IF(lwp) WRITE(numout,*) ' Damping time scale: ',rn_time_dmp(ib_bdy),' days' |
---|
252 | IF((lwp).AND.rn_time_dmp(ib_bdy)<0) CALL ctl_stop( 'Time scale must be positive' ) |
---|
253 | ENDIF |
---|
254 | ELSE |
---|
255 | IF(lwp) WRITE(numout,*) ' NO T/S relaxation' |
---|
256 | ENDIF |
---|
257 | IF(lwp) WRITE(numout,*) |
---|
258 | |
---|
259 | #if defined key_lim2 |
---|
260 | IF(lwp) WRITE(numout,*) 'Boundary conditions for sea ice: ' |
---|
261 | SELECT CASE( nn_ice_lim2(ib_bdy) ) |
---|
262 | CASE( 0 ) ; IF(lwp) WRITE(numout,*) ' no open boundary condition' |
---|
263 | CASE( 1 ) ; IF(lwp) WRITE(numout,*) ' Flow Relaxation Scheme' |
---|
264 | CASE DEFAULT ; CALL ctl_stop( 'unrecognised value for nn_tra' ) |
---|
265 | END SELECT |
---|
266 | IF( nn_ice_lim2(ib_bdy) .gt. 0 ) THEN |
---|
267 | SELECT CASE( nn_ice_lim2_dta(ib_bdy) ) ! |
---|
268 | CASE( 0 ) ; IF(lwp) WRITE(numout,*) ' initial state used for bdy data' |
---|
269 | CASE( 1 ) ; IF(lwp) WRITE(numout,*) ' boundary data taken from file' |
---|
270 | CASE DEFAULT ; CALL ctl_stop( 'nn_ice_lim2_dta must be 0 or 1' ) |
---|
271 | END SELECT |
---|
272 | ENDIF |
---|
273 | IF(lwp) WRITE(numout,*) |
---|
274 | #endif |
---|
275 | |
---|
276 | IF(lwp) WRITE(numout,*) ' Width of relaxation zone = ', nn_rimwidth(ib_bdy) |
---|
277 | IF(lwp) WRITE(numout,*) |
---|
278 | |
---|
279 | ENDDO |
---|
280 | |
---|
281 | IF (nb_bdy .gt. 0) THEN |
---|
282 | IF( ln_vol ) THEN ! check volume conservation (nn_volctl value) |
---|
283 | IF(lwp) WRITE(numout,*) 'Volume correction applied at open boundaries' |
---|
284 | IF(lwp) WRITE(numout,*) |
---|
285 | SELECT CASE ( nn_volctl ) |
---|
286 | CASE( 1 ) ; IF(lwp) WRITE(numout,*) ' The total volume will be constant' |
---|
287 | CASE( 0 ) ; IF(lwp) WRITE(numout,*) ' The total volume will vary according to the surface E-P flux' |
---|
288 | CASE DEFAULT ; CALL ctl_stop( 'nn_volctl must be 0 or 1' ) |
---|
289 | END SELECT |
---|
290 | IF(lwp) WRITE(numout,*) |
---|
291 | ELSE |
---|
292 | IF(lwp) WRITE(numout,*) 'No volume correction applied at open boundaries' |
---|
293 | IF(lwp) WRITE(numout,*) |
---|
294 | ENDIF |
---|
295 | ENDIF |
---|
296 | |
---|
297 | ! ------------------------------------------------- |
---|
298 | ! Initialise indices arrays for open boundaries |
---|
299 | ! ------------------------------------------------- |
---|
300 | |
---|
301 | ! Work out global dimensions of boundary data |
---|
302 | ! --------------------------------------------- |
---|
303 | REWIND( numnam ) |
---|
304 | |
---|
305 | nblendta(:,:) = 0 |
---|
306 | nbdysege = 0 |
---|
307 | nbdysegw = 0 |
---|
308 | nbdysegn = 0 |
---|
309 | nbdysegs = 0 |
---|
310 | icount = 0 ! count user defined segments |
---|
311 | ! Dimensions below are used to allocate arrays to read external data |
---|
312 | jpbdtas = 1 ! Maximum size of boundary data (structured case) |
---|
313 | jpbdtau = 1 ! Maximum size of boundary data (unstructured case) |
---|
314 | |
---|
315 | DO ib_bdy = 1, nb_bdy |
---|
316 | |
---|
317 | IF( .NOT. ln_coords_file(ib_bdy) ) THEN ! Work out size of global arrays from namelist parameters |
---|
318 | |
---|
319 | icount = icount + 1 |
---|
320 | ! No REWIND here because may need to read more than one nambdy_index namelist. |
---|
321 | READ ( numnam, nambdy_index ) |
---|
322 | |
---|
323 | SELECT CASE ( TRIM(ctypebdy) ) |
---|
324 | CASE( 'N' ) |
---|
325 | IF( nbdyind == -1 ) THEN ! Automatic boundary definition: if nbdysegX = -1 |
---|
326 | nbdyind = jpjglo - 2 ! set boundary to whole side of model domain. |
---|
327 | nbdybeg = 2 |
---|
328 | nbdyend = jpiglo - 1 |
---|
329 | ENDIF |
---|
330 | nbdysegn = nbdysegn + 1 |
---|
331 | npckgn(nbdysegn) = ib_bdy ! Save bdy package number |
---|
332 | jpjnob(nbdysegn) = nbdyind |
---|
333 | jpindt(nbdysegn) = nbdybeg |
---|
334 | jpinft(nbdysegn) = nbdyend |
---|
335 | ! |
---|
336 | CASE( 'S' ) |
---|
337 | IF( nbdyind == -1 ) THEN ! Automatic boundary definition: if nbdysegX = -1 |
---|
338 | nbdyind = 2 ! set boundary to whole side of model domain. |
---|
339 | nbdybeg = 2 |
---|
340 | nbdyend = jpiglo - 1 |
---|
341 | ENDIF |
---|
342 | nbdysegs = nbdysegs + 1 |
---|
343 | npckgs(nbdysegs) = ib_bdy ! Save bdy package number |
---|
344 | jpjsob(nbdysegs) = nbdyind |
---|
345 | jpisdt(nbdysegs) = nbdybeg |
---|
346 | jpisft(nbdysegs) = nbdyend |
---|
347 | ! |
---|
348 | CASE( 'E' ) |
---|
349 | IF( nbdyind == -1 ) THEN ! Automatic boundary definition: if nbdysegX = -1 |
---|
350 | nbdyind = jpiglo - 2 ! set boundary to whole side of model domain. |
---|
351 | nbdybeg = 2 |
---|
352 | nbdyend = jpjglo - 1 |
---|
353 | ENDIF |
---|
354 | nbdysege = nbdysege + 1 |
---|
355 | npckge(nbdysege) = ib_bdy ! Save bdy package number |
---|
356 | jpieob(nbdysege) = nbdyind |
---|
357 | jpjedt(nbdysege) = nbdybeg |
---|
358 | jpjeft(nbdysege) = nbdyend |
---|
359 | ! |
---|
360 | CASE( 'W' ) |
---|
361 | IF( nbdyind == -1 ) THEN ! Automatic boundary definition: if nbdysegX = -1 |
---|
362 | nbdyind = 2 ! set boundary to whole side of model domain. |
---|
363 | nbdybeg = 2 |
---|
364 | nbdyend = jpjglo - 1 |
---|
365 | ENDIF |
---|
366 | nbdysegw = nbdysegw + 1 |
---|
367 | npckgw(nbdysegw) = ib_bdy ! Save bdy package number |
---|
368 | jpiwob(nbdysegw) = nbdyind |
---|
369 | jpjwdt(nbdysegw) = nbdybeg |
---|
370 | jpjwft(nbdysegw) = nbdyend |
---|
371 | ! |
---|
372 | CASE DEFAULT ; CALL ctl_stop( 'ctypebdy must be N, S, E or W' ) |
---|
373 | END SELECT |
---|
374 | |
---|
375 | ! For simplicity we assume that in case of straight bdy, arrays have the same length |
---|
376 | ! (even if it is true that last tangential velocity points |
---|
377 | ! are useless). This simplifies a little bit boundary data format (and agrees with format |
---|
378 | ! used so far in obc package) |
---|
379 | |
---|
380 | nblendta(1:jpbgrd,ib_bdy) = (nbdyend - nbdybeg + 1) * nn_rimwidth(ib_bdy) |
---|
381 | jpbdtas = MAX(jpbdtas, (nbdyend - nbdybeg + 1)) |
---|
382 | IF (lwp.and.(nn_rimwidth(ib_bdy)>nrimmax)) & |
---|
383 | & CALL ctl_stop( 'rimwidth must be lower than nrimmax' ) |
---|
384 | |
---|
385 | ELSE ! Read size of arrays in boundary coordinates file. |
---|
386 | CALL iom_open( cn_coords_file(ib_bdy), inum ) |
---|
387 | DO igrd = 1, jpbgrd |
---|
388 | id_dummy = iom_varid( inum, 'nbi'//cgrid(igrd), kdimsz=kdimsz ) |
---|
389 | nblendta(igrd,ib_bdy) = kdimsz(1) |
---|
390 | jpbdtau = MAX(jpbdtau, kdimsz(1)) |
---|
391 | ENDDO |
---|
392 | CALL iom_close( inum ) |
---|
393 | |
---|
394 | ENDIF |
---|
395 | |
---|
396 | ENDDO ! ib_bdy |
---|
397 | |
---|
398 | IF (nb_bdy>0) THEN |
---|
399 | jpbdta = MAXVAL(nblendta(1:jpbgrd,1:nb_bdy)) |
---|
400 | |
---|
401 | ! Allocate arrays |
---|
402 | !--------------- |
---|
403 | ALLOCATE( nbidta(jpbdta, jpbgrd, nb_bdy), nbjdta(jpbdta, jpbgrd, nb_bdy), & |
---|
404 | & nbrdta(jpbdta, jpbgrd, nb_bdy) ) |
---|
405 | |
---|
406 | ALLOCATE( dta_global(jpbdtau, 1, jpk) ) |
---|
407 | IF ( icount>0 ) ALLOCATE( dta_global2(jpbdtas, nrimmax, jpk) ) |
---|
408 | ! |
---|
409 | ENDIF |
---|
410 | |
---|
411 | ! Now look for crossings in user (namelist) defined open boundary segments: |
---|
412 | !-------------------------------------------------------------------------- |
---|
413 | IF ( icount>0 ) CALL bdy_ctl_seg |
---|
414 | |
---|
415 | ! Calculate global boundary index arrays or read in from file |
---|
416 | !------------------------------------------------------------ |
---|
417 | ! 1. Read global index arrays from boundary coordinates file. |
---|
418 | DO ib_bdy = 1, nb_bdy |
---|
419 | |
---|
420 | IF( ln_coords_file(ib_bdy) ) THEN |
---|
421 | |
---|
422 | CALL iom_open( cn_coords_file(ib_bdy), inum ) |
---|
423 | DO igrd = 1, jpbgrd |
---|
424 | CALL iom_get( inum, jpdom_unknown, 'nbi'//cgrid(igrd), dta_global(1:nblendta(igrd,ib_bdy),:,1) ) |
---|
425 | DO ii = 1,nblendta(igrd,ib_bdy) |
---|
426 | nbidta(ii,igrd,ib_bdy) = INT( dta_global(ii,1,1) ) |
---|
427 | END DO |
---|
428 | CALL iom_get( inum, jpdom_unknown, 'nbj'//cgrid(igrd), dta_global(1:nblendta(igrd,ib_bdy),:,1) ) |
---|
429 | DO ii = 1,nblendta(igrd,ib_bdy) |
---|
430 | nbjdta(ii,igrd,ib_bdy) = INT( dta_global(ii,1,1) ) |
---|
431 | END DO |
---|
432 | CALL iom_get( inum, jpdom_unknown, 'nbr'//cgrid(igrd), dta_global(1:nblendta(igrd,ib_bdy),:,1) ) |
---|
433 | DO ii = 1,nblendta(igrd,ib_bdy) |
---|
434 | nbrdta(ii,igrd,ib_bdy) = INT( dta_global(ii,1,1) ) |
---|
435 | END DO |
---|
436 | |
---|
437 | ibr_max = MAXVAL( nbrdta(:,igrd,ib_bdy) ) |
---|
438 | IF(lwp) WRITE(numout,*) |
---|
439 | IF(lwp) WRITE(numout,*) ' Maximum rimwidth in file is ', ibr_max |
---|
440 | IF(lwp) WRITE(numout,*) ' nn_rimwidth from namelist is ', nn_rimwidth(ib_bdy) |
---|
441 | IF (ibr_max < nn_rimwidth(ib_bdy)) & |
---|
442 | CALL ctl_stop( 'nn_rimwidth is larger than maximum rimwidth in file',cn_coords_file(ib_bdy) ) |
---|
443 | END DO |
---|
444 | CALL iom_close( inum ) |
---|
445 | |
---|
446 | ENDIF |
---|
447 | |
---|
448 | ENDDO |
---|
449 | |
---|
450 | ! 2. Now fill indices corresponding to straight open boundary arrays: |
---|
451 | ! East |
---|
452 | !----- |
---|
453 | DO iseg = 1, nbdysege |
---|
454 | ib_bdy = npckge(iseg) |
---|
455 | ! |
---|
456 | ! ------------ T points ------------- |
---|
457 | igrd=1 |
---|
458 | icount=0 |
---|
459 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
460 | DO ij = jpjedt(iseg), jpjeft(iseg) |
---|
461 | icount = icount + 1 |
---|
462 | nbidta(icount, igrd, ib_bdy) = jpieob(iseg) + 2 - ir |
---|
463 | nbjdta(icount, igrd, ib_bdy) = ij |
---|
464 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
465 | ENDDO |
---|
466 | ENDDO |
---|
467 | ! |
---|
468 | ! ------------ U points ------------- |
---|
469 | igrd=2 |
---|
470 | icount=0 |
---|
471 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
472 | DO ij = jpjedt(iseg), jpjeft(iseg) |
---|
473 | icount = icount + 1 |
---|
474 | nbidta(icount, igrd, ib_bdy) = jpieob(iseg) + 1 - ir |
---|
475 | nbjdta(icount, igrd, ib_bdy) = ij |
---|
476 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
477 | ENDDO |
---|
478 | ENDDO |
---|
479 | ! |
---|
480 | ! ------------ V points ------------- |
---|
481 | igrd=3 |
---|
482 | icount=0 |
---|
483 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
484 | ! DO ij = jpjedt(iseg), jpjeft(iseg) - 1 |
---|
485 | DO ij = jpjedt(iseg), jpjeft(iseg) |
---|
486 | icount = icount + 1 |
---|
487 | nbidta(icount, igrd, ib_bdy) = jpieob(iseg) + 2 - ir |
---|
488 | nbjdta(icount, igrd, ib_bdy) = ij |
---|
489 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
490 | ENDDO |
---|
491 | nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
492 | nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
493 | ENDDO |
---|
494 | ENDDO |
---|
495 | ! |
---|
496 | ! West |
---|
497 | !----- |
---|
498 | DO iseg = 1, nbdysegw |
---|
499 | ib_bdy = npckgw(iseg) |
---|
500 | ! |
---|
501 | ! ------------ T points ------------- |
---|
502 | igrd=1 |
---|
503 | icount=0 |
---|
504 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
505 | DO ij = jpjwdt(iseg), jpjwft(iseg) |
---|
506 | icount = icount + 1 |
---|
507 | nbidta(icount, igrd, ib_bdy) = jpiwob(iseg) + ir - 1 |
---|
508 | nbjdta(icount, igrd, ib_bdy) = ij |
---|
509 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
510 | ENDDO |
---|
511 | ENDDO |
---|
512 | ! |
---|
513 | ! ------------ U points ------------- |
---|
514 | igrd=2 |
---|
515 | icount=0 |
---|
516 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
517 | DO ij = jpjwdt(iseg), jpjwft(iseg) |
---|
518 | icount = icount + 1 |
---|
519 | nbidta(icount, igrd, ib_bdy) = jpiwob(iseg) + ir - 1 |
---|
520 | nbjdta(icount, igrd, ib_bdy) = ij |
---|
521 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
522 | ENDDO |
---|
523 | ENDDO |
---|
524 | ! |
---|
525 | ! ------------ V points ------------- |
---|
526 | igrd=3 |
---|
527 | icount=0 |
---|
528 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
529 | ! DO ij = jpjwdt(iseg), jpjwft(iseg) - 1 |
---|
530 | DO ij = jpjwdt(iseg), jpjwft(iseg) |
---|
531 | icount = icount + 1 |
---|
532 | nbidta(icount, igrd, ib_bdy) = jpiwob(iseg) + ir - 1 |
---|
533 | nbjdta(icount, igrd, ib_bdy) = ij |
---|
534 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
535 | ENDDO |
---|
536 | nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
537 | nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
538 | ENDDO |
---|
539 | ENDDO |
---|
540 | ! |
---|
541 | ! North |
---|
542 | !----- |
---|
543 | DO iseg = 1, nbdysegn |
---|
544 | ib_bdy = npckgn(iseg) |
---|
545 | ! |
---|
546 | ! ------------ T points ------------- |
---|
547 | igrd=1 |
---|
548 | icount=0 |
---|
549 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
550 | DO ii = jpindt(iseg), jpinft(iseg) |
---|
551 | icount = icount + 1 |
---|
552 | nbidta(icount, igrd, ib_bdy) = ii |
---|
553 | nbjdta(icount, igrd, ib_bdy) = jpjnob(iseg) + 2 - ir |
---|
554 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
555 | ENDDO |
---|
556 | ENDDO |
---|
557 | ! |
---|
558 | ! ------------ U points ------------- |
---|
559 | igrd=2 |
---|
560 | icount=0 |
---|
561 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
562 | ! DO ii = jpindt(iseg), jpinft(iseg) - 1 |
---|
563 | DO ii = jpindt(iseg), jpinft(iseg) |
---|
564 | icount = icount + 1 |
---|
565 | nbidta(icount, igrd, ib_bdy) = ii |
---|
566 | nbjdta(icount, igrd, ib_bdy) = jpjnob(iseg) + 2 - ir |
---|
567 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
568 | ENDDO |
---|
569 | nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
570 | nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
571 | ENDDO |
---|
572 | ! |
---|
573 | ! ------------ V points ------------- |
---|
574 | igrd=3 |
---|
575 | icount=0 |
---|
576 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
577 | DO ii = jpindt(iseg), jpinft(iseg) |
---|
578 | icount = icount + 1 |
---|
579 | nbidta(icount, igrd, ib_bdy) = ii |
---|
580 | nbjdta(icount, igrd, ib_bdy) = jpjnob(iseg) + 1 - ir |
---|
581 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
582 | ENDDO |
---|
583 | ENDDO |
---|
584 | ENDDO |
---|
585 | ! |
---|
586 | ! South |
---|
587 | !----- |
---|
588 | DO iseg = 1, nbdysegs |
---|
589 | ib_bdy = npckgs(iseg) |
---|
590 | ! |
---|
591 | ! ------------ T points ------------- |
---|
592 | igrd=1 |
---|
593 | icount=0 |
---|
594 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
595 | DO ii = jpisdt(iseg), jpisft(iseg) |
---|
596 | icount = icount + 1 |
---|
597 | nbidta(icount, igrd, ib_bdy) = ii |
---|
598 | nbjdta(icount, igrd, ib_bdy) = jpjsob(iseg) + ir - 1 |
---|
599 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
600 | ENDDO |
---|
601 | ENDDO |
---|
602 | ! |
---|
603 | ! ------------ U points ------------- |
---|
604 | igrd=2 |
---|
605 | icount=0 |
---|
606 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
607 | ! DO ii = jpisdt(iseg), jpisft(iseg) - 1 |
---|
608 | DO ii = jpisdt(iseg), jpisft(iseg) |
---|
609 | icount = icount + 1 |
---|
610 | nbidta(icount, igrd, ib_bdy) = ii |
---|
611 | nbjdta(icount, igrd, ib_bdy) = jpjsob(iseg) + ir - 1 |
---|
612 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
613 | ENDDO |
---|
614 | nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
615 | nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point |
---|
616 | ENDDO |
---|
617 | ! |
---|
618 | ! ------------ V points ------------- |
---|
619 | igrd=3 |
---|
620 | icount=0 |
---|
621 | DO ir = 1, nn_rimwidth(ib_bdy) |
---|
622 | DO ii = jpisdt(iseg), jpisft(iseg) |
---|
623 | icount = icount + 1 |
---|
624 | nbidta(icount, igrd, ib_bdy) = ii |
---|
625 | nbjdta(icount, igrd, ib_bdy) = jpjsob(iseg) + ir - 1 |
---|
626 | nbrdta(icount, igrd, ib_bdy) = ir |
---|
627 | ENDDO |
---|
628 | ENDDO |
---|
629 | ENDDO |
---|
630 | |
---|
631 | ! Deal with duplicated points |
---|
632 | !----------------------------- |
---|
633 | ! We assign negative indices to duplicated points (to remove them from bdy points to be updated) |
---|
634 | ! if their distance to the bdy is greater than the other |
---|
635 | ! If their distance are the same, just keep only one to avoid updating a point twice |
---|
636 | DO igrd = 1, jpbgrd |
---|
637 | DO ib_bdy1 = 1, nb_bdy |
---|
638 | DO ib_bdy2 = 1, nb_bdy |
---|
639 | IF (ib_bdy1/=ib_bdy2) THEN |
---|
640 | DO ib1 = 1, nblendta(igrd,ib_bdy1) |
---|
641 | DO ib2 = 1, nblendta(igrd,ib_bdy2) |
---|
642 | IF ((nbidta(ib1, igrd, ib_bdy1)==nbidta(ib2, igrd, ib_bdy2)).AND. & |
---|
643 | & (nbjdta(ib1, igrd, ib_bdy1)==nbjdta(ib2, igrd, ib_bdy2))) THEN |
---|
644 | ! IF ((lwp).AND.(igrd==1)) WRITE(numout,*) ' found coincident point ji, jj:', & |
---|
645 | ! & nbidta(ib1, igrd, ib_bdy1), & |
---|
646 | ! & nbjdta(ib2, igrd, ib_bdy2) |
---|
647 | ! keep only points with the lowest distance to boundary: |
---|
648 | IF (nbrdta(ib1, igrd, ib_bdy1)<nbrdta(ib2, igrd, ib_bdy2)) THEN |
---|
649 | nbidta(ib2, igrd, ib_bdy2) =-ib_bdy2 |
---|
650 | nbjdta(ib2, igrd, ib_bdy2) =-ib_bdy2 |
---|
651 | ELSEIF (nbrdta(ib1, igrd, ib_bdy1)>nbrdta(ib2, igrd, ib_bdy2)) THEN |
---|
652 | nbidta(ib1, igrd, ib_bdy1) =-ib_bdy1 |
---|
653 | nbjdta(ib1, igrd, ib_bdy1) =-ib_bdy1 |
---|
654 | ! Arbitrary choice if distances are the same: |
---|
655 | ELSE |
---|
656 | nbidta(ib1, igrd, ib_bdy1) =-ib_bdy1 |
---|
657 | nbjdta(ib1, igrd, ib_bdy1) =-ib_bdy1 |
---|
658 | ENDIF |
---|
659 | END IF |
---|
660 | END DO |
---|
661 | END DO |
---|
662 | ENDIF |
---|
663 | END DO |
---|
664 | END DO |
---|
665 | END DO |
---|
666 | |
---|
667 | ! Work out dimensions of boundary data on each processor |
---|
668 | ! ------------------------------------------------------ |
---|
669 | |
---|
670 | ! Rather assume that boundary data indices are given on global domain |
---|
671 | ! TO BE DISCUSSED ? |
---|
672 | ! iw = mig(1) + 1 ! if monotasking and no zoom, iw=2 |
---|
673 | ! ie = mig(1) + nlci-1 - 1 ! if monotasking and no zoom, ie=jpim1 |
---|
674 | ! is = mjg(1) + 1 ! if monotasking and no zoom, is=2 |
---|
675 | ! in = mjg(1) + nlcj-1 - 1 ! if monotasking and no zoom, in=jpjm1 |
---|
676 | iw = mig(1) - jpizoom + 2 ! if monotasking and no zoom, iw=2 |
---|
677 | ie = mig(1) + nlci - jpizoom - 1 ! if monotasking and no zoom, ie=jpim1 |
---|
678 | is = mjg(1) - jpjzoom + 2 ! if monotasking and no zoom, is=2 |
---|
679 | in = mjg(1) + nlcj - jpjzoom - 1 ! if monotasking and no zoom, in=jpjm1 |
---|
680 | |
---|
681 | ALLOCATE( nbondi_bdy(nb_bdy)) |
---|
682 | ALLOCATE( nbondj_bdy(nb_bdy)) |
---|
683 | nbondi_bdy(:)=2 |
---|
684 | nbondj_bdy(:)=2 |
---|
685 | ALLOCATE( nbondi_bdy_b(nb_bdy)) |
---|
686 | ALLOCATE( nbondj_bdy_b(nb_bdy)) |
---|
687 | nbondi_bdy_b(:)=2 |
---|
688 | nbondj_bdy_b(:)=2 |
---|
689 | |
---|
690 | ! Work out dimensions of boundary data on each neighbour process |
---|
691 | IF(nbondi .eq. 0) THEN |
---|
692 | iw_b(1) = jpizoom + nimppt(nowe+1) |
---|
693 | ie_b(1) = jpizoom + nimppt(nowe+1)+nlcit(nowe+1)-3 |
---|
694 | is_b(1) = jpjzoom + njmppt(nowe+1) |
---|
695 | in_b(1) = jpjzoom + njmppt(nowe+1)+nlcjt(nowe+1)-3 |
---|
696 | |
---|
697 | iw_b(2) = jpizoom + nimppt(noea+1) |
---|
698 | ie_b(2) = jpizoom + nimppt(noea+1)+nlcit(noea+1)-3 |
---|
699 | is_b(2) = jpjzoom + njmppt(noea+1) |
---|
700 | in_b(2) = jpjzoom + njmppt(noea+1)+nlcjt(noea+1)-3 |
---|
701 | ELSEIF(nbondi .eq. 1) THEN |
---|
702 | iw_b(1) = jpizoom + nimppt(nowe+1) |
---|
703 | ie_b(1) = jpizoom + nimppt(nowe+1)+nlcit(nowe+1)-3 |
---|
704 | is_b(1) = jpjzoom + njmppt(nowe+1) |
---|
705 | in_b(1) = jpjzoom + njmppt(nowe+1)+nlcjt(nowe+1)-3 |
---|
706 | ELSEIF(nbondi .eq. -1) THEN |
---|
707 | iw_b(2) = jpizoom + nimppt(noea+1) |
---|
708 | ie_b(2) = jpizoom + nimppt(noea+1)+nlcit(noea+1)-3 |
---|
709 | is_b(2) = jpjzoom + njmppt(noea+1) |
---|
710 | in_b(2) = jpjzoom + njmppt(noea+1)+nlcjt(noea+1)-3 |
---|
711 | ENDIF |
---|
712 | |
---|
713 | IF(nbondj .eq. 0) THEN |
---|
714 | iw_b(3) = jpizoom + nimppt(noso+1) |
---|
715 | ie_b(3) = jpizoom + nimppt(noso+1)+nlcit(noso+1)-3 |
---|
716 | is_b(3) = jpjzoom + njmppt(noso+1) |
---|
717 | in_b(3) = jpjzoom + njmppt(noso+1)+nlcjt(noso+1)-3 |
---|
718 | |
---|
719 | iw_b(4) = jpizoom + nimppt(nono+1) |
---|
720 | ie_b(4) = jpizoom + nimppt(nono+1)+nlcit(nono+1)-3 |
---|
721 | is_b(4) = jpjzoom + njmppt(nono+1) |
---|
722 | in_b(4) = jpjzoom + njmppt(nono+1)+nlcjt(nono+1)-3 |
---|
723 | ELSEIF(nbondj .eq. 1) THEN |
---|
724 | iw_b(3) = jpizoom + nimppt(noso+1) |
---|
725 | ie_b(3) = jpizoom + nimppt(noso+1)+nlcit(noso+1)-3 |
---|
726 | is_b(3) = jpjzoom + njmppt(noso+1) |
---|
727 | in_b(3) = jpjzoom + njmppt(noso+1)+nlcjt(noso+1)-3 |
---|
728 | ELSEIF(nbondj .eq. -1) THEN |
---|
729 | iw_b(4) = jpizoom + nimppt(nono+1) |
---|
730 | ie_b(4) = jpizoom + nimppt(nono+1)+nlcit(nono+1)-3 |
---|
731 | is_b(4) = jpjzoom + njmppt(nono+1) |
---|
732 | in_b(4) = jpjzoom + njmppt(nono+1)+nlcjt(nono+1)-3 |
---|
733 | ENDIF |
---|
734 | |
---|
735 | DO ib_bdy = 1, nb_bdy |
---|
736 | DO igrd = 1, jpbgrd |
---|
737 | icount = 0 |
---|
738 | icountr = 0 |
---|
739 | idx_bdy(ib_bdy)%nblen(igrd) = 0 |
---|
740 | idx_bdy(ib_bdy)%nblenrim(igrd) = 0 |
---|
741 | DO ib = 1, nblendta(igrd,ib_bdy) |
---|
742 | ! check that data is in correct order in file |
---|
743 | ibm1 = MAX(1,ib-1) |
---|
744 | IF(lwp) THEN ! Since all procs read global data only need to do this check on one proc... |
---|
745 | IF( nbrdta(ib,igrd,ib_bdy) < nbrdta(ibm1,igrd,ib_bdy) ) THEN |
---|
746 | CALL ctl_stop('bdy_init : ERROR : boundary data in file & |
---|
747 | must be defined in order of distance from edge nbr.', & |
---|
748 | 'A utility for re-ordering boundary coordinates and data & |
---|
749 | files exists in the TOOLS/OBC directory') |
---|
750 | ENDIF |
---|
751 | ENDIF |
---|
752 | ! check if point is in local domain |
---|
753 | IF( nbidta(ib,igrd,ib_bdy) >= iw .AND. nbidta(ib,igrd,ib_bdy) <= ie .AND. & |
---|
754 | & nbjdta(ib,igrd,ib_bdy) >= is .AND. nbjdta(ib,igrd,ib_bdy) <= in ) THEN |
---|
755 | ! |
---|
756 | icount = icount + 1 |
---|
757 | ! |
---|
758 | IF( nbrdta(ib,igrd,ib_bdy) == 1 ) icountr = icountr+1 |
---|
759 | ENDIF |
---|
760 | ENDDO |
---|
761 | idx_bdy(ib_bdy)%nblenrim(igrd) = icountr !: length of rim boundary data on each proc |
---|
762 | idx_bdy(ib_bdy)%nblen (igrd) = icount !: length of boundary data on each proc |
---|
763 | ENDDO ! igrd |
---|
764 | |
---|
765 | ! Allocate index arrays for this boundary set |
---|
766 | !-------------------------------------------- |
---|
767 | ilen1 = MAXVAL(idx_bdy(ib_bdy)%nblen(:)) |
---|
768 | ALLOCATE( idx_bdy(ib_bdy)%nbi(ilen1,jpbgrd) ) |
---|
769 | ALLOCATE( idx_bdy(ib_bdy)%nbj(ilen1,jpbgrd) ) |
---|
770 | ALLOCATE( idx_bdy(ib_bdy)%nbr(ilen1,jpbgrd) ) |
---|
771 | ALLOCATE( idx_bdy(ib_bdy)%nbd(ilen1,jpbgrd) ) |
---|
772 | ALLOCATE( idx_bdy(ib_bdy)%nbmap(ilen1,jpbgrd) ) |
---|
773 | ALLOCATE( idx_bdy(ib_bdy)%nbw(ilen1,jpbgrd) ) |
---|
774 | ALLOCATE( idx_bdy(ib_bdy)%flagu(ilen1) ) |
---|
775 | ALLOCATE( idx_bdy(ib_bdy)%flagv(ilen1) ) |
---|
776 | |
---|
777 | ! Dispatch mapping indices and discrete distances on each processor |
---|
778 | ! ----------------------------------------------------------------- |
---|
779 | |
---|
780 | com_east = 0 |
---|
781 | com_west = 0 |
---|
782 | com_south = 0 |
---|
783 | com_north = 0 |
---|
784 | |
---|
785 | com_east_b = 0 |
---|
786 | com_west_b = 0 |
---|
787 | com_south_b = 0 |
---|
788 | com_north_b = 0 |
---|
789 | DO igrd = 1, jpbgrd |
---|
790 | icount = 0 |
---|
791 | ! Loop on rimwidth to ensure outermost points come first in the local arrays. |
---|
792 | DO ir=1, nn_rimwidth(ib_bdy) |
---|
793 | DO ib = 1, nblendta(igrd,ib_bdy) |
---|
794 | ! check if point is in local domain and equals ir |
---|
795 | IF( nbidta(ib,igrd,ib_bdy) >= iw .AND. nbidta(ib,igrd,ib_bdy) <= ie .AND. & |
---|
796 | & nbjdta(ib,igrd,ib_bdy) >= is .AND. nbjdta(ib,igrd,ib_bdy) <= in .AND. & |
---|
797 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
798 | ! |
---|
799 | icount = icount + 1 |
---|
800 | |
---|
801 | ! Rather assume that boundary data indices are given on global domain |
---|
802 | ! TO BE DISCUSSED ? |
---|
803 | ! idx_bdy(ib_bdy)%nbi(icount,igrd) = nbidta(ib,igrd,ib_bdy)- mig(1)+1 |
---|
804 | ! idx_bdy(ib_bdy)%nbj(icount,igrd) = nbjdta(ib,igrd,ib_bdy)- mjg(1)+1 |
---|
805 | idx_bdy(ib_bdy)%nbi(icount,igrd) = nbidta(ib,igrd,ib_bdy)- mig(1)+jpizoom |
---|
806 | idx_bdy(ib_bdy)%nbj(icount,igrd) = nbjdta(ib,igrd,ib_bdy)- mjg(1)+jpjzoom |
---|
807 | ! check if point has to be sent |
---|
808 | ii = idx_bdy(ib_bdy)%nbi(icount,igrd) |
---|
809 | ij = idx_bdy(ib_bdy)%nbj(icount,igrd) |
---|
810 | if((com_east .ne. 1) .and. (ii .eq. (nlci-1)) .and. (nbondi .le. 0)) then |
---|
811 | com_east = 1 |
---|
812 | elseif((com_west .ne. 1) .and. (ii .eq. 2) .and. (nbondi .ge. 0) .and. (nbondi .ne. 2)) then |
---|
813 | com_west = 1 |
---|
814 | endif |
---|
815 | if((com_south .ne. 1) .and. (ij .eq. 2) .and. (nbondj .ge. 0) .and. (nbondj .ne. 2)) then |
---|
816 | com_south = 1 |
---|
817 | elseif((com_north .ne. 1) .and. (ij .eq. (nlcj-1)) .and. (nbondj .le. 0)) then |
---|
818 | com_north = 1 |
---|
819 | endif |
---|
820 | idx_bdy(ib_bdy)%nbr(icount,igrd) = nbrdta(ib,igrd,ib_bdy) |
---|
821 | idx_bdy(ib_bdy)%nbmap(icount,igrd) = ib |
---|
822 | ENDIF |
---|
823 | ! check if point has to be received from a neighbour |
---|
824 | IF(nbondi .eq. 0) THEN |
---|
825 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(1) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(1) .AND. & |
---|
826 | & nbjdta(ib,igrd,ib_bdy) >= is_b(1) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(1) .AND. & |
---|
827 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
828 | ii = nbidta(ib,igrd,ib_bdy)- iw_b(1)+2 |
---|
829 | if((com_west_b .ne. 1) .and. (ii .eq. (nlcit(nowe+1)-1))) then |
---|
830 | ij = nbjdta(ib,igrd,ib_bdy) - is_b(1)+2 |
---|
831 | if((ij .eq. 2) .and. (nbondj .eq. 0 .or. nbondj .eq. 1)) then |
---|
832 | com_south = 1 |
---|
833 | elseif((ij .eq. nlcjt(nowe+1)-1) .and. (nbondj .eq. 0 .or. nbondj .eq. -1)) then |
---|
834 | com_north = 1 |
---|
835 | endif |
---|
836 | com_west_b = 1 |
---|
837 | endif |
---|
838 | ENDIF |
---|
839 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(2) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(2) .AND. & |
---|
840 | & nbjdta(ib,igrd,ib_bdy) >= is_b(2) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(2) .AND. & |
---|
841 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
842 | ii = nbidta(ib,igrd,ib_bdy)- iw_b(2)+2 |
---|
843 | if((com_east_b .ne. 1) .and. (ii .eq. 2)) then |
---|
844 | ij = nbjdta(ib,igrd,ib_bdy) - is_b(2)+2 |
---|
845 | if((ij .eq. 2) .and. (nbondj .eq. 0 .or. nbondj .eq. 1)) then |
---|
846 | com_south = 1 |
---|
847 | elseif((ij .eq. nlcjt(noea+1)-1) .and. (nbondj .eq. 0 .or. nbondj .eq. -1)) then |
---|
848 | com_north = 1 |
---|
849 | endif |
---|
850 | com_east_b = 1 |
---|
851 | endif |
---|
852 | ENDIF |
---|
853 | ELSEIF(nbondi .eq. 1) THEN |
---|
854 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(1) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(1) .AND. & |
---|
855 | & nbjdta(ib,igrd,ib_bdy) >= is_b(1) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(1) .AND. & |
---|
856 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
857 | ii = nbidta(ib,igrd,ib_bdy)- iw_b(1)+2 |
---|
858 | if((com_west_b .ne. 1) .and. (ii .eq. (nlcit(nowe+1)-1))) then |
---|
859 | ij = nbjdta(ib,igrd,ib_bdy) - is_b(1)+2 |
---|
860 | if((ij .eq. 2) .and. (nbondj .eq. 0 .or. nbondj .eq. 1)) then |
---|
861 | com_south = 1 |
---|
862 | elseif((ij .eq. nlcjt(nowe+1)-1) .and. (nbondj .eq. 0 .or. nbondj .eq. -1)) then |
---|
863 | com_north = 1 |
---|
864 | endif |
---|
865 | com_west_b = 1 |
---|
866 | endif |
---|
867 | ENDIF |
---|
868 | ELSEIF(nbondi .eq. -1) THEN |
---|
869 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(2) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(2) .AND. & |
---|
870 | & nbjdta(ib,igrd,ib_bdy) >= is_b(2) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(2) .AND. & |
---|
871 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
872 | ii = nbidta(ib,igrd,ib_bdy)- iw_b(2)+2 |
---|
873 | if((com_east_b .ne. 1) .and. (ii .eq. 2)) then |
---|
874 | ij = nbjdta(ib,igrd,ib_bdy) - is_b(2)+2 |
---|
875 | if((ij .eq. 2) .and. (nbondj .eq. 0 .or. nbondj .eq. 1)) then |
---|
876 | com_south = 1 |
---|
877 | elseif((ij .eq. nlcjt(noea+1)-1) .and. (nbondj .eq. 0 .or. nbondj .eq. -1)) then |
---|
878 | com_north = 1 |
---|
879 | endif |
---|
880 | com_east_b = 1 |
---|
881 | endif |
---|
882 | ENDIF |
---|
883 | ENDIF |
---|
884 | IF(nbondj .eq. 0) THEN |
---|
885 | IF(com_north_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(4)-1 & |
---|
886 | & .OR. nbidta(ib,igrd,ib_bdy) == ie_b(4)+1) .AND. & |
---|
887 | & nbjdta(ib,igrd,ib_bdy) == is_b(4) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN |
---|
888 | com_north_b = 1 |
---|
889 | ENDIF |
---|
890 | IF(com_south_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(3)-1 & |
---|
891 | &.OR. nbidta(ib,igrd,ib_bdy) == ie_b(3)+1) .AND. & |
---|
892 | & nbjdta(ib,igrd,ib_bdy) == in_b(3) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN |
---|
893 | com_south_b = 1 |
---|
894 | ENDIF |
---|
895 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(3) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(3) .AND. & |
---|
896 | & nbjdta(ib,igrd,ib_bdy) >= is_b(3) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(3) .AND. & |
---|
897 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
898 | ij = nbjdta(ib,igrd,ib_bdy)- is_b(3)+2 |
---|
899 | if((com_south_b .ne. 1) .and. (ij .eq. (nlcjt(noso+1)-1))) then |
---|
900 | com_south_b = 1 |
---|
901 | endif |
---|
902 | ENDIF |
---|
903 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(4) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(4) .AND. & |
---|
904 | & nbjdta(ib,igrd,ib_bdy) >= is_b(4) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(4) .AND. & |
---|
905 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
906 | ij = nbjdta(ib,igrd,ib_bdy)- is_b(4)+2 |
---|
907 | if((com_north_b .ne. 1) .and. (ij .eq. 2)) then |
---|
908 | com_north_b = 1 |
---|
909 | endif |
---|
910 | ENDIF |
---|
911 | ELSEIF(nbondj .eq. 1) THEN |
---|
912 | IF( com_south_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(3)-1 .OR. & |
---|
913 | & nbidta(ib,igrd,ib_bdy) == ie_b(3)+1) .AND. & |
---|
914 | & nbjdta(ib,igrd,ib_bdy) == in_b(3) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN |
---|
915 | com_south_b = 1 |
---|
916 | ENDIF |
---|
917 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(3) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(3) .AND. & |
---|
918 | & nbjdta(ib,igrd,ib_bdy) >= is_b(3) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(3) .AND. & |
---|
919 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
920 | ij = nbjdta(ib,igrd,ib_bdy)- is_b(3)+2 |
---|
921 | if((com_south_b .ne. 1) .and. (ij .eq. (nlcjt(noso+1)-1))) then |
---|
922 | com_south_b = 1 |
---|
923 | endif |
---|
924 | ENDIF |
---|
925 | ELSEIF(nbondj .eq. -1) THEN |
---|
926 | IF(com_north_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(4)-1 & |
---|
927 | & .OR. nbidta(ib,igrd,ib_bdy) == ie_b(4)+1) .AND. & |
---|
928 | & nbjdta(ib,igrd,ib_bdy) == is_b(4) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN |
---|
929 | com_north_b = 1 |
---|
930 | ENDIF |
---|
931 | IF( nbidta(ib,igrd,ib_bdy) >= iw_b(4) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(4) .AND. & |
---|
932 | & nbjdta(ib,igrd,ib_bdy) >= is_b(4) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(4) .AND. & |
---|
933 | & nbrdta(ib,igrd,ib_bdy) == ir ) THEN |
---|
934 | ij = nbjdta(ib,igrd,ib_bdy)- is_b(4)+2 |
---|
935 | if((com_north_b .ne. 1) .and. (ij .eq. 2)) then |
---|
936 | com_north_b = 1 |
---|
937 | endif |
---|
938 | ENDIF |
---|
939 | ENDIF |
---|
940 | ENDDO |
---|
941 | ENDDO |
---|
942 | ENDDO |
---|
943 | ! definition of the i- and j- direction local boundaries arrays |
---|
944 | ! used for sending the boudaries |
---|
945 | IF((com_east .eq. 1) .and. (com_west .eq. 1)) THEN |
---|
946 | nbondi_bdy(ib_bdy) = 0 |
---|
947 | ELSEIF ((com_east .eq. 1) .and. (com_west .eq. 0)) THEN |
---|
948 | nbondi_bdy(ib_bdy) = -1 |
---|
949 | ELSEIF ((com_east .eq. 0) .and. (com_west .eq. 1)) THEN |
---|
950 | nbondi_bdy(ib_bdy) = 1 |
---|
951 | ENDIF |
---|
952 | |
---|
953 | IF((com_north .eq. 1) .and. (com_south .eq. 1)) THEN |
---|
954 | nbondj_bdy(ib_bdy) = 0 |
---|
955 | ELSEIF ((com_north .eq. 1) .and. (com_south .eq. 0)) THEN |
---|
956 | nbondj_bdy(ib_bdy) = -1 |
---|
957 | ELSEIF ((com_north .eq. 0) .and. (com_south .eq. 1)) THEN |
---|
958 | nbondj_bdy(ib_bdy) = 1 |
---|
959 | ENDIF |
---|
960 | |
---|
961 | ! definition of the i- and j- direction local boundaries arrays |
---|
962 | ! used for receiving the boudaries |
---|
963 | IF((com_east_b .eq. 1) .and. (com_west_b .eq. 1)) THEN |
---|
964 | nbondi_bdy_b(ib_bdy) = 0 |
---|
965 | ELSEIF ((com_east_b .eq. 1) .and. (com_west_b .eq. 0)) THEN |
---|
966 | nbondi_bdy_b(ib_bdy) = -1 |
---|
967 | ELSEIF ((com_east_b .eq. 0) .and. (com_west_b .eq. 1)) THEN |
---|
968 | nbondi_bdy_b(ib_bdy) = 1 |
---|
969 | ENDIF |
---|
970 | |
---|
971 | IF((com_north_b .eq. 1) .and. (com_south_b .eq. 1)) THEN |
---|
972 | nbondj_bdy_b(ib_bdy) = 0 |
---|
973 | ELSEIF ((com_north_b .eq. 1) .and. (com_south_b .eq. 0)) THEN |
---|
974 | nbondj_bdy_b(ib_bdy) = -1 |
---|
975 | ELSEIF ((com_north_b .eq. 0) .and. (com_south_b .eq. 1)) THEN |
---|
976 | nbondj_bdy_b(ib_bdy) = 1 |
---|
977 | ENDIF |
---|
978 | |
---|
979 | ! Compute rim weights for FRS scheme |
---|
980 | ! ---------------------------------- |
---|
981 | DO igrd = 1, jpbgrd |
---|
982 | DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd) |
---|
983 | nbr => idx_bdy(ib_bdy)%nbr(ib,igrd) |
---|
984 | idx_bdy(ib_bdy)%nbw(ib,igrd) = 1.- TANH( FLOAT( nbr - 1 ) *0.5 ) ! tanh formulation |
---|
985 | ! idx_bdy(ib_bdy)%nbw(ib,igrd) = (FLOAT(nn_rimwidth(ib_bdy)+1-nbr)/FLOAT(nn_rimwidth(ib_bdy)))**2. ! quadratic |
---|
986 | ! idx_bdy(ib_bdy)%nbw(ib,igrd) = FLOAT(nn_rimwidth(ib_bdy)+1-nbr)/FLOAT(nn_rimwidth(ib_bdy)) ! linear |
---|
987 | END DO |
---|
988 | END DO |
---|
989 | |
---|
990 | ! Compute damping coefficients |
---|
991 | ! ---------------------------- |
---|
992 | DO igrd = 1, jpbgrd |
---|
993 | DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd) |
---|
994 | nbr => idx_bdy(ib_bdy)%nbr(ib,igrd) |
---|
995 | idx_bdy(ib_bdy)%nbd(ib,igrd) = 1. / ( rn_time_dmp(ib_bdy) * rday ) & |
---|
996 | & *(FLOAT(nn_rimwidth(ib_bdy)+1-nbr)/FLOAT(nn_rimwidth(ib_bdy)))**2. ! quadratic |
---|
997 | END DO |
---|
998 | END DO |
---|
999 | |
---|
1000 | ENDDO |
---|
1001 | |
---|
1002 | ! ------------------------------------------------------ |
---|
1003 | ! Initialise masks and find normal/tangential directions |
---|
1004 | ! ------------------------------------------------------ |
---|
1005 | |
---|
1006 | ! Read global 2D mask at T-points: bdytmask |
---|
1007 | ! ----------------------------------------- |
---|
1008 | ! bdytmask = 1 on the computational domain AND on open boundaries |
---|
1009 | ! = 0 elsewhere |
---|
1010 | |
---|
1011 | IF( ln_mask_file ) THEN |
---|
1012 | CALL iom_open( cn_mask_file, inum ) |
---|
1013 | CALL iom_get ( inum, jpdom_data, 'bdy_msk', bdytmask(:,:) ) |
---|
1014 | CALL iom_close( inum ) |
---|
1015 | |
---|
1016 | ! Derive mask on U and V grid from mask on T grid |
---|
1017 | bdyumask(:,:) = 0.e0 |
---|
1018 | bdyvmask(:,:) = 0.e0 |
---|
1019 | DO ij=1, jpjm1 |
---|
1020 | DO ii=1, jpim1 |
---|
1021 | bdyumask(ii,ij)=bdytmask(ii,ij)*bdytmask(ii+1, ij ) |
---|
1022 | bdyvmask(ii,ij)=bdytmask(ii,ij)*bdytmask(ii ,ij+1) |
---|
1023 | END DO |
---|
1024 | END DO |
---|
1025 | CALL lbc_lnk( bdyumask(:,:), 'U', 1. ) ; CALL lbc_lnk( bdyvmask(:,:), 'V', 1. ) ! Lateral boundary cond. |
---|
1026 | |
---|
1027 | |
---|
1028 | ! Mask corrections |
---|
1029 | ! ---------------- |
---|
1030 | DO ik = 1, jpkm1 |
---|
1031 | DO ij = 1, jpj |
---|
1032 | DO ii = 1, jpi |
---|
1033 | tmask(ii,ij,ik) = tmask(ii,ij,ik) * bdytmask(ii,ij) |
---|
1034 | umask(ii,ij,ik) = umask(ii,ij,ik) * bdyumask(ii,ij) |
---|
1035 | vmask(ii,ij,ik) = vmask(ii,ij,ik) * bdyvmask(ii,ij) |
---|
1036 | bmask(ii,ij) = bmask(ii,ij) * bdytmask(ii,ij) |
---|
1037 | END DO |
---|
1038 | END DO |
---|
1039 | END DO |
---|
1040 | |
---|
1041 | DO ik = 1, jpkm1 |
---|
1042 | DO ij = 2, jpjm1 |
---|
1043 | DO ii = 2, jpim1 |
---|
1044 | fmask(ii,ij,ik) = fmask(ii,ij,ik) * bdytmask(ii,ij ) * bdytmask(ii+1,ij ) & |
---|
1045 | & * bdytmask(ii,ij+1) * bdytmask(ii+1,ij+1) |
---|
1046 | END DO |
---|
1047 | END DO |
---|
1048 | END DO |
---|
1049 | |
---|
1050 | tmask_i (:,:) = tmask(:,:,1) * tmask_i(:,:) |
---|
1051 | |
---|
1052 | ENDIF ! ln_mask_file=.TRUE. |
---|
1053 | |
---|
1054 | bdytmask(:,:) = tmask(:,:,1) |
---|
1055 | |
---|
1056 | ! bdy masks and bmask are now set to zero on boundary points: |
---|
1057 | igrd = 1 ! In the free surface case, bmask is at T-points |
---|
1058 | DO ib_bdy = 1, nb_bdy |
---|
1059 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1060 | bmask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0.e0 |
---|
1061 | ENDDO |
---|
1062 | ENDDO |
---|
1063 | ! |
---|
1064 | igrd = 1 |
---|
1065 | DO ib_bdy = 1, nb_bdy |
---|
1066 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1067 | bdytmask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0.e0 |
---|
1068 | ENDDO |
---|
1069 | ENDDO |
---|
1070 | ! |
---|
1071 | igrd = 2 |
---|
1072 | DO ib_bdy = 1, nb_bdy |
---|
1073 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1074 | bdyumask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0.e0 |
---|
1075 | ENDDO |
---|
1076 | ENDDO |
---|
1077 | ! |
---|
1078 | igrd = 3 |
---|
1079 | DO ib_bdy = 1, nb_bdy |
---|
1080 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1081 | bdyvmask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0.e0 |
---|
1082 | ENDDO |
---|
1083 | ENDDO |
---|
1084 | |
---|
1085 | ! Lateral boundary conditions |
---|
1086 | CALL lbc_lnk( fmask , 'F', 1. ) ; CALL lbc_lnk( bdytmask(:,:), 'T', 1. ) |
---|
1087 | CALL lbc_lnk( bdyumask(:,:), 'U', 1. ) ; CALL lbc_lnk( bdyvmask(:,:), 'V', 1. ) |
---|
1088 | |
---|
1089 | DO ib_bdy = 1, nb_bdy ! Indices and directions of rim velocity components |
---|
1090 | |
---|
1091 | idx_bdy(ib_bdy)%flagu(:) = 0.e0 |
---|
1092 | idx_bdy(ib_bdy)%flagv(:) = 0.e0 |
---|
1093 | icount = 0 |
---|
1094 | |
---|
1095 | !flagu = -1 : u component is normal to the dynamical boundary but its direction is outward |
---|
1096 | !flagu = 0 : u is tangential |
---|
1097 | !flagu = 1 : u is normal to the boundary and is direction is inward |
---|
1098 | |
---|
1099 | igrd = 2 ! u-component |
---|
1100 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1101 | nbi => idx_bdy(ib_bdy)%nbi(ib,igrd) |
---|
1102 | nbj => idx_bdy(ib_bdy)%nbj(ib,igrd) |
---|
1103 | zefl = bdytmask(nbi ,nbj) |
---|
1104 | zwfl = bdytmask(nbi+1,nbj) |
---|
1105 | IF( zefl + zwfl == 2 ) THEN |
---|
1106 | icount = icount + 1 |
---|
1107 | ELSE |
---|
1108 | idx_bdy(ib_bdy)%flagu(ib)=-zefl+zwfl |
---|
1109 | ENDIF |
---|
1110 | END DO |
---|
1111 | |
---|
1112 | !flagv = -1 : u component is normal to the dynamical boundary but its direction is outward |
---|
1113 | !flagv = 0 : u is tangential |
---|
1114 | !flagv = 1 : u is normal to the boundary and is direction is inward |
---|
1115 | |
---|
1116 | igrd = 3 ! v-component |
---|
1117 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1118 | nbi => idx_bdy(ib_bdy)%nbi(ib,igrd) |
---|
1119 | nbj => idx_bdy(ib_bdy)%nbj(ib,igrd) |
---|
1120 | znfl = bdytmask(nbi,nbj ) |
---|
1121 | zsfl = bdytmask(nbi,nbj+1) |
---|
1122 | IF( znfl + zsfl == 2 ) THEN |
---|
1123 | icount = icount + 1 |
---|
1124 | ELSE |
---|
1125 | idx_bdy(ib_bdy)%flagv(ib) = -znfl + zsfl |
---|
1126 | END IF |
---|
1127 | END DO |
---|
1128 | |
---|
1129 | IF( icount /= 0 ) THEN |
---|
1130 | IF(lwp) WRITE(numout,*) |
---|
1131 | IF(lwp) WRITE(numout,*) ' E R R O R : Some data velocity points,', & |
---|
1132 | ' are not boundary points. Check nbi, nbj, indices for boundary set ',ib_bdy |
---|
1133 | IF(lwp) WRITE(numout,*) ' ========== ' |
---|
1134 | IF(lwp) WRITE(numout,*) |
---|
1135 | nstop = nstop + 1 |
---|
1136 | ENDIF |
---|
1137 | |
---|
1138 | ENDDO |
---|
1139 | |
---|
1140 | ! Compute total lateral surface for volume correction: |
---|
1141 | ! ---------------------------------------------------- |
---|
1142 | ! JC: this must be done at each time step with key_vvl |
---|
1143 | bdysurftot = 0.e0 |
---|
1144 | IF( ln_vol ) THEN |
---|
1145 | igrd = 2 ! Lateral surface at U-points |
---|
1146 | DO ib_bdy = 1, nb_bdy |
---|
1147 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1148 | nbi => idx_bdy(ib_bdy)%nbi(ib,igrd) |
---|
1149 | nbj => idx_bdy(ib_bdy)%nbj(ib,igrd) |
---|
1150 | flagu => idx_bdy(ib_bdy)%flagu(ib) |
---|
1151 | bdysurftot = bdysurftot + hu (nbi , nbj) & |
---|
1152 | & * e2u (nbi , nbj) * ABS( flagu ) & |
---|
1153 | & * tmask_i(nbi , nbj) & |
---|
1154 | & * tmask_i(nbi+1, nbj) |
---|
1155 | ENDDO |
---|
1156 | ENDDO |
---|
1157 | |
---|
1158 | igrd=3 ! Add lateral surface at V-points |
---|
1159 | DO ib_bdy = 1, nb_bdy |
---|
1160 | DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) |
---|
1161 | nbi => idx_bdy(ib_bdy)%nbi(ib,igrd) |
---|
1162 | nbj => idx_bdy(ib_bdy)%nbj(ib,igrd) |
---|
1163 | flagv => idx_bdy(ib_bdy)%flagv(ib) |
---|
1164 | bdysurftot = bdysurftot + hv (nbi, nbj ) & |
---|
1165 | & * e1v (nbi, nbj ) * ABS( flagv ) & |
---|
1166 | & * tmask_i(nbi, nbj ) & |
---|
1167 | & * tmask_i(nbi, nbj+1) |
---|
1168 | ENDDO |
---|
1169 | ENDDO |
---|
1170 | ! |
---|
1171 | IF( lk_mpp ) CALL mpp_sum( bdysurftot ) ! sum over the global domain |
---|
1172 | END IF |
---|
1173 | ! |
---|
1174 | ! Tidy up |
---|
1175 | !-------- |
---|
1176 | IF (nb_bdy>0) THEN |
---|
1177 | DEALLOCATE(nbidta, nbjdta, nbrdta) |
---|
1178 | ENDIF |
---|
1179 | |
---|
1180 | IF( nn_timing == 1 ) CALL timing_stop('bdy_init') |
---|
1181 | |
---|
1182 | END SUBROUTINE bdy_init |
---|
1183 | |
---|
1184 | SUBROUTINE bdy_ctl_seg |
---|
1185 | !!---------------------------------------------------------------------- |
---|
1186 | !! *** ROUTINE bdy_ctl_seg *** |
---|
1187 | !! |
---|
1188 | !! ** Purpose : Check straight open boundary segments location |
---|
1189 | !! |
---|
1190 | !! ** Method : - Look for open boundary corners |
---|
1191 | !! - Check that segments start or end on land |
---|
1192 | !!---------------------------------------------------------------------- |
---|
1193 | INTEGER :: ib, ib1, ib2, ji ,jj, itest |
---|
1194 | INTEGER, DIMENSION(jp_nseg,2) :: icorne, icornw, icornn, icorns |
---|
1195 | REAL(wp), DIMENSION(2) :: ztestmask |
---|
1196 | !!---------------------------------------------------------------------- |
---|
1197 | ! |
---|
1198 | IF (lwp) WRITE(numout,*) ' ' |
---|
1199 | IF (lwp) WRITE(numout,*) 'bdy_ctl_seg: Check analytical segments' |
---|
1200 | IF (lwp) WRITE(numout,*) '~~~~~~~~~~~~' |
---|
1201 | ! |
---|
1202 | IF(lwp) WRITE(numout,*) 'Number of east segments : ', nbdysege |
---|
1203 | IF(lwp) WRITE(numout,*) 'Number of west segments : ', nbdysegw |
---|
1204 | IF(lwp) WRITE(numout,*) 'Number of north segments : ', nbdysegn |
---|
1205 | IF(lwp) WRITE(numout,*) 'Number of south segments : ', nbdysegs |
---|
1206 | ! 1. Check bounds |
---|
1207 | !---------------- |
---|
1208 | DO ib = 1, nbdysegn |
---|
1209 | IF (lwp) WRITE(numout,*) '**check north seg bounds pckg: ', npckgn(ib) |
---|
1210 | IF ((jpjnob(ib).ge.jpjglo-1).or.& |
---|
1211 | &(jpjnob(ib).le.1)) CALL ctl_stop( 'nbdyind out of domain' ) |
---|
1212 | IF (jpindt(ib).ge.jpinft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' ) |
---|
1213 | IF (jpindt(ib).le.1 ) CALL ctl_stop( 'Start index out of domain' ) |
---|
1214 | IF (jpinft(ib).ge.jpiglo) CALL ctl_stop( 'End index out of domain' ) |
---|
1215 | END DO |
---|
1216 | ! |
---|
1217 | DO ib = 1, nbdysegs |
---|
1218 | IF (lwp) WRITE(numout,*) '**check south seg bounds pckg: ', npckgs(ib) |
---|
1219 | IF ((jpjsob(ib).ge.jpjglo-1).or.& |
---|
1220 | &(jpjsob(ib).le.1)) CALL ctl_stop( 'nbdyind out of domain' ) |
---|
1221 | IF (jpisdt(ib).ge.jpisft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' ) |
---|
1222 | IF (jpisdt(ib).le.1 ) CALL ctl_stop( 'Start index out of domain' ) |
---|
1223 | IF (jpisft(ib).ge.jpiglo) CALL ctl_stop( 'End index out of domain' ) |
---|
1224 | END DO |
---|
1225 | ! |
---|
1226 | DO ib = 1, nbdysege |
---|
1227 | IF (lwp) WRITE(numout,*) '**check east seg bounds pckg: ', npckge(ib) |
---|
1228 | IF ((jpieob(ib).ge.jpiglo-1).or.& |
---|
1229 | &(jpieob(ib).le.1)) CALL ctl_stop( 'nbdyind out of domain' ) |
---|
1230 | IF (jpjedt(ib).ge.jpjeft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' ) |
---|
1231 | IF (jpjedt(ib).le.1 ) CALL ctl_stop( 'Start index out of domain' ) |
---|
1232 | IF (jpjeft(ib).ge.jpjglo) CALL ctl_stop( 'End index out of domain' ) |
---|
1233 | END DO |
---|
1234 | ! |
---|
1235 | DO ib = 1, nbdysegw |
---|
1236 | IF (lwp) WRITE(numout,*) '**check west seg bounds pckg: ', npckgw(ib) |
---|
1237 | IF ((jpiwob(ib).ge.jpiglo-1).or.& |
---|
1238 | &(jpiwob(ib).le.1)) CALL ctl_stop( 'nbdyind out of domain' ) |
---|
1239 | IF (jpjwdt(ib).ge.jpjwft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' ) |
---|
1240 | IF (jpjwdt(ib).le.1 ) CALL ctl_stop( 'Start index out of domain' ) |
---|
1241 | IF (jpjwft(ib).ge.jpjglo) CALL ctl_stop( 'End index out of domain' ) |
---|
1242 | ENDDO |
---|
1243 | ! |
---|
1244 | ! |
---|
1245 | ! 2. Look for segment crossings |
---|
1246 | !------------------------------ |
---|
1247 | IF (lwp) WRITE(numout,*) '**Look for segments corners :' |
---|
1248 | ! |
---|
1249 | itest = 0 ! corner number |
---|
1250 | ! |
---|
1251 | ! flag to detect if start or end of open boundary belongs to a corner |
---|
1252 | ! if not (=0), it must be on land. |
---|
1253 | ! if a corner is detected, save bdy package number for further tests |
---|
1254 | icorne(:,:)=0. ; icornw(:,:)=0. ; icornn(:,:)=0. ; icorns(:,:)=0. |
---|
1255 | ! South/West crossings |
---|
1256 | IF ((nbdysegw > 0).AND.(nbdysegs > 0)) THEN |
---|
1257 | DO ib1 = 1, nbdysegw |
---|
1258 | DO ib2 = 1, nbdysegs |
---|
1259 | IF (( jpisdt(ib2)<=jpiwob(ib1)).AND. & |
---|
1260 | & ( jpisft(ib2)>=jpiwob(ib1)).AND. & |
---|
1261 | & ( jpjwdt(ib1)<=jpjsob(ib2)).AND. & |
---|
1262 | & ( jpjwft(ib1)>=jpjsob(ib2))) THEN |
---|
1263 | IF ((jpjwdt(ib1)==jpjsob(ib2)).AND.(jpisdt(ib2)==jpiwob(ib1))) THEN |
---|
1264 | ! We have a possible South-West corner |
---|
1265 | ! WRITE(numout,*) ' Found a South-West corner at (i,j): ', jpisdt(ib2), jpjwdt(ib1) |
---|
1266 | ! WRITE(numout,*) ' between segments: ', npckgw(ib1), npckgs(ib2) |
---|
1267 | icornw(ib1,1) = npckgs(ib2) |
---|
1268 | icorns(ib2,1) = npckgw(ib1) |
---|
1269 | ELSEIF ((jpisft(ib2)==jpiwob(ib1)).AND.(jpjwft(ib1)==jpjsob(ib2))) THEN |
---|
1270 | IF(lwp) WRITE(numout,*) |
---|
1271 | IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', & |
---|
1272 | & jpisft(ib2), jpjwft(ib1) |
---|
1273 | IF(lwp) WRITE(numout,*) ' ========== Not allowed yet' |
---|
1274 | IF(lwp) WRITE(numout,*) ' Crossing problem with West segment: ',npckgw(ib1), & |
---|
1275 | & ' and South segment: ',npckgs(ib2) |
---|
1276 | IF(lwp) WRITE(numout,*) |
---|
1277 | nstop = nstop + 1 |
---|
1278 | ELSE |
---|
1279 | IF(lwp) WRITE(numout,*) |
---|
1280 | IF(lwp) WRITE(numout,*) ' E R R O R : Check South and West Open boundary indices' |
---|
1281 | IF(lwp) WRITE(numout,*) ' ========== Crossing problem with West segment: ',npckgw(ib1) , & |
---|
1282 | & ' and South segment: ',npckgs(ib2) |
---|
1283 | IF(lwp) WRITE(numout,*) |
---|
1284 | nstop = nstop+1 |
---|
1285 | END IF |
---|
1286 | END IF |
---|
1287 | END DO |
---|
1288 | END DO |
---|
1289 | END IF |
---|
1290 | ! |
---|
1291 | ! South/East crossings |
---|
1292 | IF ((nbdysege > 0).AND.(nbdysegs > 0)) THEN |
---|
1293 | DO ib1 = 1, nbdysege |
---|
1294 | DO ib2 = 1, nbdysegs |
---|
1295 | IF (( jpisdt(ib2)<=jpieob(ib1)+1).AND. & |
---|
1296 | & ( jpisft(ib2)>=jpieob(ib1)+1).AND. & |
---|
1297 | & ( jpjedt(ib1)<=jpjsob(ib2) ).AND. & |
---|
1298 | & ( jpjeft(ib1)>=jpjsob(ib2) )) THEN |
---|
1299 | IF ((jpjedt(ib1)==jpjsob(ib2)).AND.(jpisft(ib2)==jpieob(ib1)+1)) THEN |
---|
1300 | ! We have a possible South-East corner |
---|
1301 | ! WRITE(numout,*) ' Found a South-East corner at (i,j): ', jpisft(ib2), jpjedt(ib1) |
---|
1302 | ! WRITE(numout,*) ' between segments: ', npckge(ib1), npckgs(ib2) |
---|
1303 | icorne(ib1,1) = npckgs(ib2) |
---|
1304 | icorns(ib2,2) = npckge(ib1) |
---|
1305 | ELSEIF ((jpjeft(ib1)==jpjsob(ib2)).AND.(jpisdt(ib2)==jpieob(ib1)+1)) THEN |
---|
1306 | IF(lwp) WRITE(numout,*) |
---|
1307 | IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', & |
---|
1308 | & jpisdt(ib2), jpjeft(ib1) |
---|
1309 | IF(lwp) WRITE(numout,*) ' ========== Not allowed yet' |
---|
1310 | IF(lwp) WRITE(numout,*) ' Crossing problem with East segment: ',npckge(ib1), & |
---|
1311 | & ' and South segment: ',npckgs(ib2) |
---|
1312 | IF(lwp) WRITE(numout,*) |
---|
1313 | nstop = nstop + 1 |
---|
1314 | ELSE |
---|
1315 | IF(lwp) WRITE(numout,*) |
---|
1316 | IF(lwp) WRITE(numout,*) ' E R R O R : Check South and East Open boundary indices' |
---|
1317 | IF(lwp) WRITE(numout,*) ' ========== Crossing problem with East segment: ',npckge(ib1), & |
---|
1318 | & ' and South segment: ',npckgs(ib2) |
---|
1319 | IF(lwp) WRITE(numout,*) |
---|
1320 | nstop = nstop + 1 |
---|
1321 | END IF |
---|
1322 | END IF |
---|
1323 | END DO |
---|
1324 | END DO |
---|
1325 | END IF |
---|
1326 | ! |
---|
1327 | ! North/West crossings |
---|
1328 | IF ((nbdysegn > 0).AND.(nbdysegw > 0)) THEN |
---|
1329 | DO ib1 = 1, nbdysegw |
---|
1330 | DO ib2 = 1, nbdysegn |
---|
1331 | IF (( jpindt(ib2)<=jpiwob(ib1) ).AND. & |
---|
1332 | & ( jpinft(ib2)>=jpiwob(ib1) ).AND. & |
---|
1333 | & ( jpjwdt(ib1)<=jpjnob(ib2)+1).AND. & |
---|
1334 | & ( jpjwft(ib1)>=jpjnob(ib2)+1)) THEN |
---|
1335 | IF ((jpjwft(ib1)==jpjnob(ib2)+1).AND.(jpindt(ib2)==jpiwob(ib1))) THEN |
---|
1336 | ! We have a possible North-West corner |
---|
1337 | ! WRITE(numout,*) ' Found a North-West corner at (i,j): ', jpindt(ib2), jpjwft(ib1) |
---|
1338 | ! WRITE(numout,*) ' between segments: ', npckgw(ib1), npckgn(ib2) |
---|
1339 | icornw(ib1,2) = npckgn(ib2) |
---|
1340 | icornn(ib2,1) = npckgw(ib1) |
---|
1341 | ELSEIF ((jpjwdt(ib1)==jpjnob(ib2)+1).AND.(jpinft(ib2)==jpiwob(ib1))) THEN |
---|
1342 | IF(lwp) WRITE(numout,*) |
---|
1343 | IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', & |
---|
1344 | & jpinft(ib2), jpjwdt(ib1) |
---|
1345 | IF(lwp) WRITE(numout,*) ' ========== Not allowed yet' |
---|
1346 | IF(lwp) WRITE(numout,*) ' Crossing problem with West segment: ',npckgw(ib1), & |
---|
1347 | & ' and North segment: ',npckgn(ib2) |
---|
1348 | IF(lwp) WRITE(numout,*) |
---|
1349 | nstop = nstop + 1 |
---|
1350 | ELSE |
---|
1351 | IF(lwp) WRITE(numout,*) |
---|
1352 | IF(lwp) WRITE(numout,*) ' E R R O R : Check North and West Open boundary indices' |
---|
1353 | IF(lwp) WRITE(numout,*) ' ========== Crossing problem with West segment: ',npckgw(ib1), & |
---|
1354 | & ' and North segment: ',npckgn(ib2) |
---|
1355 | IF(lwp) WRITE(numout,*) |
---|
1356 | nstop = nstop + 1 |
---|
1357 | END IF |
---|
1358 | END IF |
---|
1359 | END DO |
---|
1360 | END DO |
---|
1361 | END IF |
---|
1362 | ! |
---|
1363 | ! North/East crossings |
---|
1364 | IF ((nbdysegn > 0).AND.(nbdysege > 0)) THEN |
---|
1365 | DO ib1 = 1, nbdysege |
---|
1366 | DO ib2 = 1, nbdysegn |
---|
1367 | IF (( jpindt(ib2)<=jpieob(ib1)+1).AND. & |
---|
1368 | & ( jpinft(ib2)>=jpieob(ib1)+1).AND. & |
---|
1369 | & ( jpjedt(ib1)<=jpjnob(ib2)+1).AND. & |
---|
1370 | & ( jpjeft(ib1)>=jpjnob(ib2)+1)) THEN |
---|
1371 | IF ((jpjeft(ib1)==jpjnob(ib2)+1).AND.(jpinft(ib2)==jpieob(ib1)+1)) THEN |
---|
1372 | ! We have a possible North-East corner |
---|
1373 | ! WRITE(numout,*) ' Found a North-East corner at (i,j): ', jpinft(ib2), jpjeft(ib1) |
---|
1374 | ! WRITE(numout,*) ' between segments: ', npckge(ib1), npckgn(ib2) |
---|
1375 | icorne(ib1,2) = npckgn(ib2) |
---|
1376 | icornn(ib2,2) = npckge(ib1) |
---|
1377 | ELSEIF ((jpjedt(ib1)==jpjnob(ib2)+1).AND.(jpindt(ib2)==jpieob(ib1)+1)) THEN |
---|
1378 | IF(lwp) WRITE(numout,*) |
---|
1379 | IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', & |
---|
1380 | & jpindt(ib2), jpjedt(ib1) |
---|
1381 | IF(lwp) WRITE(numout,*) ' ========== Not allowed yet' |
---|
1382 | IF(lwp) WRITE(numout,*) ' Crossing problem with East segment: ',npckge(ib1), & |
---|
1383 | & ' and North segment: ',npckgn(ib2) |
---|
1384 | IF(lwp) WRITE(numout,*) |
---|
1385 | nstop = nstop + 1 |
---|
1386 | ELSE |
---|
1387 | IF(lwp) WRITE(numout,*) |
---|
1388 | IF(lwp) WRITE(numout,*) ' E R R O R : Check North and East Open boundary indices' |
---|
1389 | IF(lwp) WRITE(numout,*) ' ========== Crossing problem with East segment: ',npckge(ib1), & |
---|
1390 | & ' and North segment: ',npckgn(ib2) |
---|
1391 | IF(lwp) WRITE(numout,*) |
---|
1392 | nstop = nstop + 1 |
---|
1393 | END IF |
---|
1394 | END IF |
---|
1395 | END DO |
---|
1396 | END DO |
---|
1397 | END IF |
---|
1398 | ! |
---|
1399 | ! 3. Check if segment extremities are on land |
---|
1400 | !-------------------------------------------- |
---|
1401 | ! |
---|
1402 | ! West segments |
---|
1403 | DO ib = 1, nbdysegw |
---|
1404 | ! get mask at boundary extremities: |
---|
1405 | ztestmask(1:2)=0. |
---|
1406 | DO ji = 1, jpi |
---|
1407 | DO jj = 1, jpj |
---|
1408 | IF (((ji + nimpp - 1) == jpiwob(ib)).AND. & |
---|
1409 | & ((jj + njmpp - 1) == jpjwdt(ib))) ztestmask(1)=tmask(ji,jj,1) |
---|
1410 | IF (((ji + nimpp - 1) == jpiwob(ib)).AND. & |
---|
1411 | & ((jj + njmpp - 1) == jpjwft(ib))) ztestmask(2)=tmask(ji,jj,1) |
---|
1412 | END DO |
---|
1413 | END DO |
---|
1414 | IF( lk_mpp ) CALL mpp_sum( ztestmask, 2 ) ! sum over the global domain |
---|
1415 | |
---|
1416 | IF (ztestmask(1)==1) THEN |
---|
1417 | IF (icornw(ib,1)==0) THEN |
---|
1418 | IF(lwp) WRITE(numout,*) |
---|
1419 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgw(ib) |
---|
1420 | IF(lwp) WRITE(numout,*) ' ========== does not start on land or on a corner' |
---|
1421 | IF(lwp) WRITE(numout,*) |
---|
1422 | nstop = nstop + 1 |
---|
1423 | ELSE |
---|
1424 | ! This is a corner |
---|
1425 | WRITE(numout,*) 'Found a South-West corner at (i,j): ', jpiwob(ib), jpjwdt(ib) |
---|
1426 | CALL bdy_ctl_corn(npckgw(ib), icornw(ib,1)) |
---|
1427 | itest=itest+1 |
---|
1428 | ENDIF |
---|
1429 | ENDIF |
---|
1430 | IF (ztestmask(2)==1) THEN |
---|
1431 | IF (icornw(ib,2)==0) THEN |
---|
1432 | IF(lwp) WRITE(numout,*) |
---|
1433 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgw(ib) |
---|
1434 | IF(lwp) WRITE(numout,*) ' ========== does not end on land or on a corner' |
---|
1435 | IF(lwp) WRITE(numout,*) |
---|
1436 | nstop = nstop + 1 |
---|
1437 | ELSE |
---|
1438 | ! This is a corner |
---|
1439 | WRITE(numout,*) 'Found a North-West corner at (i,j): ', jpiwob(ib), jpjwft(ib) |
---|
1440 | CALL bdy_ctl_corn(npckgw(ib), icornw(ib,2)) |
---|
1441 | itest=itest+1 |
---|
1442 | ENDIF |
---|
1443 | ENDIF |
---|
1444 | END DO |
---|
1445 | ! |
---|
1446 | ! East segments |
---|
1447 | DO ib = 1, nbdysege |
---|
1448 | ! get mask at boundary extremities: |
---|
1449 | ztestmask(1:2)=0. |
---|
1450 | DO ji = 1, jpi |
---|
1451 | DO jj = 1, jpj |
---|
1452 | IF (((ji + nimpp - 1) == jpieob(ib)+1).AND. & |
---|
1453 | & ((jj + njmpp - 1) == jpjedt(ib))) ztestmask(1)=tmask(ji,jj,1) |
---|
1454 | IF (((ji + nimpp - 1) == jpieob(ib)+1).AND. & |
---|
1455 | & ((jj + njmpp - 1) == jpjeft(ib))) ztestmask(2)=tmask(ji,jj,1) |
---|
1456 | END DO |
---|
1457 | END DO |
---|
1458 | IF( lk_mpp ) CALL mpp_sum( ztestmask, 2 ) ! sum over the global domain |
---|
1459 | |
---|
1460 | IF (ztestmask(1)==1) THEN |
---|
1461 | IF (icorne(ib,1)==0) THEN |
---|
1462 | IF(lwp) WRITE(numout,*) |
---|
1463 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckge(ib) |
---|
1464 | IF(lwp) WRITE(numout,*) ' ========== does not start on land or on a corner' |
---|
1465 | IF(lwp) WRITE(numout,*) |
---|
1466 | nstop = nstop + 1 |
---|
1467 | ELSE |
---|
1468 | ! This is a corner |
---|
1469 | WRITE(numout,*) 'Found a South-East corner at (i,j): ', jpieob(ib)+1, jpjedt(ib) |
---|
1470 | CALL bdy_ctl_corn(npckge(ib), icorne(ib,1)) |
---|
1471 | itest=itest+1 |
---|
1472 | ENDIF |
---|
1473 | ENDIF |
---|
1474 | IF (ztestmask(2)==1) THEN |
---|
1475 | IF (icorne(ib,2)==0) THEN |
---|
1476 | IF(lwp) WRITE(numout,*) |
---|
1477 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckge(ib) |
---|
1478 | IF(lwp) WRITE(numout,*) ' ========== does not end on land or on a corner' |
---|
1479 | IF(lwp) WRITE(numout,*) |
---|
1480 | nstop = nstop + 1 |
---|
1481 | ELSE |
---|
1482 | ! This is a corner |
---|
1483 | WRITE(numout,*) 'Found a North-East corner at (i,j): ', jpieob(ib)+1, jpjeft(ib) |
---|
1484 | CALL bdy_ctl_corn(npckge(ib), icorne(ib,2)) |
---|
1485 | itest=itest+1 |
---|
1486 | ENDIF |
---|
1487 | ENDIF |
---|
1488 | END DO |
---|
1489 | ! |
---|
1490 | ! South segments |
---|
1491 | DO ib = 1, nbdysegs |
---|
1492 | ! get mask at boundary extremities: |
---|
1493 | ztestmask(1:2)=0. |
---|
1494 | DO ji = 1, jpi |
---|
1495 | DO jj = 1, jpj |
---|
1496 | IF (((jj + njmpp - 1) == jpjsob(ib)).AND. & |
---|
1497 | & ((ji + nimpp - 1) == jpisdt(ib))) ztestmask(1)=tmask(ji,jj,1) |
---|
1498 | IF (((jj + njmpp - 1) == jpjsob(ib)).AND. & |
---|
1499 | & ((ji + nimpp - 1) == jpisft(ib))) ztestmask(2)=tmask(ji,jj,1) |
---|
1500 | END DO |
---|
1501 | END DO |
---|
1502 | IF( lk_mpp ) CALL mpp_sum( ztestmask, 2 ) ! sum over the global domain |
---|
1503 | |
---|
1504 | IF ((ztestmask(1)==1).AND.(icorns(ib,1)==0)) THEN |
---|
1505 | IF(lwp) WRITE(numout,*) |
---|
1506 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgs(ib) |
---|
1507 | IF(lwp) WRITE(numout,*) ' ========== does not start on land or on a corner' |
---|
1508 | IF(lwp) WRITE(numout,*) |
---|
1509 | nstop = nstop + 1 |
---|
1510 | ENDIF |
---|
1511 | IF ((ztestmask(2)==1).AND.(icorns(ib,2)==0)) THEN |
---|
1512 | IF(lwp) WRITE(numout,*) |
---|
1513 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgs(ib) |
---|
1514 | IF(lwp) WRITE(numout,*) ' ========== does not end on land or on a corner' |
---|
1515 | IF(lwp) WRITE(numout,*) |
---|
1516 | nstop = nstop + 1 |
---|
1517 | ENDIF |
---|
1518 | END DO |
---|
1519 | ! |
---|
1520 | ! North segments |
---|
1521 | DO ib = 1, nbdysegn |
---|
1522 | ! get mask at boundary extremities: |
---|
1523 | ztestmask(1:2)=0. |
---|
1524 | DO ji = 1, jpi |
---|
1525 | DO jj = 1, jpj |
---|
1526 | IF (((jj + njmpp - 1) == jpjnob(ib)+1).AND. & |
---|
1527 | & ((ji + nimpp - 1) == jpindt(ib))) ztestmask(1)=tmask(ji,jj,1) |
---|
1528 | IF (((jj + njmpp - 1) == jpjnob(ib)+1).AND. & |
---|
1529 | & ((ji + nimpp - 1) == jpinft(ib))) ztestmask(2)=tmask(ji,jj,1) |
---|
1530 | END DO |
---|
1531 | END DO |
---|
1532 | IF( lk_mpp ) CALL mpp_sum( ztestmask, 2 ) ! sum over the global domain |
---|
1533 | |
---|
1534 | IF ((ztestmask(1)==1).AND.(icornn(ib,1)==0)) THEN |
---|
1535 | IF(lwp) WRITE(numout,*) |
---|
1536 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgn(ib) |
---|
1537 | IF(lwp) WRITE(numout,*) ' ========== does not start on land' |
---|
1538 | IF(lwp) WRITE(numout,*) |
---|
1539 | nstop = nstop + 1 |
---|
1540 | ENDIF |
---|
1541 | IF ((ztestmask(2)==1).AND.(icornn(ib,2)==0)) THEN |
---|
1542 | IF(lwp) WRITE(numout,*) |
---|
1543 | IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgn(ib) |
---|
1544 | IF(lwp) WRITE(numout,*) ' ========== does not end on land' |
---|
1545 | IF(lwp) WRITE(numout,*) |
---|
1546 | nstop = nstop + 1 |
---|
1547 | ENDIF |
---|
1548 | END DO |
---|
1549 | ! |
---|
1550 | IF ((itest==0).AND.(lwp)) WRITE(numout,*) 'NO open boundary corner found' |
---|
1551 | ! |
---|
1552 | ! Other tests TBD: |
---|
1553 | ! segments completly on land |
---|
1554 | ! optimized open boundary array length according to landmask |
---|
1555 | ! Nudging layers that overlap with interior domain |
---|
1556 | ! |
---|
1557 | END SUBROUTINE bdy_ctl_seg |
---|
1558 | |
---|
1559 | SUBROUTINE bdy_ctl_corn( ib1, ib2 ) |
---|
1560 | !!---------------------------------------------------------------------- |
---|
1561 | !! *** ROUTINE bdy_ctl_corn *** |
---|
1562 | !! |
---|
1563 | !! ** Purpose : Check numerical schemes consistency between |
---|
1564 | !! segments having a common corner |
---|
1565 | !! |
---|
1566 | !! ** Method : |
---|
1567 | !!---------------------------------------------------------------------- |
---|
1568 | INTEGER, INTENT(in) :: ib1, ib2 |
---|
1569 | INTEGER :: itest |
---|
1570 | !!---------------------------------------------------------------------- |
---|
1571 | itest = 0 |
---|
1572 | |
---|
1573 | IF (nn_dyn2d(ib1)/=nn_dyn2d(ib2)) itest = itest + 1 |
---|
1574 | IF (nn_dyn3d(ib1)/=nn_dyn3d(ib2)) itest = itest + 1 |
---|
1575 | IF (nn_tra(ib1)/=nn_tra(ib2)) itest = itest + 1 |
---|
1576 | ! |
---|
1577 | IF (nn_dyn2d_dta(ib1)/=nn_dyn2d_dta(ib2)) itest = itest + 1 |
---|
1578 | IF (nn_dyn3d_dta(ib1)/=nn_dyn3d_dta(ib2)) itest = itest + 1 |
---|
1579 | IF (nn_tra_dta(ib1)/=nn_tra_dta(ib2)) itest = itest + 1 |
---|
1580 | ! |
---|
1581 | IF (nn_rimwidth(ib1)/=nn_rimwidth(ib2)) itest = itest + 1 |
---|
1582 | ! |
---|
1583 | IF ( itest>0 ) THEN |
---|
1584 | IF(lwp) WRITE(numout,*) ' E R R O R : Segments ', ib1, 'and ', ib2 |
---|
1585 | IF(lwp) WRITE(numout,*) ' ========== have different open bdy schemes' |
---|
1586 | IF(lwp) WRITE(numout,*) |
---|
1587 | nstop = nstop + 1 |
---|
1588 | ENDIF |
---|
1589 | ! |
---|
1590 | END SUBROUTINE bdy_ctl_corn |
---|
1591 | |
---|
1592 | #else |
---|
1593 | !!--------------------------------------------------------------------------------- |
---|
1594 | !! Dummy module NO open boundaries |
---|
1595 | !!--------------------------------------------------------------------------------- |
---|
1596 | CONTAINS |
---|
1597 | SUBROUTINE bdy_init ! Dummy routine |
---|
1598 | END SUBROUTINE bdy_init |
---|
1599 | #endif |
---|
1600 | |
---|
1601 | !!================================================================================= |
---|
1602 | END MODULE bdyini |
---|