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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/TRP/trctrp.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/TRP/trctrp.F90

    r10068 r12928  
    2020   USE trcadv          ! advection                           (trc_adv routine) 
    2121   USE trczdf          ! vertical diffusion                  (trc_zdf routine) 
    22    USE trcnxt          ! time-stepping                       (trc_nxt routine) 
     22   USE trcatf          ! time filtering                      (trc_atf routine) 
    2323   USE trcrad          ! positivity                          (trc_rad routine) 
    2424   USE trcsbc          ! surface boundary condition          (trc_sbc routine) 
     25   USE trcbc           ! Tracers boundary condtions          ( trc_bc routine) 
    2526   USE zpshde          ! partial step: hor. derivative       (zps_hde routine) 
    2627   USE bdy_oce   , ONLY: ln_bdy 
     
    4445CONTAINS 
    4546 
    46    SUBROUTINE trc_trp( kt ) 
     47   SUBROUTINE trc_trp( kt, Kbb, Kmm, Krhs, Kaa ) 
    4748      !!---------------------------------------------------------------------- 
    4849      !!                     ***  ROUTINE trc_trp  *** 
     
    5354      !!              - Update the passive tracers 
    5455      !!---------------------------------------------------------------------- 
    55       INTEGER, INTENT( in ) ::  kt  ! ocean time-step index 
     56      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
     57      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices (not swapped in this routine) 
    5658      !! --------------------------------------------------------------------- 
    5759      ! 
     
    6062      IF( .NOT. lk_c1d ) THEN 
    6163         ! 
    62                                 CALL trc_sbc    ( kt )      ! surface boundary condition 
    63          IF( ln_trabbl )        CALL trc_bbl    ( kt )      ! advective (and/or diffusive) bottom boundary layer scheme 
    64          IF( ln_trcdmp )        CALL trc_dmp    ( kt )      ! internal damping trends 
    65          IF( ln_bdy )           CALL trc_bdy_dmp( kt )      ! BDY damping trends 
    66                                 CALL trc_adv    ( kt )      ! horizontal & vertical advection  
     64                                CALL trc_sbc    ( kt,      Kmm, tr, Krhs )      ! surface boundary condition 
     65         IF( ln_trcbc .AND. lltrcbc .AND. kt /= nit000 )  & 
     66                                CALL trc_bc     ( kt,      Kmm, tr, Krhs )      ! tracers: surface and lateral Boundary Conditions  
     67         IF( ln_trabbl )        CALL trc_bbl    ( kt, Kbb, Kmm, tr, Krhs )      ! advective (and/or diffusive) bottom boundary layer scheme 
     68         IF( ln_trcdmp )        CALL trc_dmp    ( kt, Kbb, Kmm, tr, Krhs )      ! internal damping trends 
     69         IF( ln_bdy )           CALL trc_bdy_dmp( kt, Kbb,      Krhs )      ! BDY damping trends 
     70                                CALL trc_adv    ( kt, Kbb, Kmm, tr, Krhs )      ! horizontal & vertical advection  
    6771         !                                                         ! Partial top/bottom cell: GRADh( trb )   
    6872         IF( ln_zps ) THEN 
    69            IF( ln_isfcav ) THEN ; CALL zps_hde_isf( kt, jptra, trb, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )  ! both top & bottom 
    70            ELSE                 ; CALL zps_hde    ( kt, jptra, trb, gtru, gtrv )                                      !  only bottom 
     73           IF( ln_isfcav ) THEN ; CALL zps_hde_isf( kt, Kmm, jptra, tr(:,:,:,:,Kbb), pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )  ! both top & bottom 
     74           ELSE                 ; CALL zps_hde    ( kt, Kmm, jptra, tr(:,:,:,:,Kbb), gtru, gtrv )                                      !  only bottom 
    7175           ENDIF 
    7276         ENDIF 
    7377         !                                                       
    74                                 CALL trc_ldf    ( kt )      ! lateral mixing 
     78                                CALL trc_ldf    ( kt, Kbb, Kmm,       tr, Krhs )  ! lateral mixing 
    7579#if defined key_agrif 
    7680         IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_trc       ! tracers sponge 
    7781#endif 
    78                                 CALL trc_zdf    ( kt )      ! vertical mixing and after tracer fields 
    79                                 CALL trc_nxt    ( kt )      ! tracer fields at next time step      
    80          IF( ln_trcrad )        CALL trc_rad    ( kt )      ! Correct artificial negative concentrations 
    81          IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt )      ! internal damping trends on closed seas only 
     82                                CALL trc_zdf    ( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer   ==> after 
     83                                CALL trc_atf    ( kt, Kbb, Kmm, Kaa , tr )        ! time filtering of "now" tracer fields     
     84         ! 
     85         ! Subsequent calls use the filtered values: Kmm and Kaa  
     86         ! These are used explicitly here since time levels will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp 
     87         ! 
     88         IF( ln_trcrad )        CALL trc_rad    ( kt, Kmm, Kaa, tr       )    ! Correct artificial negative concentrations 
     89         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt, Kmm, Kaa )              ! internal damping trends on closed seas only 
    8290 
    8391         ! 
    8492      ELSE                                               ! 1D vertical configuration 
    85                                 CALL trc_sbc( kt )            ! surface boundary condition 
    86          IF( ln_trcdmp )        CALL trc_dmp( kt )            ! internal damping trends 
    87                                 CALL trc_zdf( kt )            ! vertical mixing and after tracer fields 
    88                                 CALL trc_nxt( kt )            ! tracer fields at next time step      
    89           IF( ln_trcrad )       CALL trc_rad( kt )            ! Correct artificial negative concentrations 
     93                                CALL trc_sbc( kt,      Kmm,       tr, Krhs )  ! surface boundary condition 
     94         IF( ln_trcdmp )        CALL trc_dmp( kt, Kbb, Kmm,       tr, Krhs )  ! internal damping trends 
     95                                CALL trc_zdf( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer ==> after 
     96                                CALL trc_atf( kt, Kbb, Kmm, Kaa , tr )        ! time filtering of "now" tracer fields 
     97         ! 
     98         ! Subsequent calls use the filtered values: Kmm and Kaa  
     99         ! These are used explicitly here since time levels will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp 
     100         ! 
     101         IF( ln_trcrad )       CALL trc_rad( kt, Kmm, Kaa, tr       )  ! Correct artificial negative concentrations 
    90102         ! 
    91103      END IF 
Note: See TracChangeset for help on using the changeset viewer.