New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
bdyini.F90 in branches/2017/dev_r8126_ROBUST08_no_ghost/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2017/dev_r8126_ROBUST08_no_ghost/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 @ 8809

Last change on this file since 8809 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • Property svn:keywords set to Id
File size: 84.0 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_lim2
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_frld  = .false.
359             dta_bdy(ib_bdy)%ll_hicif = .false.
360             dta_bdy(ib_bdy)%ll_hsnif = .false.
361          CASE('frs')
362             IF(lwp) WRITE(numout,*) '      Flow Relaxation Scheme'
363             dta_bdy(ib_bdy)%ll_frld  = .true.
364             dta_bdy(ib_bdy)%ll_hicif = .true.
365             dta_bdy(ib_bdy)%ll_hsnif = .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#elif defined key_lim3
377        IF(lwp) WRITE(numout,*) 'Boundary conditions for sea ice:  '
378        SELECT CASE( cn_ice_lim(ib_bdy) )                 
379          CASE('none')
380             IF(lwp) WRITE(numout,*) '      no open boundary condition'       
381             dta_bdy(ib_bdy)%ll_a_i  = .false.
382             dta_bdy(ib_bdy)%ll_ht_i = .false.
383             dta_bdy(ib_bdy)%ll_ht_s = .false.
384          CASE('frs')
385             IF(lwp) WRITE(numout,*) '      Flow Relaxation Scheme'
386             dta_bdy(ib_bdy)%ll_a_i  = .true.
387             dta_bdy(ib_bdy)%ll_ht_i = .true.
388             dta_bdy(ib_bdy)%ll_ht_s = .true.
389          CASE DEFAULT   ;   CALL ctl_stop( 'unrecognised value for cn_ice_lim' )
390        END SELECT
391        IF( cn_ice_lim(ib_bdy) /= 'none' ) THEN
392           SELECT CASE( nn_ice_lim_dta(ib_bdy) )                   !
393              CASE( 0 )      ;   IF(lwp) WRITE(numout,*) '      initial state used for bdy data'       
394              CASE( 1 )      ;   IF(lwp) WRITE(numout,*) '      boundary data taken from file'
395              CASE DEFAULT   ;   CALL ctl_stop( 'nn_ice_lim_dta must be 0 or 1' )
396           END SELECT
397        ENDIF
398        IF(lwp) WRITE(numout,*)
399        IF(lwp) WRITE(numout,*) '      tem of bdy sea-ice = ', rn_ice_tem(ib_bdy)         
400        IF(lwp) WRITE(numout,*) '      sal of bdy sea-ice = ', rn_ice_sal(ib_bdy)         
401        IF(lwp) WRITE(numout,*) '      age of bdy sea-ice = ', rn_ice_age(ib_bdy)         
402#endif
403
404        IF(lwp) WRITE(numout,*) '      Width of relaxation zone = ', nn_rimwidth(ib_bdy)
405        IF(lwp) WRITE(numout,*)
406
407      ENDDO
408
409     IF (nb_bdy .gt. 0) THEN
410        IF( ln_vol ) THEN                     ! check volume conservation (nn_volctl value)
411          IF(lwp) WRITE(numout,*) 'Volume correction applied at open boundaries'
412          IF(lwp) WRITE(numout,*)
413          SELECT CASE ( nn_volctl )
414            CASE( 1 )      ;   IF(lwp) WRITE(numout,*) '      The total volume will be constant'
415            CASE( 0 )      ;   IF(lwp) WRITE(numout,*) '      The total volume will vary according to the surface E-P flux'
416            CASE DEFAULT   ;   CALL ctl_stop( 'nn_volctl must be 0 or 1' )
417          END SELECT
418          IF(lwp) WRITE(numout,*)
419        ELSE
420          IF(lwp) WRITE(numout,*) 'No volume correction applied at open boundaries'
421          IF(lwp) WRITE(numout,*)
422        ENDIF
423        IF( nb_jpk_bdy > 0 ) THEN
424           IF(lwp) WRITE(numout,*) '*** open boundary will be interpolate in the vertical onto the native grid ***'
425        ELSE
426           IF(lwp) WRITE(numout,*) '*** open boundary will be read straight onto the native grid without vertical interpolation ***'
427        ENDIF
428     ENDIF
429
430      ! -------------------------------------------------
431      ! Initialise indices arrays for open boundaries
432      ! -------------------------------------------------
433
434      ! Work out global dimensions of boundary data
435      ! ---------------------------------------------
436      REWIND( numnam_cfg )     
437
438      nblendta(:,:) = 0
439      nbdysege = 0
440      nbdysegw = 0
441      nbdysegn = 0
442      nbdysegs = 0
443      icount   = 0 ! count user defined segments
444      ! Dimensions below are used to allocate arrays to read external data
445      jpbdtas = 1 ! Maximum size of boundary data (structured case)
446      jpbdtau = 1 ! Maximum size of boundary data (unstructured case)
447
448      DO ib_bdy = 1, nb_bdy
449
450         IF( .NOT. ln_coords_file(ib_bdy) ) THEN ! Work out size of global arrays from namelist parameters
451 
452            icount = icount + 1
453            ! No REWIND here because may need to read more than one nambdy_index namelist.
454            ! Read only namelist_cfg to avoid unseccessfull overwrite
455!!          REWIND( numnam_ref )              ! Namelist nambdy_index in reference namelist : Open boundaries indexes
456!!          READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 903)
457!!903       IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_index in reference namelist', lwp )
458
459!!          REWIND( numnam_cfg )              ! Namelist nambdy_index in configuration namelist : Open boundaries indexes
460            READ  ( numnam_cfg, nambdy_index, IOSTAT = ios, ERR = 904 )
461904         IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_index in configuration namelist', lwp )
462            IF(lwm) WRITE ( numond, nambdy_index )
463
464            SELECT CASE ( TRIM(ctypebdy) )
465              CASE( 'N' )
466                 IF( nbdyind == -1 ) THEN  ! Automatic boundary definition: if nbdysegX = -1
467                    nbdyind  = jpjglo - 2  ! set boundary to whole side of model domain.
468                    nbdybeg  = 2
469                    nbdyend  = jpiglo - 1
470                 ENDIF
471                 nbdysegn = nbdysegn + 1
472                 npckgn(nbdysegn) = ib_bdy ! Save bdy package number
473                 jpjnob(nbdysegn) = nbdyind
474                 jpindt(nbdysegn) = nbdybeg
475                 jpinft(nbdysegn) = nbdyend
476                 !
477              CASE( 'S' )
478                 IF( nbdyind == -1 ) THEN  ! Automatic boundary definition: if nbdysegX = -1
479                    nbdyind  = 2           ! set boundary to whole side of model domain.
480                    nbdybeg  = 2
481                    nbdyend  = jpiglo - 1
482                 ENDIF
483                 nbdysegs = nbdysegs + 1
484                 npckgs(nbdysegs) = ib_bdy ! Save bdy package number
485                 jpjsob(nbdysegs) = nbdyind
486                 jpisdt(nbdysegs) = nbdybeg
487                 jpisft(nbdysegs) = nbdyend
488                 !
489              CASE( 'E' )
490                 IF( nbdyind == -1 ) THEN  ! Automatic boundary definition: if nbdysegX = -1
491                    nbdyind  = jpiglo - 2  ! set boundary to whole side of model domain.
492                    nbdybeg  = 2
493                    nbdyend  = jpjglo - 1
494                 ENDIF
495                 nbdysege = nbdysege + 1 
496                 npckge(nbdysege) = ib_bdy ! Save bdy package number
497                 jpieob(nbdysege) = nbdyind
498                 jpjedt(nbdysege) = nbdybeg
499                 jpjeft(nbdysege) = nbdyend
500                 !
501              CASE( 'W' )
502                 IF( nbdyind == -1 ) THEN  ! Automatic boundary definition: if nbdysegX = -1
503                    nbdyind  = 2           ! set boundary to whole side of model domain.
504                    nbdybeg  = 2
505                    nbdyend  = jpjglo - 1
506                 ENDIF
507                 nbdysegw = nbdysegw + 1
508                 npckgw(nbdysegw) = ib_bdy ! Save bdy package number
509                 jpiwob(nbdysegw) = nbdyind
510                 jpjwdt(nbdysegw) = nbdybeg
511                 jpjwft(nbdysegw) = nbdyend
512                 !
513              CASE DEFAULT   ;   CALL ctl_stop( 'ctypebdy must be N, S, E or W' )
514            END SELECT
515
516            ! For simplicity we assume that in case of straight bdy, arrays have the same length
517            ! (even if it is true that last tangential velocity points
518            ! are useless). This simplifies a little bit boundary data format (and agrees with format
519            ! used so far in obc package)
520
521            nblendta(1:jpbgrd,ib_bdy) =  (nbdyend - nbdybeg + 1) * nn_rimwidth(ib_bdy)
522            jpbdtas = MAX(jpbdtas, (nbdyend - nbdybeg + 1))
523            IF (lwp.and.(nn_rimwidth(ib_bdy)>nrimmax)) &
524            & CALL ctl_stop( 'rimwidth must be lower than nrimmax' )
525
526         ELSE            ! Read size of arrays in boundary coordinates file.
527            CALL iom_open( cn_coords_file(ib_bdy), inum )
528            DO igrd = 1, jpbgrd
529               id_dummy = iom_varid( inum, 'nbi'//cgrid(igrd), kdimsz=kdimsz ) 
530               !clem nblendta(igrd,ib_bdy) = kdimsz(1)
531               !clem jpbdtau = MAX(jpbdtau, kdimsz(1))
532               nblendta(igrd,ib_bdy) = MAXVAL(kdimsz)
533               jpbdtau = MAX(jpbdtau, MAXVAL(kdimsz))
534            END DO
535            CALL iom_close( inum )
536            !
537         ENDIF 
538         !
539      END DO ! ib_bdy
540
541      IF (nb_bdy>0) THEN
542         jpbdta = MAXVAL(nblendta(1:jpbgrd,1:nb_bdy))
543
544         ! Allocate arrays
545         !---------------
546         ALLOCATE( nbidta(jpbdta, jpbgrd, nb_bdy), nbjdta(jpbdta, jpbgrd, nb_bdy),    &
547            &      nbrdta(jpbdta, jpbgrd, nb_bdy) )
548
549         IF( nb_jpk_bdy>0 ) THEN
550            ALLOCATE( dta_global(jpbdtau, 1, nb_jpk_bdy) )
551            ALLOCATE( dta_global_z(jpbdtau, 1, nb_jpk_bdy) )
552            ALLOCATE( dta_global_dz(jpbdtau, 1, nb_jpk_bdy) )
553         ELSE
554            ALLOCATE( dta_global(jpbdtau, 1, jpk) )
555            ALLOCATE( dta_global_z(jpbdtau, 1, jpk) ) ! needed ?? TODO
556            ALLOCATE( dta_global_dz(jpbdtau, 1, jpk) )! needed ?? TODO
557         ENDIF
558
559         IF ( icount>0 ) THEN
560            IF( nb_jpk_bdy>0 ) THEN
561               ALLOCATE( dta_global2(jpbdtas, nrimmax, nb_jpk_bdy) )
562               ALLOCATE( dta_global2_z(jpbdtas, nrimmax, nb_jpk_bdy) )
563               ALLOCATE( dta_global2_dz(jpbdtas, nrimmax, nb_jpk_bdy) )
564            ELSE
565               ALLOCATE( dta_global2(jpbdtas, nrimmax, jpk) )
566               ALLOCATE( dta_global2_z(jpbdtas, nrimmax, jpk) ) ! needed ?? TODO
567               ALLOCATE( dta_global2_dz(jpbdtas, nrimmax, jpk) )! needed ?? TODO 
568            ENDIF
569         ENDIF
570         !
571      ENDIF
572
573      ! Now look for crossings in user (namelist) defined open boundary segments:
574      !--------------------------------------------------------------------------
575      IF( icount>0 )   CALL bdy_ctl_seg
576
577      ! Calculate global boundary index arrays or read in from file
578      !------------------------------------------------------------               
579      ! 1. Read global index arrays from boundary coordinates file.
580      DO ib_bdy = 1, nb_bdy
581         !
582         IF( ln_coords_file(ib_bdy) ) THEN
583            !
584            CALL iom_open( cn_coords_file(ib_bdy), inum )
585            DO igrd = 1, jpbgrd
586               CALL iom_get( inum, jpdom_unknown, 'nbi'//cgrid(igrd), dta_global(1:nblendta(igrd,ib_bdy),:,1) )
587               DO ii = 1,nblendta(igrd,ib_bdy)
588                  nbidta(ii,igrd,ib_bdy) = INT( dta_global(ii,1,1) )
589               END DO
590               CALL iom_get( inum, jpdom_unknown, 'nbj'//cgrid(igrd), dta_global(1:nblendta(igrd,ib_bdy),:,1) )
591               DO ii = 1,nblendta(igrd,ib_bdy)
592                  nbjdta(ii,igrd,ib_bdy) = INT( dta_global(ii,1,1) )
593               END DO
594               CALL iom_get( inum, jpdom_unknown, 'nbr'//cgrid(igrd), dta_global(1:nblendta(igrd,ib_bdy),:,1) )
595               DO ii = 1,nblendta(igrd,ib_bdy)
596                  nbrdta(ii,igrd,ib_bdy) = INT( dta_global(ii,1,1) )
597               END DO
598               !
599               ibr_max = MAXVAL( nbrdta(:,igrd,ib_bdy) )
600               IF(lwp) WRITE(numout,*)
601               IF(lwp) WRITE(numout,*) ' Maximum rimwidth in file is ', ibr_max
602               IF(lwp) WRITE(numout,*) ' nn_rimwidth from namelist is ', nn_rimwidth(ib_bdy)
603               IF (ibr_max < nn_rimwidth(ib_bdy))   &
604                     CALL ctl_stop( 'nn_rimwidth is larger than maximum rimwidth in file',cn_coords_file(ib_bdy) )
605            END DO
606            CALL iom_close( inum )
607            !
608         ENDIF 
609         !
610      END DO     
611   
612      ! 2. Now fill indices corresponding to straight open boundary arrays:
613      ! East
614      !-----
615      DO iseg = 1, nbdysege
616         ib_bdy = npckge(iseg)
617         !
618         ! ------------ T points -------------
619         igrd=1
620         icount=0
621         DO ir = 1, nn_rimwidth(ib_bdy)
622            DO ij = jpjedt(iseg), jpjeft(iseg)
623               icount = icount + 1
624               nbidta(icount, igrd, ib_bdy) = jpieob(iseg) + 2 - ir
625               nbjdta(icount, igrd, ib_bdy) = ij
626               nbrdta(icount, igrd, ib_bdy) = ir
627            ENDDO
628         ENDDO
629         !
630         ! ------------ U points -------------
631         igrd=2
632         icount=0
633         DO ir = 1, nn_rimwidth(ib_bdy)
634            DO ij = jpjedt(iseg), jpjeft(iseg)
635               icount = icount + 1
636               nbidta(icount, igrd, ib_bdy) = jpieob(iseg) + 1 - ir
637               nbjdta(icount, igrd, ib_bdy) = ij
638               nbrdta(icount, igrd, ib_bdy) = ir
639            ENDDO
640         ENDDO
641         !
642         ! ------------ V points -------------
643         igrd=3
644         icount=0
645         DO ir = 1, nn_rimwidth(ib_bdy)
646!            DO ij = jpjedt(iseg), jpjeft(iseg) - 1
647            DO ij = jpjedt(iseg), jpjeft(iseg)
648               icount = icount + 1
649               nbidta(icount, igrd, ib_bdy) = jpieob(iseg) + 2 - ir
650               nbjdta(icount, igrd, ib_bdy) = ij
651               nbrdta(icount, igrd, ib_bdy) = ir
652            ENDDO
653            nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
654            nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
655         ENDDO
656      ENDDO
657      !
658      ! West
659      !-----
660      DO iseg = 1, nbdysegw
661         ib_bdy = npckgw(iseg)
662         !
663         ! ------------ T points -------------
664         igrd=1
665         icount=0
666         DO ir = 1, nn_rimwidth(ib_bdy)
667            DO ij = jpjwdt(iseg), jpjwft(iseg)
668               icount = icount + 1
669               nbidta(icount, igrd, ib_bdy) = jpiwob(iseg) + ir - 1
670               nbjdta(icount, igrd, ib_bdy) = ij
671               nbrdta(icount, igrd, ib_bdy) = ir
672            ENDDO
673         ENDDO
674         !
675         ! ------------ U points -------------
676         igrd=2
677         icount=0
678         DO ir = 1, nn_rimwidth(ib_bdy)
679            DO ij = jpjwdt(iseg), jpjwft(iseg)
680               icount = icount + 1
681               nbidta(icount, igrd, ib_bdy) = jpiwob(iseg) + ir - 1
682               nbjdta(icount, igrd, ib_bdy) = ij
683               nbrdta(icount, igrd, ib_bdy) = ir
684            ENDDO
685         ENDDO
686         !
687         ! ------------ V points -------------
688         igrd=3
689         icount=0
690         DO ir = 1, nn_rimwidth(ib_bdy)
691!            DO ij = jpjwdt(iseg), jpjwft(iseg) - 1
692            DO ij = jpjwdt(iseg), jpjwft(iseg)
693               icount = icount + 1
694               nbidta(icount, igrd, ib_bdy) = jpiwob(iseg) + ir - 1
695               nbjdta(icount, igrd, ib_bdy) = ij
696               nbrdta(icount, igrd, ib_bdy) = ir
697            ENDDO
698            nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
699            nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
700         ENDDO
701      ENDDO
702      !
703      ! North
704      !-----
705      DO iseg = 1, nbdysegn
706         ib_bdy = npckgn(iseg)
707         !
708         ! ------------ T points -------------
709         igrd=1
710         icount=0
711         DO ir = 1, nn_rimwidth(ib_bdy)
712            DO ii = jpindt(iseg), jpinft(iseg)
713               icount = icount + 1
714               nbidta(icount, igrd, ib_bdy) = ii
715               nbjdta(icount, igrd, ib_bdy) = jpjnob(iseg) + 2 - ir 
716               nbrdta(icount, igrd, ib_bdy) = ir
717            ENDDO
718         ENDDO
719         !
720         ! ------------ U points -------------
721         igrd=2
722         icount=0
723         DO ir = 1, nn_rimwidth(ib_bdy)
724!            DO ii = jpindt(iseg), jpinft(iseg) - 1
725            DO ii = jpindt(iseg), jpinft(iseg)
726               icount = icount + 1
727               nbidta(icount, igrd, ib_bdy) = ii
728               nbjdta(icount, igrd, ib_bdy) = jpjnob(iseg) + 2 - ir
729               nbrdta(icount, igrd, ib_bdy) = ir
730            ENDDO
731            nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
732            nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
733         ENDDO
734         !
735         ! ------------ V points -------------
736         igrd=3
737         icount=0
738         DO ir = 1, nn_rimwidth(ib_bdy)
739            DO ii = jpindt(iseg), jpinft(iseg)
740               icount = icount + 1
741               nbidta(icount, igrd, ib_bdy) = ii
742               nbjdta(icount, igrd, ib_bdy) = jpjnob(iseg) + 1 - ir
743               nbrdta(icount, igrd, ib_bdy) = ir
744            ENDDO
745         ENDDO
746      ENDDO
747      !
748      ! South
749      !-----
750      DO iseg = 1, nbdysegs
751         ib_bdy = npckgs(iseg)
752         !
753         ! ------------ T points -------------
754         igrd=1
755         icount=0
756         DO ir = 1, nn_rimwidth(ib_bdy)
757            DO ii = jpisdt(iseg), jpisft(iseg)
758               icount = icount + 1
759               nbidta(icount, igrd, ib_bdy) = ii
760               nbjdta(icount, igrd, ib_bdy) = jpjsob(iseg) + ir - 1
761               nbrdta(icount, igrd, ib_bdy) = ir
762            ENDDO
763         ENDDO
764         !
765         ! ------------ U points -------------
766         igrd=2
767         icount=0
768         DO ir = 1, nn_rimwidth(ib_bdy)
769!            DO ii = jpisdt(iseg), jpisft(iseg) - 1
770            DO ii = jpisdt(iseg), jpisft(iseg)
771               icount = icount + 1
772               nbidta(icount, igrd, ib_bdy) = ii
773               nbjdta(icount, igrd, ib_bdy) = jpjsob(iseg) + ir - 1
774               nbrdta(icount, igrd, ib_bdy) = ir
775            ENDDO
776            nbidta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
777            nbjdta(icount, igrd, ib_bdy) = -ib_bdy ! Discount this point
778         ENDDO
779         !
780         ! ------------ V points -------------
781         igrd=3
782         icount=0
783         DO ir = 1, nn_rimwidth(ib_bdy)
784            DO ii = jpisdt(iseg), jpisft(iseg)
785               icount = icount + 1
786               nbidta(icount, igrd, ib_bdy) = ii
787               nbjdta(icount, igrd, ib_bdy) = jpjsob(iseg) + ir - 1
788               nbrdta(icount, igrd, ib_bdy) = ir
789            ENDDO
790         ENDDO
791      ENDDO
792
793      !  Deal with duplicated points
794      !-----------------------------
795      ! We assign negative indices to duplicated points (to remove them from bdy points to be updated)
796      ! if their distance to the bdy is greater than the other
797      ! If their distance are the same, just keep only one to avoid updating a point twice
798      DO igrd = 1, jpbgrd
799         DO ib_bdy1 = 1, nb_bdy
800            DO ib_bdy2 = 1, nb_bdy
801               IF (ib_bdy1/=ib_bdy2) THEN
802                  DO ib1 = 1, nblendta(igrd,ib_bdy1)
803                     DO ib2 = 1, nblendta(igrd,ib_bdy2)
804                        IF ((nbidta(ib1, igrd, ib_bdy1)==nbidta(ib2, igrd, ib_bdy2)).AND. &
805                        &   (nbjdta(ib1, igrd, ib_bdy1)==nbjdta(ib2, igrd, ib_bdy2))) THEN
806!                           IF ((lwp).AND.(igrd==1)) WRITE(numout,*) ' found coincident point ji, jj:', &
807!                                                       &              nbidta(ib1, igrd, ib_bdy1),      &
808!                                                       &              nbjdta(ib2, igrd, ib_bdy2)
809                           ! keep only points with the lowest distance to boundary:
810                           IF (nbrdta(ib1, igrd, ib_bdy1)<nbrdta(ib2, igrd, ib_bdy2)) THEN
811                             nbidta(ib2, igrd, ib_bdy2) =-ib_bdy2
812                             nbjdta(ib2, igrd, ib_bdy2) =-ib_bdy2
813                           ELSEIF (nbrdta(ib1, igrd, ib_bdy1)>nbrdta(ib2, igrd, ib_bdy2)) THEN
814                             nbidta(ib1, igrd, ib_bdy1) =-ib_bdy1
815                             nbjdta(ib1, igrd, ib_bdy1) =-ib_bdy1
816                           ! Arbitrary choice if distances are the same:
817                           ELSE
818                             nbidta(ib1, igrd, ib_bdy1) =-ib_bdy1
819                             nbjdta(ib1, igrd, ib_bdy1) =-ib_bdy1
820                           ENDIF
821                        END IF
822                     END DO
823                  END DO
824               ENDIF
825            END DO
826         END DO
827      END DO
828
829      ! Work out dimensions of boundary data on each processor
830      ! ------------------------------------------------------
831
832      ! Rather assume that boundary data indices are given on global domain
833      ! TO BE DISCUSSED ?
834!      iw = mig(1) + 1            ! if monotasking and no zoom, iw=2
835!      ie = mig(1) + nlci-1 - 1   ! if monotasking and no zoom, ie=jpim1
836!      is = mjg(1) + 1            ! if monotasking and no zoom, is=2
837!      in = mjg(1) + nlcj-1 - 1   ! if monotasking and no zoom, in=jpjm1     
838      iwe = mig(1) - 1 + 2         ! if monotasking and no zoom, iw=2
839      ies = mig(1) + nlci-1 - 1  ! if monotasking and no zoom, ie=jpim1
840      iso = mjg(1) - 1 + 2         ! if monotasking and no zoom, is=2
841      ino = mjg(1) + nlcj-1 - 1  ! if monotasking and no zoom, in=jpjm1
842
843      ALLOCATE( nbondi_bdy(nb_bdy))
844      ALLOCATE( nbondj_bdy(nb_bdy))
845      nbondi_bdy(:)=2
846      nbondj_bdy(:)=2
847      ALLOCATE( nbondi_bdy_b(nb_bdy))
848      ALLOCATE( nbondj_bdy_b(nb_bdy))
849      nbondi_bdy_b(:)=2
850      nbondj_bdy_b(:)=2
851
852      ! Work out dimensions of boundary data on each neighbour process
853      IF(nbondi == 0) THEN
854         iw_b(1) = 1 + nimppt(nowe+1)
855         ie_b(1) = 1 + nimppt(nowe+1)+nlcit(nowe+1)-3
856         is_b(1) = 1 + njmppt(nowe+1)
857         in_b(1) = 1 + njmppt(nowe+1)+nlcjt(nowe+1)-3
858
859         iw_b(2) = 1 + nimppt(noea+1)
860         ie_b(2) = 1 + nimppt(noea+1)+nlcit(noea+1)-3
861         is_b(2) = 1 + njmppt(noea+1)
862         in_b(2) = 1 + njmppt(noea+1)+nlcjt(noea+1)-3
863      ELSEIF(nbondi == 1) THEN
864         iw_b(1) = 1 + nimppt(nowe+1)
865         ie_b(1) = 1 + nimppt(nowe+1)+nlcit(nowe+1)-3
866         is_b(1) = 1 + njmppt(nowe+1)
867         in_b(1) = 1 + njmppt(nowe+1)+nlcjt(nowe+1)-3
868      ELSEIF(nbondi == -1) THEN
869         iw_b(2) = 1 + nimppt(noea+1)
870         ie_b(2) = 1 + nimppt(noea+1)+nlcit(noea+1)-3
871         is_b(2) = 1 + njmppt(noea+1)
872         in_b(2) = 1 + njmppt(noea+1)+nlcjt(noea+1)-3
873      ENDIF
874
875      IF(nbondj == 0) THEN
876         iw_b(3) = 1 + nimppt(noso+1)
877         ie_b(3) = 1 + nimppt(noso+1)+nlcit(noso+1)-3
878         is_b(3) = 1 + njmppt(noso+1)
879         in_b(3) = 1 + njmppt(noso+1)+nlcjt(noso+1)-3
880
881         iw_b(4) = 1 + nimppt(nono+1)
882         ie_b(4) = 1 + nimppt(nono+1)+nlcit(nono+1)-3
883         is_b(4) = 1 + njmppt(nono+1)
884         in_b(4) = 1 + njmppt(nono+1)+nlcjt(nono+1)-3
885      ELSEIF(nbondj == 1) THEN
886         iw_b(3) = 1 + nimppt(noso+1)
887         ie_b(3) = 1 + nimppt(noso+1)+nlcit(noso+1)-3
888         is_b(3) = 1 + njmppt(noso+1)
889         in_b(3) = 1 + njmppt(noso+1)+nlcjt(noso+1)-3
890      ELSEIF(nbondj == -1) THEN
891         iw_b(4) = 1 + nimppt(nono+1)
892         ie_b(4) = 1 + nimppt(nono+1)+nlcit(nono+1)-3
893         is_b(4) = 1 + njmppt(nono+1)
894         in_b(4) = 1 + njmppt(nono+1)+nlcjt(nono+1)-3
895      ENDIF
896
897      DO ib_bdy = 1, nb_bdy
898         DO igrd = 1, jpbgrd
899            icount  = 0
900            icountr = 0
901            idx_bdy(ib_bdy)%nblen(igrd)    = 0
902            idx_bdy(ib_bdy)%nblenrim(igrd) = 0
903            DO ib = 1, nblendta(igrd,ib_bdy)
904               ! check that data is in correct order in file
905               ibm1 = MAX(1,ib-1)
906               IF(lwp) THEN         ! Since all procs read global data only need to do this check on one proc...
907                  IF( nbrdta(ib,igrd,ib_bdy) < nbrdta(ibm1,igrd,ib_bdy) ) THEN
908                     CALL ctl_stop('bdy_segs : ERROR : boundary data in file must be defined ', &
909                          &        ' in order of distance from edge nbr A utility for re-ordering ', &
910                          &        ' boundary coordinates and data files exists in the TOOLS/OBC directory')
911                  ENDIF   
912               ENDIF
913               ! check if point is in local domain
914               IF(  nbidta(ib,igrd,ib_bdy) >= iwe .AND. nbidta(ib,igrd,ib_bdy) <= ies .AND.   &
915                  & nbjdta(ib,igrd,ib_bdy) >= iso .AND. nbjdta(ib,igrd,ib_bdy) <= ino      ) THEN
916                  !
917                  icount = icount  + 1
918                  !
919                  IF( nbrdta(ib,igrd,ib_bdy) == 1 )   icountr = icountr+1
920               ENDIF
921            ENDDO
922            idx_bdy(ib_bdy)%nblenrim(igrd) = icountr !: length of rim boundary data on each proc
923            idx_bdy(ib_bdy)%nblen   (igrd) = icount  !: length of boundary data on each proc       
924         ENDDO  ! igrd
925
926         ! Allocate index arrays for this boundary set
927         !--------------------------------------------
928         ilen1 = MAXVAL( idx_bdy(ib_bdy)%nblen(:) )
929         ALLOCATE( idx_bdy(ib_bdy)%nbi   (ilen1,jpbgrd) )
930         ALLOCATE( idx_bdy(ib_bdy)%nbj   (ilen1,jpbgrd) )
931         ALLOCATE( idx_bdy(ib_bdy)%nbr   (ilen1,jpbgrd) )
932         ALLOCATE( idx_bdy(ib_bdy)%nbd   (ilen1,jpbgrd) )
933         ALLOCATE( idx_bdy(ib_bdy)%nbdout(ilen1,jpbgrd) )
934         ALLOCATE( idx_bdy(ib_bdy)%nbmap (ilen1,jpbgrd) )
935         ALLOCATE( idx_bdy(ib_bdy)%nbw   (ilen1,jpbgrd) )
936         ALLOCATE( idx_bdy(ib_bdy)%flagu (ilen1,jpbgrd) )
937         ALLOCATE( idx_bdy(ib_bdy)%flagv (ilen1,jpbgrd) )
938
939         ! Dispatch mapping indices and discrete distances on each processor
940         ! -----------------------------------------------------------------
941
942         com_east  = 0
943         com_west  = 0
944         com_south = 0
945         com_north = 0
946
947         com_east_b  = 0
948         com_west_b  = 0
949         com_south_b = 0
950         com_north_b = 0
951
952         DO igrd = 1, jpbgrd
953            icount  = 0
954            ! Loop on rimwidth to ensure outermost points come first in the local arrays.
955            DO ir=1, nn_rimwidth(ib_bdy)
956               DO ib = 1, nblendta(igrd,ib_bdy)
957                  ! check if point is in local domain and equals ir
958                  IF(  nbidta(ib,igrd,ib_bdy) >= iwe .AND. nbidta(ib,igrd,ib_bdy) <= ies .AND.   &
959                     & nbjdta(ib,igrd,ib_bdy) >= iso .AND. nbjdta(ib,igrd,ib_bdy) <= ino .AND.   &
960                     & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
961                     !
962                     icount = icount  + 1
963
964                     ! Rather assume that boundary data indices are given on global domain
965                     ! TO BE DISCUSSED ?
966!                     idx_bdy(ib_bdy)%nbi(icount,igrd)   = nbidta(ib,igrd,ib_bdy)- mig(1)+1
967!                     idx_bdy(ib_bdy)%nbj(icount,igrd)   = nbjdta(ib,igrd,ib_bdy)- mjg(1)+1
968                     idx_bdy(ib_bdy)%nbi(icount,igrd)   = nbidta(ib,igrd,ib_bdy)- mig(1)+1
969                     idx_bdy(ib_bdy)%nbj(icount,igrd)   = nbjdta(ib,igrd,ib_bdy)- mjg(1)+1
970                     ! check if point has to be sent
971                     ii = idx_bdy(ib_bdy)%nbi(icount,igrd)
972                     ij = idx_bdy(ib_bdy)%nbj(icount,igrd)
973                     if((com_east .ne. 1) .and. (ii == (nlci-1)) .and. (nbondi .le. 0)) then
974                        com_east = 1
975                     elseif((com_west .ne. 1) .and. (ii == 2) .and. (nbondi .ge. 0) .and. (nbondi .ne. 2)) then
976                        com_west = 1
977                     endif
978                     if((com_south .ne. 1) .and. (ij == 2) .and. (nbondj .ge. 0) .and. (nbondj .ne. 2)) then
979                        com_south = 1
980                     elseif((com_north .ne. 1) .and. (ij == (nlcj-1)) .and. (nbondj .le. 0)) then
981                        com_north = 1
982                     endif
983                     idx_bdy(ib_bdy)%nbr(icount,igrd)   = nbrdta(ib,igrd,ib_bdy)
984                     idx_bdy(ib_bdy)%nbmap(icount,igrd) = ib
985                  ENDIF
986                  ! check if point has to be received from a neighbour
987                  IF(nbondi == 0) THEN
988                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(1) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(1) .AND.   &
989                       & nbjdta(ib,igrd,ib_bdy) >= is_b(1) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(1) .AND.   &
990                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
991                       ii = nbidta(ib,igrd,ib_bdy)- iw_b(1)+2
992                       if((com_west_b .ne. 1) .and. (ii == (nlcit(nowe+1)-1))) then
993                          ij = nbjdta(ib,igrd,ib_bdy) - is_b(1)+2
994                          if((ij == 2) .and. (nbondj == 0 .or. nbondj == 1)) then
995                            com_south = 1
996                          elseif((ij == nlcjt(nowe+1)-1) .and. (nbondj == 0 .or. nbondj == -1)) then
997                            com_north = 1
998                          endif
999                          com_west_b = 1
1000                       endif
1001                     ENDIF
1002                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(2) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(2) .AND.   &
1003                       & nbjdta(ib,igrd,ib_bdy) >= is_b(2) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(2) .AND.   &
1004                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1005                       ii = nbidta(ib,igrd,ib_bdy)- iw_b(2)+2
1006                       if((com_east_b .ne. 1) .and. (ii == 2)) then
1007                          ij = nbjdta(ib,igrd,ib_bdy) - is_b(2)+2
1008                          if((ij == 2) .and. (nbondj == 0 .or. nbondj == 1)) then
1009                            com_south = 1
1010                          elseif((ij == nlcjt(noea+1)-1) .and. (nbondj == 0 .or. nbondj == -1)) then
1011                            com_north = 1
1012                          endif
1013                          com_east_b = 1
1014                       endif
1015                     ENDIF
1016                  ELSEIF(nbondi == 1) THEN
1017                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(1) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(1) .AND.   &
1018                       & nbjdta(ib,igrd,ib_bdy) >= is_b(1) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(1) .AND.   &
1019                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1020                       ii = nbidta(ib,igrd,ib_bdy)- iw_b(1)+2
1021                       if((com_west_b .ne. 1) .and. (ii == (nlcit(nowe+1)-1))) then
1022                          ij = nbjdta(ib,igrd,ib_bdy) - is_b(1)+2
1023                          if((ij == 2) .and. (nbondj == 0 .or. nbondj == 1)) then
1024                            com_south = 1
1025                          elseif((ij == nlcjt(nowe+1)-1) .and. (nbondj == 0 .or. nbondj == -1)) then
1026                            com_north = 1
1027                          endif
1028                          com_west_b = 1
1029                       endif
1030                     ENDIF
1031                  ELSEIF(nbondi == -1) THEN
1032                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(2) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(2) .AND.   &
1033                       & nbjdta(ib,igrd,ib_bdy) >= is_b(2) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(2) .AND.   &
1034                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1035                       ii = nbidta(ib,igrd,ib_bdy)- iw_b(2)+2
1036                       if((com_east_b .ne. 1) .and. (ii == 2)) then
1037                          ij = nbjdta(ib,igrd,ib_bdy) - is_b(2)+2
1038                          if((ij == 2) .and. (nbondj == 0 .or. nbondj == 1)) then
1039                            com_south = 1
1040                          elseif((ij == nlcjt(noea+1)-1) .and. (nbondj == 0 .or. nbondj == -1)) then
1041                            com_north = 1
1042                          endif
1043                          com_east_b = 1
1044                       endif
1045                     ENDIF
1046                  ENDIF
1047                  IF(nbondj == 0) THEN
1048                     IF(com_north_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(4)-1  &
1049                       & .OR. nbidta(ib,igrd,ib_bdy) == ie_b(4)+1) .AND. &
1050                       & nbjdta(ib,igrd,ib_bdy) == is_b(4) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN
1051                       com_north_b = 1 
1052                     ENDIF
1053                     IF(com_south_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(3)-1  &
1054                       &.OR. nbidta(ib,igrd,ib_bdy) == ie_b(3)+1) .AND. &
1055                       & nbjdta(ib,igrd,ib_bdy) == in_b(3) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN
1056                       com_south_b = 1 
1057                     ENDIF
1058                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(3) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(3) .AND.   &
1059                       & nbjdta(ib,igrd,ib_bdy) >= is_b(3) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(3) .AND.   &
1060                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1061                       ij = nbjdta(ib,igrd,ib_bdy)- is_b(3)+2
1062                       if((com_south_b .ne. 1) .and. (ij == (nlcjt(noso+1)-1))) then
1063                          com_south_b = 1
1064                       endif
1065                     ENDIF
1066                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(4) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(4) .AND.   &
1067                       & nbjdta(ib,igrd,ib_bdy) >= is_b(4) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(4) .AND.   &
1068                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1069                       ij = nbjdta(ib,igrd,ib_bdy)- is_b(4)+2
1070                       if((com_north_b .ne. 1) .and. (ij == 2)) then
1071                          com_north_b = 1
1072                       endif
1073                     ENDIF
1074                  ELSEIF(nbondj == 1) THEN
1075                     IF( com_south_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(3)-1 .OR. &
1076                       & nbidta(ib,igrd,ib_bdy) == ie_b(3)+1) .AND. &
1077                       & nbjdta(ib,igrd,ib_bdy) == in_b(3) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN
1078                       com_south_b = 1 
1079                     ENDIF
1080                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(3) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(3) .AND.   &
1081                       & nbjdta(ib,igrd,ib_bdy) >= is_b(3) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(3) .AND.   &
1082                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1083                       ij = nbjdta(ib,igrd,ib_bdy)- is_b(3)+2
1084                       if((com_south_b .ne. 1) .and. (ij == (nlcjt(noso+1)-1))) then
1085                          com_south_b = 1
1086                       endif
1087                     ENDIF
1088                  ELSEIF(nbondj == -1) THEN
1089                     IF(com_north_b .ne. 1 .AND. (nbidta(ib,igrd,ib_bdy) == iw_b(4)-1  &
1090                       & .OR. nbidta(ib,igrd,ib_bdy) == ie_b(4)+1) .AND. &
1091                       & nbjdta(ib,igrd,ib_bdy) == is_b(4) .AND. nbrdta(ib,igrd,ib_bdy) == ir) THEN
1092                       com_north_b = 1 
1093                     ENDIF
1094                     IF( nbidta(ib,igrd,ib_bdy) >= iw_b(4) .AND. nbidta(ib,igrd,ib_bdy) <= ie_b(4) .AND.   &
1095                       & nbjdta(ib,igrd,ib_bdy) >= is_b(4) .AND. nbjdta(ib,igrd,ib_bdy) <= in_b(4) .AND.   &
1096                       & nbrdta(ib,igrd,ib_bdy) == ir  ) THEN
1097                       ij = nbjdta(ib,igrd,ib_bdy)- is_b(4)+2
1098                       if((com_north_b .ne. 1) .and. (ij == 2)) then
1099                          com_north_b = 1
1100                       endif
1101                     ENDIF
1102                  ENDIF
1103               ENDDO
1104            ENDDO
1105         ENDDO 
1106
1107         ! definition of the i- and j- direction local boundaries arrays used for sending the boundaries
1108         IF(     (com_east  == 1) .and. (com_west  == 1) ) THEN   ;   nbondi_bdy(ib_bdy) =  0
1109         ELSEIF( (com_east  == 1) .and. (com_west  == 0) ) THEN   ;   nbondi_bdy(ib_bdy) = -1
1110         ELSEIF( (com_east  == 0) .and. (com_west  == 1) ) THEN   ;   nbondi_bdy(ib_bdy) =  1
1111         ENDIF
1112         IF(     (com_north == 1) .and. (com_south == 1) ) THEN   ;   nbondj_bdy(ib_bdy) =  0
1113         ELSEIF( (com_north == 1) .and. (com_south == 0) ) THEN   ;   nbondj_bdy(ib_bdy) = -1
1114         ELSEIF( (com_north == 0) .and. (com_south == 1) ) THEN   ;   nbondj_bdy(ib_bdy) =  1
1115         ENDIF
1116
1117         ! definition of the i- and j- direction local boundaries arrays used for receiving the boundaries
1118         IF(     (com_east_b  == 1) .and. (com_west_b  == 1) ) THEN   ;   nbondi_bdy_b(ib_bdy) =  0
1119         ELSEIF( (com_east_b  == 1) .and. (com_west_b  == 0) ) THEN   ;   nbondi_bdy_b(ib_bdy) = -1
1120         ELSEIF( (com_east_b  == 0) .and. (com_west_b  == 1) ) THEN   ;   nbondi_bdy_b(ib_bdy) =  1
1121         ENDIF
1122         IF(     (com_north_b == 1) .and. (com_south_b == 1) ) THEN   ;   nbondj_bdy_b(ib_bdy) =  0
1123         ELSEIF( (com_north_b == 1) .and. (com_south_b == 0) ) THEN   ;   nbondj_bdy_b(ib_bdy) = -1
1124         ELSEIF( (com_north_b == 0) .and. (com_south_b == 1) ) THEN   ;   nbondj_bdy_b(ib_bdy) =  1
1125         ENDIF
1126
1127         ! Compute rim weights for FRS scheme
1128         ! ----------------------------------
1129         DO igrd = 1, jpbgrd
1130            DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd)
1131               nbr => idx_bdy(ib_bdy)%nbr(ib,igrd)
1132               idx_bdy(ib_bdy)%nbw(ib,igrd) = 1.- TANH( REAL( nbr - 1 ) *0.5 )      ! tanh formulation
1133!               idx_bdy(ib_bdy)%nbw(ib,igrd) = (REAL(nn_rimwidth(ib_bdy)+1-nbr)/REAL(nn_rimwidth(ib_bdy)))**2.  ! quadratic
1134!               idx_bdy(ib_bdy)%nbw(ib,igrd) =  REAL(nn_rimwidth(ib_bdy)+1-nbr)/REAL(nn_rimwidth(ib_bdy))       ! linear
1135            END DO
1136         END DO 
1137
1138         ! Compute damping coefficients
1139         ! ----------------------------
1140         DO igrd = 1, jpbgrd
1141            DO ib = 1, idx_bdy(ib_bdy)%nblen(igrd)
1142               nbr => idx_bdy(ib_bdy)%nbr(ib,igrd)
1143               idx_bdy(ib_bdy)%nbd(ib,igrd) = 1. / ( rn_time_dmp(ib_bdy) * rday ) & 
1144               & *(REAL(nn_rimwidth(ib_bdy)+1-nbr)/REAL(nn_rimwidth(ib_bdy)))**2.   ! quadratic
1145               idx_bdy(ib_bdy)%nbdout(ib,igrd) = 1. / ( rn_time_dmp_out(ib_bdy) * rday ) & 
1146               & *(REAL(nn_rimwidth(ib_bdy)+1-nbr)/REAL(nn_rimwidth(ib_bdy)))**2.   ! quadratic
1147            END DO
1148         END DO
1149
1150      ENDDO
1151
1152      ! ------------------------------------------------------
1153      ! Initialise masks and find normal/tangential directions
1154      ! ------------------------------------------------------
1155
1156      ! Read global 2D mask at T-points: bdytmask
1157      ! -----------------------------------------
1158      ! bdytmask = 1  on the computational domain AND on open boundaries
1159      !          = 0  elsewhere   
1160 
1161      bdytmask(:,:) = ssmask(:,:)
1162
1163      IF( ln_mask_file ) THEN
1164         CALL iom_open( cn_mask_file, inum )
1165         CALL iom_get ( inum, jpdom_data, 'bdy_msk', bdytmask(:,:) )
1166         CALL iom_close( inum )
1167
1168         ! Derive mask on U and V grid from mask on T grid
1169         bdyumask(:,:) = 0._wp
1170         bdyvmask(:,:) = 0._wp
1171         DO ij=1, jpjm1
1172            DO ii=1, jpim1
1173               bdyumask(ii,ij) = bdytmask(ii,ij) * bdytmask(ii+1, ij )
1174               bdyvmask(ii,ij) = bdytmask(ii,ij) * bdytmask(ii  ,ij+1) 
1175            END DO
1176         END DO
1177         CALL lbc_lnk( bdyumask(:,:), 'U', 1. )   ;   CALL lbc_lnk( bdyvmask(:,:), 'V', 1. )      ! Lateral boundary cond.
1178
1179      ENDIF ! ln_mask_file=.TRUE.
1180     
1181      IF( .NOT.ln_mask_file ) THEN
1182         ! If .not. ln_mask_file then we need to derive mask on U and V grid from mask on T grid here.
1183         bdyumask(:,:) = 0._wp
1184         bdyvmask(:,:) = 0._wp
1185         DO ij = 1, jpjm1
1186            DO ii = 1, jpim1
1187               bdyumask(ii,ij) = bdytmask(ii,ij) * bdytmask(ii+1, ij )
1188               bdyvmask(ii,ij) = bdytmask(ii,ij) * bdytmask(ii  ,ij+1) 
1189            END DO
1190         END DO
1191         CALL lbc_lnk( bdyumask(:,:), 'U', 1. )   ;   CALL lbc_lnk( bdyvmask(:,:), 'V', 1. )      ! Lateral boundary cond.
1192      ENDIF
1193
1194      ! bdy masks are now set to zero on boundary points:
1195      !
1196      igrd = 1
1197      DO ib_bdy = 1, nb_bdy
1198        DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd)     
1199          bdytmask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0._wp
1200        END DO
1201      END DO
1202      !
1203      igrd = 2
1204      DO ib_bdy = 1, nb_bdy
1205        DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd)
1206          bdyumask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0._wp
1207        END DO
1208      END DO
1209      !
1210      igrd = 3
1211      DO ib_bdy = 1, nb_bdy
1212        DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd)
1213          bdyvmask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0._wp
1214        ENDDO
1215      ENDDO
1216
1217      ! For the flagu/flagv calculation below we require a version of fmask without
1218      ! the land boundary condition (shlat) included:
1219      CALL wrk_alloc(jpi,jpj,  zfmask ) 
1220      DO ij = 2, jpjm1
1221         DO ii = 2, jpim1
1222            zfmask(ii,ij) = tmask(ii,ij  ,1) * tmask(ii+1,ij  ,1)   &
1223           &              * tmask(ii,ij+1,1) * tmask(ii+1,ij+1,1)
1224         END DO     
1225      END DO
1226
1227      ! Lateral boundary conditions
1228      CALL lbc_lnk( zfmask       , 'F', 1. )
1229      CALL lbc_lnk( fmask        , 'F', 1. )   ;   CALL lbc_lnk( bdytmask(:,:), 'T', 1. )
1230      CALL lbc_lnk( bdyumask(:,:), 'U', 1. )   ;   CALL lbc_lnk( bdyvmask(:,:), 'V', 1. )
1231
1232      DO ib_bdy = 1, nb_bdy       ! Indices and directions of rim velocity components
1233
1234         idx_bdy(ib_bdy)%flagu(:,:) = 0._wp
1235         idx_bdy(ib_bdy)%flagv(:,:) = 0._wp
1236         icount = 0 
1237
1238         ! Calculate relationship of U direction to the local orientation of the boundary
1239         ! flagu = -1 : u component is normal to the dynamical boundary and its direction is outward
1240         ! flagu =  0 : u is tangential
1241         ! flagu =  1 : u is normal to the boundary and is direction is inward
1242 
1243         DO igrd = 1,jpbgrd 
1244            SELECT CASE( igrd )
1245               CASE( 1 )   ;   pmask => umask   (:,:,1)   ;   i_offset = 0
1246               CASE( 2 )   ;   pmask => bdytmask(:,:)     ;   i_offset = 1
1247               CASE( 3 )   ;   pmask => zfmask  (:,:)     ;   i_offset = 0
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               zefl = pmask(nbi+i_offset-1,nbj)
1254               zwfl = pmask(nbi+i_offset,nbj)
1255               ! This error check only works if you are using the bdyXmask arrays
1256               IF( i_offset == 1 .and. zefl + zwfl == 2 ) THEN
1257                  icount = icount + 1
1258                  IF(lwp) WRITE(numout,*) 'Problem with igrd = ',igrd,' at (global) nbi, nbj : ',mig(nbi),mjg(nbj)
1259               ELSE
1260                  idx_bdy(ib_bdy)%flagu(ib,igrd) = -zefl + zwfl
1261               ENDIF
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 (flagu 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         ! Calculate relationship of V direction to the local orientation of the boundary
1274         ! flagv = -1 : v component is normal to the dynamical boundary but its direction is outward
1275         ! flagv =  0 : v is tangential
1276         ! flagv =  1 : v is normal to the boundary and is direction is inward
1277
1278         DO igrd = 1, jpbgrd 
1279            SELECT CASE( igrd )
1280               CASE( 1 )   ;   pmask => vmask (:,:,1)   ;   j_offset = 0
1281               CASE( 2 )   ;   pmask => zfmask(:,:)     ;   j_offset = 0
1282               CASE( 3 )   ;   pmask => bdytmask        ;   j_offset = 1
1283            END SELECT
1284            icount = 0
1285            DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd) 
1286               nbi => idx_bdy(ib_bdy)%nbi(ib,igrd)
1287               nbj => idx_bdy(ib_bdy)%nbj(ib,igrd)
1288               znfl = pmask(nbi,nbj+j_offset-1)
1289               zsfl = pmask(nbi,nbj+j_offset  )
1290               ! This error check only works if you are using the bdyXmask arrays
1291               IF( j_offset == 1 .and. znfl + zsfl == 2 ) THEN
1292                  IF(lwp) WRITE(numout,*) 'Problem with igrd = ',igrd,' at (global) nbi, nbj : ',mig(nbi),mjg(nbj)
1293                  icount = icount + 1
1294               ELSE
1295                  idx_bdy(ib_bdy)%flagv(ib,igrd) = -znfl + zsfl
1296               END IF
1297            END DO
1298            IF( icount /= 0 ) THEN
1299               IF(lwp) WRITE(numout,*)
1300               IF(lwp) WRITE(numout,*) ' E R R O R : Some ',cgrid(igrd),' grid points,',   &
1301                  ' are not boundary points (flagv calculation). Check nbi, nbj, indices for boundary set ',ib_bdy
1302               IF(lwp) WRITE(numout,*) ' ========== '
1303               IF(lwp) WRITE(numout,*)
1304               nstop = nstop + 1
1305            ENDIF
1306         END DO
1307         !
1308      END DO
1309
1310      ! Compute total lateral surface for volume correction:
1311      ! ----------------------------------------------------
1312      ! JC: this must be done at each time step with non-linear free surface
1313      bdysurftot = 0._wp 
1314      IF( ln_vol ) THEN 
1315         igrd = 2      ! Lateral surface at U-points
1316         DO ib_bdy = 1, nb_bdy
1317            DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd)
1318               nbi => idx_bdy(ib_bdy)%nbi(ib,igrd)
1319               nbj => idx_bdy(ib_bdy)%nbj(ib,igrd)
1320               flagu => idx_bdy(ib_bdy)%flagu(ib,igrd)
1321               bdysurftot = bdysurftot + hu_n   (nbi  , nbj)                           &
1322                  &                    * e2u    (nbi  , nbj) * ABS( flagu ) &
1323                  &                    * tmask_i(nbi  , nbj)                           &
1324                  &                    * tmask_i(nbi+1, nbj)                   
1325            END DO
1326         END DO
1327
1328         igrd=3 ! Add lateral surface at V-points
1329         DO ib_bdy = 1, nb_bdy
1330            DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd)
1331               nbi => idx_bdy(ib_bdy)%nbi(ib,igrd)
1332               nbj => idx_bdy(ib_bdy)%nbj(ib,igrd)
1333               flagv => idx_bdy(ib_bdy)%flagv(ib,igrd)
1334               bdysurftot = bdysurftot + hv_n   (nbi, nbj  )                           &
1335                  &                    * e1v    (nbi, nbj  ) * ABS( flagv ) &
1336                  &                    * tmask_i(nbi, nbj  )                           &
1337                  &                    * tmask_i(nbi, nbj+1)
1338            END DO
1339         END DO
1340         !
1341         IF( lk_mpp )   CALL mpp_sum( bdysurftot )      ! sum over the global domain
1342      END IF   
1343      !
1344      ! Tidy up
1345      !--------
1346      IF( nb_bdy>0 )   DEALLOCATE( nbidta, nbjdta, nbrdta )
1347      !
1348      CALL wrk_dealloc(jpi,jpj,   zfmask ) 
1349      !
1350      IF( nn_timing == 1 )   CALL timing_stop('bdy_segs')
1351      !
1352   END SUBROUTINE bdy_segs
1353
1354   SUBROUTINE bdy_ctl_seg
1355      !!----------------------------------------------------------------------
1356      !!                 ***  ROUTINE bdy_ctl_seg  ***
1357      !!
1358      !! ** Purpose :   Check straight open boundary segments location
1359      !!
1360      !! ** Method  :   - Look for open boundary corners
1361      !!                - Check that segments start or end on land
1362      !!----------------------------------------------------------------------
1363      INTEGER  ::   ib, ib1, ib2, ji ,jj, itest 
1364      INTEGER, DIMENSION(jp_nseg,2) :: icorne, icornw, icornn, icorns 
1365      REAL(wp), DIMENSION(2) ::   ztestmask
1366      !!----------------------------------------------------------------------
1367      !
1368      IF (lwp) WRITE(numout,*) ' '
1369      IF (lwp) WRITE(numout,*) 'bdy_ctl_seg: Check analytical segments'
1370      IF (lwp) WRITE(numout,*) '~~~~~~~~~~~~'
1371      !
1372      IF(lwp) WRITE(numout,*) 'Number of east  segments     : ', nbdysege
1373      IF(lwp) WRITE(numout,*) 'Number of west  segments     : ', nbdysegw
1374      IF(lwp) WRITE(numout,*) 'Number of north segments     : ', nbdysegn
1375      IF(lwp) WRITE(numout,*) 'Number of south segments     : ', nbdysegs
1376      ! 1. Check bounds
1377      !----------------
1378      DO ib = 1, nbdysegn
1379         IF (lwp) WRITE(numout,*) '**check north seg bounds pckg: ', npckgn(ib)
1380         IF ((jpjnob(ib).ge.jpjglo-1).or.& 
1381            &(jpjnob(ib).le.1))        CALL ctl_stop( 'nbdyind out of domain' )
1382         IF (jpindt(ib).ge.jpinft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' )
1383         IF (jpindt(ib).le.1     )     CALL ctl_stop( 'Start index out of domain' )
1384         IF (jpinft(ib).ge.jpiglo)     CALL ctl_stop( 'End index out of domain' )
1385      END DO
1386      !
1387      DO ib = 1, nbdysegs
1388         IF (lwp) WRITE(numout,*) '**check south seg bounds pckg: ', npckgs(ib)
1389         IF ((jpjsob(ib).ge.jpjglo-1).or.& 
1390            &(jpjsob(ib).le.1))        CALL ctl_stop( 'nbdyind out of domain' )
1391         IF (jpisdt(ib).ge.jpisft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' )
1392         IF (jpisdt(ib).le.1     )     CALL ctl_stop( 'Start index out of domain' )
1393         IF (jpisft(ib).ge.jpiglo)     CALL ctl_stop( 'End index out of domain' )
1394      END DO
1395      !
1396      DO ib = 1, nbdysege
1397         IF (lwp) WRITE(numout,*) '**check east  seg bounds pckg: ', npckge(ib)
1398         IF ((jpieob(ib).ge.jpiglo-1).or.& 
1399            &(jpieob(ib).le.1))        CALL ctl_stop( 'nbdyind out of domain' )
1400         IF (jpjedt(ib).ge.jpjeft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' )
1401         IF (jpjedt(ib).le.1     )     CALL ctl_stop( 'Start index out of domain' )
1402         IF (jpjeft(ib).ge.jpjglo)     CALL ctl_stop( 'End index out of domain' )
1403      END DO
1404      !
1405      DO ib = 1, nbdysegw
1406         IF (lwp) WRITE(numout,*) '**check west  seg bounds pckg: ', npckgw(ib)
1407         IF ((jpiwob(ib).ge.jpiglo-1).or.& 
1408            &(jpiwob(ib).le.1))        CALL ctl_stop( 'nbdyind out of domain' )
1409         IF (jpjwdt(ib).ge.jpjwft(ib)) CALL ctl_stop( 'Bdy start index is greater than end index' )
1410         IF (jpjwdt(ib).le.1     )     CALL ctl_stop( 'Start index out of domain' )
1411         IF (jpjwft(ib).ge.jpjglo)     CALL ctl_stop( 'End index out of domain' )
1412      ENDDO
1413      !
1414      !     
1415      ! 2. Look for segment crossings
1416      !------------------------------
1417      IF (lwp) WRITE(numout,*) '**Look for segments corners  :'
1418      !
1419      itest = 0 ! corner number
1420      !
1421      ! flag to detect if start or end of open boundary belongs to a corner
1422      ! if not (=0), it must be on land.
1423      ! if a corner is detected, save bdy package number for further tests
1424      icorne(:,:)=0. ; icornw(:,:)=0. ; icornn(:,:)=0. ; icorns(:,:)=0.
1425      ! South/West crossings
1426      IF ((nbdysegw > 0).AND.(nbdysegs > 0)) THEN
1427         DO ib1 = 1, nbdysegw       
1428            DO ib2 = 1, nbdysegs
1429               IF (( jpisdt(ib2)<=jpiwob(ib1)).AND. &
1430                &  ( jpisft(ib2)>=jpiwob(ib1)).AND. &
1431                &  ( jpjwdt(ib1)<=jpjsob(ib2)).AND. &
1432                &  ( jpjwft(ib1)>=jpjsob(ib2))) THEN
1433                  IF ((jpjwdt(ib1)==jpjsob(ib2)).AND.(jpisdt(ib2)==jpiwob(ib1))) THEN 
1434                     ! We have a possible South-West corner                     
1435!                     WRITE(numout,*) ' Found a South-West corner at (i,j): ', jpisdt(ib2), jpjwdt(ib1)
1436!                     WRITE(numout,*) ' between segments: ', npckgw(ib1), npckgs(ib2)
1437                     icornw(ib1,1) = npckgs(ib2)
1438                     icorns(ib2,1) = npckgw(ib1)
1439                  ELSEIF ((jpisft(ib2)==jpiwob(ib1)).AND.(jpjwft(ib1)==jpjsob(ib2))) THEN
1440                     IF(lwp) WRITE(numout,*)
1441                     IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', &
1442                     &                                     jpisft(ib2), jpjwft(ib1)
1443                     IF(lwp) WRITE(numout,*) ' ==========  Not allowed yet'
1444                     IF(lwp) WRITE(numout,*) '             Crossing problem with West segment: ',npckgw(ib1), & 
1445                     &                                                    ' and South segment: ',npckgs(ib2)
1446                     IF(lwp) WRITE(numout,*)
1447                     nstop = nstop + 1
1448                  ELSE
1449                     IF(lwp) WRITE(numout,*)
1450                     IF(lwp) WRITE(numout,*) ' E R R O R : Check South and West Open boundary indices'
1451                     IF(lwp) WRITE(numout,*) ' ==========  Crossing problem with West segment: ',npckgw(ib1) , &
1452                     &                                                    ' and South segment: ',npckgs(ib2)
1453                     IF(lwp) WRITE(numout,*)
1454                     nstop = nstop+1
1455                  END IF
1456               END IF
1457            END DO
1458         END DO
1459      END IF
1460      !
1461      ! South/East crossings
1462      IF ((nbdysege > 0).AND.(nbdysegs > 0)) THEN
1463         DO ib1 = 1, nbdysege
1464            DO ib2 = 1, nbdysegs
1465               IF (( jpisdt(ib2)<=jpieob(ib1)+1).AND. &
1466                &  ( jpisft(ib2)>=jpieob(ib1)+1).AND. &
1467                &  ( jpjedt(ib1)<=jpjsob(ib2)  ).AND. &
1468                &  ( jpjeft(ib1)>=jpjsob(ib2)  )) THEN
1469                  IF ((jpjedt(ib1)==jpjsob(ib2)).AND.(jpisft(ib2)==jpieob(ib1)+1)) THEN
1470                     ! We have a possible South-East corner
1471!                     WRITE(numout,*) ' Found a South-East corner at (i,j): ', jpisft(ib2), jpjedt(ib1)
1472!                     WRITE(numout,*) ' between segments: ', npckge(ib1), npckgs(ib2)
1473                     icorne(ib1,1) = npckgs(ib2)
1474                     icorns(ib2,2) = npckge(ib1)
1475                  ELSEIF ((jpjeft(ib1)==jpjsob(ib2)).AND.(jpisdt(ib2)==jpieob(ib1)+1)) THEN
1476                     IF(lwp) WRITE(numout,*)
1477                     IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', &
1478                     &                                     jpisdt(ib2), jpjeft(ib1)
1479                     IF(lwp) WRITE(numout,*) ' ==========  Not allowed yet'
1480                     IF(lwp) WRITE(numout,*) '             Crossing problem with East segment: ',npckge(ib1), &
1481                     &                                                    ' and South segment: ',npckgs(ib2)
1482                     IF(lwp) WRITE(numout,*)
1483                     nstop = nstop + 1
1484                  ELSE
1485                     IF(lwp) WRITE(numout,*)
1486                     IF(lwp) WRITE(numout,*) ' E R R O R : Check South and East Open boundary indices'
1487                     IF(lwp) WRITE(numout,*) ' ==========  Crossing problem with East segment: ',npckge(ib1), &
1488                     &                                                    ' and South segment: ',npckgs(ib2)
1489                     IF(lwp) WRITE(numout,*)
1490                     nstop = nstop + 1
1491                  END IF
1492               END IF
1493            END DO
1494         END DO
1495      END IF
1496      !
1497      ! North/West crossings
1498      IF ((nbdysegn > 0).AND.(nbdysegw > 0)) THEN
1499         DO ib1 = 1, nbdysegw       
1500            DO ib2 = 1, nbdysegn
1501               IF (( jpindt(ib2)<=jpiwob(ib1)  ).AND. &
1502                &  ( jpinft(ib2)>=jpiwob(ib1)  ).AND. &
1503                &  ( jpjwdt(ib1)<=jpjnob(ib2)+1).AND. &
1504                &  ( jpjwft(ib1)>=jpjnob(ib2)+1)) THEN
1505                  IF ((jpjwft(ib1)==jpjnob(ib2)+1).AND.(jpindt(ib2)==jpiwob(ib1))) THEN
1506                     ! We have a possible North-West corner
1507!                     WRITE(numout,*) ' Found a North-West corner at (i,j): ', jpindt(ib2), jpjwft(ib1)
1508!                     WRITE(numout,*) ' between segments: ', npckgw(ib1), npckgn(ib2)
1509                     icornw(ib1,2) = npckgn(ib2)
1510                     icornn(ib2,1) = npckgw(ib1)
1511                  ELSEIF ((jpjwdt(ib1)==jpjnob(ib2)+1).AND.(jpinft(ib2)==jpiwob(ib1))) THEN
1512                     IF(lwp) WRITE(numout,*)
1513                     IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', &
1514                     &                                     jpinft(ib2), jpjwdt(ib1)
1515                     IF(lwp) WRITE(numout,*) ' ==========  Not allowed yet'
1516                     IF(lwp) WRITE(numout,*) '             Crossing problem with West segment: ',npckgw(ib1), &
1517                     &                                                    ' and North segment: ',npckgn(ib2)
1518                     IF(lwp) WRITE(numout,*)
1519                     nstop = nstop + 1
1520                  ELSE
1521                     IF(lwp) WRITE(numout,*)
1522                     IF(lwp) WRITE(numout,*) ' E R R O R : Check North and West Open boundary indices'
1523                     IF(lwp) WRITE(numout,*) ' ==========  Crossing problem with West segment: ',npckgw(ib1), &
1524                     &                                                    ' and North segment: ',npckgn(ib2)
1525                     IF(lwp) WRITE(numout,*)
1526                     nstop = nstop + 1
1527                  END IF
1528               END IF
1529            END DO
1530         END DO
1531      END IF
1532      !
1533      ! North/East crossings
1534      IF ((nbdysegn > 0).AND.(nbdysege > 0)) THEN
1535         DO ib1 = 1, nbdysege       
1536            DO ib2 = 1, nbdysegn
1537               IF (( jpindt(ib2)<=jpieob(ib1)+1).AND. &
1538                &  ( jpinft(ib2)>=jpieob(ib1)+1).AND. &
1539                &  ( jpjedt(ib1)<=jpjnob(ib2)+1).AND. &
1540                &  ( jpjeft(ib1)>=jpjnob(ib2)+1)) THEN
1541                  IF ((jpjeft(ib1)==jpjnob(ib2)+1).AND.(jpinft(ib2)==jpieob(ib1)+1)) THEN
1542                     ! We have a possible North-East corner
1543!                     WRITE(numout,*) ' Found a North-East corner at (i,j): ', jpinft(ib2), jpjeft(ib1)
1544!                     WRITE(numout,*) ' between segments: ', npckge(ib1), npckgn(ib2)
1545                     icorne(ib1,2) = npckgn(ib2)
1546                     icornn(ib2,2) = npckge(ib1)
1547                  ELSEIF ((jpjedt(ib1)==jpjnob(ib2)+1).AND.(jpindt(ib2)==jpieob(ib1)+1)) THEN
1548                     IF(lwp) WRITE(numout,*)
1549                     IF(lwp) WRITE(numout,*) ' E R R O R : Found an acute open boundary corner at point (i,j)= ', &
1550                     &                                     jpindt(ib2), jpjedt(ib1)
1551                     IF(lwp) WRITE(numout,*) ' ==========  Not allowed yet'
1552                     IF(lwp) WRITE(numout,*) '             Crossing problem with East segment: ',npckge(ib1), &
1553                     &                                                    ' and North segment: ',npckgn(ib2)
1554                     IF(lwp) WRITE(numout,*)
1555                     nstop = nstop + 1
1556                  ELSE
1557                     IF(lwp) WRITE(numout,*)
1558                     IF(lwp) WRITE(numout,*) ' E R R O R : Check North and East Open boundary indices'
1559                     IF(lwp) WRITE(numout,*) ' ==========  Crossing problem with East segment: ',npckge(ib1), &
1560                     &                                                    ' and North segment: ',npckgn(ib2)
1561                     IF(lwp) WRITE(numout,*)
1562                     nstop = nstop + 1
1563                  END IF
1564               END IF
1565            END DO
1566         END DO
1567      END IF
1568      !
1569      ! 3. Check if segment extremities are on land
1570      !--------------------------------------------
1571      !
1572      ! West segments
1573      DO ib = 1, nbdysegw
1574         ! get mask at boundary extremities:
1575         ztestmask(1:2)=0.
1576         DO ji = 1, jpi
1577            DO jj = 1, jpj             
1578              IF (((ji + nimpp - 1) == jpiwob(ib)).AND. & 
1579               &  ((jj + njmpp - 1) == jpjwdt(ib))) ztestmask(1)=tmask(ji,jj,1)
1580              IF (((ji + nimpp - 1) == jpiwob(ib)).AND. & 
1581               &  ((jj + njmpp - 1) == jpjwft(ib))) ztestmask(2)=tmask(ji,jj,1) 
1582            END DO
1583         END DO
1584         IF( lk_mpp )   CALL mpp_sum( ztestmask, 2 )   ! sum over the global domain
1585
1586         IF (ztestmask(1)==1) THEN
1587            IF (icornw(ib,1)==0) THEN
1588               IF(lwp) WRITE(numout,*)
1589               IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgw(ib)
1590               IF(lwp) WRITE(numout,*) ' ==========  does not start on land or on a corner'                                                 
1591               IF(lwp) WRITE(numout,*)
1592               nstop = nstop + 1
1593            ELSE
1594               ! This is a corner
1595               IF(lwp) WRITE(numout,*) 'Found a South-West corner at (i,j): ', jpiwob(ib), jpjwdt(ib)
1596               CALL bdy_ctl_corn(npckgw(ib), icornw(ib,1))
1597               itest=itest+1
1598            ENDIF
1599         ENDIF
1600         IF (ztestmask(2)==1) THEN
1601            IF (icornw(ib,2)==0) THEN
1602               IF(lwp) WRITE(numout,*)
1603               IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgw(ib)
1604               IF(lwp) WRITE(numout,*) ' ==========  does not end on land or on a corner'                                                 
1605               IF(lwp) WRITE(numout,*)
1606               nstop = nstop + 1
1607            ELSE
1608               ! This is a corner
1609               IF(lwp) WRITE(numout,*) 'Found a North-West corner at (i,j): ', jpiwob(ib), jpjwft(ib)
1610               CALL bdy_ctl_corn(npckgw(ib), icornw(ib,2))
1611               itest=itest+1
1612            ENDIF
1613         ENDIF
1614      END DO
1615      !
1616      ! East segments
1617      DO ib = 1, nbdysege
1618         ! get mask at boundary extremities:
1619         ztestmask(1:2)=0.
1620         DO ji = 1, jpi
1621            DO jj = 1, jpj             
1622              IF (((ji + nimpp - 1) == jpieob(ib)+1).AND. & 
1623               &  ((jj + njmpp - 1) == jpjedt(ib))) ztestmask(1)=tmask(ji,jj,1)
1624              IF (((ji + nimpp - 1) == jpieob(ib)+1).AND. & 
1625               &  ((jj + njmpp - 1) == jpjeft(ib))) ztestmask(2)=tmask(ji,jj,1) 
1626            END DO
1627         END DO
1628         IF( lk_mpp )   CALL mpp_sum( ztestmask, 2 )   ! sum over the global domain
1629
1630         IF (ztestmask(1)==1) THEN
1631            IF (icorne(ib,1)==0) THEN
1632               IF(lwp) WRITE(numout,*)
1633               IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckge(ib)
1634               IF(lwp) WRITE(numout,*) ' ==========  does not start on land or on a corner'                                                 
1635               IF(lwp) WRITE(numout,*)
1636               nstop = nstop + 1 
1637            ELSE
1638               ! This is a corner
1639               IF(lwp) WRITE(numout,*) 'Found a South-East corner at (i,j): ', jpieob(ib)+1, jpjedt(ib)
1640               CALL bdy_ctl_corn(npckge(ib), icorne(ib,1))
1641               itest=itest+1
1642            ENDIF
1643         ENDIF
1644         IF (ztestmask(2)==1) THEN
1645            IF (icorne(ib,2)==0) THEN
1646               IF(lwp) WRITE(numout,*)
1647               IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckge(ib)
1648               IF(lwp) WRITE(numout,*) ' ==========  does not end on land or on a corner'                                                 
1649               IF(lwp) WRITE(numout,*)
1650               nstop = nstop + 1
1651            ELSE
1652               ! This is a corner
1653               IF(lwp) WRITE(numout,*) 'Found a North-East corner at (i,j): ', jpieob(ib)+1, jpjeft(ib)
1654               CALL bdy_ctl_corn(npckge(ib), icorne(ib,2))
1655               itest=itest+1
1656            ENDIF
1657         ENDIF
1658      END DO
1659      !
1660      ! South segments
1661      DO ib = 1, nbdysegs
1662         ! get mask at boundary extremities:
1663         ztestmask(1:2)=0.
1664         DO ji = 1, jpi
1665            DO jj = 1, jpj             
1666              IF (((jj + njmpp - 1) == jpjsob(ib)).AND. & 
1667               &  ((ji + nimpp - 1) == jpisdt(ib))) ztestmask(1)=tmask(ji,jj,1)
1668              IF (((jj + njmpp - 1) == jpjsob(ib)).AND. & 
1669               &  ((ji + nimpp - 1) == jpisft(ib))) ztestmask(2)=tmask(ji,jj,1) 
1670            END DO
1671         END DO
1672         IF( lk_mpp )   CALL mpp_sum( ztestmask, 2 )   ! sum over the global domain
1673
1674         IF ((ztestmask(1)==1).AND.(icorns(ib,1)==0)) THEN
1675            IF(lwp) WRITE(numout,*)
1676            IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgs(ib)
1677            IF(lwp) WRITE(numout,*) ' ==========  does not start on land or on a corner'                                                 
1678            IF(lwp) WRITE(numout,*)
1679            nstop = nstop + 1
1680         ENDIF
1681         IF ((ztestmask(2)==1).AND.(icorns(ib,2)==0)) THEN
1682            IF(lwp) WRITE(numout,*)
1683            IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgs(ib)
1684            IF(lwp) WRITE(numout,*) ' ==========  does not end on land or on a corner'                                                 
1685            IF(lwp) WRITE(numout,*)
1686            nstop = nstop + 1
1687         ENDIF
1688      END DO
1689      !
1690      ! North segments
1691      DO ib = 1, nbdysegn
1692         ! get mask at boundary extremities:
1693         ztestmask(1:2)=0.
1694         DO ji = 1, jpi
1695            DO jj = 1, jpj             
1696              IF (((jj + njmpp - 1) == jpjnob(ib)+1).AND. & 
1697               &  ((ji + nimpp - 1) == jpindt(ib))) ztestmask(1)=tmask(ji,jj,1)
1698              IF (((jj + njmpp - 1) == jpjnob(ib)+1).AND. & 
1699               &  ((ji + nimpp - 1) == jpinft(ib))) ztestmask(2)=tmask(ji,jj,1) 
1700            END DO
1701         END DO
1702         IF( lk_mpp )   CALL mpp_sum( ztestmask, 2 )   ! sum over the global domain
1703
1704         IF ((ztestmask(1)==1).AND.(icornn(ib,1)==0)) THEN
1705            IF(lwp) WRITE(numout,*)
1706            IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgn(ib)
1707            IF(lwp) WRITE(numout,*) ' ==========  does not start on land'                                                 
1708            IF(lwp) WRITE(numout,*)
1709            nstop = nstop + 1
1710         ENDIF
1711         IF ((ztestmask(2)==1).AND.(icornn(ib,2)==0)) THEN
1712            IF(lwp) WRITE(numout,*)
1713            IF(lwp) WRITE(numout,*) ' E R R O R : Open boundary segment ', npckgn(ib)
1714            IF(lwp) WRITE(numout,*) ' ==========  does not end on land'                                                 
1715            IF(lwp) WRITE(numout,*)
1716            nstop = nstop + 1
1717         ENDIF
1718      END DO
1719      !
1720      IF ((itest==0).AND.(lwp)) WRITE(numout,*) 'NO open boundary corner found'
1721      !
1722      ! Other tests TBD:
1723      ! segments completly on land
1724      ! optimized open boundary array length according to landmask
1725      ! Nudging layers that overlap with interior domain
1726      !
1727   END SUBROUTINE bdy_ctl_seg
1728
1729   SUBROUTINE bdy_ctl_corn( ib1, ib2 )
1730      !!----------------------------------------------------------------------
1731      !!                 ***  ROUTINE bdy_ctl_corn  ***
1732      !!
1733      !! ** Purpose :   Check numerical schemes consistency between
1734      !!                segments having a common corner
1735      !!
1736      !! ** Method  :   
1737      !!----------------------------------------------------------------------
1738      INTEGER, INTENT(in)  ::   ib1, ib2
1739      INTEGER :: itest
1740      !!----------------------------------------------------------------------
1741      itest = 0
1742
1743      IF( cn_dyn2d(ib1) /= cn_dyn2d(ib2) )   itest = itest + 1
1744      IF( cn_dyn3d(ib1) /= cn_dyn3d(ib2) )   itest = itest + 1
1745      IF( cn_tra  (ib1) /= cn_tra  (ib2) )   itest = itest + 1
1746      !
1747      IF( nn_dyn2d_dta(ib1) /= nn_dyn2d_dta(ib2) )   itest = itest + 1
1748      IF( nn_dyn3d_dta(ib1) /= nn_dyn3d_dta(ib2) )   itest = itest + 1
1749      IF( nn_tra_dta  (ib1) /= nn_tra_dta  (ib2) )   itest = itest + 1
1750      !
1751      IF( nn_rimwidth(ib1) /= nn_rimwidth(ib2) )   itest = itest + 1   
1752      !
1753      IF( itest>0 ) THEN
1754         IF(lwp) WRITE(numout,*) ' E R R O R : Segments ', ib1, 'and ', ib2
1755         IF(lwp) WRITE(numout,*) ' ==========  have different open bdy schemes'                                                 
1756         IF(lwp) WRITE(numout,*)
1757         nstop = nstop + 1
1758      ENDIF
1759      !
1760   END SUBROUTINE bdy_ctl_corn
1761
1762   !!=================================================================================
1763END MODULE bdyini
Note: See TracBrowser for help on using the repository browser.