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/CONFIG/TEST_CASES/WAD/MY_SRC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/CONFIG/TEST_CASES/WAD/MY_SRC/bdyini.F90 @ 9124

Last change on this file since 9124 was 9124, checked in by gm, 6 years ago

dev_merge_2017: ln_timing instead of nn_timing + restricted timing to nemo_init and routine called by step in OPA_SRC

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