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 13151 for NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/src/OCE/DYN/dynatf.F90 – NEMO

Ignore:
Timestamp:
2020-06-24T14:38:26+02:00 (4 years ago)
Author:
gm
Message:

result from merge with qco r12983

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/src/OCE/DYN/dynatf.F90

    r12489 r13151  
    1313   !!             -   !  2002-10  (C. Talandier, A-M. Treguier) Open boundary cond. 
    1414   !!            2.0  !  2005-11  (V. Garnier) Surface pressure gradient organization 
    15    !!            2.3  !  2007-07  (D. Storkey) Calls to BDY routines.  
     15   !!            2.3  !  2007-07  (D. Storkey) Calls to BDY routines. 
    1616   !!            3.2  !  2009-06  (G. Madec, R.Benshila)  re-introduce the vvl option 
    1717   !!            3.3  !  2010-09  (D. Storkey, E.O'Dea) Bug fix for BDY module 
     
    2222   !!            4.1  !  2019-08  (A. Coward, D. Storkey) Rename dynnxt.F90 -> dynatf.F90. Now just does time filtering. 
    2323   !!------------------------------------------------------------------------- 
    24    
     24 
    2525   !!---------------------------------------------------------------------------------------------- 
    2626   !!   dyn_atf       : apply Asselin time filtering to "now" velocities and vertical scale factors 
     
    4242   USE trdken         ! trend manager: kinetic energy 
    4343   USE isf_oce   , ONLY: ln_isf     ! ice shelf 
    44    USE isfdynatf , ONLY: isf_dynatf ! ice shelf volume filter correction subroutine  
     44   USE isfdynatf , ONLY: isf_dynatf ! ice shelf volume filter correction subroutine 
    4545   ! 
    4646   USE in_out_manager ! I/O manager 
     
    5959   PUBLIC    dyn_atf   ! routine called by step.F90 
    6060 
     61#if defined key_qco 
     62   !!---------------------------------------------------------------------- 
     63   !!   'key_qco'      EMPTY ROUTINE     Quasi-Eulerian vertical coordonate 
     64   !!---------------------------------------------------------------------- 
     65CONTAINS 
     66 
     67   SUBROUTINE dyn_atf ( kt, Kbb, Kmm, Kaa, puu, pvv, pe3t, pe3u, pe3v ) 
     68      INTEGER                             , INTENT(in   ) :: kt               ! ocean time-step index 
     69      INTEGER                             , INTENT(in   ) :: Kbb, Kmm, Kaa    ! before and after time level indices 
     70      REAL(wp), DIMENSION(jpi,jpj,jpk,jpt), INTENT(inout) :: puu, pvv         ! velocities to be time filtered 
     71      REAL(wp), DIMENSION(jpi,jpj,jpk,jpt), INTENT(inout) :: pe3t, pe3u, pe3v ! scale factors to be time filtered 
     72 
     73      WRITE(*,*) 'dyn_atf: You should not have seen this print! error?', kt 
     74   END SUBROUTINE dyn_atf 
     75 
     76#else 
     77 
    6178   !! * Substitutions 
    6279#  include "do_loop_substitute.h90" 
    6380   !!---------------------------------------------------------------------- 
    6481   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    65    !! $Id$  
     82   !! $Id$ 
    6683   !! Software governed by the CeCILL license (see ./LICENSE) 
    6784   !!---------------------------------------------------------------------- 
     
    7188      !!---------------------------------------------------------------------- 
    7289      !!                  ***  ROUTINE dyn_atf  *** 
    73       !!                    
    74       !! ** Purpose :   Finalize after horizontal velocity. Apply the boundary  
     90      !! 
     91      !! ** Purpose :   Finalize after horizontal velocity. Apply the boundary 
    7592      !!             condition on the after velocity and apply the Asselin time 
    7693      !!             filter to the now fields. 
     
    7996      !!             estimate (ln_dynspg_ts=T) 
    8097      !! 
    81       !!              * Apply lateral boundary conditions on after velocity  
     98      !!              * Apply lateral boundary conditions on after velocity 
    8299      !!             at the local domain boundaries through lbc_lnk call, 
    83100      !!             at the one-way open boundaries (ln_bdy=T), 
     
    86103      !!              * Apply the Asselin time filter to the now fields 
    87104      !!             arrays to start the next time step: 
    88       !!                (puu(Kmm),pvv(Kmm)) = (puu(Kmm),pvv(Kmm))  
     105      !!                (puu(Kmm),pvv(Kmm)) = (puu(Kmm),pvv(Kmm)) 
    89106      !!                                    + rn_atfp [ (puu(Kbb),pvv(Kbb)) + (puu(Kaa),pvv(Kaa)) - 2 (puu(Kmm),pvv(Kmm)) ] 
    90107      !!             Note that with flux form advection and non linear free surface, 
     
    92109      !!             As a result, dyn_atf MUST be called after tra_atf. 
    93110      !! 
    94       !! ** Action :   puu(Kmm),pvv(Kmm)   filtered now horizontal velocity  
     111      !! ** Action :   puu(Kmm),pvv(Kmm)   filtered now horizontal velocity 
    95112      !!---------------------------------------------------------------------- 
    96113      INTEGER                             , INTENT(in   ) :: kt               ! ocean time-step index 
     
    103120      REAL(wp) ::   zve3a, zve3n, zve3b, z1_2dt   !   -      - 
    104121      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   zue, zve, zwfld 
    105       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ze3t_f, ze3u_f, ze3v_f, zua, zva  
     122      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ze3t_f, ze3u_f, ze3v_f, zua, zva 
    106123      !!---------------------------------------------------------------------- 
    107124      ! 
     
    131148         ! 
    132149         IF( .NOT.ln_bt_fw ) THEN 
    133             ! Remove advective velocity from "now velocities"  
    134             ! prior to asselin filtering      
    135             ! In the forward case, this is done below after asselin filtering    
    136             ! so that asselin contribution is removed at the same time  
     150            ! Remove advective velocity from "now velocities" 
     151            ! prior to asselin filtering 
     152            ! In the forward case, this is done below after asselin filtering 
     153            ! so that asselin contribution is removed at the same time 
    137154            DO jk = 1, jpkm1 
    138155               puu(:,:,jk,Kmm) = ( puu(:,:,jk,Kmm) - un_adv(:,:)*r1_hu(:,:,Kmm) + uu_b(:,:,Kmm) )*umask(:,:,jk) 
    139156               pvv(:,:,jk,Kmm) = ( pvv(:,:,jk,Kmm) - vn_adv(:,:)*r1_hv(:,:,Kmm) + vv_b(:,:,Kmm) )*vmask(:,:,jk) 
    140             END DO   
     157            END DO 
    141158         ENDIF 
    142159      ENDIF 
    143160 
    144161      ! Update after velocity on domain lateral boundaries 
    145       ! --------------------------------------------------       
     162      ! -------------------------------------------------- 
    146163# if defined key_agrif 
    147164      CALL Agrif_dyn( kt )             !* AGRIF zoom boundaries 
     
    198215            zwfld(:,:) = emp_b(:,:) - emp(:,:) 
    199216            IF ( ln_rnf ) zwfld(:,:) =  zwfld(:,:) - ( rnf_b(:,:) - rnf(:,:) ) 
     217 
    200218            DO jk = 1, jpkm1 
    201219               ze3t_f(:,:,jk) = ze3t_f(:,:,jk) - zcoef * zwfld(:,:) * tmask(:,:,jk) & 
    202                               &                        * pe3t(:,:,jk,Kmm) / ( ht(:,:) + 1._wp - ssmask(:,:) )  
     220                              &                        * pe3t(:,:,jk,Kmm) / ( ht(:,:) + 1._wp - ssmask(:,:) ) 
    203221            END DO 
    204222            ! 
     
    237255                  pvv(ji,jj,jk,Kmm) = ( zve3n + rn_atfp * ( zve3b - 2._wp * zve3n  + zve3a ) ) / ze3v_f(ji,jj,jk) 
    238256               END_3D 
    239                pe3u(:,:,1:jpkm1,Kmm) = ze3u_f(:,:,1:jpkm1)   
     257               pe3u(:,:,1:jpkm1,Kmm) = ze3u_f(:,:,1:jpkm1) 
    240258               pe3v(:,:,1:jpkm1,Kmm) = ze3v_f(:,:,1:jpkm1) 
    241259               ! 
     
    248266         IF( ln_dynspg_ts .AND. ln_bt_fw ) THEN 
    249267            ! Revert filtered "now" velocities to time split estimate 
    250             ! Doing it here also means that asselin filter contribution is removed   
     268            ! Doing it here also means that asselin filter contribution is removed 
    251269            zue(:,:) = pe3u(:,:,1,Kmm) * puu(:,:,1,Kmm) * umask(:,:,1) 
    252             zve(:,:) = pe3v(:,:,1,Kmm) * pvv(:,:,1,Kmm) * vmask(:,:,1)     
     270            zve(:,:) = pe3v(:,:,1,Kmm) * pvv(:,:,1,Kmm) * vmask(:,:,1) 
    253271            DO jk = 2, jpkm1 
    254272               zue(:,:) = zue(:,:) + pe3u(:,:,jk,Kmm) * puu(:,:,jk,Kmm) * umask(:,:,jk) 
    255                zve(:,:) = zve(:,:) + pe3v(:,:,jk,Kmm) * pvv(:,:,jk,Kmm) * vmask(:,:,jk)     
     273               zve(:,:) = zve(:,:) + pe3v(:,:,jk,Kmm) * pvv(:,:,jk,Kmm) * vmask(:,:,jk) 
    256274            END DO 
    257275            DO jk = 1, jpkm1 
     
    305323      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Kaa), clinfo1=' nxt  - puu(:,:,:,Kaa): ', mask1=umask,   & 
    306324         &                                  tab3d_2=pvv(:,:,:,Kaa), clinfo2=' pvv(:,:,:,Kaa): '       , mask2=vmask ) 
    307       !  
     325      ! 
    308326      IF( ln_dynspg_ts )   DEALLOCATE( zue, zve ) 
    309327      IF( l_trddyn     )   DEALLOCATE( zua, zva ) 
     
    312330   END SUBROUTINE dyn_atf 
    313331 
     332#endif 
     333 
    314334   !!========================================================================= 
    315335END MODULE dynatf 
Note: See TracChangeset for help on using the changeset viewer.