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 – NEMO

Changeset 13551 for NEMO/branches


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

Location:
NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE
Files:
16 edited

Legend:

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

    r13516 r13551  
    9090      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts            ! active tracers and RHS of tracer equation 
    9191      ! 
    92       ! TEMP: This change not necessary after trd_tra is tiled 
    93       INTEGER ::   itile 
    9492      INTEGER ::   ji, jj, jk   ! dummy loop index 
    9593      ! TEMP: This change not necessary and can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    9694      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE :: zuu, zvv, zww   ! 3D workspace 
    97       ! TEMP: This change not necessary after trd_tra is tiled 
    98       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE :: ztrdt, ztrds 
     95      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: ztrdt, ztrds 
    9996      ! TEMP: This change not necessary after extra haloes development 
    10097      LOGICAL :: lskip 
     
    108105      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    109106         ALLOCATE( zuu(jpi,jpj,jpk), zvv(jpi,jpj,jpk), zww(jpi,jpj,jpk) ) 
    110          ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    111          IF( l_trdtra ) ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    112       ENDIF 
    113  
    114       ! TEMP: These changes not necessary after extra haloes development (lbc_lnk removed from tra_adv_*, ldf_eiv_dia) 
     107      ENDIF 
     108 
     109      ! TEMP: These changes not necessary after extra haloes development (lbc_lnk removed from tra_adv_*) 
    115110      IF( nadv /= np_CEN .OR. (nadv == np_CEN .AND. nn_cen_h == 4) .OR. ln_ldfeiv_dia )  THEN 
    116111         IF( ln_tile ) THEN 
     
    123118      ENDIF 
    124119      IF( .NOT. lskip ) THEN 
    125  
    126          ! TEMP: This change not necessary after trd_tra is tiled 
    127          itile = ntile 
    128120         !                                         !==  effective transport  ==! 
    129121         ! TODO: NOT TESTED- requires waves 
     
    178170 
    179171         IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    180             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    181                ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    182                ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) 
    183             END_3D 
     172            ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
     173            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
     174            ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
    184175         ENDIF 
    185176         ! 
     
    199190         END SELECT 
    200191         ! 
    201          ! TEMP: These changes not necessary after trd_tra is tiled 
    202192         IF( l_trdtra )   THEN                      ! save the advective trends for further diagnostics 
    203             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    204                ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    205                ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) - ztrds(ji,jj,jk) 
    206             END_3D 
    207  
    208             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    209                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    210  
    211                ! TODO: TO BE TILED- trd_tra 
    212                CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_totad, ztrdt ) 
    213                CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_totad, ztrds ) 
    214                DEALLOCATE( ztrdt, ztrds ) 
    215  
    216                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    217             ENDIF 
    218          ENDIF 
    219  
    220          ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed from tra_adv_*, ldf_eiv_dia) 
     193            DO jk = 1, jpkm1 
     194               ztrdt(:,:,jk) = pts(:,:,jk,jp_tem,Krhs) - ztrdt(:,:,jk) 
     195               ztrds(:,:,jk) = pts(:,:,jk,jp_sal,Krhs) - ztrds(:,:,jk) 
     196            END DO 
     197            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_totad, ztrdt ) 
     198            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_totad, ztrds ) 
     199            DEALLOCATE( ztrdt, ztrds ) 
     200         ENDIF 
     201 
     202         ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed from tra_adv_*) 
    221203         IF( ln_tile .AND. ntile == 0 ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 1 ) 
    222204 
     
    224206      !                                              ! print mean trends (used for debugging) 
    225207      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' adv  - Ta: ', mask1=tmask, & 
    226          &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, & 
    227          &                                  clinfo3='tra' ) 
     208         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    228209 
    229210      ! TEMP: This change not necessary if using XIOS (subdomain support) 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traadv_cen.F90

    r13516 r13551  
    1212   !!---------------------------------------------------------------------- 
    1313   USE dom_oce        ! ocean space and time domain 
    14    ! TEMP: This change not necessary after trd_tra is tiled 
    15    USE domain, ONLY : dom_tile 
    1614   USE eosbn2         ! equation of state 
    1715   USE traadv_fct     ! acces to routine interp_4th_cpt  
     
    7371      INTEGER                                  , INTENT(in   ) ::   kn_cen_h        ! =2/4 (2nd or 4th order scheme) 
    7472      INTEGER                                  , INTENT(in   ) ::   kn_cen_v        ! =2/4 (2nd or 4th order scheme) 
    75       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     73      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    7674      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU, pV, pW      ! 3 ocean volume flux components 
    7775      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! tracers and RHS of tracer equation 
     
    7977      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    8078      INTEGER  ::   ierr             ! local integer 
    81       ! TEMP: This change not necessary after trd_tra is tiled 
    82       INTEGER  ::   itile 
    8379      REAL(wp) ::   zC2t_u, zC2t_v   ! local scalars 
    8480      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   zwx, zwy, zwz, ztu, ztv, ztw, zltu, zltv 
    85       ! TEMP: This change not necessary after trd_tra is tiled 
    86       REAL(wp), DIMENSION(:,:,:,:), SAVE, ALLOCATABLE ::   ztrdx, ztrdy, ztrdz 
    8781      !!---------------------------------------------------------------------- 
    88       ! TEMP: This change not necessary after trd_tra is tiled 
    89       itile = ntile 
    9082      ! 
    9183      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     
    10395         IF(   cdtype == 'TRA' .AND. ( iom_use("uadv_heattr") .OR. iom_use("vadv_heattr") .OR. & 
    10496            &                          iom_use("uadv_salttr") .OR. iom_use("vadv_salttr")  ) )  l_hst = .TRUE. 
    105  
    106          ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    107          IF( kt == kit000 .AND. l_trd ) THEN 
    108             ALLOCATE( ztrdx(jpi,jpj,jpk,jpts), ztrdy(jpi,jpj,jpk,jpts), ztrdz(jpi,jpj,jpk,jpts) ) 
    109          ENDIF 
    11097      ENDIF 
    11198      ! 
     
    187174         END_3D 
    188175         !                             ! trend diagnostics 
    189          ! TEMP: These changes not necessary after trd_tra is tiled 
    190176         IF( l_trd ) THEN 
    191             DO_3D( 1, 0, 1, 0, 1, jpk ) 
    192                ztrdx(ji,jj,jk,jn) = zwx(ji,jj,jk) 
    193                ztrdy(ji,jj,jk,jn) = zwy(ji,jj,jk) 
    194                ztrdz(ji,jj,jk,jn) = zwz(ji,jj,jk) 
    195             END_3D 
    196  
    197             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    198                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    199  
    200                ! TODO: TO BE TILED- trd_tra 
    201                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztrdx(:,:,:,jn), pU, pt(:,:,:,jn,Kmm) ) 
    202                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztrdy(:,:,:,jn), pV, pt(:,:,:,jn,Kmm) ) 
    203                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, ztrdz(:,:,:,jn), pW, pt(:,:,:,jn,Kmm) ) 
    204  
    205                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    206             ENDIF 
     177            CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, zwx, pU, pt(:,:,:,jn,Kmm) ) 
     178            CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, zwy, pV, pt(:,:,:,jn,Kmm) ) 
     179            CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, zwz, pW, pt(:,:,:,jn,Kmm) ) 
    207180         ENDIF 
    208181         !                                 ! "Poleward" heat and salt transports 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traadv_fct.F90

    r13516 r13551  
    1515   USE oce            ! ocean dynamics and active tracers 
    1616   USE dom_oce        ! ocean space and time domain 
    17    ! TEMP: This change not necessary after trd_tra is tiled 
    18    USE domain, ONLY : dom_tile 
    1917   USE trc_oce        ! share passive tracers/Ocean variables 
    2018   USE trd_oce        ! trends: ocean variables 
     
    8179      INTEGER                                  , INTENT(in   ) ::   kn_fct_v        ! order of the FCT scheme (=2 or 4) 
    8280      REAL(wp)                                 , INTENT(in   ) ::   p2dt            ! tracer time-step 
    83       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     81      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    8482      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU, pV, pW      ! 3 ocean volume flux components 
    8583      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! tracers and RHS of tracer equation 
    8684      ! 
    87       INTEGER  ::   ji, jj, jk, jn                           ! dummy loop indices   
    88       ! TEMP: This change not necessary after trd_tra is tiled 
    89       INTEGER  ::   itile 
     85      INTEGER  ::   ji, jj, jk, jn                           ! dummy loop indices 
    9086      REAL(wp) ::   ztra                                     ! local scalar 
    9187      REAL(wp) ::   zfp_ui, zfp_vj, zfp_wk, zC2t_u, zC4t_u   !   -      - 
    9288      REAL(wp) ::   zfm_ui, zfm_vj, zfm_wk, zC2t_v, zC4t_v   !   -      - 
    9389      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk)        ::   zwi, zwx, zwy, zwz, ztu, ztv, zltu, zltv, ztw 
    94       ! TEMP: This change not necessary after trd_tra is tiled 
    95       REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   ztrdx, ztrdy, ztrdz 
    96       REAL(wp), DIMENSION(:,:,:)      , ALLOCATABLE ::   zptry 
    97       REAL(wp), DIMENSION(:,:,:)      , ALLOCATABLE ::   zwinf, zwdia, zwsup 
     90      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdx, ztrdy, ztrdz, zptry 
     91      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   zwinf, zwdia, zwsup 
    9892      LOGICAL  ::   ll_zAimp                                 ! flag to apply adaptive implicit vertical advection 
    9993      !!---------------------------------------------------------------------- 
    100       ! TEMP: This change not necessary after trd_tra is tiled 
    101       itile = ntile 
    10294      ! 
    10395      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     
    10799            IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    108100         ENDIF 
    109       !! -- init to 0 
    110       zwi(:,:,:) = 0._wp 
    111       zwx(:,:,:) = 0._wp 
    112       zwy(:,:,:) = 0._wp 
    113       zwz(:,:,:) = 0._wp 
    114       ztu(:,:,:) = 0._wp 
    115       ztv(:,:,:) = 0._wp 
    116       zltu(:,:,:) = 0._wp 
    117       zltv(:,:,:) = 0._wp 
    118       ztw(:,:,:) = 0._wp 
     101         !! -- init to 0 
     102         zwi(:,:,:) = 0._wp 
     103         zwx(:,:,:) = 0._wp 
     104         zwy(:,:,:) = 0._wp 
     105         zwz(:,:,:) = 0._wp 
     106         ztu(:,:,:) = 0._wp 
     107         ztv(:,:,:) = 0._wp 
     108         zltu(:,:,:) = 0._wp 
     109         zltv(:,:,:) = 0._wp 
     110         ztw(:,:,:) = 0._wp 
    119111         ! 
    120112         l_trd = .FALSE.            ! set local switches 
     
    127119            &                         iom_use("uadv_salttr") .OR. iom_use("vadv_salttr")  ) )  l_hst = .TRUE. 
    128120         ! 
    129          ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    130          IF( kt == kit000 .AND. (l_trd .OR. l_hst) )  THEN 
    131             ALLOCATE( ztrdx(jpi,jpj,jpk), ztrdy(jpi,jpj,jpk), ztrdz(jpi,jpj,jpk) ) 
    132          ENDIF 
    133121      ENDIF 
    134122      ! 
    135       IF( l_ptr ) THEN   
     123      IF( l_trd .OR. l_hst )  THEN 
     124         ALLOCATE( ztrdx(ST_2D(nn_hls),jpk), ztrdy(ST_2D(nn_hls),jpk), ztrdz(ST_2D(nn_hls),jpk) ) 
     125         ztrdx(:,:,:) = 0._wp   ;    ztrdy(:,:,:) = 0._wp   ;   ztrdz(:,:,:) = 0._wp 
     126      ENDIF 
     127      ! 
     128      IF( l_ptr ) THEN 
    136129         ALLOCATE( zptry(ST_2D(nn_hls),jpk) ) 
    137130         zptry(:,:,:) = 0._wp 
     
    218211            ! 
    219212         END IF 
    220          !                 
    221          ! TEMP: This change not necessary after trd_tra is tiled 
     213         ! 
    222214         IF( l_trd .OR. l_hst )  THEN             ! trend diagnostics (contribution of upstream fluxes) 
    223             DO_3D( 1, 0, 1, 0, 1, jpk ) 
    224                ztrdx(ji,jj,jk) = zwx(ji,jj,jk)   ;   ztrdy(ji,jj,jk) = zwy(ji,jj,jk)   ;   ztrdz(ji,jj,jk) = zwz(ji,jj,jk) 
    225             END_3D 
     215            ztrdx(:,:,:) = zwx(:,:,:)   ;   ztrdy(:,:,:) = zwy(:,:,:)   ;   ztrdz(:,:,:) = zwz(:,:,:) 
    226216         END IF 
    227217         !                             ! "Poleward" heat and salt transports (contribution of upstream fluxes) 
     
    351341         END IF          
    352342         ! 
    353          ! TEMP: These changes not necessary after trd_tra is tiled 
    354343         IF( l_trd .OR. l_hst ) THEN   ! trend diagnostics // heat/salt transport 
    355             DO_3D( 1, 0, 1, 0, 1, jpk ) 
    356                ztrdx(ji,jj,jk) = ztrdx(ji,jj,jk) + zwx(ji,jj,jk)  ! <<< add anti-diffusive fluxes 
    357                ztrdy(ji,jj,jk) = ztrdy(ji,jj,jk) + zwy(ji,jj,jk)  !     to upstream fluxes 
    358                ztrdz(ji,jj,jk) = ztrdz(ji,jj,jk) + zwz(ji,jj,jk)  ! 
    359             END_3D 
    360             ! 
    361             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    362                IF( l_trd ) THEN              ! trend diagnostics 
    363                   IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    364  
    365                   ! TODO: TO BE TILED- trd_tra 
    366                   CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztrdx, pU, pt(:,:,:,jn,Kmm) ) 
    367                   CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztrdy, pV, pt(:,:,:,jn,Kmm) ) 
    368                   CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, ztrdz, pW, pt(:,:,:,jn,Kmm) ) 
    369  
    370                   IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    371                ENDIF 
     344            ztrdx(:,:,:) = ztrdx(:,:,:) + zwx(:,:,:)  ! <<< add anti-diffusive fluxes 
     345            ztrdy(:,:,:) = ztrdy(:,:,:) + zwy(:,:,:)  !     to upstream fluxes 
     346            ztrdz(:,:,:) = ztrdz(:,:,:) + zwz(:,:,:)  ! 
     347            ! 
     348            IF( l_trd ) THEN              ! trend diagnostics 
     349               CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztrdx, pU, pt(:,:,:,jn,Kmm) ) 
     350               CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztrdy, pV, pt(:,:,:,jn,Kmm) ) 
     351               CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, ztrdz, pW, pt(:,:,:,jn,Kmm) ) 
    372352            ENDIF 
    373353            !                             ! heat/salt transport 
    374             IF( l_hst )   CALL dia_ar5_hst( jn, 'adv', ztrdx(ST_2D(nn_hls),:), ztrdy(ST_2D(nn_hls),:) ) 
     354            IF( l_hst )   CALL dia_ar5_hst( jn, 'adv', ztrdx(:,:,:), ztrdy(:,:,:) ) 
    375355            ! 
    376356         ENDIF 
     
    385365         DEALLOCATE( zwdia, zwinf, zwsup ) 
    386366      ENDIF 
    387       ! TEMP: These changes not necessary after trd_tra is tiled 
    388 !      IF( l_trd .OR. l_hst ) THEN 
    389 !         DEALLOCATE( ztrdx, ztrdy, ztrdz ) 
    390 !      ENDIF 
     367      IF( l_trd .OR. l_hst ) THEN 
     368         DEALLOCATE( ztrdx, ztrdy, ztrdz ) 
     369      ENDIF 
    391370      IF( l_ptr ) THEN  
    392371         DEALLOCATE( zptry ) 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traadv_mus.F90

    r13516 r13551  
    1919   USE trc_oce        ! share passive tracers/Ocean variables 
    2020   USE dom_oce        ! ocean space and time domain 
    21    ! TEMP: This change not necessary after trd_tra is tiled 
    22    USE domain, ONLY : dom_tile 
    2321   USE trd_oce        ! trends: ocean variables 
    2422   USE trdtra         ! tracers trends manager 
     
    8381      LOGICAL                                  , INTENT(in   ) ::   ld_msc_ups      ! use upstream scheme within muscl 
    8482      REAL(wp)                                 , INTENT(in   ) ::   p2dt            ! tracer time-step 
    85       ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
     83      ! TEMP: This can be ST_2D(nn_hls) if using XIOS (subdomain support) 
    8684      REAL(wp), DIMENSION(jpi,jpj,jpk         ), INTENT(in   ) ::   pU, pV, pW      ! 3 ocean volume flux components 
    8785      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt,jpt), INTENT(inout) ::   pt              ! tracers and RHS of tracer equation 
    8886      ! 
    89       ! TEMP: This change not necessary after trd_tra is tiled 
    90       INTEGER  ::   itile 
    9187      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
    9288      INTEGER  ::   ierr             ! local integer 
     
    9591      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   zwx, zslpx   ! 3D workspace 
    9692      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk) ::   zwy, zslpy   ! -      - 
    97       ! TEMP: This change not necessary after trd_tra is tiled 
    98       REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   ztrdx, ztrdy, ztrdz 
    9993      !!---------------------------------------------------------------------- 
    100       ! TEMP: This change not necessary after trd_tra is tiled 
    101       itile = ntile 
    10294      ! 
    10395      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     
    134126         IF(   cdtype == 'TRA' .AND. ( iom_use("uadv_heattr") .OR. iom_use("vadv_heattr") .OR. & 
    135127            &                          iom_use("uadv_salttr") .OR. iom_use("vadv_salttr")  ) ) l_hst = .TRUE. 
    136  
    137          ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    138          IF( kt == kit000 .AND. l_trd ) THEN 
    139             ALLOCATE( ztrdx(jpi,jpj,jpk), ztrdy(jpi,jpj,jpk), ztrdz(jpi,jpj,jpk) ) 
    140          ENDIF 
    141128      ENDIF 
    142129      ! 
     
    197184         END_3D 
    198185         !                                ! trend diagnostics 
    199          ! TEMP: These changes not necessary after trd_tra is tiled 
    200186         IF( l_trd )  THEN 
    201             DO_3D( 1, 0, 1, 0, 1, jpk ) 
    202                ztrdx(ji,jj,jk) = zwx(ji,jj,jk) 
    203                ztrdy(ji,jj,jk) = zwy(ji,jj,jk) 
    204             END_3D 
    205  
    206             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    207                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    208  
    209                ! TODO: TO BE TILED- trd_tra 
    210                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, ztrdx, pU, pt(:,:,:,jn,Kbb) ) 
    211                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztrdy, pV, pt(:,:,:,jn,Kbb) ) 
    212  
    213                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )   ! Revert to tile domain 
    214             ENDIF 
     187            CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_xad, zwx, pU, pt(:,:,:,jn,Kbb) ) 
     188            CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, zwy, pV, pt(:,:,:,jn,Kbb) ) 
    215189         END IF 
    216190         !                                 ! "Poleward" heat and salt transports  
     
    264238         END_3D 
    265239         !                                ! send trends for diagnostic 
    266          ! TEMP: These changes not necessary after trd_tra is tiled 
    267          IF( l_trd ) THEN 
    268             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    269                ztrdz(ji,jj,jk) = zwx(ji,jj,jk) 
    270             END_3D 
    271  
    272             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    273                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    274  
    275                ! TODO: TO BE TILED- trd_tra 
    276                CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, ztrdz, pW, pt(:,:,:,jn,Kbb) ) 
    277  
    278                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    279             ENDIF 
    280          ENDIF 
     240         IF( l_trd )  CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_zad, zwx, pW, pt(:,:,:,jn,Kbb) ) 
    281241         ! 
    282242      END DO                     ! end of tracer loop 
  • 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 
  • 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         ! 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/trabbc.F90

    r13518 r13551  
    1717   USE oce            ! ocean variables 
    1818   USE dom_oce        ! domain: ocean 
    19    ! TEMP: This change not necessary after trd_tra is tiled 
    20    USE domain, ONLY : dom_tile 
    2119   USE phycst         ! physical constants 
    2220   USE trd_oce        ! trends: ocean variables 
     
    8381      ! 
    8482      INTEGER  ::   ji, jj, jk    ! dummy loop indices 
    85       ! TEMP: This change not necessary after trd_tra is tiled 
    86       REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ztrdt   ! 3D workspace 
     83      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt   ! 3D workspace 
    8784      !!---------------------------------------------------------------------- 
    8885      ! 
     
    9087      ! 
    9188      IF( l_trdtra ) THEN           ! Save the input temperature trend 
    92          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    93             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    94             ALLOCATE( ztrdt(jpi,jpj,jpk) ) 
    95          ENDIF 
    96  
    97          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    98             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    99          END_3D 
     89         ALLOCATE( ztrdt(jpi,jpj,jpk) ) 
     90         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
    10091      ENDIF 
    10192      !                             !  Add the geothermal trend on temperature 
     
    10596      END_2D 
    10697      ! 
    107       ! TEMP: These changes not necessary after trd_tra is tiled, lbc_lnk not necessary if using XIOS (subdomain support, will not output haloes) 
    108       IF( l_trdtra ) THEN 
    109          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    110             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    111          END_3D 
     98      IF( l_trdtra ) THEN        ! Send the trend for diagnostics 
     99         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     100         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_bbc, ztrdt ) 
     101         DEALLOCATE( ztrdt ) 
    112102      ENDIF 
    113  
     103      ! 
    114104      IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    115          ! 
    116          IF( l_trdtra ) THEN        ! Send the trend for diagnostics 
    117             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    118  
    119             ! TODO: TO BE TILED- trd_tra 
    120             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_bbc, ztrdt ) 
    121             DEALLOCATE( ztrdt ) 
    122  
    123             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    124          ENDIF 
    125          ! 
    126105         CALL iom_put ( "hfgeou" , rho0_rcp * qgh_trd0(:,:) ) 
    127106      ENDIF 
    128  
    129       IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbc  - Ta: ', mask1=tmask, & 
    130          &                                  clinfo3='tra-ta' ) 
     107      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
    131108      ! 
    132109      IF( ln_timing )   CALL timing_stop('tra_bbc') 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/trabbl.F90

    r13518 r13551  
    2626   USE oce            ! ocean dynamics and active tracers 
    2727   USE dom_oce        ! ocean space and time domain 
    28    ! TEMP: This change not necessary after trd_tra is tiled 
    29    USE domain, ONLY : dom_tile 
    3028   USE phycst         ! physical constant 
    3129   USE eosbn2         ! equation of state 
     
    109107      ! 
    110108      INTEGER  ::   ji, jj, jk   ! Dummy loop indices 
    111       ! TEMP: This change not necessary after trd_tra is tiled 
    112       REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
     109      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
    113110      !!---------------------------------------------------------------------- 
    114111      ! 
     
    116113      ! 
    117114      IF( l_trdtra )   THEN                         !* Save the T-S input trends 
    118          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    119             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    120             ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    121          ENDIF 
    122  
    123          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    124             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    125             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) 
    126          END_3D 
     115         ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
     116         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
     117         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
    127118      ENDIF 
    128119 
     
    159150      ENDIF 
    160151 
    161       ! TEMP: These changes not necessary after trd_tra is tiled 
    162152      IF( l_trdtra )   THEN                      ! send the trends for further diagnostics 
    163          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    164             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    165             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) - ztrds(ji,jj,jk) 
    166          END_3D 
    167  
    168          IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    169             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    170  
    171             ! TODO: TO BE TILED- trd_tra 
    172             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_bbl, ztrdt ) 
    173             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_bbl, ztrds ) 
    174             DEALLOCATE( ztrdt, ztrds ) 
    175  
    176             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    177          ENDIF 
     153         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     154         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
     155         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_bbl, ztrdt ) 
     156         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_bbl, ztrds ) 
     157         DEALLOCATE( ztrdt, ztrds ) 
    178158      ENDIF 
    179159      ! 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/tradmp.F90

    r13518 r13551  
    2424   USE oce            ! ocean: variables 
    2525   USE dom_oce        ! ocean: domain variables 
    26    ! TEMP: This change not necessary after trd_tra is tiled 
    27    USE domain, ONLY : dom_tile 
    2826   USE c1d            ! 1D vertical configuration 
    2927   USE trd_oce        ! trends: ocean variables 
     
    9896      INTEGER ::   ji, jj, jk, jn   ! dummy loop indices 
    9997      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk,jpts)     ::  zts_dta 
    100       ! TEMP: This change not necessary after trd_tra is tiled 
    101       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, SAVE ::  ztrdts 
     98      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  ztrdts 
    10299      !!---------------------------------------------------------------------- 
    103100      ! 
     
    105102      ! 
    106103      IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    107          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    108             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    109             ALLOCATE( ztrdts(jpi,jpj,jpk,jpts) ) 
    110          ENDIF 
    111  
    112          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    113             ztrdts(ji,jj,jk,:) = pts(ji,jj,jk,:,Krhs) 
    114          END_3D 
     104         ALLOCATE( ztrdts(jpi,jpj,jpk,jpts) ) 
     105         ztrdts(:,:,:,:) = pts(:,:,:,:,Krhs) 
    115106      ENDIF 
    116107      !                           !==  input T-S data at kt  ==! 
     
    149140      END SELECT 
    150141      ! 
    151       ! TEMP: These changes not necessary after trd_tra is tiled 
    152142      IF( l_trdtra )   THEN       ! trend diagnostic 
    153          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    154             ztrdts(ji,jj,jk,:) = pts(ji,jj,jk,:,Krhs) - ztrdts(ji,jj,jk,:) 
    155          END_3D 
    156  
    157          IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    158             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    159  
    160             ! TODO: TO BE TILED- trd_tra 
    161             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_dmp, ztrdts(:,:,:,jp_tem) ) 
    162             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_dmp, ztrdts(:,:,:,jp_sal) ) 
    163             DEALLOCATE( ztrdts ) 
    164  
    165             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    166          ENDIF 
     143         ztrdts(:,:,:,:) = pts(:,:,:,:,Krhs) - ztrdts(:,:,:,:) 
     144         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_dmp, ztrdts(:,:,:,jp_tem) ) 
     145         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_dmp, ztrdts(:,:,:,jp_sal) ) 
     146         DEALLOCATE( ztrdts ) 
    167147      ENDIF 
    168148      !                           ! Control print 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traldf.F90

    r13515 r13551  
    1717   USE oce            ! ocean dynamics and tracers 
    1818   USE dom_oce        ! ocean space and time domain 
    19    ! TEMP: This change not necessary after trd_tra is tiled 
     19   ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    2020   USE domain, ONLY : dom_tile 
    2121   USE phycst         ! physical constants 
     
    4040   PUBLIC   tra_ldf_init   ! called by nemogcm.F90  
    4141 
    42    !! * Substitutions 
    43 #  include "do_loop_substitute.h90" 
    4442   !!---------------------------------------------------------------------- 
    4543   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    5957      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts             ! active tracers and RHS of tracer equation 
    6058      !! 
    61       ! TEMP: This change not necessary after trd_tra is tiled 
    62       INTEGER ::   itile 
    63       INTEGER ::   ji, jj, jk    ! dummy loop indices 
    64       ! TEMP: This change not necessary after trd_tra is tiled 
    65       REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
    66       ! TEMP: This change not necessary after extra haloes development 
     59      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
     60      ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    6761      LOGICAL :: lskip 
    6862      !!---------------------------------------------------------------------- 
     
    7266      lskip = .FALSE. 
    7367 
    74       IF( l_trdtra ) THEN 
    75          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    76             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    77             ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    78          ENDIF 
     68      IF( l_trdtra )   THEN                    !* Save ta and sa trends 
     69         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
     70         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
     71         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
    7972      ENDIF 
    8073 
     
    9083      ENDIF 
    9184      IF( .NOT. lskip ) THEN 
    92  
    93          ! TEMP: This change not necessary after trd_tra is tiled 
    94          itile = ntile 
    95  
    96          IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    97             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    98                ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    99                ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) 
    100             END_3D 
    101          ENDIF 
    10285         ! 
    10386         SELECT CASE ( nldf_tra )                 !* compute lateral mixing trend and add it to the general trend 
     
    11295         END SELECT 
    11396         ! 
    114          ! TEMP: These changes not necessary after trd_tra is tiled 
    11597         IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics 
    116             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    117                ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    118                ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) - ztrds(ji,jj,jk) 
    119             END_3D 
    120  
    121             IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    122                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    123  
    124                ! TODO: TO BE TILED- trd_tra 
    125                CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 
    126                CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 
    127                DEALLOCATE( ztrdt, ztrds ) 
    128  
    129                IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )     ! Revert to tile domain 
    130             ENDIF 
     98            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     99            ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
     100            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 
     101            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 
     102            DEALLOCATE( ztrdt, ztrds ) 
    131103         ENDIF 
    132104 
    133105         ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    134106         IF( ln_tile .AND. ntile == 0 ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 1 ) 
    135  
    136107      ENDIF 
    137108      !                                        !* print mean trends (used for debugging) 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/tranpc.F90

    r13517 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 and extra haloes development (lbc_lnk removed) 
     19   ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed) 
    2020   USE domain, ONLY : dom_tile 
    2121   USE phycst         ! physical constants 
     
    7777      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk     )   ::   zn2              ! N^2 
    7878      REAL(wp), DIMENSION(ST_2D(nn_hls),jpk,jpts)   ::   zab              ! alpha and beta 
    79       ! TEMP: This change not necessary after trd_tra is tiled 
    80       REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ztrdt, ztrds ! 3D workspace 
     79      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds ! 3D workspace 
    8180      ! 
    8281      LOGICAL, PARAMETER :: l_LB_debug = .FALSE. ! set to true if you want to follow what is 
     
    8685      ! 
    8786      IF( ln_timing )   CALL timing_start('tra_npc') 
    88  
    89       IF( l_trdtra )   THEN 
    90          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    91             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    92             ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    93          ENDIF 
    94       ENDIF 
    9587      ! 
    9688      IF( MOD( kt, nn_npc ) == 0 ) THEN 
    9789         ! 
    9890         IF( l_trdtra )   THEN                    !* Save initial after fields 
    99             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    100                ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Kaa) 
    101                ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Kaa) 
    102             END_3D 
     91            ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
     92            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa) 
     93            ztrds(:,:,:) = pts(:,:,:,jp_sal,Kaa) 
    10394         ENDIF 
    10495         ! 
     
    314305         END_2D 
    315306         ! 
    316          ! TEMP: These changes not necessary after trd_tra is tiled and extra haloes development (lbc_lnk removed) 
    317          IF( l_trdtra ) THEN 
     307         IF( l_trdtra ) THEN         ! send the Non penetrative mixing trends for diagnostic 
    318308            z1_rDt = 1._wp / (2._wp * rn_Dt) 
    319  
    320             DO_3D( 0, 0, 0, 0, 1, jpk ) 
    321                ztrdt(ji,jj,jk) = ( pts(ji,jj,jk,jp_tem,Kaa) - ztrdt(ji,jj,jk) ) * z1_rDt 
    322                ztrds(ji,jj,jk) = ( pts(ji,jj,jk,jp_sal,Kaa) - ztrds(ji,jj,jk) ) * z1_rDt 
    323             END_3D 
     309            ztrdt(:,:,:) = ( pts(:,:,:,jp_tem,Kaa) - ztrdt(:,:,:) ) * z1_rDt 
     310            ztrds(:,:,:) = ( pts(:,:,:,jp_sal,Kaa) - ztrds(:,:,:) ) * z1_rDt 
     311            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_npc, ztrdt ) 
     312            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_npc, ztrds ) 
     313            DEALLOCATE( ztrdt, ztrds ) 
    324314         ENDIF 
    325  
     315         ! 
     316         ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed) 
    326317         IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    327             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    328  
    329             IF( l_trdtra ) THEN         ! send the Non penetrative mixing trends for diagnostic 
    330                ! TODO: TO BE TILED- trd_tra 
    331                CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_npc, ztrdt ) 
    332                CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_npc, ztrds ) 
    333                DEALLOCATE( ztrdt, ztrds ) 
    334             ENDIF 
    335  
    336             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    337             ! 
    338318            CALL lbc_lnk_multi( 'tranpc', pts(:,:,:,jp_tem,Kaa), 'T', 1.0_wp, pts(:,:,:,jp_sal,Kaa), 'T', 1.0_wp ) 
    339319            ! 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/traqsr.F90

    r13518 r13551  
    115115      REAL(wp) ::   zCb, zCmax, zpsi, zpsimax, zrdpsi, zCze 
    116116      REAL(wp) ::   zlogc, zlogze, zlogCtot, zlogCze 
    117       ! TEMP: These changes not necessary after trd_tra is tiled 
    118       REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ztrdt 
    119117      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   :: ze0, ze1, ze2, ze3 
    120118      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: ztrdt, zetot, ztmp3d 
     
    132130      ! 
    133131      IF( l_trdtra ) THEN      ! trends diagnostic: save the input temperature trend 
    134          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    135             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    136             ALLOCATE( ztrdt(jpi,jpj,jpk) ) 
    137          ENDIF 
    138  
    139          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    140             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    141          END_3D 
     132         ALLOCATE( ztrdt(jpi,jpj,jpk) ) 
     133         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
    142134      ENDIF 
    143135      ! 
     
    236228            ! Convert chlorophyll value to attenuation coefficient look-up table index 
    237229            zlui = 41 + 20.*LOG10(zchl) + 1.e-15 
    238             DO_3D( 1, 1, 1, 1, 1, nksr + 1 ) 
    239                ztmp3d(ji,jj,jk) = zlui 
    240             END_3D 
     230            DO jk = 1, nksr + 1 
     231               ztmp3d(:,:,jk) = zlui 
     232            END DO 
    241233         ENDIF 
    242234         ! 
     
    325317      ENDIF 
    326318      ! 
    327       ! TEMP: These changes not necessary after trd_tra is tiled 
    328319      IF( l_trdtra ) THEN     ! qsr tracers trends saved for diagnostics 
    329          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    330             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    331          END_3D 
    332  
    333          IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    334             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    335  
    336             ! TODO: TO BE TILED- trd_tra 
    337             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_qsr, ztrdt ) 
    338             DEALLOCATE( ztrdt ) 
    339  
    340             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    341          ENDIF 
     320         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     321         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_qsr, ztrdt ) 
     322         DEALLOCATE( ztrdt ) 
    342323      ENDIF 
    343324      !                       ! print mean trends (used for debugging) 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/trasbc.F90

    r13518 r13551  
    1919   USE sbc_oce        ! surface boundary condition: ocean 
    2020   USE dom_oce        ! ocean space domain variables 
    21    ! TEMP: This change not necessary after trd_tra is tiled 
    22    USE domain, ONLY : dom_tile 
    2321   USE phycst         ! physical constant 
    2422   USE eosbn2         ! Equation Of State 
     
    8179      INTEGER  ::   ikt, ikb                    ! local integers 
    8280      REAL(wp) ::   zfact, z1_e3t, zdep, ztim   ! local scalar 
    83       ! TEMP: This change not necessary after trd_tra is tiled 
    84       REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ztrdt, ztrds 
     81      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::  ztrdt, ztrds 
    8582      !!---------------------------------------------------------------------- 
    8683      ! 
     
    9693      ! 
    9794      IF( l_trdtra ) THEN                    !* Save ta and sa trends 
    98          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    99             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    100             ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    101          ENDIF 
    102  
    103          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    104             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    105             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) 
    106          END_3D 
     95         ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
     96         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
     97         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
    10798      ENDIF 
    10899      ! 
     
    160151      DO jn = 1, jpts               !==  update tracer trend  ==! 
    161152         DO_2D( 0, 0, 0, 0 ) 
    162             pts(ji,jj,1,jn,Krhs) = pts(ji,jj,1,jn,Krhs) + zfact * ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) ) / e3t(ji,jj,1,Kmm) 
     153            pts(ji,jj,1,jn,Krhs) = pts(ji,jj,1,jn,Krhs) + zfact * ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) )    & 
     154               &                                                / e3t(ji,jj,1,Kmm) 
    163155         END_2D 
    164156      END DO 
     
    192184      ENDIF 
    193185 
    194       IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     186      IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
    195187         IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*pts(:,:,1,jp_tem,Kmm) )   ! runoff term on sst 
    196188         IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*pts(:,:,1,jp_sal,Kmm) )   ! runoff term on sss 
     
    223215#endif 
    224216      ! 
    225       ! TEMP: These changes not necessary after trd_tra is tiled 
    226217      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics 
    227          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    228             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    229             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) - ztrds(ji,jj,jk) 
    230          END_3D 
    231  
    232          IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    233             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    234  
    235             ! TODO: TO BE TILED- trd_tra 
    236             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_nsr, ztrdt ) 
    237             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_nsr, ztrds ) 
    238             DEALLOCATE( ztrdt , ztrds ) 
    239  
    240             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    241          ENDIF 
     218         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     219         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
     220         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_nsr, ztrdt ) 
     221         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_nsr, ztrds ) 
     222         DEALLOCATE( ztrdt , ztrds ) 
    242223      ENDIF 
    243224      ! 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/trazdf.F90

    r13517 r13551  
    1313   !!---------------------------------------------------------------------- 
    1414   USE oce            ! ocean dynamics and tracers variables 
    15    USE dom_oce        ! ocean space and time domain variables  
    16    ! TEMP: This change not necessary after trd_tra is tiled 
    17    USE domain, ONLY : dom_tile 
     15   USE dom_oce        ! ocean space and time domain variables 
    1816   USE domvvl         ! variable volume 
    1917   USE phycst         ! physical constant 
     
    5856      ! 
    5957      INTEGER  ::   ji, jj, jk   ! Dummy loop indices 
    60       ! TEMP: This change not necessary after trd_tra is tiled 
    61       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE ::   ztrdt, ztrds   ! 3D workspace 
     58      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdt, ztrds   ! 3D workspace 
    6259      !!--------------------------------------------------------------------- 
    6360      ! 
     
    7370      ! 
    7471      IF( l_trdtra )   THEN                  !* Save ta and sa trends 
    75          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    76             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    77             ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    78          ENDIF 
    79  
    80          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    81             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Kaa) 
    82             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Kaa) 
    83          END_3D 
     72         ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
     73         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa) 
     74         ztrds(:,:,:) = pts(:,:,:,jp_sal,Kaa) 
    8475      ENDIF 
    8576      ! 
     
    9485!!gm 
    9586 
    96       ! TEMP: These changes not necessary after trd_tra is tiled 
    9787      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics 
    98          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    99             ztrdt(ji,jj,jk) = ( ( pts(ji,jj,jk,jp_tem,Kaa)*e3t(ji,jj,jk,Kaa) - pts(ji,jj,jk,jp_tem,Kbb)*e3t(ji,jj,jk,Kbb) ) & 
    100                &          / (e3t(ji,jj,jk,Kmm)*rDt) ) - ztrdt(ji,jj,jk) 
    101             ztrds(ji,jj,jk) = ( ( pts(ji,jj,jk,jp_sal,Kaa)*e3t(ji,jj,jk,Kaa) - pts(ji,jj,jk,jp_sal,Kbb)*e3t(ji,jj,jk,Kbb) ) & 
    102               &           / (e3t(ji,jj,jk,Kmm)*rDt) ) - ztrds(ji,jj,jk) 
    103          END_3D 
    104  
    105          IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    106             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    107  
    108             ! TODO: TO BE TILED- trd_tra 
    109             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_zdf, ztrdt ) 
    110             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_zdf, ztrds ) 
    111             DEALLOCATE( ztrdt , ztrds ) 
    112  
    113             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    114          ENDIF 
     88         DO jk = 1, jpk 
     89            ztrdt(:,:,jk) = (   (  pts(:,:,jk,jp_tem,Kaa)*e3t(:,:,jk,Kaa)     & 
     90               &                 - pts(:,:,jk,jp_tem,Kbb)*e3t(:,:,jk,Kbb)  )  & 
     91               &              / (  e3t(:,:,jk,Kmm)*rDt  )   )                 & 
     92               &          - ztrdt(:,:,jk) 
     93            ztrds(:,:,jk) = (   (  pts(:,:,jk,jp_sal,Kaa)*e3t(:,:,jk,Kaa)     & 
     94               &                 - pts(:,:,jk,jp_sal,Kbb)*e3t(:,:,jk,Kbb)  )  & 
     95               &             / (   e3t(:,:,jk,Kmm)*rDt  )   )                 & 
     96               &          - ztrds(:,:,jk) 
     97         END DO 
     98         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_zdf, ztrdt ) 
     99         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_zdf, ztrds ) 
     100         DEALLOCATE( ztrdt , ztrds ) 
    115101      ENDIF 
    116102      !                                          ! print mean trends (used for debugging) 
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRD/trdini.F90

    r12377 r13551  
    1111   !!---------------------------------------------------------------------- 
    1212   USE dom_oce        ! ocean domain 
     13   USE domain, ONLY : dom_tile 
    1314   USE trd_oce        ! trends: ocean variables 
    1415   USE trdken         ! trends: 3D kinetic   energy 
     
    8889      ! 
    8990!      IF( .NOT.ln_linssh .AND. ( l_trdtra .OR. l_trddyn ) )  CALL ctl_stop( 'trend diagnostics with variable volume not validated' ) 
    90        
     91 
     92      IF( ln_tile .AND. ( l_trdtra .OR. l_trddyn ) ) THEN 
     93         CALL ctl_warn('Tiling is not yet implemented for the trends diagnostics; ln_tile is forced to FALSE') 
     94         ln_tile = .FALSE. 
     95         CALL dom_tile( ntsi, ntsj, ntei, ntej ) 
     96      ENDIF 
     97 
    9198!!gm  : Potential BUG : 3D output only for vector invariant form!  add a ctl_stop or code the flux form case 
    9299!!gm  : bug/pb for vertical advection of tracer in vvl case: add T.dt[eta] in the output...  
  • NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/ZDF/zdfosm.F90

    r13517 r13551  
    4444                      ! uses ww from previous time step (which is now wb) to calculate hbl 
    4545   USE dom_oce        ! ocean space and time domain 
    46    ! TEMP: This change not necessary after trd_tra is tiled 
    47    USE domain, ONLY : dom_tile 
    4846   USE zdf_oce        ! ocean vertical physics 
    4947   USE sbc_oce        ! surface boundary condition: ocean 
     
    15451543      !! ** Method  :   ??? 
    15461544      !!---------------------------------------------------------------------- 
    1547       ! TEMP: This change not necessary after trd_tra is tiled 
    1548       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE ::   ztrdt, ztrds   ! 3D workspace 
     1545      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdt, ztrds   ! 3D workspace 
    15491546      !!---------------------------------------------------------------------- 
    15501547      INTEGER                                  , INTENT(in)    :: kt        ! time step index 
     
    15631560 
    15641561      IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    1565          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    1566             ! TEMP: This can be ST_2D(nn_hls) after trd_tra is tiled 
    1567             ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) ) 
    1568          ENDIF 
    1569  
    1570          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    1571             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) 
    1572             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) 
    1573          END_3D 
     1562         ALLOCATE( ztrdt(jpi,jpj,jpk) )   ;    ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
     1563         ALLOCATE( ztrds(jpi,jpj,jpk) )   ;    ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
    15741564      ENDIF 
    15751565 
     
    15841574      END_3D 
    15851575 
    1586       ! TEMP: These changes not necessary after trd_tra is tiled 
     1576 
    15871577      ! save the non-local tracer flux trends for diagnostic 
    15881578      IF( l_trdtra )   THEN 
    1589          DO_3D( 0, 0, 0, 0, 1, jpk ) 
    1590             ztrdt(ji,jj,jk) = pts(ji,jj,jk,jp_tem,Krhs) - ztrdt(ji,jj,jk) 
    1591             ztrds(ji,jj,jk) = pts(ji,jj,jk,jp_sal,Krhs) - ztrds(ji,jj,jk) 
    1592          END_3D 
    1593  
    1594          IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    1595             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )         ! Use full domain 
    1596  
     1579         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     1580         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
    15971581!!bug gm jpttdzdf ==> jpttosm 
    1598             ! TODO: TO BE TILED- trd_tra 
    1599             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_zdf, ztrdt ) 
    1600             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_zdf, ztrds ) 
    1601             DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds ) 
    1602  
    1603             IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = nijtile )   ! Revert to tile domain 
    1604          ENDIF 
     1582         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_zdf, ztrdt ) 
     1583         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_zdf, ztrds ) 
     1584         DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds ) 
    16051585      ENDIF 
    16061586 
Note: See TracChangeset for help on using the changeset viewer.