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.
mpp_bdy_generic.h90 in NEMO/branches/2019/ENHANCE-03_domcfg/src – NEMO

source: NEMO/branches/2019/ENHANCE-03_domcfg/src/mpp_bdy_generic.h90 @ 11602

Last change on this file since 11602 was 10727, checked in by rblod, 5 years ago

new nesting tools (attempt) and brutal cleaning of DOMAINcfg, see ticket #2129

File size: 12.4 KB
Line 
1#   define ARRAY_TYPE(i,j,k,l,f)    REAL(wp)                    , INTENT(inout) ::   ARRAY_IN(i,j,k,l,f)
2#   define NAT_IN(k)                cd_nat
3#   define SGN_IN(k)                psgn
4#   define IBD_IN(k)                kb_bdy
5#   define F_SIZE(ptab)             1
6#   define OPT_K(k)                 
7#   if defined DIM_2d
8#      define ARRAY_IN(i,j,k,l,f)   ptab(i,j)
9#      define K_SIZE(ptab)          1
10#      define L_SIZE(ptab)          1
11#   endif
12#   if defined DIM_3d
13#      define ARRAY_IN(i,j,k,l,f)   ptab(i,j,k)
14#      define K_SIZE(ptab)          SIZE(ptab,3)
15#      define L_SIZE(ptab)          1
16#   endif
17#   if defined DIM_4d
18#      define ARRAY_IN(i,j,k,l,f)   ptab(i,j,k,l)
19#      define K_SIZE(ptab)          SIZE(ptab,3)
20#      define L_SIZE(ptab)          SIZE(ptab,4)
21#   endif
22
23   SUBROUTINE ROUTINE_BDY( cdname, ptab, cd_nat, psgn      , kb_bdy )
24      !!----------------------------------------------------------------------
25      !!                  ***  routine mpp_lnk_bdy_3d  ***
26      !!
27      !! ** Purpose :   Message passing management
28      !!
29      !! ** Method  :   Use mppsend and mpprecv function for passing BDY boundaries
30      !!      between processors following neighboring subdomains.
31      !!            domain parameters
32      !!                    nlci   : first dimension of the local subdomain
33      !!                    nlcj   : second dimension of the local subdomain
34      !!                    nbondi_bdy : mark for "east-west local boundary"
35      !!                    nbondj_bdy : mark for "north-south local boundary"
36      !!                    noea   : number for local neighboring processors
37      !!                    nowe   : number for local neighboring processors
38      !!                    noso   : number for local neighboring processors
39      !!                    nono   : number for local neighboring processors
40      !!
41      !! ** Action  :   ptab with update value at its periphery
42      !!
43      !!----------------------------------------------------------------------
44      CHARACTER(len=*)            , INTENT(in   ) ::   cdname      ! name of the calling subroutine
45      ARRAY_TYPE(:,:,:,:,:)   ! array or pointer of arrays on which the boundary condition is applied
46      CHARACTER(len=1)            , INTENT(in   ) ::   NAT_IN(:)   ! nature of array grid-points
47      REAL(wp)                    , INTENT(in   ) ::   SGN_IN(:)   ! sign used across the north fold boundary
48      INTEGER                     , INTENT(in   ) ::   IBD_IN(:)   ! BDY boundary set
49      !
50      INTEGER  ::   ji, jj, jk, jl, jh, jf     ! dummy loop indices
51      INTEGER  ::   ipk, ipl, ipf              ! 3dimension of the input array
52      INTEGER  ::   imigr, iihom, ijhom        ! local integers
53      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
54      REAL(wp) ::   zland                      ! local scalar
55      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
56      !
57      REAL(wp), DIMENSION(:,:,:,:,:,:), ALLOCATABLE ::   zt3ns, zt3sn   ! 3d for north-south & south-north
58      REAL(wp), DIMENSION(:,:,:,:,:,:), ALLOCATABLE ::   zt3ew, zt3we   ! 3d for east-west & west-east
59      !!----------------------------------------------------------------------
60      !
61      ipk = K_SIZE(ptab)   ! 3rd dimension
62      ipl = L_SIZE(ptab)   ! 4th    -
63      ipf = F_SIZE(ptab)   ! 5th    -      use in "multi" case (array of pointers)
64      !
65      IF( narea == 1 .AND. numcom == -1 ) CALL mpp_report( cdname, ipk, ipl, ipf, ld_lbc = .TRUE. )
66      !     
67      ALLOCATE( zt3ns(jpi,nn_hls,ipk,ipl,ipf,2), zt3sn(jpi,nn_hls,ipk,ipl,ipf,2),   &
68         &      zt3ew(jpj,nn_hls,ipk,ipl,ipf,2), zt3we(jpj,nn_hls,ipk,ipl,ipf,2)  )
69
70      zland = 0._wp
71
72      ! 1. standard boundary treatment
73      ! ------------------------------
74      !
75      DO jf = 1, ipf                   ! number of arrays to be treated
76         !
77         !                                ! East-West boundaries
78         !                   
79         IF( nbondi == 2) THEN                  ! neither subdomain to the east nor to the west
80            !                                      !* Cyclic
81            IF( l_Iperio ) THEN
82               ARRAY_IN( 1 ,:,:,:,jf) = ARRAY_IN(jpim1,:,:,:,jf)
83               ARRAY_IN(jpi,:,:,:,jf) = ARRAY_IN(  2  ,:,:,:,jf)
84            ELSE                                   !* Closed
85               IF( .NOT. NAT_IN(jf) == 'F' )   ARRAY_IN(     1       :nn_hls,:,:,:,jf) = zland  ! east except F-point
86                                               ARRAY_IN(nlci-nn_hls+1:jpi   ,:,:,:,jf) = zland  ! west
87            ENDIF
88         ELSEIF(nbondi == -1) THEN              ! subdomain to the east only
89            IF( .NOT. NAT_IN(jf) == 'F' )   ARRAY_IN(1:nn_hls,:,:,:,jf) = zland     ! south except F-point
90            !
91         ELSEIF(nbondi ==  1) THEN              ! subdomain to the west only
92            ARRAY_IN(nlci-nn_hls+1:jpi,:,:,:,jf) = zland    ! north
93         ENDIF
94         !                                ! North-South boundaries
95         !
96         IF( nbondj == 2) THEN                  ! neither subdomain to the north nor to the south
97            !                                      !* Cyclic
98            IF( l_Jperio ) THEN
99               ARRAY_IN(:, 1 ,:,:,jf) = ARRAY_IN(:,jpjm1,:,:,jf)
100               ARRAY_IN(:,jpj,:,:,jf) = ARRAY_IN(:,  2  ,:,:,jf)
101            ELSE                                   !* Closed
102               IF( .NOT. NAT_IN(jf) == 'F' )   ARRAY_IN(:,     1       :nn_hls,:,:,jf) = zland  ! east except F-point
103                                               ARRAY_IN(:,nlcj-nn_hls+1:jpj   ,:,:,jf) = zland  ! west
104            ENDIF
105         ELSEIF(nbondj == -1) THEN              ! subdomain to the east only
106            IF( .NOT. NAT_IN(jf) == 'F' )   ARRAY_IN(:,1:nn_hls,:,:,jf) = zland     ! south except F-point
107            !
108         ELSEIF(nbondj ==  1) THEN              ! subdomain to the west only
109            ARRAY_IN(:,nlcj-nn_hls+1:jpj,:,:,jf) = zland    ! north
110         ENDIF
111         !
112      END DO
113
114      ! 2. East and west directions exchange
115      ! ------------------------------------
116      ! we play with the neigbours AND the row number because of the periodicity
117      !
118      !
119      DO jf = 1, ipf
120         SELECT CASE ( nbondi_bdy(IBD_IN(jf)) )      ! Read Dirichlet lateral conditions
121         CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
122            iihom = nlci-nreci
123               DO jl = 1, ipl
124                  DO jk = 1, ipk
125                     DO jh = 1, nn_hls
126                        zt3ew(:,jh,jk,jl,jf,1) = ARRAY_IN(nn_hls+jh,:,jk,jl,jf)
127                        zt3we(:,jh,jk,jl,jf,1) = ARRAY_IN(iihom +jh,:,jk,jl,jf)
128                     END DO
129                  END DO
130               END DO
131         END SELECT
132         !
133         !                           ! Migrations
134!!gm      imigr = nn_hls * jpj * ipk * ipl * ipf
135         imigr = nn_hls * jpj * ipk * ipl
136         !
137         IF( ln_timing ) CALL tic_tac(.TRUE.)
138         !
139         SELECT CASE ( nbondi_bdy(IBD_IN(jf)) )
140         CASE ( -1 )
141            CALL mppsend( 2, zt3we(1,1,1,1,1,1), imigr, noea, ml_req1 )
142            CALL mpprecv( 1, zt3ew(1,1,1,1,1,2), imigr, noea )
143            IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
144         CASE ( 0 )
145            CALL mppsend( 1, zt3ew(1,1,1,1,1,1), imigr, nowe, ml_req1 )
146            CALL mppsend( 2, zt3we(1,1,1,1,1,1), imigr, noea, ml_req2 )
147            CALL mpprecv( 1, zt3ew(1,1,1,1,1,2), imigr, noea )
148            CALL mpprecv( 2, zt3we(1,1,1,1,1,2), imigr, nowe )
149            IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
150            IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
151         CASE ( 1 )
152            CALL mppsend( 1, zt3ew(1,1,1,1,1,1), imigr, nowe, ml_req1 )
153            CALL mpprecv( 2, zt3we(1,1,1,1,1,2), imigr, nowe )
154            IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
155         END SELECT
156         !
157         IF( ln_timing ) CALL tic_tac(.FALSE.)
158         !
159         !                           ! Write Dirichlet lateral conditions
160         iihom = nlci-nn_hls
161         !
162         !
163         SELECT CASE ( nbondi_bdy_b(IBD_IN(jf)) )
164         CASE ( -1 )
165            DO jl = 1, ipl
166               DO jk = 1, ipk
167                  DO jh = 1, nn_hls
168                     ARRAY_IN(iihom+jh,:,jk,jl,jf) = zt3ew(:,jh,jk,jl,jf,2)
169                  END DO
170               END DO
171            END DO
172         CASE ( 0 )
173            DO jl = 1, ipl
174               DO jk = 1, ipk
175                  DO jh = 1, nn_hls
176                     ARRAY_IN(jh      ,:,jk,jl,jf) = zt3we(:,jh,jk,jl,jf,2)
177                     ARRAY_IN(iihom+jh,:,jk,jl,jf) = zt3ew(:,jh,jk,jl,jf,2)
178                  END DO
179               END DO
180            END DO
181         CASE ( 1 )
182            DO jl = 1, ipl
183               DO jk = 1, ipk
184                  DO jh = 1, nn_hls
185                     ARRAY_IN(jh      ,:,jk,jl,jf) = zt3we(:,jh,jk,jl,jf,2)
186                  END DO
187               END DO
188            END DO
189         END SELECT
190         !
191      END DO
192
193      ! 3. north fold treatment
194      ! -----------------------
195      !
196      ! do it before south directions so concerned processes can do it without waiting for the comm with the sourthern neighbor
197      IF( npolj /= 0) THEN
198         !
199         SELECT CASE ( jpni )
200         CASE ( 1 )     ;   CALL lbc_nfd( ptab, NAT_IN(:), SGN_IN(:) OPT_K(:) )   ! only 1 northern proc, no mpp
201         CASE DEFAULT   ;   CALL mpp_nfd( ptab, NAT_IN(:), SGN_IN(:) OPT_K(:) )   ! for all northern procs.
202         END SELECT
203         !
204      ENDIF
205
206      ! 4. North and south directions
207      ! -----------------------------
208      ! always closed : we play only with the neigbours
209      !
210      DO jf = 1, ipf
211         IF( nbondj_bdy(IBD_IN(jf)) /= 2 ) THEN      ! Read Dirichlet lateral conditions
212            ijhom = nlcj-nrecj
213            DO jl = 1, ipl
214               DO jk = 1, ipk
215                  DO jh = 1, nn_hls
216                     zt3sn(:,jh,jk,jl,jf,1) = ARRAY_IN(:,ijhom +jh,jk,jl,jf)
217                     zt3ns(:,jh,jk,jl,jf,1) = ARRAY_IN(:,nn_hls+jh,jk,jl,jf)
218                  END DO
219               END DO
220            END DO
221         ENDIF
222         !
223         !                           ! Migrations
224!!gm      imigr = nn_hls * jpi * ipk * ipl * ipf
225         imigr = nn_hls * jpi * ipk * ipl
226         !
227         IF( ln_timing ) CALL tic_tac(.TRUE.)
228         !
229         SELECT CASE ( nbondj_bdy(IBD_IN(jf)) )
230         CASE ( -1 )
231            CALL mppsend( 4, zt3sn(1,1,1,1,1,1), imigr, nono, ml_req1 )
232            CALL mpprecv( 3, zt3ns(1,1,1,1,1,2), imigr, nono )
233            IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
234         CASE ( 0 )
235            CALL mppsend( 3, zt3ns(1,1,1,1,1,1), imigr, noso, ml_req1 )
236            CALL mppsend( 4, zt3sn(1,1,1,1,1,1), imigr, nono, ml_req2 )
237            CALL mpprecv( 3, zt3ns(1,1,1,1,1,2), imigr, nono )
238            CALL mpprecv( 4, zt3sn(1,1,1,1,1,2), imigr, noso )
239            IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
240            IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
241         CASE ( 1 )
242            CALL mppsend( 3, zt3ns(1,1,1,1,1,1), imigr, noso, ml_req1 )
243            CALL mpprecv( 4, zt3sn(1,1,1,1,1,2), imigr, noso )
244            IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
245         END SELECT
246         !
247         IF( ln_timing ) CALL tic_tac(.FALSE.)
248         !
249         !                           ! Write Dirichlet lateral conditions
250         ijhom = nlcj-nn_hls
251         !
252         SELECT CASE ( nbondj_bdy_b(IBD_IN(jf)) )
253         CASE ( -1 )
254            DO jl = 1, ipl
255               DO jk = 1, ipk
256                  DO jh = 1, nn_hls
257                     ARRAY_IN(:,ijhom+jh,jk,jl,jf) = zt3ns(:,jh,jk,jl,jf,2)
258                  END DO
259               END DO
260            END DO
261         CASE ( 0 )
262            DO jl = 1, ipl
263               DO jk = 1, ipk
264                  DO jh = 1, nn_hls
265                     ARRAY_IN(:,      jh,jk,jl,jf) = zt3sn(:,jh,jk,jl,jf,2)
266                     ARRAY_IN(:,ijhom+jh,jk,jl,jf) = zt3ns(:,jh,jk,jl,jf,2)
267                  END DO
268               END DO
269            END DO
270         CASE ( 1 )
271            DO jl = 1, ipl
272               DO jk = 1, ipk
273                  DO jh = 1, nn_hls
274                     ARRAY_IN(:,jh,jk,jl,jf) = zt3sn(:,jh,jk,jl,jf,2)
275                  END DO
276               END DO
277            END DO
278         END SELECT
279      END DO
280      !
281      DEALLOCATE( zt3ns, zt3sn, zt3ew, zt3we  )
282      !
283   END SUBROUTINE ROUTINE_BDY
284
285#undef ARRAY_TYPE
286#undef NAT_IN
287#undef SGN_IN
288#undef IBD_IN
289#undef ARRAY_IN
290#undef K_SIZE
291#undef L_SIZE
292#undef F_SIZE
293#undef OPT_K
Note: See TracBrowser for help on using the repository browser.