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 13766 for NEMO/branches/2020/dev_12905_xios_ancil/src/OCE/LBC/mpp_lnk_generic.h90 – NEMO

Ignore:
Timestamp:
2020-11-10T12:57:08+01:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2475: merge with trunk rev 13688

Location:
NEMO/branches/2020/dev_12905_xios_ancil
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_12905_xios_ancil

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
        88 
        99# SETTE 
        10 ^/utils/CI/sette@HEAD         sette 
         10^/utils/CI/sette@13559        sette 
  • NEMO/branches/2020/dev_12905_xios_ancil/src/OCE/LBC/mpp_lnk_generic.h90

    r11536 r13766  
    55#   define OPT_K(k)                 ,ipf 
    66#   if defined DIM_2d 
    7 #      define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_2D)                , INTENT(inout) ::   ptab(f) 
     7#      if defined SINGLE_PRECISION 
     8#         define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_2D_sp)                , INTENT(inout) ::   ptab(f) 
     9#      else 
     10#         define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_2D_dp)                , INTENT(inout) ::   ptab(f) 
     11#      endif 
    812#      define ARRAY_IN(i,j,k,l,f)      ptab(f)%pt2d(i,j) 
    913#      define K_SIZE(ptab)             1 
     
    1115#   endif 
    1216#   if defined DIM_3d 
    13 #      define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_3D)                , INTENT(inout) ::   ptab(f) 
     17#      if defined SINGLE_PRECISION 
     18#         define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_3D_sp)                , INTENT(inout) ::   ptab(f) 
     19#      else 
     20#         define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_3D_dp)                , INTENT(inout) ::   ptab(f) 
     21#      endif 
    1422#      define ARRAY_IN(i,j,k,l,f)      ptab(f)%pt3d(i,j,k) 
    1523#      define K_SIZE(ptab)             SIZE(ptab(1)%pt3d,3) 
     
    1725#   endif 
    1826#   if defined DIM_4d 
    19 #      define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_4D)                , INTENT(inout) ::   ptab(f) 
     27#      if defined SINGLE_PRECISION 
     28#         define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_4D_sp)                , INTENT(inout) ::   ptab(f) 
     29#      else 
     30#         define ARRAY_TYPE(i,j,k,l,f)    TYPE(PTR_4D_dp)                , INTENT(inout) ::   ptab(f) 
     31#      endif 
    2032#      define ARRAY_IN(i,j,k,l,f)      ptab(f)%pt4d(i,j,k,l) 
    2133#      define K_SIZE(ptab)             SIZE(ptab(1)%pt4d,3) 
     
    2335#   endif 
    2436#else 
    25 #   define ARRAY_TYPE(i,j,k,l,f)    REAL(wp)                    , INTENT(inout) ::   ARRAY_IN(i,j,k,l,f) 
     37#   if defined SINGLE_PRECISION 
     38#      define ARRAY_TYPE(i,j,k,l,f)    REAL(sp)                    , INTENT(inout) ::   ARRAY_IN(i,j,k,l,f) 
     39#   else 
     40#      define ARRAY_TYPE(i,j,k,l,f)    REAL(dp)                    , INTENT(inout) ::   ARRAY_IN(i,j,k,l,f) 
     41#   endif 
    2642#   define NAT_IN(k)                cd_nat 
    2743#   define SGN_IN(k)                psgn 
     
    4561#endif 
    4662 
     63# if defined SINGLE_PRECISION 
     64#    define PRECISION sp 
     65#    define SENDROUTINE mppsend_sp 
     66#    define RECVROUTINE mpprecv_sp 
     67# else 
     68#    define PRECISION dp 
     69#    define SENDROUTINE mppsend_dp 
     70#    define RECVROUTINE mpprecv_dp 
     71# endif 
     72 
    4773#if defined MULTI 
    48    SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn, kfld, kfillmode, pfillval, lsend, lrecv, ihlcom ) 
     74   SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn, kfld, kfillmode, pfillval, lsend, lrecv ) 
    4975      INTEGER             , INTENT(in   ) ::   kfld        ! number of pt3d arrays 
    5076#else 
    51    SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn      , kfillmode, pfillval, lsend, lrecv, ihlcom ) 
     77   SUBROUTINE ROUTINE_LNK( cdname, ptab, cd_nat, psgn      , kfillmode, pfillval, lsend, lrecv ) 
    5278#endif 
    5379      ARRAY_TYPE(:,:,:,:,:)                                        ! array or pointer of arrays on which the boundary condition is applied 
     
    5884      REAL(wp),             OPTIONAL, INTENT(in   ) ::   pfillval    ! background value (used at closed boundaries) 
    5985      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 
    6186      ! 
    6287      INTEGER  ::    ji,  jj,  jk,  jl,  jf      ! dummy loop indices 
     
    6691      INTEGER  ::   ierr 
    6792      INTEGER  ::   ifill_we, ifill_ea, ifill_so, ifill_no 
    68       INTEGER  ::   ihl                          ! number of ranks and rows to be communicated  
    6993      REAL(wp) ::   zland 
    7094      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 
     95      REAL(PRECISION), DIMENSION(:,:,:,:,:), ALLOCATABLE ::   zsnd_we, zrcv_we, zsnd_ea, zrcv_ea   ! east -west  & west - east  halos 
     96      REAL(PRECISION), DIMENSION(:,:,:,:,:), ALLOCATABLE ::   zsnd_so, zrcv_so, zsnd_no, zrcv_no   ! north-south & south-north  halos 
    7397      LOGICAL  ::   llsend_we, llsend_ea, llsend_no, llsend_so       ! communication send 
    7498      LOGICAL  ::   llrecv_we, llrecv_ea, llrecv_no, llrecv_so       ! communication receive  
     
    83107      ipl = L_SIZE(ptab)   ! 4th    - 
    84108      ipf = F_SIZE(ptab)   ! 5th    -      use in "multi" case (array of pointers) 
    85       ! 
    86       IF( PRESENT(ihlcom) ) THEN   ;   ihl = ihlcom 
    87       ELSE                         ;   ihl = 1 
    88       END IF 
    89109      ! 
    90110      IF( narea == 1 .AND. numcom == -1 ) CALL mpp_report( cdname, ipk, ipl, ipf, ld_lbc = .TRUE. ) 
     
    149169      ! 
    150170      ! 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       
     171      isize = nn_hls * jpj * ipk * ipl * ipf       
    152172      ! 
    153173      ! 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) ) 
     174      IF( llsend_we )   ALLOCATE( zsnd_we(nn_hls,jpj,ipk,ipl,ipf) ) 
     175      IF( llsend_ea )   ALLOCATE( zsnd_ea(nn_hls,jpj,ipk,ipl,ipf) ) 
     176      IF( llrecv_we )   ALLOCATE( zrcv_we(nn_hls,jpj,ipk,ipl,ipf) ) 
     177      IF( llrecv_ea )   ALLOCATE( zrcv_ea(nn_hls,jpj,ipk,ipl,ipf) ) 
    158178      ! 
    159179      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 
     180         ishift = nn_hls 
     181         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
     182            zsnd_we(ji,jj,jk,jl,jf) = ARRAY_IN(ishift+ji,jj,jk,jl,jf)   ! nn_hls + 1 -> 2*nn_hls 
    163183         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    164184      ENDIF 
    165185      ! 
    166186      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 
     187         ishift = jpi - 2 * nn_hls 
     188         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
     189            zsnd_ea(ji,jj,jk,jl,jf) = ARRAY_IN(ishift+ji,jj,jk,jl,jf)   ! jpi - 2*nn_hls + 1 -> jpi - nn_hls 
    170190         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    171191      ENDIF 
     
    174194      ! 
    175195      ! 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 ) 
     196      IF( llsend_we )   CALL SENDROUTINE( 1, zsnd_we(1,1,1,1,1), isize, nowe, ireq_we ) 
     197      IF( llsend_ea )   CALL SENDROUTINE( 2, zsnd_ea(1,1,1,1,1), isize, noea, ireq_ea ) 
    178198      ! 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 ) 
     199      IF( llrecv_we )   CALL RECVROUTINE( 2, zrcv_we(1,1,1,1,1), isize, nowe ) 
     200      IF( llrecv_ea )   CALL RECVROUTINE( 1, zrcv_ea(1,1,1,1,1), isize, noea ) 
    181201      ! 
    182202      IF( ln_timing ) CALL tic_tac(.FALSE.) 
     
    189209      ! 2.1 fill weastern halo 
    190210      ! ---------------------- 
    191       ! ishift = 0                         ! fill halo from ji = 1 to ihl 
     211      ! ishift = 0                         ! fill halo from ji = 1 to nn_hls 
    192212      SELECT CASE ( ifill_we ) 
    193213      CASE ( jpfillnothing )               ! no filling  
    194214      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 
     215         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
     216            ARRAY_IN(ji,jj,jk,jl,jf) = zrcv_we(ji,jj,jk,jl,jf)   ! 1 -> nn_hls 
     217         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    198218      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 
     219         ishift2 = jpi - 2 * nn_hls 
     220         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
    201221            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 
     222         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    203223      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 
    209             ENDIF 
    210          END DO 
     224         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
     225            ARRAY_IN(ji,jj,jk,jl,jf) = ARRAY_IN(nn_hls+1,jj,jk,jl,jf) 
     226         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    211227      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 
    218          END DO 
     228         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
     229            ARRAY_IN(ji,jj,jk,jl,jf) = zland 
     230         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    219231      END SELECT 
    220232      ! 
    221233      ! 2.2 fill eastern halo 
    222234      ! --------------------- 
    223       ishift = jpi - ihl                ! fill halo from ji = jpi-ihl+1 to jpi  
     235      ishift = jpi - nn_hls                ! fill halo from ji = jpi-nn_hls+1 to jpi  
    224236      SELECT CASE ( ifill_ea ) 
    225237      CASE ( jpfillnothing )               ! no filling  
    226238      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 
     239         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
     240            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = zrcv_ea(ji,jj,jk,jl,jf)   ! jpi - nn_hls + 1 -> jpi 
    229241         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    230242      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 
     243         ishift2 = nn_hls 
     244         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
    233245            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = ARRAY_IN(ishift2+ji,jj,jk,jl,jf) 
    234246         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    235247      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 
     248         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
    237249            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = ARRAY_IN(ishift,jj,jk,jl,jf) 
    238250         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    239251      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 
     252         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, jpj   ;   DO ji = 1, nn_hls 
    241253            ARRAY_IN(ishift+ji,jj,jk,jl,jf) = zland 
    242          END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     254         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    243255      END SELECT 
    244256      ! 
     
    252264         ! 
    253265         SELECT CASE ( jpni ) 
    254          CASE ( 1 )     ;   CALL lbc_nfd( ptab, NAT_IN(:), SGN_IN(:) OPT_K(:) )   ! only 1 northern proc, no mpp 
    255          CASE DEFAULT   ;   CALL mpp_nfd( ptab, NAT_IN(:), SGN_IN(:) OPT_K(:) )   ! for all northern procs. 
     266         CASE ( 1 )     ;   CALL lbc_nfd( ptab, NAT_IN(:), SGN_IN(:)                  OPT_K(:) )   ! only 1 northern proc, no mpp 
     267         CASE DEFAULT   ;   CALL mpp_nfd( ptab, NAT_IN(:), SGN_IN(:), ifill_no, zland OPT_K(:) )   ! for all northern procs. 
    256268         END SELECT 
    257269         ! 
     
    264276      ! ---------------------------------------------------- ! 
    265277      ! 
    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       
     278      IF( llsend_so )   ALLOCATE( zsnd_so(jpi,nn_hls,ipk,ipl,ipf) ) 
     279      IF( llsend_no )   ALLOCATE( zsnd_no(jpi,nn_hls,ipk,ipl,ipf) ) 
     280      IF( llrecv_so )   ALLOCATE( zrcv_so(jpi,nn_hls,ipk,ipl,ipf) ) 
     281      IF( llrecv_no )   ALLOCATE( zrcv_no(jpi,nn_hls,ipk,ipl,ipf) ) 
     282      ! 
     283      isize = jpi * nn_hls * ipk * ipl * ipf       
    272284 
    273285      ! allocate local temporary arrays to be sent/received. Fill arrays to be sent 
    274286      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 
     287         ishift = nn_hls 
     288         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
     289            zsnd_so(ji,jj,jk,jl,jf) = ARRAY_IN(ji,ishift+jj,jk,jl,jf)   ! nn_hls+1 -> 2*nn_hls 
    278290         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    279291      ENDIF 
    280292      ! 
    281293      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 
     294         ishift = jpj - 2 * nn_hls 
     295         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
     296            zsnd_no(ji,jj,jk,jl,jf) = ARRAY_IN(ji,ishift+jj,jk,jl,jf)   ! jpj-2*nn_hls+1 -> jpj-nn_hls 
    285297         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    286298      ENDIF 
     
    289301      ! 
    290302      ! 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 ) 
     303      IF( llsend_so )   CALL SENDROUTINE( 3, zsnd_so(1,1,1,1,1), isize, noso, ireq_so ) 
     304      IF( llsend_no )   CALL SENDROUTINE( 4, zsnd_no(1,1,1,1,1), isize, nono, ireq_no ) 
    293305      ! 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 ) 
     306      IF( llrecv_so )   CALL RECVROUTINE( 4, zrcv_so(1,1,1,1,1), isize, noso ) 
     307      IF( llrecv_no )   CALL RECVROUTINE( 3, zrcv_no(1,1,1,1,1), isize, nono ) 
    296308      ! 
    297309      IF( ln_timing ) CALL tic_tac(.FALSE.) 
     
    303315      ! 5.1 fill southern halo 
    304316      ! ---------------------- 
    305       ! ishift = 0                         ! fill halo from jj = 1 to ihl 
     317      ! ishift = 0                         ! fill halo from jj = 1 to nn_hls 
    306318      SELECT CASE ( ifill_so ) 
    307319      CASE ( jpfillnothing )               ! no filling  
    308320      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 
     321         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
     322            ARRAY_IN(ji,jj,jk,jl,jf) = zrcv_so(ji,jj,jk,jl,jf)   ! 1 -> nn_hls 
     323         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    312324      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 
     325         ishift2 = jpj - 2 * nn_hls 
     326         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
    315327            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 
     328         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    317329      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 
    324          END DO 
     330         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
     331            ARRAY_IN(ji,jj,jk,jl,jf) = ARRAY_IN(ji,nn_hls+1,jk,jl,jf) 
     332         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    325333      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 
    332          END DO 
     334         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi  
     335            ARRAY_IN(ji,jj,jk,jl,jf) = zland 
     336         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    333337      END SELECT 
    334338      ! 
    335339      ! 5.2 fill northern halo 
    336340      ! ---------------------- 
    337       ishift = jpj - ihl                ! fill halo from jj = jpj-ihl+1 to jpj  
     341      ishift = jpj - nn_hls                ! fill halo from jj = jpj-nn_hls+1 to jpj  
    338342      SELECT CASE ( ifill_no ) 
    339343      CASE ( jpfillnothing )               ! no filling  
    340344      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 
     345         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
     346            ARRAY_IN(ji,ishift+jj,jk,jl,jf) = zrcv_no(ji,jj,jk,jl,jf)   ! jpj-nn_hls+1 -> jpj 
    343347         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    344348      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 
     349         ishift2 = nn_hls 
     350         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
    347351            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 
     352         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    349353      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 
     354         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
    351355            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 
     356         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    353357      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 
     358         DO jf = 1, ipf   ;   DO jl = 1, ipl   ;   DO jk = 1, ipk   ;   DO jj = 1, nn_hls   ;   DO ji = 1, jpi 
    355359            ARRAY_IN(ji,ishift+jj,jk,jl,jf) = zland 
    356          END DO;   END DO   ;   END DO   ;   END DO   ;   END DO 
     360         END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
    357361      END SELECT 
    358362      ! 
     
    384388      ! 
    385389   END SUBROUTINE ROUTINE_LNK 
    386  
     390#undef PRECISION 
     391#undef SENDROUTINE 
     392#undef RECVROUTINE 
    387393#undef ARRAY_TYPE 
    388394#undef NAT_IN 
Note: See TracChangeset for help on using the changeset viewer.