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.
lbclnk.F90 in NEMO/branches/2019/dev_r11470_HPC_12_mpi3/src/OCE/LBC – NEMO

source: NEMO/branches/2019/dev_r11470_HPC_12_mpi3/src/OCE/LBC/lbclnk.F90 @ 11940

Last change on this file since 11940 was 11940, checked in by mocavero, 4 years ago

Add MPI3 neighbourhood collectives halo exchange in LBC and call it in tracer advection FCT scheme #2011

  • Property svn:keywords set to Id
File size: 24.4 KB
Line 
1MODULE lbclnk
2   !!======================================================================
3   !!                       ***  MODULE  lbclnk  ***
4   !! NEMO        : lateral boundary conditions
5   !!=====================================================================
6   !! History :  OPA  ! 1997-06  (G. Madec)  Original code
7   !!   NEMO     1.0  ! 2002-09  (G. Madec)  F90: Free form and module
8   !!            3.2  ! 2009-03  (R. Benshila)  External north fold treatment 
9   !!            3.5  ! 2012     (S.Mocavero, I. Epicoco)  optimization of BDY comm. via lbc_bdy_lnk and lbc_obc_lnk
10   !!            3.4  ! 2012-12  (R. Bourdalle-Badie, G. Reffray)  add a C1D case 
11   !!            3.6  ! 2015-06  (O. Tintó and M. Castrillo)  add lbc_lnk_multi 
12   !!            4.0  ! 2017-03  (G. Madec) automatique allocation of array size (use with any 3rd dim size)
13   !!             -   ! 2017-04  (G. Madec) remove duplicated routines (lbc_lnk_2d_9, lbc_lnk_2d_multiple, lbc_lnk_3d_gather)
14   !!             -   ! 2017-05  (G. Madec) create generic.h90 files to generate all lbc and north fold routines
15   !!             -   !  2019  (S. Mocavero, I. Epicoco - CMCC) create generic.h90 files to introduce MPI3 neighbourhood collectives
16
17   !!----------------------------------------------------------------------
18   !!           define the generic interfaces of lib_mpp routines
19   !!----------------------------------------------------------------------
20   !!   lbc_lnk       : generic interface for mpp_lnk_3d and mpp_lnk_2d routines defined in lib_mpp
21   !!   lbc_bdy_lnk   : generic interface for mpp_lnk_bdy_2d and mpp_lnk_bdy_3d routines defined in lib_mpp
22   !!----------------------------------------------------------------------
23   USE dom_oce        ! ocean space and time domain
24   USE lib_mpp        ! distributed memory computing library
25   USE lbcnfd         ! north fold
26   USE in_out_manager ! I/O manager
27
28   IMPLICIT NONE
29   PRIVATE
30
31   INTERFACE lbc_lnk
32      MODULE PROCEDURE   mpp_lnk_2d      , mpp_lnk_3d      , mpp_lnk_4d
33   END INTERFACE
34   INTERFACE lbc_lnk_ptr
35      MODULE PROCEDURE   mpp_lnk_2d_ptr  , mpp_lnk_3d_ptr  , mpp_lnk_4d_ptr
36   END INTERFACE
37   INTERFACE lbc_lnk_multi
38      MODULE PROCEDURE   lbc_lnk_2d_multi, lbc_lnk_3d_multi, lbc_lnk_4d_multi
39   END INTERFACE
40   INTERFACE lbc_lnk_nc_multi
41      MODULE PROCEDURE   lbc_lnk_nc_2d, lbc_lnk_nc_3d, lbc_lnk_nc_4d
42   END INTERFACE
43   INTERFACE lbc_lnk_nc
44      MODULE PROCEDURE   mpp_lnk_nc_2d, mpp_lnk_nc_3d, mpp_lnk_nc_4d
45   END INTERFACE
46   !
47   INTERFACE lbc_lnk_icb
48      MODULE PROCEDURE mpp_lnk_2d_icb
49   END INTERFACE
50
51   INTERFACE mpp_nfd
52      MODULE PROCEDURE   mpp_nfd_2d    , mpp_nfd_3d    , mpp_nfd_4d
53      MODULE PROCEDURE   mpp_nfd_2d_ptr, mpp_nfd_3d_ptr, mpp_nfd_4d_ptr
54   END INTERFACE
55
56   PUBLIC   lbc_lnk            ! ocean/ice lateral boundary conditions
57   PUBLIC   lbc_lnk_multi      ! modified ocean/ice lateral boundary conditions
58   PUBLIC   lbc_lnk_icb        ! iceberg lateral boundary conditions
59   PUBLIC   lbc_lnk_nc_multi   ! modified ocean/ice lateral boundary conditions
60
61#if   defined key_mpp_mpi
62!$AGRIF_DO_NOT_TREAT
63   INCLUDE 'mpif.h'
64!$AGRIF_END_DO_NOT_TREAT
65#endif
66
67   INTEGER, PUBLIC, PARAMETER ::   jpfillnothing = 1
68   INTEGER, PUBLIC, PARAMETER ::   jpfillcst     = 2
69   INTEGER, PUBLIC, PARAMETER ::   jpfillcopy    = 3
70   INTEGER, PUBLIC, PARAMETER ::   jpfillperio   = 4
71   INTEGER, PUBLIC, PARAMETER ::   jpfillmpi     = 5
72
73   !!----------------------------------------------------------------------
74   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
75   !! $Id$
76   !! Software governed by the CeCILL license (see ./LICENSE)
77   !!----------------------------------------------------------------------
78CONTAINS
79
80   !!----------------------------------------------------------------------
81   !!                   ***   load_ptr_(2,3,4)d   ***
82   !!
83   !!   * Dummy Argument :
84   !!       in    ==>   ptab       ! array to be loaded (2D, 3D or 4D)
85   !!                   cd_nat     ! nature of pt2d array grid-points
86   !!                   psgn       ! sign used across the north fold boundary
87   !!       inout <=>   ptab_ptr   ! array of 2D, 3D or 4D pointers
88   !!                   cdna_ptr   ! nature of ptab array grid-points
89   !!                   psgn_ptr   ! sign used across the north fold boundary
90   !!                   kfld       ! number of elements that has been attributed
91   !!----------------------------------------------------------------------
92
93   !!----------------------------------------------------------------------
94   !!                  ***   lbc_lnk_(2,3,4)d_multi   ***
95   !!                     ***   load_ptr_(2,3,4)d   ***
96   !!
97   !!   * Argument : dummy argument use in lbc_lnk_multi_... routines
98   !!
99   !!----------------------------------------------------------------------
100
101#  define DIM_2d
102#     define ROUTINE_LOAD           load_ptr_2d
103#     define ROUTINE_MULTI          lbc_lnk_2d_multi
104#     include "lbc_lnk_multi_generic.h90"
105#     undef ROUTINE_MULTI
106#     undef ROUTINE_LOAD
107#  undef DIM_2d
108
109#  define DIM_3d
110#     define ROUTINE_LOAD           load_ptr_3d
111#     define ROUTINE_MULTI          lbc_lnk_3d_multi
112#     include "lbc_lnk_multi_generic.h90"
113#     undef ROUTINE_MULTI
114#     undef ROUTINE_LOAD
115#  undef DIM_3d
116
117#  define DIM_4d
118#     define ROUTINE_LOAD           load_ptr_4d
119#     define ROUTINE_MULTI          lbc_lnk_4d_multi
120#     include "lbc_lnk_multi_generic.h90"
121#     undef ROUTINE_MULTI
122#     undef ROUTINE_LOAD
123#  undef DIM_4d
124
125   !!----------------------------------------------------------------------
126   !!                   ***  routine mpp_lnk_(2,3,4)d  ***
127   !!
128   !!   * Argument : dummy argument use in mpp_lnk_... routines
129   !!                ptab      :   array or pointer of arrays on which the boundary condition is applied
130   !!                cd_nat    :   nature of array grid-points
131   !!                psgn      :   sign used across the north fold boundary
132   !!                kfld      :   optional, number of pt3d arrays
133   !!                kfillmode :   optional, method to be use to fill the halos (see jpfill* variables)
134   !!                pfillval  :   optional, background value (used with jpfillcopy)
135   !!----------------------------------------------------------------------
136   !
137   !                       !==  2D array and array of 2D pointer  ==!
138   !
139#  define DIM_2d
140#     define ROUTINE_LNK           mpp_lnk_2d
141#     include "mpp_lnk_generic.h90"
142#     undef ROUTINE_LNK
143#     define MULTI
144#     define ROUTINE_LNK           mpp_lnk_2d_ptr
145#     include "mpp_lnk_generic.h90"
146#     undef ROUTINE_LNK
147#     undef MULTI
148#  undef DIM_2d
149   !
150   !                       !==  3D array and array of 3D pointer  ==!
151   !
152#  define DIM_3d
153#     define ROUTINE_LNK           mpp_lnk_3d
154#     include "mpp_lnk_generic.h90"
155#     undef ROUTINE_LNK
156#     define MULTI
157#     define ROUTINE_LNK           mpp_lnk_3d_ptr
158#     include "mpp_lnk_generic.h90"
159#     undef ROUTINE_LNK
160#     undef MULTI
161#  undef DIM_3d
162   !
163   !                       !==  4D array and array of 4D pointer  ==!
164   !
165#  define DIM_4d
166#     define ROUTINE_LNK           mpp_lnk_4d
167#     include "mpp_lnk_generic.h90"
168#     undef ROUTINE_LNK
169#     define MULTI
170#     define ROUTINE_LNK           mpp_lnk_4d_ptr
171#     include "mpp_lnk_generic.h90"
172#     undef ROUTINE_LNK
173#     undef MULTI
174#  undef DIM_4d
175
176   !!----------------------------------------------------------------------
177   !!                   ***  routine lbc_lnk_nc_(2,3,4)d  ***
178   !!
179   !!   * Argument : dummy argument use in lbc_lnk_nc_... routines
180   !!                ptab   :   array or pointer of arrays on which the boundary
181   !condition is applied
182   !!                cd_nat :   nature of array grid-points
183   !!                psgn   :   sign used across the north fold boundary
184   !!                kfld   :   optional, number of pt3d arrays
185   !!                cd_mpp :   optional, fill the overlap area only
186   !!                pval   :   optional, background value (used at closed
187   !boundaries)
188   !!----------------------------------------------------------------------
189   !
190   !                       !==  2D array and array of 2D pointer  ==!
191   !
192#  define DIM_2d
193#     define ROUTINE_NC_LOAD            load_ptr_nc_2d
194#     define ROUTINE_MULTI_NC           lbc_lnk_nc_2d
195#     include "lbc_lnk_nc_generic.h90"
196#     undef ROUTINE_MULTI_NC
197#     undef ROUTINE_NC_LOAD
198#  undef DIM_2d
199   !
200   !                       !==  3D array and array of 3D pointer  ==!
201   !
202#  define DIM_3d
203#     define ROUTINE_NC_LOAD            load_ptr_nc_3d
204#     define ROUTINE_MULTI_NC           lbc_lnk_nc_3d
205#     include "lbc_lnk_nc_generic.h90"
206#     undef ROUTINE_MULTI_NC
207#     undef ROUTINE_NC_LOAD
208#  undef DIM_3d
209   !
210   !                       !==  4D array and array of 4D pointer  ==!
211   !
212#  define DIM_4d
213#     define ROUTINE_NC_LOAD            load_ptr_nc_4d
214#     define ROUTINE_MULTI_NC           lbc_lnk_nc_4d
215#     include "lbc_lnk_nc_generic.h90"
216#     undef ROUTINE_LOAD
217#     undef ROUTINE_NC_LOAD
218#  undef DIM_4d
219
220   !!----------------------------------------------------------------------
221   !!                   ***  routine mpp_nc_(2,3,4)d  ***
222   !!
223   !!   * Argument : dummy argument use in mpp_nc_... routines
224   !!                ptab   :   array or pointer of arrays on which the boundary condition is applied
225   !!                cd_nat :   nature of array grid-points
226   !!                psgn   :   sign used across the north fold boundary
227   !!                kfld   :   optional, number of pt3d arrays
228   !!                cd_mpp :   optional, fill the overlap area only
229   !!                pval   :   optional, background value (used at closed boundaries)
230   !!----------------------------------------------------------------------
231   !
232   !                       !==  2D array and array of 2D pointer  ==!
233   !
234#  define DIM_2d
235#     define ROUTINE_NC           mpp_lnk_nc_2d
236#     include "mpp_nc_generic.h90"
237#     undef ROUTINE_NC
238#  undef DIM_2d
239   !
240   !                       !==  3D array and array of 3D pointer  ==!
241   !
242#  define DIM_3d
243#     define ROUTINE_NC           mpp_lnk_nc_3d
244#     include "mpp_nc_generic.h90"
245#     undef ROUTINE_NC
246#  undef DIM_3d
247   !
248   !                       !==  4D array and array of 4D pointer  ==!
249   !
250#  define DIM_4d
251#     define ROUTINE_NC           mpp_lnk_nc_4d
252#     include "mpp_nc_generic.h90"
253#     undef ROUTINE_NC
254#  undef DIM_4d
255
256   !!----------------------------------------------------------------------
257   !!                   ***  routine mpp_nfd_(2,3,4)d  ***
258   !!
259   !!   * Argument : dummy argument use in mpp_nfd_... routines
260   !!                ptab      :   array or pointer of arrays on which the boundary condition is applied
261   !!                cd_nat    :   nature of array grid-points
262   !!                psgn      :   sign used across the north fold boundary
263   !!                kfld      :   optional, number of pt3d arrays
264   !!                kfillmode :   optional, method to be use to fill the halos (see jpfill* variables)
265   !!                pfillval  :   optional, background value (used with jpfillcopy)
266   !!----------------------------------------------------------------------
267   !
268   !                       !==  2D array and array of 2D pointer  ==!
269   !
270#  define DIM_2d
271#     define ROUTINE_NFD           mpp_nfd_2d
272#     include "mpp_nfd_generic.h90"
273#     undef ROUTINE_NFD
274#     define MULTI
275#     define ROUTINE_NFD           mpp_nfd_2d_ptr
276#     include "mpp_nfd_generic.h90"
277#     undef ROUTINE_NFD
278#     undef MULTI
279#  undef DIM_2d
280   !
281   !                       !==  3D array and array of 3D pointer  ==!
282   !
283#  define DIM_3d
284#     define ROUTINE_NFD           mpp_nfd_3d
285#     include "mpp_nfd_generic.h90"
286#     undef ROUTINE_NFD
287#     define MULTI
288#     define ROUTINE_NFD           mpp_nfd_3d_ptr
289#     include "mpp_nfd_generic.h90"
290#     undef ROUTINE_NFD
291#     undef MULTI
292#  undef DIM_3d
293   !
294   !                       !==  4D array and array of 4D pointer  ==!
295   !
296#  define DIM_4d
297#     define ROUTINE_NFD           mpp_nfd_4d
298#     include "mpp_nfd_generic.h90"
299#     undef ROUTINE_NFD
300#     define MULTI
301#     define ROUTINE_NFD           mpp_nfd_4d_ptr
302#     include "mpp_nfd_generic.h90"
303#     undef ROUTINE_NFD
304#     undef MULTI
305#  undef DIM_4d
306
307
308   !!======================================================================
309
310
311
312   SUBROUTINE mpp_lbc_north_icb( pt2d, cd_type, psgn, kextj)
313      !!---------------------------------------------------------------------
314      !!                   ***  routine mpp_lbc_north_icb  ***
315      !!
316      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
317      !!              in mpp configuration in case of jpn1 > 1 and for 2d
318      !!              array with outer extra halo
319      !!
320      !! ** Method  :   North fold condition and mpp with more than one proc
321      !!              in i-direction require a specific treatment. We gather
322      !!              the 4+kextj northern lines of the global domain on 1
323      !!              processor and apply lbc north-fold on this sub array.
324      !!              Then we scatter the north fold array back to the processors.
325      !!              This routine accounts for an extra halo with icebergs
326      !!              and assumes ghost rows and columns have been suppressed.
327      !!
328      !!----------------------------------------------------------------------
329      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   pt2d     ! 2D array with extra halo
330      CHARACTER(len=1)        , INTENT(in   ) ::   cd_type  ! nature of pt3d grid-points
331      !                                                     !   = T ,  U , V , F or W -points
332      REAL(wp)                , INTENT(in   ) ::   psgn     ! = -1. the sign change across the
333      !!                                                    ! north fold, =  1. otherwise
334      INTEGER                 , INTENT(in   ) ::   kextj    ! Extra halo width at north fold
335      !
336      INTEGER ::   ji, jj, jr
337      INTEGER ::   ierr, itaille, ildi, ilei, iilb
338      INTEGER ::   ipj, ij, iproc
339      !
340      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE  ::  ztab_e, znorthloc_e
341      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE  ::  znorthgloio_e
342      !!----------------------------------------------------------------------
343#if defined key_mpp_mpi
344      !
345      ipj=4
346      ALLOCATE(        ztab_e(jpiglo, 1-kextj:ipj+kextj)       ,       &
347     &            znorthloc_e(jpimax, 1-kextj:ipj+kextj)       ,       &
348     &          znorthgloio_e(jpimax, 1-kextj:ipj+kextj,jpni)    )
349      !
350      ztab_e(:,:)      = 0._wp
351      znorthloc_e(:,:) = 0._wp
352      !
353      ij = 1 - kextj
354      ! put the last ipj+2*kextj lines of pt2d into znorthloc_e
355      DO jj = jpj - ipj + 1 - kextj , jpj + kextj
356         znorthloc_e(1:jpi,ij)=pt2d(1:jpi,jj)
357         ij = ij + 1
358      END DO
359      !
360      itaille = jpimax * ( ipj + 2*kextj )
361      !
362      IF( ln_timing ) CALL tic_tac(.TRUE.)
363      CALL MPI_ALLGATHER( znorthloc_e(1,1-kextj)    , itaille, MPI_DOUBLE_PRECISION,    &
364         &                znorthgloio_e(1,1-kextj,1), itaille, MPI_DOUBLE_PRECISION,    &
365         &                ncomm_north, ierr )
366      !
367      IF( ln_timing ) CALL tic_tac(.FALSE.)
368      !
369      DO jr = 1, ndim_rank_north            ! recover the global north array
370         iproc = nrank_north(jr) + 1
371         ildi = nldit (iproc)
372         ilei = nleit (iproc)
373         iilb = nimppt(iproc)
374         DO jj = 1-kextj, ipj+kextj
375            DO ji = ildi, ilei
376               ztab_e(ji+iilb-1,jj) = znorthgloio_e(ji,jj,jr)
377            END DO
378         END DO
379      END DO
380
381      ! 2. North-Fold boundary conditions
382      ! ----------------------------------
383      CALL lbc_nfd( ztab_e(:,1-kextj:ipj+kextj), cd_type, psgn, kextj )
384
385      ij = 1 - kextj
386      !! Scatter back to pt2d
387      DO jj = jpj - ipj + 1 - kextj , jpj + kextj
388         DO ji= 1, jpi
389            pt2d(ji,jj) = ztab_e(ji+nimpp-1,ij)
390         END DO
391         ij  = ij +1
392      END DO
393      !
394      DEALLOCATE( ztab_e, znorthloc_e, znorthgloio_e )
395      !
396#endif
397   END SUBROUTINE mpp_lbc_north_icb
398
399
400   SUBROUTINE mpp_lnk_2d_icb( cdname, pt2d, cd_type, psgn, kexti, kextj )
401      !!----------------------------------------------------------------------
402      !!                  ***  routine mpp_lnk_2d_icb  ***
403      !!
404      !! ** Purpose :   Message passing management for 2d array (with extra halo for icebergs)
405      !!                This routine receives a (1-kexti:jpi+kexti,1-kexti:jpj+kextj)
406      !!                array (usually (0:jpi+1, 0:jpj+1)) from lbc_lnk_icb calls.
407      !!
408      !! ** Method  :   Use mppsend and mpprecv function for passing mask
409      !!      between processors following neighboring subdomains.
410      !!            domain parameters
411      !!                    jpi    : first dimension of the local subdomain
412      !!                    jpj    : second dimension of the local subdomain
413      !!                    kexti  : number of columns for extra outer halo
414      !!                    kextj  : number of rows for extra outer halo
415      !!                    nbondi : mark for "east-west local boundary"
416      !!                    nbondj : mark for "north-south local boundary"
417      !!                    noea   : number for local neighboring processors
418      !!                    nowe   : number for local neighboring processors
419      !!                    noso   : number for local neighboring processors
420      !!                    nono   : number for local neighboring processors
421      !!----------------------------------------------------------------------
422      CHARACTER(len=*)                                        , INTENT(in   ) ::   cdname      ! name of the calling subroutine
423      REAL(wp), DIMENSION(1-kexti:jpi+kexti,1-kextj:jpj+kextj), INTENT(inout) ::   pt2d     ! 2D array with extra halo
424      CHARACTER(len=1)                                        , INTENT(in   ) ::   cd_type  ! nature of ptab array grid-points
425      REAL(wp)                                                , INTENT(in   ) ::   psgn     ! sign used across the north fold
426      INTEGER                                                 , INTENT(in   ) ::   kexti    ! extra i-halo width
427      INTEGER                                                 , INTENT(in   ) ::   kextj    ! extra j-halo width
428      !
429      INTEGER  ::   jl   ! dummy loop indices
430      INTEGER  ::   imigr, iihom, ijhom        ! local integers
431      INTEGER  ::   ipreci, iprecj             !   -       -
432      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
433      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
434      !!
435      REAL(wp), DIMENSION(1-kexti:jpi+kexti,nn_hls+kextj,2) ::   r2dns, r2dsn
436      REAL(wp), DIMENSION(1-kextj:jpj+kextj,nn_hls+kexti,2) ::   r2dwe, r2dew
437      !!----------------------------------------------------------------------
438
439      ipreci = nn_hls + kexti      ! take into account outer extra 2D overlap area
440      iprecj = nn_hls + kextj
441
442      IF( narea == 1 .AND. numcom == -1 ) CALL mpp_report( cdname, 1, 1, 1, ld_lbc = .TRUE. )
443
444      ! 1. standard boundary treatment
445      ! ------------------------------
446      ! Order matters Here !!!!
447      !
448      !                                      ! East-West boundaries
449      !                                           !* Cyclic east-west
450      IF( l_Iperio ) THEN
451         pt2d(1-kexti:     1   ,:) = pt2d(jpim1-kexti: jpim1 ,:)       ! east
452         pt2d(  jpi  :jpi+kexti,:) = pt2d(     2     :2+kexti,:)       ! west
453         !
454      ELSE                                        !* closed
455         IF( .NOT. cd_type == 'F' )   pt2d(  1-kexti   :nn_hls   ,:) = 0._wp    ! east except at F-point
456                                      pt2d(jpi-nn_hls+1:jpi+kexti,:) = 0._wp    ! west
457      ENDIF
458      !                                      ! North-South boundaries
459      IF( l_Jperio ) THEN                         !* cyclic (only with no mpp j-split)
460         pt2d(:,1-kextj:     1   ) = pt2d(:,jpjm1-kextj:  jpjm1)       ! north
461         pt2d(:,  jpj  :jpj+kextj) = pt2d(:,     2     :2+kextj)       ! south
462      ELSE                                        !* closed
463         IF( .NOT. cd_type == 'F' )   pt2d(:,  1-kextj   :nn_hls   ) = 0._wp    ! north except at F-point
464                                      pt2d(:,jpj-nn_hls+1:jpj+kextj) = 0._wp    ! south
465      ENDIF
466      !
467
468      ! north fold treatment
469      ! -----------------------
470      IF( npolj /= 0 ) THEN
471         !
472         SELECT CASE ( jpni )
473                   CASE ( 1 )     ;   CALL lbc_nfd          ( pt2d(1:jpi,1:jpj+kextj), cd_type, psgn, kextj )
474                   CASE DEFAULT   ;   CALL mpp_lbc_north_icb( pt2d(1:jpi,1:jpj+kextj), cd_type, psgn, kextj )
475         END SELECT
476         !
477      ENDIF
478
479      ! 2. East and west directions exchange
480      ! ------------------------------------
481      ! we play with the neigbours AND the row number because of the periodicity
482      !
483      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
484      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
485         iihom = jpi-nreci-kexti
486         DO jl = 1, ipreci
487            r2dew(:,jl,1) = pt2d(nn_hls+jl,:)
488            r2dwe(:,jl,1) = pt2d(iihom +jl,:)
489         END DO
490      END SELECT
491      !
492      !                           ! Migrations
493      imigr = ipreci * ( jpj + 2*kextj )
494      !
495      IF( ln_timing ) CALL tic_tac(.TRUE.)
496      !
497      SELECT CASE ( nbondi )
498      CASE ( -1 )
499         CALL mppsend( 2, r2dwe(1-kextj,1,1), imigr, noea, ml_req1 )
500         CALL mpprecv( 1, r2dew(1-kextj,1,2), imigr, noea )
501         CALL mpi_wait(ml_req1,ml_stat,ml_err)
502      CASE ( 0 )
503         CALL mppsend( 1, r2dew(1-kextj,1,1), imigr, nowe, ml_req1 )
504         CALL mppsend( 2, r2dwe(1-kextj,1,1), imigr, noea, ml_req2 )
505         CALL mpprecv( 1, r2dew(1-kextj,1,2), imigr, noea )
506         CALL mpprecv( 2, r2dwe(1-kextj,1,2), imigr, nowe )
507         CALL mpi_wait(ml_req1,ml_stat,ml_err)
508         CALL mpi_wait(ml_req2,ml_stat,ml_err)
509      CASE ( 1 )
510         CALL mppsend( 1, r2dew(1-kextj,1,1), imigr, nowe, ml_req1 )
511         CALL mpprecv( 2, r2dwe(1-kextj,1,2), imigr, nowe )
512         CALL mpi_wait(ml_req1,ml_stat,ml_err)
513      END SELECT
514      !
515      IF( ln_timing ) CALL tic_tac(.FALSE.)
516      !
517      !                           ! Write Dirichlet lateral conditions
518      iihom = jpi - nn_hls
519      !
520      SELECT CASE ( nbondi )
521      CASE ( -1 )
522         DO jl = 1, ipreci
523            pt2d(iihom+jl,:) = r2dew(:,jl,2)
524         END DO
525      CASE ( 0 )
526         DO jl = 1, ipreci
527            pt2d(jl-kexti,:) = r2dwe(:,jl,2)
528            pt2d(iihom+jl,:) = r2dew(:,jl,2)
529         END DO
530      CASE ( 1 )
531         DO jl = 1, ipreci
532            pt2d(jl-kexti,:) = r2dwe(:,jl,2)
533         END DO
534      END SELECT
535
536
537      ! 3. North and south directions
538      ! -----------------------------
539      ! always closed : we play only with the neigbours
540      !
541      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
542         ijhom = jpj-nrecj-kextj
543         DO jl = 1, iprecj
544            r2dsn(:,jl,1) = pt2d(:,ijhom +jl)
545            r2dns(:,jl,1) = pt2d(:,nn_hls+jl)
546         END DO
547      ENDIF
548      !
549      !                           ! Migrations
550      imigr = iprecj * ( jpi + 2*kexti )
551      !
552      IF( ln_timing ) CALL tic_tac(.TRUE.)
553      !
554      SELECT CASE ( nbondj )
555      CASE ( -1 )
556         CALL mppsend( 4, r2dsn(1-kexti,1,1), imigr, nono, ml_req1 )
557         CALL mpprecv( 3, r2dns(1-kexti,1,2), imigr, nono )
558         CALL mpi_wait(ml_req1,ml_stat,ml_err)
559      CASE ( 0 )
560         CALL mppsend( 3, r2dns(1-kexti,1,1), imigr, noso, ml_req1 )
561         CALL mppsend( 4, r2dsn(1-kexti,1,1), imigr, nono, ml_req2 )
562         CALL mpprecv( 3, r2dns(1-kexti,1,2), imigr, nono )
563         CALL mpprecv( 4, r2dsn(1-kexti,1,2), imigr, noso )
564         CALL mpi_wait(ml_req1,ml_stat,ml_err)
565         CALL mpi_wait(ml_req2,ml_stat,ml_err)
566      CASE ( 1 )
567         CALL mppsend( 3, r2dns(1-kexti,1,1), imigr, noso, ml_req1 )
568         CALL mpprecv( 4, r2dsn(1-kexti,1,2), imigr, noso )
569         CALL mpi_wait(ml_req1,ml_stat,ml_err)
570      END SELECT
571      !
572      IF( ln_timing ) CALL tic_tac(.FALSE.)
573      !
574      !                           ! Write Dirichlet lateral conditions
575      ijhom = jpj - nn_hls
576      !
577      SELECT CASE ( nbondj )
578      CASE ( -1 )
579         DO jl = 1, iprecj
580            pt2d(:,ijhom+jl) = r2dns(:,jl,2)
581         END DO
582      CASE ( 0 )
583         DO jl = 1, iprecj
584            pt2d(:,jl-kextj) = r2dsn(:,jl,2)
585            pt2d(:,ijhom+jl) = r2dns(:,jl,2)
586         END DO
587      CASE ( 1 )
588         DO jl = 1, iprecj
589            pt2d(:,jl-kextj) = r2dsn(:,jl,2)
590         END DO
591      END SELECT
592      !
593   END SUBROUTINE mpp_lnk_2d_icb
594   
595END MODULE lbclnk
596
Note: See TracBrowser for help on using the repository browser.