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/NERC/dev_r6998_ORCHESTRA/NEMOGCM/CONFIG/ORCHESTRA/MY_SRC – NEMO

source: branches/NERC/dev_r6998_ORCHESTRA/NEMOGCM/CONFIG/ORCHESTRA/MY_SRC/bdyini.F90 @ 7029

Last change on this file since 7029 was 7029, checked in by jamesharle, 8 years ago

Adding ORCHESTRA configuration
Merging with branches/2016/dev_r5549_BDY_ZEROGRAD
Merging with branches/2016/dev_r5840_BDY_MSK
Merging with branches/2014/dev_r4621_NOC4_BDY_VERT_INTERP

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