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.
updtide.F90 in NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/SBC – NEMO

source: NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/SBC/updtide.F90 @ 9939

Last change on this file since 9939 was 9939, checked in by gm, 6 years ago

#1911 (ENHANCE-04): RK3 branche phased with MLF@9937 branche

  • Property svn:keywords set to Id
File size: 3.5 KB
Line 
1MODULE updtide
2   !!======================================================================
3   !!                       ***  MODULE  updtide  ***
4   !! Initialization of tidal forcing
5   !!======================================================================
6   !! History :  9.0  !  07  (O. Le Galloudec)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   upd_tide      : update tidal potential
11   !!----------------------------------------------------------------------
12   USE oce            ! ocean dynamics and tracers variables
13   USE dom_oce        ! ocean space and time domain
14   USE in_out_manager ! I/O units
15   USE phycst         ! physical constant
16   USE sbctide        ! tide potential variable
17   USE tideini , ONLY : ln_tide_ramp, rn_ramp
18
19   IMPLICIT NONE
20   PUBLIC
21
22   PUBLIC   upd_tide   ! called in dynspg_... modules
23 
24   !!----------------------------------------------------------------------
25   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
26   !! $Id$
27   !! Software governed by the CeCILL licence     (./LICENSE)
28   !!----------------------------------------------------------------------
29CONTAINS
30
31   SUBROUTINE upd_tide( kt, kit, time_offset )
32      !!----------------------------------------------------------------------
33      !!                 ***  ROUTINE upd_tide  ***
34      !!
35      !! ** Purpose :   provide at each time step the astronomical potential
36      !!
37      !! ** Method  :   computed from pulsation and amplitude of all tide components
38      !!
39      !! ** Action  :   pot_astro   actronomical potential
40      !!----------------------------------------------------------------------     
41      INTEGER, INTENT(in)           ::   kt          ! ocean time-step index
42      INTEGER, INTENT(in), OPTIONAL ::   kit         ! external mode sub-time-step index (lk_dynspg_ts=T)
43      INTEGER, INTENT(in), OPTIONAL ::   time_offset ! time offset in number  of internal steps (lk_dynspg_ts=F)
44      !                                              !                        of external steps (lk_dynspg_ts=T)
45      !
46      INTEGER  ::   ji, jj, jk   ! dummy loop indices
47      INTEGER  ::   joffset      ! local integer
48      REAL(wp) ::   zt, zramp    ! local scalar
49      REAL(wp), DIMENSION(nb_harmo) ::   zwt 
50      !!----------------------------------------------------------------------     
51      !
52      !                               ! tide pulsation at model time step (or sub-time-step)
53      zt = ( kt - kt_tide ) * rn_Dt
54      !
55      joffset = 0
56      IF( PRESENT( time_offset ) )   joffset = time_offset
57      !
58      IF( PRESENT( kit ) )   THEN
59         zt = zt + ( kit +  joffset - 1 ) * rn_Dt / REAL( nn_e, wp )
60      ELSE
61         zt = zt + joffset * rn_Dt
62      ENDIF
63      !
64      zwt(:) = omega_tide(:) * zt
65
66      pot_astro(:,:) = 0._wp          ! update tidal potential (sum of all harmonics)
67      DO jk = 1, nb_harmo   
68         pot_astro(:,:) = pot_astro(:,:) + amp_pot(:,:,jk) * COS( zwt(jk) + phi_pot(:,:,jk) )     
69      END DO
70      !
71      IF( ln_tide_ramp ) THEN         ! linear increase if asked
72         zt = ( kt - nit000 ) * rn_Dt
73         IF( PRESENT( kit ) )   zt = zt + ( kit + joffset -1) * rn_Dt / REAL( nn_e, wp )
74         zramp = MIN(  MAX( 0._wp , zt / (rn_ramp*rday) ) , 1._wp  )
75         pot_astro(:,:) = zramp * pot_astro(:,:)
76      ENDIF
77      !
78   END SUBROUTINE upd_tide
79
80  !!======================================================================
81
82END MODULE updtide
Note: See TracBrowser for help on using the repository browser.