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

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

source: NEMO/trunk/src/OCE/BDY/bdyini.F90 @ 10629

Last change on this file since 10629 was 10629, checked in by smasson, 5 years ago

trunk: bugfix in mpp for bdy, back to v3.6, see #2213, #2224, #2225

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