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 14072 for NEMO/trunk/src/OCE/TRA/traadv_ubs.F90 – NEMO

Ignore:
Timestamp:
2020-12-04T08:48:38+01:00 (3 years ago)
Author:
laurent
Message:

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/TRA/traadv_ubs.F90

    r13982 r14072  
    1010   !!---------------------------------------------------------------------- 
    1111   !!   tra_adv_ubs : update the tracer trend with the horizontal 
    12    !!                 advection trends using a third order biaised scheme   
     12   !!                 advection trends using a third order biaised scheme 
    1313   !!---------------------------------------------------------------------- 
    1414   USE oce            ! ocean dynamics and active tracers 
     
    1616   USE trc_oce        ! share passive tracers/Ocean variables 
    1717   USE trd_oce        ! trends: ocean variables 
    18    USE traadv_fct      ! acces to routine interp_4th_cpt  
    19    USE trdtra         ! trends manager: tracers  
     18   USE traadv_fct      ! acces to routine interp_4th_cpt 
     19   USE trdtra         ! trends manager: tracers 
    2020   USE diaptr         ! poleward transport diagnostics 
    2121   USE diaar5         ! AR5 diagnostics 
     
    2525   USE lib_mpp        ! massively parallel library 
    2626   USE lbclnk         ! ocean lateral boundary condition (or mpp link) 
    27    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     27   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    2828 
    2929   IMPLICIT NONE 
     
    5151      !!---------------------------------------------------------------------- 
    5252      !!                  ***  ROUTINE tra_adv_ubs  *** 
    53       !!                  
     53      !! 
    5454      !! ** Purpose :   Compute the now trend due to the advection of tracers 
    5555      !!      and add it to the general trend of passive tracer equations. 
     
    6060      !!      For example the i-component of the advective fluxes are given by : 
    6161      !!                !  e2u e3u un ( mi(Tn) - zltu(i  ) )   if un(i) >= 0 
    62       !!          ztu = !  or  
     62      !!          ztu = !  or 
    6363      !!                !  e2u e3u un ( mi(Tn) - zltu(i+1) )   if un(i) < 0 
    6464      !!      where zltu is the second derivative of the before temperature field: 
    6565      !!          zltu = 1/e3t di[ e2u e3u / e1u di[Tb] ] 
    66       !!        This results in a dissipatively dominant (i.e. hyper-diffusive)  
    67       !!      truncation error. The overall performance of the advection scheme  
    68       !!      is similar to that reported in (Farrow and Stevens, 1995).  
     66      !!        This results in a dissipatively dominant (i.e. hyper-diffusive) 
     67      !!      truncation error. The overall performance of the advection scheme 
     68      !!      is similar to that reported in (Farrow and Stevens, 1995). 
    6969      !!        For stability reasons, the first term of the fluxes which corresponds 
    70       !!      to a second order centered scheme is evaluated using the now velocity  
    71       !!      (centered in time) while the second term which is the diffusive part  
    72       !!      of the scheme, is evaluated using the before velocity (forward in time).  
     70      !!      to a second order centered scheme is evaluated using the now velocity 
     71      !!      (centered in time) while the second term which is the diffusive part 
     72      !!      of the scheme, is evaluated using the before velocity (forward in time). 
    7373      !!      Note that UBS is not positive. Do not use it on passive tracers. 
    7474      !!                On the vertical, the advection is evaluated using a FCT scheme, 
    75       !!      as the UBS have been found to be too diffusive.  
    76       !!                kn_ubs_v argument controles whether the FCT is based on  
    77       !!      a 2nd order centrered scheme (kn_ubs_v=2) or on a 4th order compact  
     75      !!      as the UBS have been found to be too diffusive. 
     76      !!                kn_ubs_v argument controles whether the FCT is based on 
     77      !!      a 2nd order centrered scheme (kn_ubs_v=2) or on a 4th order compact 
    7878      !!      scheme (kn_ubs_v=4). 
    7979      !! 
     
    8282      !!             - poleward advective heat and salt transport (ln_diaptr=T) 
    8383      !! 
    84       !! Reference : Shchepetkin, A. F., J. C. McWilliams, 2005, Ocean Modelling, 9, 347-404.  
     84      !! Reference : Shchepetkin, A. F., J. C. McWilliams, 2005, Ocean Modelling, 9, 347-404. 
    8585      !!             Farrow, D.E., Stevens, D.P., 1995, J. Phys. Ocean. 25, 1731�1741. 
    8686      !!---------------------------------------------------------------------- 
     
    125125      DO jn = 1, kjpt                                            ! tracer loop 
    126126         !                                                       ! =========== 
    127          !                                               
     127         ! 
    128128         DO jk = 1, jpkm1                !==  horizontal laplacian of before tracer ==! 
    129129            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )                   ! First derivative (masked gradient) 
     
    138138               zltv(ji,jj,jk) = (  ztv(ji,jj,jk) - ztv(ji,jj-1,jk)  ) * zcoef 
    139139            END_2D 
    140             !                                     
    141          END DO          
     140            ! 
     141         END DO 
    142142         IF (nn_hls.EQ.1) CALL lbc_lnk_multi( 'traadv_ubs', zltu, 'T', 1.0_wp, zltv, 'T', 1.0_wp )   ! Lateral boundary cond. (unchanged sgn) 
    143          !     
     143         ! 
    144144         DO_3D( 1, 0, 1, 0, 1, jpkm1 )   !==  Horizontal advective fluxes  ==!     (UBS) 
    145145            zfp_ui = pU(ji,jj,jk) + ABS( pU(ji,jj,jk) )        ! upstream transport (x2) 
     
    166166                  &                * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm) 
    167167            END_2D 
    168             !                                              
     168            ! 
    169169         END DO 
    170170         ! 
     
    177177             CALL trd_tra( kt, Kmm, Krhs, cdtype, jn, jptra_yad, ztv, pV, pt(:,:,:,jn,Kmm) ) 
    178178         END IF 
    179          !      
     179         ! 
    180180         !                                ! "Poleward" heat and salt transports (contribution of upstream fluxes) 
    181181         IF( l_ptr )  CALL dia_ptr_hst( jn, 'adv', ztv(:,:,:) ) 
     
    188188         SELECT CASE( kn_ubs_v )       ! select the vertical advection scheme 
    189189         ! 
    190          CASE(  2  )                   ! 2nd order FCT  
    191             !          
     190         CASE(  2  )                   ! 2nd order FCT 
     191            ! 
    192192            IF( l_trd ) THEN 
    193193               DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     
    205205               IF( ln_isfcav ) THEN                   ! top of the ice-shelf cavities and at the ocean surface 
    206206                  DO_2D( 1, 1, 1, 1 ) 
    207                      ztw(ji,jj, mikt(ji,jj) ) = pW(ji,jj,mikt(ji,jj)) * pt(ji,jj,mikt(ji,jj),jn,Kbb)   ! linear free surface  
     207                     ztw(ji,jj, mikt(ji,jj) ) = pW(ji,jj,mikt(ji,jj)) * pt(ji,jj,mikt(ji,jj),jn,Kbb)   ! linear free surface 
    208208                  END_2D 
    209209               ELSE                                   ! no cavities: only at the ocean surface 
     
    217217               ztak = - ( ztw(ji,jj,jk) - ztw(ji,jj,jk+1) )    & 
    218218                  &     * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm) 
    219                pt(ji,jj,jk,jn,Krhs) =   pt(ji,jj,jk,jn,Krhs) +  ztak  
     219               pt(ji,jj,jk,jn,Krhs) =   pt(ji,jj,jk,jn,Krhs) +  ztak 
    220220               zti(ji,jj,jk)    = ( pt(ji,jj,jk,jn,Kbb) + p2dt * ( ztak + zltu(ji,jj,jk) ) ) * tmask(ji,jj,jk) 
    221221            END_3D 
     
    266266      !!--------------------------------------------------------------------- 
    267267      !!                    ***  ROUTINE nonosc_z  *** 
    268       !!      
    269       !! **  Purpose :   compute monotonic tracer fluxes from the upstream  
    270       !!       scheme and the before field by a nonoscillatory algorithm  
     268      !! 
     269      !! **  Purpose :   compute monotonic tracer fluxes from the upstream 
     270      !!       scheme and the before field by a nonoscillatory algorithm 
    271271      !! 
    272272      !! **  Method  :   ... ??? 
Note: See TracChangeset for help on using the changeset viewer.