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 14986 for NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/TRA/traldf.F90 – NEMO

Ignore:
Timestamp:
2021-06-14T13:34:08+02:00 (3 years ago)
Author:
sparonuz
Message:

Merge trunk -r14984:HEAD

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/TRA/traldf.F90

    r14219 r14986  
    1717   USE oce            ! ocean dynamics and tracers 
    1818   USE dom_oce        ! ocean space and time domain 
    19    ! TEMP: [tiling] This change not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    20    USE domtile 
    2119   USE phycst         ! physical constants 
    2220   USE ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff. 
     
    5957      !! 
    6058      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds 
    61       ! TEMP: [tiling] This change not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    62       LOGICAL :: lskip 
    6359      !!---------------------------------------------------------------------- 
    6460      ! 
    6561      IF( ln_timing )   CALL timing_start('tra_ldf') 
    6662      ! 
    67       lskip = .FALSE. 
    68  
    6963      IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    7064         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
     
    7266         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) 
    7367      ENDIF 
    74  
    75       ! TEMP: [tiling] These changes not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    76       IF( nldf_tra == np_blp .OR. nldf_tra == np_blp_i .OR. nldf_tra == np_blp_it )  THEN 
    77          IF( ln_tile ) THEN 
    78             IF( ntile == 1 ) THEN 
    79                CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 ) 
    80             ELSE 
    81                lskip = .TRUE. 
    82             ENDIF 
    83          ENDIF 
    84       ENDIF 
    85       IF( .NOT. lskip ) THEN 
    86          ! 
    87          SELECT CASE ( nldf_tra )                 !* compute lateral mixing trend and add it to the general trend 
    88          CASE ( np_lap   )                                  ! laplacian: iso-level operator 
    89             CALL tra_ldf_lap  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs),                   jpts,  1 ) 
    90          CASE ( np_lap_i )                                  ! laplacian: standard iso-neutral operator (Madec) 
    91             CALL tra_ldf_iso  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs), jpts,  1 ) 
    92          CASE ( np_lap_it )                                 ! laplacian: triad iso-neutral operator (griffies) 
    93             CALL tra_ldf_triad( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs), jpts,  1 ) 
    94          CASE ( np_blp , np_blp_i , np_blp_it )             ! bilaplacian: iso-level & iso-neutral operators 
    95             IF(nn_hls.EQ.2) CALL lbc_lnk( 'tra_ldf', pts(:,:,:,:,Kbb), 'T',1._wp) 
    96             CALL tra_ldf_blp  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs),             jpts, nldf_tra ) 
    97          END SELECT 
    98          ! 
    99          IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics 
    100             ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
    101             ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
    102             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 
    103             CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 
    104             DEALLOCATE( ztrdt, ztrds ) 
    105          ENDIF 
    106  
    107          ! TEMP: [tiling] This change not necessary after extra haloes development (lbc_lnk removed from tra_ldf_blp, zps_hde*) 
    108          IF( ln_tile .AND. ntile == 0 ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 1 ) 
     68      ! 
     69      SELECT CASE ( nldf_tra )                 !* compute lateral mixing trend and add it to the general trend 
     70      CASE ( np_lap   )                                  ! laplacian: iso-level operator 
     71         CALL tra_ldf_lap  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs),                   jpts,  1 ) 
     72      CASE ( np_lap_i )                                  ! laplacian: standard iso-neutral operator (Madec) 
     73         CALL tra_ldf_iso  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs), jpts,  1 ) 
     74      CASE ( np_lap_it )                                 ! laplacian: triad iso-neutral operator (griffies) 
     75         CALL tra_ldf_triad( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs), jpts,  1 ) 
     76      CASE ( np_blp , np_blp_i , np_blp_it )             ! bilaplacian: iso-level & iso-neutral operators 
     77         CALL tra_ldf_blp  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, CASTWP(pts(:,:,:,:,Kbb)), pts(:,:,:,:,Krhs),             jpts, nldf_tra ) 
     78      END SELECT 
     79      ! 
     80      IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics 
     81         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:) 
     82         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:) 
     83         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt ) 
     84         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds ) 
     85         DEALLOCATE( ztrdt, ztrds ) 
    10986      ENDIF 
    11087      !                                        !* print mean trends (used for debugging) 
Note: See TracChangeset for help on using the changeset viewer.