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 12590 for NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/TRA/traldf_lap_blp.F90 – NEMO

Ignore:
Timestamp:
2020-03-23T22:16:19+01:00 (4 years ago)
Author:
techene
Message:

all: add e3 substitute, OCE/DOM/domzgr_substitute.h90: correct a bug for e3f

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/TRA/traldf_lap_blp.F90

    r12377 r12590  
    44   !! Ocean tracers:  lateral diffusivity trend  (laplacian and bilaplacian) 
    55   !!============================================================================== 
    6    !! History :  3.7  ! 2014-01  (G. Madec, S. Masson)  Original code, re-entrant laplacian  
     6   !! History :  3.7  ! 2014-01  (G. Madec, S. Masson)  Original code, re-entrant laplacian 
    77   !!---------------------------------------------------------------------- 
    88 
     
    3838   !! * Substitutions 
    3939#  include "do_loop_substitute.h90" 
     40#  include "domzgr_substitute.h90" 
    4041   !!---------------------------------------------------------------------- 
    4142   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    4748   SUBROUTINE tra_ldf_lap( kt, Kmm, kit000, cdtype, pahu, pahv  ,               & 
    4849      &                                             pgu , pgv   , pgui, pgvi,   & 
    49       &                                             pt  , pt_rhs, kjpt, kpass )  
     50      &                                             pt  , pt_rhs, kjpt, kpass ) 
    5051      !!---------------------------------------------------------------------- 
    5152      !!                  ***  ROUTINE tra_ldf_lap  *** 
    52       !!                    
    53       !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive  
     53      !! 
     54      !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive 
    5455      !!      trend and add it to the general trend of tracer equation. 
    5556      !! 
    5657      !! ** Method  :   Second order diffusive operator evaluated using before 
    57       !!      fields (forward time scheme). The horizontal diffusive trends of  
     58      !!      fields (forward time scheme). The horizontal diffusive trends of 
    5859      !!      the tracer is given by: 
    5960      !!          difft = 1/(e1e2t*e3t) {  di-1[ pahu e2u*e3u/e1u di(tb) ] 
     
    6263      !!          pt_rhs = pt_rhs + difft 
    6364      !! 
    64       !! ** Action  : - Update pt_rhs arrays with the before iso-level  
     65      !! ** Action  : - Update pt_rhs arrays with the before iso-level 
    6566      !!                harmonic mixing trend. 
    6667      !!---------------------------------------------------------------------- 
     
    7576      REAL(wp), DIMENSION(jpi,jpj,    kjpt), INTENT(in   ) ::   pgui, pgvi ! tracer gradient at top   levels 
    7677      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   pt         ! before tracer fields 
    77       REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pt_rhs     ! tracer trend  
     78      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pt_rhs     ! tracer trend 
    7879      ! 
    7980      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
     
    105106      !                             ! =========== ! 
    106107      DO jn = 1, kjpt               ! tracer loop ! 
    107          !                          ! =========== !     
    108          !                                
     108         !                          ! =========== ! 
     109         ! 
    109110         DO_3D_10_10( 1, jpkm1 ) 
    110111            ztu(ji,jj,jk) = zaheeu(ji,jj,jk) * ( pt(ji+1,jj  ,jk,jn) - pt(ji,jj,jk,jn) ) 
     
    118119            IF( ln_isfcav ) THEN                ! top in ocean cavities only 
    119120               DO_2D_10_10 
    120                   IF( miku(ji,jj) > 1 )   ztu(ji,jj,miku(ji,jj)) = zaheeu(ji,jj,miku(ji,jj)) * pgui(ji,jj,jn)  
    121                   IF( mikv(ji,jj) > 1 )   ztv(ji,jj,mikv(ji,jj)) = zaheev(ji,jj,mikv(ji,jj)) * pgvi(ji,jj,jn)  
     121                  IF( miku(ji,jj) > 1 )   ztu(ji,jj,miku(ji,jj)) = zaheeu(ji,jj,miku(ji,jj)) * pgui(ji,jj,jn) 
     122                  IF( mikv(ji,jj) > 1 )   ztv(ji,jj,mikv(ji,jj)) = zaheev(ji,jj,mikv(ji,jj)) * pgvi(ji,jj,jn) 
    122123               END_2D 
    123124            ENDIF 
     
    142143      ! 
    143144   END SUBROUTINE tra_ldf_lap 
    144     
     145 
    145146 
    146147   SUBROUTINE tra_ldf_blp( kt, Kmm, kit000, cdtype, pahu, pahv  ,             & 
     
    149150      !!---------------------------------------------------------------------- 
    150151      !!                 ***  ROUTINE tra_ldf_blp  *** 
    151       !!                     
    152       !! ** Purpose :   Compute the before lateral tracer diffusive  
     152      !! 
     153      !! ** Purpose :   Compute the before lateral tracer diffusive 
    153154      !!      trend and add it to the general trend of tracer equation. 
    154155      !! 
     
    200201      ! 
    201202      CALL lbc_lnk( 'traldf_lap_blp', zlap(:,:,:,:) , 'T', 1. )     ! Lateral boundary conditions (unchanged sign) 
    202       !                                               ! Partial top/bottom cell: GRADh( zlap )   
     203      !                                               ! Partial top/bottom cell: GRADh( zlap ) 
    203204      IF( ln_isfcav .AND. ln_zps ) THEN   ;   CALL zps_hde_isf( kt, Kmm, kjpt, zlap, zglu, zglv, zgui, zgvi )  ! both top & bottom 
    204       ELSEIF(             ln_zps ) THEN   ;   CALL zps_hde    ( kt, Kmm, kjpt, zlap, zglu, zglv )              ! only bottom  
     205      ELSEIF(             ln_zps ) THEN   ;   CALL zps_hde    ( kt, Kmm, kjpt, zlap, zglu, zglv )              ! only bottom 
    205206      ENDIF 
    206207      ! 
Note: See TracChangeset for help on using the changeset viewer.