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 14986 for NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/TRA/traadv_mus.F90 – NEMO

Ignore:
Timestamp:
2021-06-14T13:34:08+02:00 (3 years ago)
Author:
sparonuz
Message:

Merge trunk -r14984:HEAD

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/TRA/traadv_mus.F90

    r14644 r14986  
    8282      LOGICAL                                  , INTENT(in   ) ::   ld_msc_ups      ! use upstream scheme within muscl 
    8383      REAL(wp)                                 , INTENT(in   ) ::   p2dt            ! tracer time-step 
    84       ! TEMP: [tiling] This can be A2D(nn_hls) if using XIOS (subdomain support) 
     84      ! TEMP: [tiling] This can be A2D(nn_hls) after all lbc_lnks removed in the nn_hls = 2 case in tra_adv_fct 
    8585      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU, pV, pW      ! 3 ocean volume flux components 
    8686      REAL(dp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! tracers and RHS of tracer equation 
     
    9494      !!---------------------------------------------------------------------- 
    9595      ! 
    96       IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     96      IF( .NOT. l_istiled .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    9797         IF( kt == kit000 )  THEN 
    9898            IF(lwp) WRITE(numout,*) 
     
    140140            zwy(ji,jj,jk) = vmask(ji,jj,jk) * ( pt(ji,jj+1,jk,jn,Kbb) - pt(ji,jj,jk,jn,Kbb) ) 
    141141         END_3D 
    142          ! lateral boundary conditions   (changed sign) 
    143          IF ( nn_hls.EQ.1 ) CALL lbc_lnk( 'traadv_mus', zwx, 'U', -1.0_wp , zwy, 'V', -1.0_wp ) 
    144142         !                                !-- Slopes of tracer 
    145143         zslpx(:,:,jpk) = 0._wp                 ! bottom values 
    146144         zslpy(:,:,jpk) = 0._wp 
    147          DO_3D( nn_hls-1, 1, nn_hls-1, 1, 1, jpkm1 ) 
     145         DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 1, jpkm1 ) 
    148146            zslpx(ji,jj,jk) =                       ( zwx(ji,jj,jk) + zwx(ji-1,jj  ,jk) )   & 
    149147               &            * ( 0.25 + SIGN( 0.25_wp, zwx(ji,jj,jk) * zwx(ji-1,jj  ,jk) ) ) 
     
    152150         END_3D 
    153151         ! 
    154          DO_3D( nn_hls-1, 1, nn_hls-1, 1, 1, jpkm1 )    !-- Slopes limitation 
     152         DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 1, jpkm1 )    !-- Slopes limitation 
    155153            zslpx(ji,jj,jk) = SIGN( 1.0_wp, zslpx(ji,jj,jk) ) * MIN(    ABS( zslpx(ji  ,jj,jk) ),   & 
    156154               &                                                     2.*ABS( zwx  (ji-1,jj,jk) ),   & 
     
    160158               &                                                     2.*ABS( zwy  (ji,jj  ,jk) ) ) 
    161159         END_3D 
    162          ! 
    163          DO_3D( nn_hls-1, 0, nn_hls-1, 0, 1, jpkm1 )    !-- MUSCL horizontal advective fluxes 
     160         ! NOTE [ comm_cleanup ] : need to change sign to ensure halo 1 - halo 2 compatibility 
     161         IF ( nn_hls==1 ) CALL lbc_lnk( 'traadv_mus', zslpx, 'T', -1.0_wp , zslpy, 'T', -1.0_wp )   ! lateral boundary conditions   (changed sign) 
     162         ! 
     163         DO_3D( 1, 0, 1, 0, 1, jpkm1 )    !-- MUSCL horizontal advective fluxes 
    164164            ! MUSCL fluxes 
    165165            z0u = SIGN( 0.5_wp, pU(ji,jj,jk) ) 
     
    177177            zwy(ji,jj,jk) = pV(ji,jj,jk) * ( zalpha * zzwx + (1.-zalpha) * zzwy ) 
    178178         END_3D 
    179          IF ( nn_hls.EQ.1 ) CALL lbc_lnk( 'traadv_mus', zwx, 'U', -1.0_wp , zwy, 'V', -1.0_wp )   ! lateral boundary conditions   (changed sign) 
    180179         ! 
    181180         DO_3D( 0, 0, 0, 0, 1, jpkm1 )    !-- Tracer advective trend 
Note: See TracChangeset for help on using the changeset viewer.