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/2014/dev_r4642_WavesWG/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/2014/dev_r4642_WavesWG/NEMOGCM/NEMO/OPA_SRC/DYN/dynstcor.F90 @ 4644

Last change on this file since 4644 was 4644, checked in by acc, 10 years ago

Branch 2014/dev_r4642_WavesWG #1323. Import of surface wave components from the 2013/dev_ECMWF_waves branch + a few compatability changes and some mislaid documentation

File size: 4.5 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_ecmwf    ! Wave module
21
22   IMPLICIT NONE
23
24   REAL(wp) :: rn_deptmaxstcor = 150.0_wp ! maximum depth [m] to be affected by Stokes-Coriolis effect
25   !PRIVATE
26
27   !! * Routine accessibility
28   PUBLIC dyn_stcor           ! routine called by step.F90
29
30   !! * Shared module variables
31   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ustc, vstc  ! Stokes-Coriolis u and v
32
33   !! * Module variables
34
35   !! * Substitutions
36#  include "vectopt_loop_substitute.h90"
37#  include "domzgr_substitute.h90"
38   !!----------------------------------------------------------------------
39   !!   OPA 9.0 , implemented by Bedford Institute of Oceanography
40   !!----------------------------------------------------------------------
41
42 CONTAINS
43
44   INTEGER FUNCTION dynstcor_alloc()
45      !!----------------------------------------------------------------------
46      !!                    ***  ROUTINE dynstcor_alloc  ***
47      !!
48      !! History :  1.0  !  2012-10  (Oyvind Breivik)
49      !!----------------------------------------------------------------------
50      ALLOCATE( ustc(jpi,jpj,jpk) , vstc(jpi,jpj,jpk) , STAT=dynstcor_alloc )
51         !
52      IF( dynstcor_alloc /= 0 )   CALL ctl_warn('dynstcor_alloc: array allocate failed.')
53   END FUNCTION dynstcor_alloc
54
55   SUBROUTINE dyn_stcor( kt )
56      !!----------------------------------------------------------------------
57      !!                  ***  ROUTINE dyn_stcor ***
58      !!
59      !! ** Purpose:  Add Stokes-Coriolis forcing to horizontal momentum equation.
60      !!
61      !! ** History:  0.1  !   2012-10  oyvind.breivik@ecmwf.int
62      !!----------------------------------------------------------------------
63      INTEGER, INTENT( in ) ::   kt  ! ocean time-step index
64      !!
65      INTEGER  ::  ji, jj, jk        ! dummy loop indices
66      REAL(wp) ::  ztransp, zsp0, zk, zfac
67      REAL(wp) ::  zus, zvs
68      !
69
70      ! Allocation at first time step.
71
72      IF ( kt == nit000 ) THEN
73         IF( dynstcor_alloc() /= 0 ) CALL ctl_stop('dyn_stcor: array allocate failed.')
74      ENDIF
75
76      !!----------------------------------------------------------------------
77      !
78      ! Update velocity tendencies ua, va by adding the Stokes-Coriolis velocities ustc, vstc
79      !
80      DO jk = 1, jpk
81         DO jj = 1, jpj
82            DO ji = 1, jpi
83               ! Skip deep levels where the Stokes-Coriolis effect is negligible
84               IF (fsdept(ji,jj,jk) <= rn_deptmaxstcor) THEN
85                  ! Stokes transport speed estimated from Hs and Tmean
86                  ztransp = 2.0_wp*rpi*swh_wavepar(ji,jj)**2.0_wp/(16.0_wp*MAX(mwp_wavepar(ji,jj),0.0000001_wp))
87
88                  ! Stokes surface speed
89                  zsp0 = SQRT(ust_wavepar(ji,jj)**2 + vst_wavepar(ji,jj)**2)
90
91                  ! Wavenumber scale
92                  zk = ABS(zsp0)/MAX(ABS(5.97_wp*ztransp),0.0000001_wp)
93
94                  ! Depth attenuation
95                  zfac = EXP(-2.0_wp*zk*fsdept(ji,jj,jk))/(1.0_wp+8.0_wp*zk*fsdept(ji,jj,jk))
96
97                  ! The Stokes-Coriolis forcing
98                  zus =  ff(ji,jj)*vst_wavepar(ji,jj)*zfac
99                  zvs = -ff(ji,jj)*ust_wavepar(ji,jj)*zfac
100
101                  ! Store arrays of tendencies for diagnostics output
102                  ! This may be removed later for efficiency
103                  ustc(ji,jj,jk) = zus
104                  vstc(ji,jj,jk) = zvs
105
106                  ua(ji,jj,jk) = ua(ji,jj,jk) + zus * umask(ji,jj,jk)
107                  va(ji,jj,jk) = va(ji,jj,jk) + zvs * vmask(ji,jj,jk)
108               ENDIF
109            ENDDO
110         ENDDO
111      ENDDO
112      !
113   END SUBROUTINE dyn_stcor
114
115
116END MODULE dynstcor
Note: See TracBrowser for help on using the repository browser.