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.
bdyini.F90 in branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 @ 9449

Last change on this file since 9449 was 9449, checked in by smasson, 6 years ago

dev_merge_2017: agrif bugfix for non-constant jpi/jpj + some cleaning...

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