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 13551 for NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traadv_ubs.F90 – NEMO

Ignore:
Timestamp:
2020-10-01T12:04:12+02:00 (4 years ago)
Author:
hadcv
Message:

#2365: Replace trd_tra workarounds with ctl_warn if using tiling

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traadv_ubs.F90

    r13516 r13551  
    1414   USE oce            ! ocean dynamics and active tracers 
    1515   USE dom_oce        ! ocean space and time domain 
    16    ! TEMP: This change not necessary after trd_tra is tiled 
    17    USE domain, ONLY : dom_tile 
    1816   USE trc_oce        ! share passive tracers/Ocean variables 
    1917   USE trd_oce        ! trends: ocean variables 
     
    9492      INTEGER                                  , INTENT(in   ) ::   kn_ubs_v        ! number of tracers 
    9593      REAL(wp)                                 , INTENT(in   ) ::   p2dt            ! tracer time-step 
    96       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     94      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    9795      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU, pV, pW      ! 3 ocean volume transport components 
    9896      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! tracers and RHS of tracer equation 
    9997      ! 
    100       ! TEMP: This change not necessary after trd_tra is tiled 
    101       INTEGER  ::   itile 
    10298      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    10399      REAL(wp) ::   ztra, zbtr, zcoef                       ! local scalars 
     
    105101      REAL(wp) ::   zfp_vj, zfm_vj, zcenvt, zeeu, zeev, z_hdivn    !   -      - 
    106102      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   ztu, ztv, zltu, zltv, zti, ztw     ! 3D workspace 
    107       ! TEMP: This change not necessary after trd_tra is tiled 
    108       REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   ztrdx, ztrdy, ztrdz 
    109       !!---------------------------------------------------------------------- 
    110       ! TEMP: This change not necessary after trd_tra is tiled 
    111       itile = ntile 
     103      !!---------------------------------------------------------------------- 
    112104      ! 
    113105      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     
    125117         IF(   cdtype == 'TRA' .AND. ( iom_use("uadv_heattr") .OR. iom_use("vadv_heattr") .OR. & 
    126118            &                          iom_use("uadv_salttr") .OR. iom_use("vadv_salttr")  ) ) l_hst = .TRUE. 
    127  
    128          ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    129          IF( kt == kit000 .AND. l_trd ) THEN 
    130             ALLOCATE( ztrdx(jpi,jpj,jpk), ztrdy(jpi,jpj,jpk), ztrdz(jpi,jpj,jpk) ) 
    131          ENDIF 
    132119      ENDIF 
    133120      ! 
     
    187174         END_3D                                                     ! and/or in trend diagnostic (l_trd=T) 
    188175         ! 
    189          ! TEMP: These changes not necessary after trd_tra is tiled 
    190176         IF( l_trd ) THEN                  ! trend diagnostics 
    191             DO_3D( 1, 0, 1, 0, 1, jpkm1 ) 
    192                ztrdx(ji,jj,jk) = ztu(ji,jj,jk) 
    193                ztrdy(ji,jj,jk) = ztv(ji,jj,jk) 
    194             END_3D 
    195  
    196             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    197                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    198  
    199                ! TODO: TO BE TILED- trd_tra 
    200                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztrdx, pU, pt(:,:,:,jn,Kmm) ) 
    201                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztrdy, pV, pt(:,:,:,jn,Kmm) ) 
    202  
    203                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    204             ENDIF 
     177             CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztu, pU, pt(:,:,:,jn,Kmm) ) 
     178             CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztv, pV, pt(:,:,:,jn,Kmm) ) 
    205179         END IF 
    206180         !      
     
    278252         END_3D 
    279253         ! 
    280          ! TEMP: These changes not necessary after trd_tra is tiled 
    281254         IF( l_trd )  THEN       ! vertical advective trend diagnostics 
    282255            DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
    283                ztrdz(ji,jj,jk) = pt(ji,jj,jk,jn,Krhs) - zltv(ji,jj,jk)                          & 
     256               zltv(ji,jj,jk) = pt(ji,jj,jk,jn,Krhs) - zltv(ji,jj,jk)                          & 
    284257                  &           + pt(ji,jj,jk,jn,Kmm) * (  pW(ji,jj,jk) - pW(ji,jj,jk+1)  )   & 
    285258                  &                              * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm) 
    286259            END_3D 
    287  
    288             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    289                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    290  
    291                ! TODO: TO BE TILED- trd_tra 
    292                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, ztrdz ) 
    293  
    294                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    295             ENDIF 
     260            CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, zltv ) 
    296261         ENDIF 
    297262         ! 
Note: See TracChangeset for help on using the changeset viewer.