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 NEMO/trunk/tests/WAD/MY_SRC – NEMO

source: NEMO/trunk/tests/WAD/MY_SRC/bdyini.F90 @ 9659

Last change on this file since 9659 was 9659, checked in by clem, 6 years ago

complete last commit with the test cases

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