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/UKMO/NEMO_4.0_GO8_package_text_diagnostics/src/OCE/SBC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_GO8_package_text_diagnostics/src/OCE/SBC/updtide.F90

Last change on this file was 10888, checked in by davestorkey, 5 years ago

branches/UKMO/NEMO_4.0_mirror : clear SVN keywords

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