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_qck.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_qck.F90

    r13516 r13551  
    1717   USE oce             ! ocean dynamics and active tracers 
    1818   USE dom_oce         ! ocean space and time domain 
    19    ! TEMP: This change not necessary after trd_tra is tiled 
    20    USE domain, ONLY : dom_tile 
    2119   USE trc_oce         ! share passive tracers/Ocean variables 
    2220   USE trd_oce         ! trends: ocean variables 
     
    9391      INTEGER                                  , INTENT(in   ) ::   kjpt            ! number of tracers 
    9492      REAL(wp)                                 , INTENT(in   ) ::   p2dt            ! tracer time-step 
    95       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     93      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    9694      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU, pV, pW      ! 3 ocean volume transport components 
    9795      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! tracers and RHS of tracer equation 
     
    132130      INTEGER                                  , INTENT(in   ) ::   kjpt       ! number of tracers 
    133131      REAL(wp)                                 , INTENT(in   ) ::   p2dt       ! tracer time-step 
    134       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     132      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    135133      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU        ! i-velocity components 
    136134      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! active tracers and RHS of tracer equation 
    137135      !! 
    138       ! TEMP: This change not necessary after trd_tra is tiled 
    139       INTEGER  ::   itile 
    140136      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    141137      REAL(wp) ::   ztra, zbtr, zdir, zdx, zmsk   ! local scalars 
    142138      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   zwx, zfu, zfc, zfd 
    143       ! TEMP: This change not necessary after trd_tra is tiled 
    144       REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   ztrdx 
    145139      !---------------------------------------------------------------------- 
    146       ! TEMP: This change not necessary after trd_tra is tiled 
    147       itile = ntile 
    148       ! 
    149       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    150       IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    151          IF( kt == nit000 .AND. l_trd ) THEN 
    152             ALLOCATE( ztrdx(jpi,jpj,jpk) ) 
    153          ENDIF 
    154       ENDIF 
     140      ! 
    155141      !                                                          ! =========== 
    156142      DO jn = 1, kjpt                                            ! tracer loop 
     
    218204         END_3D 
    219205         !                                 ! trend diagnostics 
    220          ! TEMP: These changes not necessary after trd_tra is tiled 
    221          IF( l_trd )  THEN 
    222             DO_3D( 1, 0, 1, 0, 1, jpk ) 
    223                ztrdx(ji,jj,jk) = zwx(ji,jj,jk) 
    224             END_3D 
    225  
    226             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    227                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    228  
    229                ! TODO: TO BE TILED- trd_tra 
    230                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztrdx, pU, pt(:,:,:,jn,Kmm) ) 
    231  
    232                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    233             ENDIF 
    234          ENDIF 
     206         IF( l_trd )   CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, zwx, pU, pt(:,:,:,jn,Kmm) ) 
    235207         ! 
    236208      END DO 
     
    248220      INTEGER                                  , INTENT(in   ) ::   kjpt       ! number of tracers 
    249221      REAL(wp)                                 , INTENT(in   ) ::   p2dt       ! tracer time-step 
    250       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     222      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    251223      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pV        ! j-velocity components 
    252224      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! active tracers and RHS of tracer equation 
    253225      !! 
    254       ! TEMP: This change not necessary after trd_tra is tiled 
    255       INTEGER  ::   itile 
    256226      INTEGER  :: ji, jj, jk, jn                ! dummy loop indices 
    257227      REAL(wp) :: ztra, zbtr, zdir, zdx, zmsk   ! local scalars 
    258228      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   zwy, zfu, zfc, zfd   ! 3D workspace 
    259       ! TEMP: This change not necessary after trd_tra is tiled 
    260       REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   ztrdy 
    261229      !---------------------------------------------------------------------- 
    262       ! TEMP: This change not necessary after trd_tra is tiled 
    263       itile = ntile 
    264       ! 
    265       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    266       IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    267          IF( kt == nit000 .AND. l_trd ) THEN 
    268             ALLOCATE( ztrdy(jpi,jpj,jpk) ) 
    269          ENDIF 
    270       ENDIF 
     230      ! 
    271231      !                                                          ! =========== 
    272232      DO jn = 1, kjpt                                            ! tracer loop 
     
    341301         END_3D 
    342302         !                                 ! trend diagnostics 
    343          ! TEMP: These changes not necessary after trd_tra is tiled 
    344          IF( l_trd )  THEN 
    345             DO_3D( 1, 0, 1, 0, 1, jpk ) 
    346                ztrdy(ji,jj,jk) = zwy(ji,jj,jk) 
    347             END_3D 
    348  
    349             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    350                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    351  
    352                ! TODO: TO BE TILED- trd_tra 
    353                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztrdy, pV, pt(:,:,:,jn,Kmm) ) 
    354  
    355                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    356             ENDIF 
    357          ENDIF 
     303         IF( l_trd )   CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, zwy, pV, pt(:,:,:,jn,Kmm) ) 
    358304         !                                 ! "Poleward" heat and salt transports (contribution of upstream fluxes) 
    359305         IF( l_ptr )   CALL dia_ptr_hst( jn, 'adv', zwy(:,:,:) ) 
     
    372318      CHARACTER(len=3)                         , INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator) 
    373319      INTEGER                                  , INTENT(in   ) ::   kjpt     ! number of tracers 
    374       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     320      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    375321      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pW      ! vertical velocity 
    376322      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! active tracers and RHS of tracer equation 
    377323      ! 
    378       ! TEMP: This change not necessary after trd_tra is tiled 
    379       INTEGER  ::   itile 
    380324      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    381325      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   zwz   ! 3D workspace 
    382       ! TEMP: This change not necessary after trd_tra is tiled 
    383       REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   ztrdz 
    384       !!---------------------------------------------------------------------- 
    385       ! TEMP: This change not necessary after trd_tra is tiled 
    386       itile = ntile 
    387       ! 
    388       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    389       IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    390          IF( kt == nit000 .AND. l_trd ) THEN 
    391             ALLOCATE( ztrdz(jpi,jpj,jpk) ) 
    392          ENDIF 
    393       ENDIF 
    394  
     326      !!---------------------------------------------------------------------- 
     327      ! 
    395328      zwz(:,:, 1 ) = 0._wp       ! surface & bottom values set to zero for all tracers 
    396329      zwz(:,:,jpk) = 0._wp 
     
    421354         END_3D 
    422355         !                                 ! Send trends for diagnostic 
    423          ! TEMP: These changes not necessary after trd_tra is tiled 
    424          IF( l_trd )  THEN 
    425             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    426                ztrdz(ji,jj,jk) = zwz(ji,jj,jk) 
    427             END_3D 
    428  
    429             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    430                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    431  
    432                ! TODO: TO BE TILED- trd_tra 
    433                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, ztrdz, pW, pt(:,:,:,jn,Kmm) ) 
    434  
    435                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    436             ENDIF 
    437          ENDIF 
     356         IF( l_trd )  CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, zwz, pW, pt(:,:,:,jn,Kmm) ) 
    438357         ! 
    439358      END DO 
Note: See TracChangeset for help on using the changeset viewer.