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/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 @ 8738

Last change on this file since 8738 was 8738, checked in by dancopsey, 6 years ago

Merged in main ICEMODEL branch (branches/2017/dev_r8183_ICEMODEL) up to revision 8588

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