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.
dynstcor.F90 in branches/UKMO/r5518_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/UKMO/r5518_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/DYN/dynstcor.F90 @ 7152

Last change on this file since 7152 was 7152, checked in by jcastill, 7 years ago

Initial implementation of wave coupling branch - INGV wave branch + UKMO wave coupling branch

File size: 3.3 KB
Line 
1MODULE dynstcor
2   !!======================================================================
3   !!                       ***  MODULE  dynstcor  ***
4   !! Ocean dynamics: Stokes-Coriolis effect.
5   !!
6   !!======================================================================
7   !! History :  0.1  !  2012-10  (Oyvind Breivik)
8   !!----------------------------------------------------------------------
9   !! dyn_stcor        : Add the Stokes-Coriolis forcing to the momentum equation
10   !!----------------------------------------------------------------------
11   USE oce              ! ocean dynamics and tracers
12   USE dom_oce          ! ocean space and time domain
13   USE in_out_manager   ! I/O manager
14   USE lib_mpp          ! distributed memory computing
15   USE prtctl           ! Print control
16   USE phycst
17   USE lbclnk
18   USE wrk_nemo         ! Memory Allocation
19   USE sbcmod           ! Access to ln_stcor (sbc_oce) and wave parameters (sbc_wave)
20   USE sbcwave          ! Wave module
21   USE timing          ! Timing
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Routine accessibility
27   PUBLIC dyn_stcor      ! routine called by step.F90
28
29   !! * Substitutions
30#  include "vectopt_loop_substitute.h90"
31#  include "domzgr_substitute.h90"
32   !!----------------------------------------------------------------------
33   !! NEMO/OPA 3.6 , NEMO Consortium (2010)
34   !! $Id$
35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37 CONTAINS
38
39   SUBROUTINE dyn_stcor( kt )
40      !!----------------------------------------------------------------------
41      !!                  ***  ROUTINE dyn_stcor ***
42      !!
43      !! ** Purpose:  Add Stokes-Coriolis forcing to horizontal momentum equation.
44      !!
45      !! ** History:  3.4  !   2012-10  (O. Breivik)   Initial version
46      !!              3.6  !   2014-10  (R. Benshila)
47      !!----------------------------------------------------------------------
48      INTEGER, INTENT( in ) ::   kt  ! ocean time-step index
49      !!
50      INTEGER  ::  ji, jj, jk        ! dummy loop indices
51      REAL(wp) :: zx1, zx2, zy1, zy2
52      !!----------------------------------------------------------------------
53      !
54      IF( nn_timing == 1 )  CALL timing_start('dyn_stcor')
55      !
56      IF( kt == nit000 ) THEN
57         IF(lwp) WRITE(numout,*)
58         IF(lwp) WRITE(numout,*) 'dyn_stcor : time stepping'
59         IF(lwp) WRITE(numout,*) '~~~~~~~'
60      ENDIF
61
62      !
63      ! Update velocity tendencies ua, va by adding the Stokes-Coriolis velocities
64      !
65      DO jk = 1, jpkm1
66         DO jj = 2, jpjm1
67            DO ji = 2, jpim1
68               zy1 = ff(ji  ,jj-1) * ( vsd3d(ji  ,jj-1,jk) + vsd3d(ji+1,jj-1,jk) )
69               zy2 = ff(ji  ,jj  ) * ( vsd3d(ji  ,jj  ,jk) + vsd3d(ji+1,jj  ,jk) )
70               zx1 = ff(ji-1,jj  ) * ( usd3d(ji-1,jj  ,jk) + usd3d(ji-1,jj+1,jk) )
71               zx2 = ff(ji  ,jj  ) * ( usd3d(ji  ,jj  ,jk) + usd3d(ji  ,jj+1,jk) )
72
73               ua(ji,jj,jk) = ua(ji,jj,jk) + 0.25 * ( zy1 + zy2 ) *umask(ji,jj,jk)
74               va(ji,jj,jk) = va(ji,jj,jk) - 0.25 * ( zx1 + zx2 ) *vmask(ji,jj,jk)
75            ENDDO
76         ENDDO
77      ENDDO
78      !
79      IF( nn_timing == 1 )  CALL timing_stop('dynst_cor')
80      !
81   END SUBROUTINE dyn_stcor
82
83END MODULE dynstcor
Note: See TracBrowser for help on using the repository browser.