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.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.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) 
Note: See TracChangeset for help on using the changeset viewer.