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.
Changeset 11573 for NEMO/branches/2019/dev_r11233_AGRIF-05_jchanut_vert_coord_interp/src/OCE/LBC/mpp_lnk_generic.h90 – NEMO

Ignore:
Timestamp:
2019-09-19T11:18:03+02:00 (5 years ago)
Author:
jchanut
Message:

#2222, merged with trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11233_AGRIF-05_jchanut_vert_coord_interp/src/OCE/LBC/mpp_lnk_generic.h90

    r10542 r11573  
    4646 
    4747#if defined MULTI 
    48    SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn, kfld, cd_mpp, pval ) 
    49       INTEGER                     , INTENT(in   ) ::   kfld        ! number of pt3d arrays 
     48   SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn, kfld, kfillmode, pfillval, lsend, lrecv, ihlcom ) 
     49      INTEGER             , INTENT(in   ) ::   kfld        ! number of pt3d arrays 
    5050#else 
    51    SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn      , cd_mpp, pval ) 
     51   SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn      , kfillmode, pfillval, lsend, lrecv, ihlcom ) 
    5252#endif 
    5353      ARRAY_TYPE(:,:,:,:,:)                                        ! array or pointer of arrays on which the boundary condition is applied 
    54       CHARACTER(len=*)            , INTENT(in   ) ::   cdname      ! name of the calling subroutine 
    55       CHARACTER(len=1)            , INTENT(in   ) ::   NAT_IN(:)   ! nature of array grid-points 
    56       REAL(wp)                    , INTENT(in   ) ::   SGN_IN(:)   ! sign used across the north fold boundary 
    57       CHARACTER(len=3), OPTIONAL  , INTENT(in   ) ::   cd_mpp      ! fill the overlap area only 
    58       REAL(wp)        , OPTIONAL  , INTENT(in   ) ::   pval        ! background value (used at closed boundaries) 
    59       ! 
    60       INTEGER  ::    ji,  jj,  jk,  jl, jh, jf   ! dummy loop indices 
     54      CHARACTER(len=*)              , INTENT(in   ) ::   cdname      ! name of the calling subroutine 
     55      CHARACTER(len=1)              , INTENT(in   ) ::   NAT_IN(:)   ! nature of array grid-points 
     56      REAL(wp)                      , INTENT(in   ) ::   SGN_IN(:)   ! sign used across the north fold boundary 
     57      INTEGER ,             OPTIONAL, INTENT(in   ) ::   kfillmode   ! filling method for halo over land (default = constant) 
     58      REAL(wp),             OPTIONAL, INTENT(in   ) ::   pfillval    ! background value (used at closed boundaries) 
     59      LOGICAL, DIMENSION(4),OPTIONAL, INTENT(in   ) ::   lsend, lrecv  ! communication with other 4 proc 
     60      INTEGER              ,OPTIONAL, INTENT(in   ) ::   ihlcom        ! number of ranks and rows to be communicated 
     61      ! 
     62      INTEGER  ::    ji,  jj,  jk,  jl,  jf      ! dummy loop indices 
    6163      INTEGER  ::   ipi, ipj, ipk, ipl, ipf      ! dimension of the input array 
    62       INTEGER  ::   imigr, iihom, ijhom          ! local integers 
    63       INTEGER  ::   ml_req1, ml_req2, ml_err     ! for key_mpi_isend 
     64      INTEGER  ::   isize, ishift, ishift2       ! local integers 
     65      INTEGER  ::   ireq_we, ireq_ea, ireq_so, ireq_no     ! mpi_request id 
    6466      INTEGER  ::   ierr 
     67      INTEGER  ::   ifill_we, ifill_ea, ifill_so, ifill_no 
     68      INTEGER  ::   ihl                          ! number of ranks and rows to be communicated  
    6569      REAL(wp) ::   zland 
    66       INTEGER , DIMENSION(MPI_STATUS_SIZE)      ::   ml_stat        ! for key_mpi_isend 
    67       REAL(wp), DIMENSION(:,:,:,:,:,:), ALLOCATABLE ::   zt3ns, zt3sn   ! north-south & south-north  halos 
    68       REAL(wp), DIMENSION(:,:,:,:,:,:), ALLOCATABLE ::   zt3ew, zt3we   ! east -west  & west - east  halos 
     70      INTEGER , DIMENSION(MPI_STATUS_SIZE)        ::   istat          ! for mpi_isend 
     71      REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE ::   zsnd_we, zrcv_we, zsnd_ea, zrcv_ea   ! east -west  & west - east  halos 
     72      REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE ::   zsnd_so, zrcv_so, zsnd_no, zrcv_no   ! north-south & south-north  halos 
     73      LOGICAL  ::   llsend_we, llsend_ea, llsend_no, llsend_so       ! communication send 
     74      LOGICAL  ::   llrecv_we, llrecv_ea, llrecv_no, llrecv_so       ! communication receive  
     75      LOGICAL  ::   lldo_nfd                                     ! do north pole folding 
    6976      !!---------------------------------------------------------------------- 
     77      ! 
     78      ! ----------------------------------------- ! 
     79      !     0. local variables initialization     ! 
     80      ! ----------------------------------------- ! 
    7081      ! 
    7182      ipk = K_SIZE(ptab)   ! 3rd dimension 
     
    7384      ipf = F_SIZE(ptab)   ! 5th    -      use in "multi" case (array of pointers) 
    7485      ! 
     86      IF( PRESENT(ihlcom) ) THEN   ;   ihl = ihlcom 
     87      ELSE                         ;   ihl = 1 
     88      END IF 
     89      ! 
    7590      IF( narea == 1 .AND. numcom == -1 ) CALL mpp_report( cdname, ipk, ipl, ipf, ld_lbc = .TRUE. ) 
    7691      ! 
    77       IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value 
    78       ELSE                         ;   zland = 0._wp     ! zero by default 
    79       ENDIF 
    80  
    81       ! ------------------------------- ! 
    82       !   standard boundary treatment   !    ! CAUTION: semi-column notation is often impossible 
    83       ! ------------------------------- ! 
    84       ! 
    85       IF( .NOT. PRESENT( cd_mpp ) ) THEN     !==  standard close or cyclic treatment  ==! 
    86          ! 
    87          DO jf = 1, ipf                      ! number of arrays to be treated 
    88             ! 
    89             !                                ! East-West boundaries 
    90             IF( l_Iperio ) THEN                    !* cyclic 
    91                ARRAY_IN( 1 ,:,:,:,jf) = ARRAY_IN(jpim1,:,:,:,jf) 
    92                ARRAY_IN(jpi,:,:,:,jf) = ARRAY_IN(  2  ,:,:,:,jf) 
    93             ELSE                                   !* closed 
    94                IF( .NOT. NAT_IN(jf) == 'F' )   ARRAY_IN(     1       :nn_hls,:,:,:,jf) = zland    ! east except F-point 
    95                                                ARRAY_IN(nlci-nn_hls+1:jpi   ,:,:,:,jf) = zland    ! west 
    96             ENDIF 
    97             !                                ! North-South boundaries 
    98             IF( l_Jperio ) THEN                    !* cyclic (only with no mpp j-split) 
    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    ! south except F-point 
    103                                                ARRAY_IN(:,nlcj-nn_hls+1:jpj   ,:,:,jf) = zland    ! north 
     92      IF     ( PRESENT(lsend) .AND. PRESENT(lrecv) ) THEN 
     93         llsend_we = lsend(1)   ;   llsend_ea = lsend(2)   ;   llsend_so = lsend(3)   ;   llsend_no = lsend(4) 
     94         llrecv_we = lrecv(1)   ;   llrecv_ea = lrecv(2)   ;   llrecv_so = lrecv(3)   ;   llrecv_no = lrecv(4) 
     95      ELSE IF( PRESENT(lsend) .OR.  PRESENT(lrecv) ) THEN 
     96         WRITE(ctmp1,*) ' E R R O R : Routine ', cdname, '  is calling lbc_lnk with only one of the two arguments lsend or lrecv' 
     97         WRITE(ctmp2,*) ' ========== ' 
     98         CALL ctl_stop( ' ', ctmp1, ctmp2, ' ' ) 
     99      ELSE   ! send and receive with every neighbour 
     100         llsend_we = nbondi ==  1 .OR. nbondi == 0   ! keep for compatibility, should be defined in mppini 
     101         llsend_ea = nbondi == -1 .OR. nbondi == 0   ! keep for compatibility, should be defined in mppini 
     102         llsend_so = nbondj ==  1 .OR. nbondj == 0   ! keep for compatibility, should be defined in mppini 
     103         llsend_no = nbondj == -1 .OR. nbondj == 0   ! keep for compatibility, should be defined in mppini 
     104         llrecv_we = llsend_we   ;   llrecv_ea = llsend_ea   ;   llrecv_so = llsend_so   ;   llrecv_no = llsend_no 
     105      END IF 
     106          
     107          
     108      lldo_nfd = npolj /= 0                      ! keep for compatibility, should be defined in mppini 
     109 
     110      zland = 0._wp                                     ! land filling value: zero by default 
     111      IF( PRESENT( pfillval ) )   zland = pfillval      ! set land value 
     112 
     113      ! define the method we will use to fill the halos in each direction 
     114      IF(              llrecv_we ) THEN   ;   ifill_we = jpfillmpi 
     115      ELSEIF(           l_Iperio ) THEN   ;   ifill_we = jpfillperio 
     116      ELSEIF( PRESENT(kfillmode) ) THEN   ;   ifill_we = kfillmode 
     117      ELSE                                ;   ifill_we = jpfillcst 
     118      END IF 
     119      ! 
     120      IF(              llrecv_ea ) THEN   ;   ifill_ea = jpfillmpi 
     121      ELSEIF(           l_Iperio ) THEN   ;   ifill_ea = jpfillperio 
     122      ELSEIF( PRESENT(kfillmode) ) THEN   ;   ifill_ea = kfillmode 
     123      ELSE                                ;   ifill_ea = jpfillcst 
     124      END IF 
     125      ! 
     126      IF(              llrecv_so ) THEN   ;   ifill_so = jpfillmpi 
     127      ELSEIF(           l_Jperio ) THEN   ;   ifill_so = jpfillperio 
     128      ELSEIF( PRESENT(kfillmode) ) THEN   ;   ifill_so = kfillmode 
     129      ELSE                                ;   ifill_so = jpfillcst 
     130      END IF 
     131      ! 
     132      IF(              llrecv_no ) THEN   ;   ifill_no = jpfillmpi 
     133      ELSEIF(           l_Jperio ) THEN   ;   ifill_no = jpfillperio 
     134      ELSEIF( PRESENT(kfillmode) ) THEN   ;   ifill_no = kfillmode 
     135      ELSE                                ;   ifill_no = jpfillcst 
     136      END IF 
     137      ! 
     138#if defined PRINT_CAUTION 
     139      ! 
     140      ! ================================================================================== ! 
     141      ! CAUTION: semi-column notation is often impossible because of the cpp preprocessing ! 
     142      ! ================================================================================== ! 
     143      ! 
     144#endif 
     145      ! 
     146      ! -------------------------------------------------- ! 
     147      !     1. Do east and west MPI exchange if needed     ! 
     148      ! -------------------------------------------------- ! 
     149      ! 
     150      ! Must exchange the whole column (from 1 to jpj) to get the corners if we have no south/north neighbourg 
     151      isize = ihl * jpj * ipk * ipl * ipf       
     152      ! 
     153      ! Allocate local temporary arrays to be sent/received. Fill arrays to be sent 
     154      IF( llsend_we )   ALLOCATE( zsnd_we(ihl,jpj,ipk,ipl,ipf) ) 
     155      IF( llsend_ea )   ALLOCATE( zsnd_ea(ihl,jpj,ipk,ipl,ipf) ) 
     156      IF( llrecv_we )   ALLOCATE( zrcv_we(ihl,jpj,ipk,ipl,ipf) ) 
     157      IF( llrecv_ea )   ALLOCATE( zrcv_ea(ihl,jpj,ipk,ipl,ipf) ) 
     158      ! 
     159      IF( llsend_we ) THEN   ! copy western side of the inner mpi domain in local temporary array to be sent by MPI 
     160         ishift = ihl 
     161         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     162            zsnd_we(ji,jj,jk,jl,jf) = ARRAY_IN(ishift+ji,jj,jk,jl,jf)   ! ihl + 1 -> 2*ihl 
     163         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     164      ENDIF 
     165      ! 
     166      IF(llsend_ea  ) THEN   ! copy eastern side of the inner mpi domain in local temporary array to be sent by MPI 
     167         ishift = jpi - 2 * ihl 
     168         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     169            zsnd_ea(ji,jj,jk,jl,jf) = ARRAY_IN(ishift+ji,jj,jk,jl,jf)   ! jpi - 2*ihl + 1 -> jpi - ihl 
     170         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     171      ENDIF 
     172      ! 
     173      IF( ln_timing ) CALL tic_tac(.TRUE.) 
     174      ! 
     175      ! non-blocking send of the western/eastern side using local temporary arrays 
     176      IF( llsend_we )   CALL mppsend( 1, zsnd_we(1,1,1,1,1), isize, nowe, ireq_we ) 
     177      IF( llsend_ea )   CALL mppsend( 2, zsnd_ea(1,1,1,1,1), isize, noea, ireq_ea ) 
     178      ! blocking receive of the western/eastern halo in local temporary arrays 
     179      IF( llrecv_we )   CALL mpprecv( 2, zrcv_we(1,1,1,1,1), isize, nowe ) 
     180      IF( llrecv_ea )   CALL mpprecv( 1, zrcv_ea(1,1,1,1,1), isize, noea ) 
     181      ! 
     182      IF( ln_timing ) CALL tic_tac(.FALSE.) 
     183      ! 
     184      ! 
     185      ! ----------------------------------- ! 
     186      !     2. Fill east and west halos     ! 
     187      ! ----------------------------------- ! 
     188      ! 
     189      ! 2.1 fill weastern halo 
     190      ! ---------------------- 
     191      ! ishift = 0                         ! fill halo from ji = 1 to ihl 
     192      SELECT CASE ( ifill_we ) 
     193      CASE ( jpfillnothing )               ! no filling  
     194      CASE ( jpfillmpi   )                 ! use data received by MPI  
     195         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     196            ARRAY_IN(ji,jj,jk,jl,jf) = zrcv_we(ji,jj,jk,jl,jf)   ! 1 -> ihl 
     197         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     198      CASE ( jpfillperio )                 ! use east-weast periodicity 
     199         ishift2 = jpi - 2 * ihl 
     200         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     201            ARRAY_IN(ji,jj,jk,jl,jf) = ARRAY_IN(ishift2+ji,jj,jk,jl,jf) 
     202         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     203      CASE ( jpfillcopy  )                 ! filling with inner domain values 
     204         DO jf = 1, ipf                               ! number of arrays to be treated 
     205            IF( .NOT. NAT_IN(jf) == 'F' ) THEN        ! do nothing for F point 
     206               DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     207                  ARRAY_IN(ji,jj,jk,jl,jf) = ARRAY_IN(ihl+1,jj,jk,jl,jf) 
     208               END DO   ;   END DO   ;   END DO   ;   END DO 
    104209            ENDIF 
    105210         END DO 
    106          ! 
    107       ENDIF 
    108  
    109       ! ------------------------------- ! 
    110       !      East and west exchange     ! 
    111       ! ------------------------------- ! 
    112       ! we play with the neigbours AND the row number because of the periodicity 
    113       ! 
    114       IF( ABS(nbondi) == 1 ) ALLOCATE( zt3ew(jpj,nn_hls,ipk,ipl,ipf,1), zt3we(jpj,nn_hls,ipk,ipl,ipf,1) ) 
    115       IF(     nbondi  == 0 ) ALLOCATE( zt3ew(jpj,nn_hls,ipk,ipl,ipf,2), zt3we(jpj,nn_hls,ipk,ipl,ipf,2) ) 
    116       ! 
    117       SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions 
    118       CASE ( -1 ) 
    119          iihom = nlci-nreci 
    120          DO jf = 1, ipf 
    121             DO jl = 1, ipl 
    122                DO jk = 1, ipk 
    123                   DO jh = 1, nn_hls 
    124                      zt3we(:,jh,jk,jl,jf,1) = ARRAY_IN(iihom +jh,:,jk,jl,jf) 
    125                   END DO 
    126                END DO 
    127             END DO 
    128          END DO 
    129       CASE ( 0 ) 
    130          iihom = nlci-nreci 
    131          DO jf = 1, ipf 
    132             DO jl = 1, ipl 
    133                DO jk = 1, ipk 
    134                   DO jh = 1, nn_hls 
    135                      zt3ew(:,jh,jk,jl,jf,1) = ARRAY_IN(nn_hls+jh,:,jk,jl,jf) 
    136                      zt3we(:,jh,jk,jl,jf,1) = ARRAY_IN(iihom +jh,:,jk,jl,jf) 
    137                   END DO 
    138                END DO 
    139             END DO 
    140          END DO 
    141       CASE ( 1 ) 
    142          iihom = nlci-nreci 
    143          DO jf = 1, ipf 
    144             DO jl = 1, ipl 
    145                DO jk = 1, ipk 
    146                   DO jh = 1, nn_hls 
    147                      zt3ew(:,jh,jk,jl,jf,1) = ARRAY_IN(nn_hls+jh,:,jk,jl,jf) 
    148                   END DO 
    149                END DO 
    150             END DO 
     211      CASE ( jpfillcst   )                 ! filling with constant value 
     212         DO jf = 1, ipf                               ! number of arrays to be treated 
     213            IF( .NOT. NAT_IN(jf) == 'F' ) THEN        ! do nothing for F point 
     214               DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     215                  ARRAY_IN(ji,jj,jk,jl,jf) = zland 
     216               END DO;   END DO   ;   END DO   ;   END DO 
     217            ENDIF 
    151218         END DO 
    152219      END SELECT 
    153       !                           ! Migrations 
    154       imigr = nn_hls * jpj * ipk * ipl * ipf       
    155       ! 
    156       IF( ln_timing ) CALL tic_tac(.TRUE.) 
    157       ! 
    158       SELECT CASE ( nbondi ) 
    159       CASE ( -1 ) 
    160          CALL mppsend( 2, zt3we(1,1,1,1,1,1), imigr, noea, ml_req1 ) 
    161          CALL mpprecv( 1, zt3ew(1,1,1,1,1,1), imigr, noea ) 
    162          IF(l_isend)   CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    163       CASE ( 0 ) 
    164          CALL mppsend( 1, zt3ew(1,1,1,1,1,1), imigr, nowe, ml_req1 ) 
    165          CALL mppsend( 2, zt3we(1,1,1,1,1,1), imigr, noea, ml_req2 ) 
    166          CALL mpprecv( 1, zt3ew(1,1,1,1,1,2), imigr, noea ) 
    167          CALL mpprecv( 2, zt3we(1,1,1,1,1,2), imigr, nowe ) 
    168          IF(l_isend)   CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    169          IF(l_isend)   CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    170       CASE ( 1 ) 
    171          CALL mppsend( 1, zt3ew(1,1,1,1,1,1), imigr, nowe, ml_req1 ) 
    172          CALL mpprecv( 2, zt3we(1,1,1,1,1,1), imigr, nowe ) 
    173          IF(l_isend)   CALL mpi_wait(ml_req1, ml_stat, ml_err ) 
     220      ! 
     221      ! 2.2 fill eastern halo 
     222      ! --------------------- 
     223      ishift = jpi - ihl                ! fill halo from ji = jpi-ihl+1 to jpi  
     224      SELECT CASE ( ifill_ea ) 
     225      CASE ( jpfillnothing )               ! no filling  
     226      CASE ( jpfillmpi   )                 ! use data received by MPI  
     227         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     228            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = zrcv_ea(ji,jj,jk,jl,jf)   ! jpi - ihl + 1 -> jpi 
     229         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     230      CASE ( jpfillperio )                 ! use east-weast periodicity 
     231         ishift2 = ihl 
     232         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     233            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = ARRAY_IN(ishift2+ji,jj,jk,jl,jf) 
     234         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     235      CASE ( jpfillcopy  )                 ! filling with inner domain values 
     236         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     237            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = ARRAY_IN(ishift,jj,jk,jl,jf) 
     238         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     239      CASE ( jpfillcst   )                 ! filling with constant value 
     240         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, ihl 
     241            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = zland 
     242         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
    174243      END SELECT 
    175       ! 
    176       IF( ln_timing ) CALL tic_tac(.FALSE.) 
    177       ! 
    178       !                           ! Write Dirichlet lateral conditions 
    179       iihom = nlci-nn_hls 
    180       ! 
    181       SELECT CASE ( nbondi ) 
    182       CASE ( -1 ) 
    183          DO jf = 1, ipf 
    184             DO jl = 1, ipl 
    185                DO jk = 1, ipk 
    186                   DO jh = 1, nn_hls 
    187                      ARRAY_IN(iihom+jh,:,jk,jl,jf) = zt3ew(:,jh,jk,jl,jf,1) 
    188                   END DO 
    189                END DO 
    190             END DO 
    191          END DO 
    192       CASE ( 0 ) 
    193          DO jf = 1, ipf 
    194             DO jl = 1, ipl 
    195                DO jk = 1, ipk 
    196                   DO jh = 1, nn_hls 
    197                      ARRAY_IN(jh      ,:,jk,jl,jf) = zt3we(:,jh,jk,jl,jf,2) 
    198                      ARRAY_IN(iihom+jh,:,jk,jl,jf) = zt3ew(:,jh,jk,jl,jf,2) 
    199                   END DO 
    200                END DO 
    201             END DO 
    202          END DO 
    203       CASE ( 1 ) 
    204          DO jf = 1, ipf 
    205             DO jl = 1, ipl 
    206                DO jk = 1, ipk 
    207                   DO jh = 1, nn_hls 
    208                      ARRAY_IN(jh      ,:,jk,jl,jf) = zt3we(:,jh,jk,jl,jf,1) 
    209                   END DO 
    210                END DO 
    211             END DO 
    212          END DO 
    213       END SELECT 
    214       ! 
    215       IF( nbondi /= 2 ) DEALLOCATE( zt3ew, zt3we ) 
    216244      ! 
    217245      ! ------------------------------- ! 
    218246      !     3. north fold treatment     ! 
    219247      ! ------------------------------- ! 
     248      ! 
    220249      ! do it before south directions so concerned processes can do it without waiting for the comm with the sourthern neighbor 
    221       IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN 
     250      ! 
     251      IF( lldo_nfd .AND. ifill_no /= jpfillnothing ) THEN 
    222252         ! 
    223253         SELECT CASE ( jpni ) 
     
    226256         END SELECT 
    227257         ! 
    228       ENDIF 
    229       ! 
    230       ! ------------------------------- ! 
    231       !  4. North and south directions  ! 
    232       ! ------------------------------- ! 
    233       ! always closed : we play only with the neigbours 
    234       ! 
    235       IF( ABS(nbondj) == 1 ) ALLOCATE( zt3ns(jpi,nn_hls,ipk,ipl,ipf,1), zt3sn(jpi,nn_hls,ipk,ipl,ipf,1) ) 
    236       IF(     nbondj  == 0 ) ALLOCATE( zt3ns(jpi,nn_hls,ipk,ipl,ipf,2), zt3sn(jpi,nn_hls,ipk,ipl,ipf,2) ) 
    237       ! 
    238       SELECT CASE ( nbondj ) 
    239       CASE ( -1 ) 
    240          ijhom = nlcj-nrecj 
    241          DO jf = 1, ipf 
    242             DO jl = 1, ipl 
    243                DO jk = 1, ipk 
    244                   DO jh = 1, nn_hls 
    245                      zt3sn(:,jh,jk,jl,jf,1) = ARRAY_IN(:,ijhom +jh,jk,jl,jf) 
    246                   END DO 
    247                END DO 
    248             END DO 
     258         ifill_no = jpfillnothing  ! force to do nothing for the northern halo as we just done the north pole folding 
     259         ! 
     260      ENDIF 
     261      ! 
     262      ! ---------------------------------------------------- ! 
     263      !     4. Do north and south MPI exchange if needed     ! 
     264      ! ---------------------------------------------------- ! 
     265      ! 
     266      IF( llsend_so )   ALLOCATE( zsnd_so(jpi,ihl,ipk,ipl,ipf) ) 
     267      IF( llsend_no )   ALLOCATE( zsnd_no(jpi,ihl,ipk,ipl,ipf) ) 
     268      IF( llrecv_so )   ALLOCATE( zrcv_so(jpi,ihl,ipk,ipl,ipf) ) 
     269      IF( llrecv_no )   ALLOCATE( zrcv_no(jpi,ihl,ipk,ipl,ipf) ) 
     270      ! 
     271      isize = jpi * ihl * ipk * ipl * ipf       
     272 
     273      ! allocate local temporary arrays to be sent/received. Fill arrays to be sent 
     274      IF( llsend_so ) THEN   ! copy sourhern side of the inner mpi domain in local temporary array to be sent by MPI 
     275         ishift = ihl 
     276         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     277            zsnd_so(ji,jj,jk,jl,jf) = ARRAY_IN(ji,ishift+jj,jk,jl,jf)   ! ihl+1 -> 2*ihl 
     278         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     279      ENDIF 
     280      ! 
     281      IF( llsend_no ) THEN   ! copy eastern side of the inner mpi domain in local temporary array to be sent by MPI 
     282         ishift = jpj - 2 * ihl 
     283         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     284            zsnd_no(ji,jj,jk,jl,jf) = ARRAY_IN(ji,ishift+jj,jk,jl,jf)   ! jpj-2*ihl+1 -> jpj-ihl 
     285         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     286      ENDIF 
     287      ! 
     288      IF( ln_timing ) CALL tic_tac(.TRUE.) 
     289      ! 
     290      ! non-blocking send of the southern/northern side 
     291      IF( llsend_so )   CALL mppsend( 3, zsnd_so(1,1,1,1,1), isize, noso, ireq_so ) 
     292      IF( llsend_no )   CALL mppsend( 4, zsnd_no(1,1,1,1,1), isize, nono, ireq_no ) 
     293      ! blocking receive of the southern/northern halo 
     294      IF( llrecv_so )   CALL mpprecv( 4, zrcv_so(1,1,1,1,1), isize, noso ) 
     295      IF( llrecv_no )   CALL mpprecv( 3, zrcv_no(1,1,1,1,1), isize, nono ) 
     296      ! 
     297      IF( ln_timing ) CALL tic_tac(.FALSE.) 
     298      ! 
     299      ! ------------------------------------- ! 
     300      !     5. Fill south and north halos     ! 
     301      ! ------------------------------------- ! 
     302      ! 
     303      ! 5.1 fill southern halo 
     304      ! ---------------------- 
     305      ! ishift = 0                         ! fill halo from jj = 1 to ihl 
     306      SELECT CASE ( ifill_so ) 
     307      CASE ( jpfillnothing )               ! no filling  
     308      CASE ( jpfillmpi   )                 ! use data received by MPI  
     309         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     310            ARRAY_IN(ji,jj,jk,jl,jf) = zrcv_so(ji,jj,jk,jl,jf)   ! 1 -> ihl 
     311         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     312      CASE ( jpfillperio )                 ! use north-south periodicity 
     313         ishift2 = jpj - 2 * ihl 
     314         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     315            ARRAY_IN(ji,jj,jk,jl,jf) = ARRAY_IN(ji,ishift2+jj,jk,jl,jf) 
     316         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     317      CASE ( jpfillcopy  )                 ! filling with inner domain values 
     318         DO jf = 1, ipf                               ! number of arrays to be treated 
     319            IF( .NOT. NAT_IN(jf) == 'F' ) THEN        ! do nothing for F point 
     320               DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     321                  ARRAY_IN(ji,jj,jk,jl,jf) = ARRAY_IN(ji,ihl+1,jk,jl,jf) 
     322               END DO   ;   END DO   ;   END DO   ;   END DO 
     323            ENDIF 
    249324         END DO 
    250       CASE ( 0 ) 
    251          ijhom = nlcj-nrecj 
    252          DO jf = 1, ipf 
    253             DO jl = 1, ipl 
    254                DO jk = 1, ipk 
    255                   DO jh = 1, nn_hls 
    256                      zt3sn(:,jh,jk,jl,jf,1) = ARRAY_IN(:,ijhom +jh,jk,jl,jf) 
    257                      zt3ns(:,jh,jk,jl,jf,1) = ARRAY_IN(:,nn_hls+jh,jk,jl,jf) 
    258                   END DO 
    259                END DO 
    260             END DO 
    261          END DO 
    262       CASE ( 1 ) 
    263          ijhom = nlcj-nrecj 
    264          DO jf = 1, ipf 
    265             DO jl = 1, ipl 
    266                DO jk = 1, ipk 
    267                   DO jh = 1, nn_hls 
    268                      zt3ns(:,jh,jk,jl,jf,1) = ARRAY_IN(:,nn_hls+jh,jk,jl,jf) 
    269                   END DO 
    270                END DO 
    271             END DO 
     325      CASE ( jpfillcst   )                 ! filling with constant value 
     326         DO jf = 1, ipf                               ! number of arrays to be treated 
     327            IF( .NOT. NAT_IN(jf) == 'F' ) THEN        ! do nothing for F point 
     328               DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi  
     329                  ARRAY_IN(ji,jj,jk,jl,jf) = zland 
     330               END DO;   END DO   ;   END DO   ;   END DO 
     331            ENDIF 
    272332         END DO 
    273333      END SELECT 
    274334      ! 
    275       !                           ! Migrations 
    276       imigr = nn_hls * jpi * ipk * ipl * ipf 
    277       ! 
    278       IF( ln_timing ) CALL tic_tac(.TRUE.) 
    279       !  
    280       SELECT CASE ( nbondj ) 
    281       CASE ( -1 ) 
    282          CALL mppsend( 4, zt3sn(1,1,1,1,1,1), imigr, nono, ml_req1 ) 
    283          CALL mpprecv( 3, zt3ns(1,1,1,1,1,1), imigr, nono ) 
    284          IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err ) 
    285       CASE ( 0 ) 
    286          CALL mppsend( 3, zt3ns(1,1,1,1,1,1), imigr, noso, ml_req1 ) 
    287          CALL mppsend( 4, zt3sn(1,1,1,1,1,1), imigr, nono, ml_req2 ) 
    288          CALL mpprecv( 3, zt3ns(1,1,1,1,1,2), imigr, nono ) 
    289          CALL mpprecv( 4, zt3sn(1,1,1,1,1,2), imigr, noso ) 
    290          IF(l_isend)   CALL mpi_wait(ml_req1, ml_stat, ml_err ) 
    291          IF(l_isend)   CALL mpi_wait(ml_req2, ml_stat, ml_err ) 
    292       CASE ( 1 ) 
    293          CALL mppsend( 3, zt3ns(1,1,1,1,1,1), imigr, noso, ml_req1 ) 
    294          CALL mpprecv( 4, zt3sn(1,1,1,1,1,1), imigr, noso ) 
    295          IF(l_isend)   CALL mpi_wait(ml_req1, ml_stat, ml_err ) 
     335      ! 5.2 fill northern halo 
     336      ! ---------------------- 
     337      ishift = jpj - ihl                ! fill halo from jj = jpj-ihl+1 to jpj  
     338      SELECT CASE ( ifill_no ) 
     339      CASE ( jpfillnothing )               ! no filling  
     340      CASE ( jpfillmpi   )                 ! use data received by MPI  
     341         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     342            ARRAY_IN(ji,ishift+jj,jk,jl,jf) = zrcv_no(ji,jj,jk,jl,jf)   ! jpj-ihl+1 -> jpj 
     343         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     344      CASE ( jpfillperio )                 ! use north-south periodicity 
     345         ishift2 = ihl 
     346         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     347            ARRAY_IN(ji,ishift+jj,jk,jl,jf) = ARRAY_IN(ji,ishift2+jj,jk,jl,jf) 
     348         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     349      CASE ( jpfillcopy  )                 ! filling with inner domain values 
     350         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     351            ARRAY_IN(ji,ishift+jj,jk,jl,jf) = ARRAY_IN(ji,ishift,jk,jl,jf) 
     352         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     353      CASE ( jpfillcst   )                 ! filling with constant value 
     354         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, ihl   ;   DO ji = 1, jpi 
     355            ARRAY_IN(ji,ishift+jj,jk,jl,jf) = zland 
     356         END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
    296357      END SELECT 
    297358      ! 
    298       IF( ln_timing ) CALL tic_tac(.FALSE.) 
    299       !                           ! Write Dirichlet lateral conditions 
    300       ijhom = nlcj-nn_hls 
    301       ! 
    302       SELECT CASE ( nbondj ) 
    303       CASE ( -1 ) 
    304          DO jf = 1, ipf 
    305             DO jl = 1, ipl 
    306                DO jk = 1, ipk 
    307                   DO jh = 1, nn_hls 
    308                      ARRAY_IN(:,ijhom+jh,jk,jl,jf) = zt3ns(:,jh,jk,jl,jf,1) 
    309                   END DO 
    310                END DO 
    311             END DO 
    312          END DO 
    313       CASE ( 0 ) 
    314          DO jf = 1, ipf 
    315             DO jl = 1, ipl 
    316                DO jk = 1, ipk 
    317                   DO jh = 1, nn_hls 
    318                      ARRAY_IN(:,      jh,jk,jl,jf) = zt3sn(:,jh,jk,jl,jf,2) 
    319                      ARRAY_IN(:,ijhom+jh,jk,jl,jf) = zt3ns(:,jh,jk,jl,jf,2) 
    320                   END DO 
    321                END DO 
    322             END DO 
    323          END DO 
    324       CASE ( 1 ) 
    325          DO jf = 1, ipf 
    326             DO jl = 1, ipl 
    327                DO jk = 1, ipk 
    328                   DO jh = 1, nn_hls 
    329                      ARRAY_IN(:,jh,jk,jl,jf) = zt3sn(:,jh,jk,jl,jf,1) 
    330                   END DO 
    331                END DO 
    332             END DO 
    333          END DO 
    334       END SELECT 
    335       ! 
    336       IF( nbondj /= 2 ) DEALLOCATE( zt3ns, zt3sn ) 
     359      ! -------------------------------------------- ! 
     360      !     6. deallocate local temporary arrays     ! 
     361      ! -------------------------------------------- ! 
     362      ! 
     363      IF( llsend_we ) THEN 
     364         CALL mpi_wait(ireq_we, istat, ierr ) 
     365         DEALLOCATE( zsnd_we ) 
     366      ENDIF 
     367      IF( llsend_ea )  THEN 
     368         CALL mpi_wait(ireq_ea, istat, ierr ) 
     369         DEALLOCATE( zsnd_ea ) 
     370      ENDIF 
     371      IF( llsend_so ) THEN 
     372         CALL mpi_wait(ireq_so, istat, ierr ) 
     373         DEALLOCATE( zsnd_so ) 
     374      ENDIF 
     375      IF( llsend_no ) THEN 
     376         CALL mpi_wait(ireq_no, istat, ierr ) 
     377         DEALLOCATE( zsnd_no ) 
     378      ENDIF 
     379      ! 
     380      IF( llrecv_we )   DEALLOCATE( zrcv_we ) 
     381      IF( llrecv_ea )   DEALLOCATE( zrcv_ea ) 
     382      IF( llrecv_so )   DEALLOCATE( zrcv_so ) 
     383      IF( llrecv_no )   DEALLOCATE( zrcv_no ) 
    337384      ! 
    338385   END SUBROUTINE ROUTINE_LNK 
Note: See TracChangeset for help on using the changeset viewer.