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

source: branches/UKMO/r6232_HZG_WAVE/NEMOGCM/NEMO/OPA_SRC/DYN/dynstcor.F90 @ 7807

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

Changes as in HZG wave forcing branch, but adapted to r6232

  • Property svn:executable set to *
File size: 5.4 KB
Line 
1MODULE dynstcor
2!! PHILLIPPS PARAMETRIZATION
3   !!======================================================================
4   !!                       ***  MODULE  dynstcor  ***
5   !! Ocean dynamics: Stokes-Coriolis effect.
6   !!
7   !!======================================================================
8   !! History :  0.1  !  2012-10  (Oyvind Breivik)
9   !!            0.2  !  2016-06  (oyvind.breivik@met.no)
10   !!                 !           Changed Stokes profile to the Phillips approximation
11   !!                        Ref: Breivik, O, J-R Bidlot, P A Janssen (2016).
12   !!                             A Stokes drift approximation based on the Phillips spectrum,
13   !!                             Ocean Model, 100, pp 49-56, doi:10.1016/j.ocemod.2016.01.005
14   !!            0.2.1! 2016-12   WAVE2NEMO: adapted to NEMO3.6, this is the PHILLIPS approximation
15   !!----------------------------------------------------------------------
16   !! dyn_stcor        : Add the Stokes-Coriolis forcing to the momentum equation
17   !!----------------------------------------------------------------------
18   USE oce              ! ocean dynamics and tracers
19   USE dom_oce          ! ocean space and time domain
20!  USE obc_oce          ! ocean lateral open boundary condition !! WAVE2NEMO: does not exist in NEMO36
21   USE in_out_manager   ! I/O manager
22   USE lib_mpp          ! distributed memory computing
23   USE prtctl           ! Print control
24   USE phycst
25   USE lbclnk
26   USE wrk_nemo         ! Memory Allocation
27   USE sbcmod           ! Access to ln_stcor (sbc_oce) and wave parameters (sbc_wave)
28   USE sbcwave          ! Wave module
29
30   IMPLICIT NONE
31
32   REAL(wp) :: rn_deptmaxstcor = 150.0_wp ! maximum depth [m] to be affected by Stokes-Coriolis effect
33   !PRIVATE
34
35   !! * Routine accessibility
36   PUBLIC dyn_stcor           ! routine called by step.F90
37
38   !! * Shared module variables
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ustc, vstc  ! Stokes-Coriolis u and v
40
41   !! * Module variables
42
43   !! * Substitutions
44#  include "vectopt_loop_substitute.h90"
45#  include "domzgr_substitute.h90"
46   !!----------------------------------------------------------------------
47   !!   OPA 9.0 , implemented by Bedford Institute of Oceanography
48   !!----------------------------------------------------------------------
49
50 CONTAINS
51
52   INTEGER FUNCTION dynstcor_alloc()
53      !!----------------------------------------------------------------------
54      !!                    ***  ROUTINE dynstcor_alloc  ***
55      !!
56      !! History :  1.0  !  2012-10  (Oyvind Breivik)
57      !!----------------------------------------------------------------------
58      ALLOCATE( ustc(jpi,jpj,jpk) , vstc(jpi,jpj,jpk) , STAT=dynstcor_alloc )
59         !
60      IF( dynstcor_alloc /= 0 )   CALL ctl_warn('dynstcor_alloc: array allocate failed.')
61   END FUNCTION dynstcor_alloc
62
63   SUBROUTINE dyn_stcor( kt )
64      !!----------------------------------------------------------------------
65      !!                  ***  ROUTINE dyn_stcor ***
66      !!
67      !! ** Purpose:  Add Stokes-Coriolis forcing to horizontal momentum equation.
68      !!
69      !! ** History:  0.1  !   2012-10  oyvind.breivik@ecmwf.int
70      !!----------------------------------------------------------------------
71      INTEGER, INTENT( in ) ::   kt  ! ocean time-step index
72      !!
73      INTEGER  ::  ji, jj, jk        ! dummy loop indices
74      REAL(wp) ::  ztransp, zsp0, zk, zfac
75      REAL(wp) ::  zus, zvs
76      !
77
78      ! Allocation at first time step.
79
80      IF ( kt == nit000 ) THEN
81         IF( dynstcor_alloc() /= 0 ) CALL ctl_stop('dyn_stcor_phil: array allocate failed.')
82      ENDIF
83
84      !!----------------------------------------------------------------------
85      !
86      ! Update velocity tendencies ua, va by adding the Stokes-Coriolis velocities ustc, vstc
87      !
88      DO jk = 1, jpk
89         DO jj = 1, jpj
90            DO ji = 1, jpi
91               ! Skip deep levels where the Stokes-Coriolis effect is negligible
92               IF (fsdept(ji,jj,jk) <= rn_deptmaxstcor) THEN
93                  ! Stokes transport speed estimated from Hs and Tmean
94                  ztransp = 2.0_wp*rpi*swh_wavepar(ji,jj)**2.0_wp/(16.0_wp*MAX(mwp_wavepar(ji,jj),0.0000001_wp))
95
96                  ! Stokes surface speed
97                  zsp0 = SQRT(ust_wavepar(ji,jj)**2 + vst_wavepar(ji,jj)**2)
98
99                  ! Wavenumber scale
100                  !zk = ABS(zsp0)/MAX(ABS(5.97_wp*ztransp),0.0000001_wp)
101                  zk = (1.0_wp-2.0_wp/3.0_wp)*zsp0/MAX(2.0_wp*ztransp,0.0000001_wp)
102
103                  ! Depth attenuation
104                  !zfac = EXP(-2.0_wp*zk*fsdept(ji,jj,jk))/(1.0_wp+8.0_wp*zk*fsdept(ji,jj,jk))
105                  zfac = EXP(-2.0*zk*fsdept(ji,jj,jk)) - SQRT(2.0_wp*rpi*zk*fsdept(ji,jj,jk))*ERFC(SQRT(2.0_wp*zk*fsdept(ji,jj,jk)))
106
107                  ! The Stokes-Coriolis forcing
108                  zus =  ff(ji,jj)*vst_wavepar(ji,jj)*zfac
109                  zvs = -ff(ji,jj)*ust_wavepar(ji,jj)*zfac
110
111                  ! Store arrays of tendencies for diagnostics output
112                  ! This may be removed later for efficiency
113                  ustc(ji,jj,jk) = zus
114                  vstc(ji,jj,jk) = zvs
115
116                  ua(ji,jj,jk) = ua(ji,jj,jk) + zus * umask(ji,jj,jk)
117                  va(ji,jj,jk) = va(ji,jj,jk) + zvs * vmask(ji,jj,jk)
118               ENDIF
119            ENDDO
120         ENDDO
121      ENDDO
122      !
123   END SUBROUTINE dyn_stcor
124
125
126END MODULE dynstcor
Note: See TracBrowser for help on using the repository browser.