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