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 12766 for NEMO/branches/UKMO/dev_r12745_HPC-02_Daley_Tiling_trial_structure/src/OCE/TRA/traldf.F90 – NEMO

Ignore:
Timestamp:
2020-04-17T14:54:46+02:00 (4 years ago)
Author:
hadcv
Message:

tra_ldf_iso trial using structures

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/dev_r12745_HPC-02_Daley_Tiling_trial_structure/src/OCE/TRA/traldf.F90

    r12377 r12766  
    4545CONTAINS 
    4646 
    47    SUBROUTINE tra_ldf( kt, Kbb, Kmm, pts, Krhs ) 
     47   SUBROUTINE tra_ldf(ktile, kt, Kbb, Kmm, pts, Krhs ) 
    4848      !!---------------------------------------------------------------------- 
    4949      !!                  ***  ROUTINE tra_ldf  *** 
     
    5151      !! ** Purpose :   compute the lateral ocean tracer physics. 
    5252      !!---------------------------------------------------------------------- 
     53      TYPE(TILE),                                INTENT(in   ) :: ktile           ! Tile indices 
    5354      INTEGER,                                   INTENT(in   ) :: kt              ! ocean time-step index 
    5455      INTEGER,                                   INTENT(in   ) :: Kbb, Kmm, Krhs  ! ocean time level indices 
     
    5859      !!---------------------------------------------------------------------- 
    5960      ! 
    60       IF( ln_timing )   CALL timing_start('tra_ldf') 
     61      IF( ktile % ntile == 1 )  THEN              ! Do only on the first tile 
     62         ! TODO: TO BE TILED 
     63         IF( ln_timing )   CALL timing_start('tra_ldf') 
     64      ENDIF 
    6165      ! 
    62       IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    63          ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )  
    64          ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs)  
    65          ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
     66      IF( ktile % ntile == jpnijtile )  THEN      ! Do only after all tiles finish 
     67         IF( l_trdtra )   THEN                    !* Save ta and sa trends 
     68            ! TODO: TO BE TILED 
     69            ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
     70            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
     71            ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
     72         ENDIF 
    6673      ENDIF 
    6774      ! 
     
    7077         CALL tra_ldf_lap  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs),                   jpts,  1 ) 
    7178      CASE ( np_lap_i )                                  ! laplacian: standard iso-neutral operator (Madec) 
    72          CALL tra_ldf_iso  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts,  1 ) 
     79         CALL tra_ldf_iso  ( ktile, kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts,  1 ) 
    7380      CASE ( np_lap_it )                                 ! laplacian: triad iso-neutral operator (griffies) 
    7481         CALL tra_ldf_triad( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts,  1 ) 
     
    7784      END SELECT 
    7885      ! 
    79       IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics 
    80          ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
    81          ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
    82          CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 
    83          CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 
    84          DEALLOCATE( ztrdt, ztrds )  
     86      IF( ktile % ntile == jpnijtile )  THEN      ! Do only after all tiles finish 
     87         IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics 
     88            ! TODO: TO BE TILED 
     89            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     90            ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
     91            ! TODO: TO BE TILED 
     92            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 
     93            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 
     94            DEALLOCATE( ztrdt, ztrds ) 
     95         ENDIF 
     96 
     97         !                                        !* print mean trends (used for debugging) 
     98         ! TODO: TO BE TILED 
     99         IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf  - Ta: ', mask1=tmask,               & 
     100            &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     101         ! 
     102         ! TODO: TO BE TILED 
     103         IF( ln_timing )   CALL timing_stop('tra_ldf') 
    85104      ENDIF 
    86       !                                        !* print mean trends (used for debugging) 
    87       IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf  - Ta: ', mask1=tmask,               & 
    88          &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    89       ! 
    90       IF( ln_timing )   CALL timing_stop('tra_ldf') 
    91105      ! 
    92106   END SUBROUTINE tra_ldf 
Note: See TracChangeset for help on using the changeset viewer.