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/2019/dev_r12114_ticket_2263/src/OCE/SBC – NEMO

source: NEMO/branches/2019/dev_r12114_ticket_2263/src/OCE/SBC/updtide.F90 @ 12127

Last change on this file since 12127 was 12127, checked in by smasson, 4 years ago

dev_r12114_ticket_2263: replace integer kt_offset by real pt_offset, see #2263

  • Property svn:keywords set to Id
File size: 3.5 KB
RevLine 
[2952]1MODULE updtide
[4292]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
[2952]16
[4292]17   IMPLICIT NONE
18   PUBLIC
[2952]19
[4292]20   PUBLIC   upd_tide   ! called in dynspg_... modules
21 
22   !!----------------------------------------------------------------------
[9598]23   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[5215]24   !! $Id$
[10068]25   !! Software governed by the CeCILL license (see ./LICENSE)
[4292]26   !!----------------------------------------------------------------------
[2952]27CONTAINS
28
[12127]29   SUBROUTINE upd_tide( kt, kit, pt_offset )
[4292]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
[5913]40      INTEGER, INTENT(in), OPTIONAL ::   kit     ! external mode sub-time-step index (lk_dynspg_ts=T)
[12127]41      REAL(wp),INTENT(in), OPTIONAL ::   pt_offset ! time offset in number
[5913]42                                                     ! of internal steps             (lk_dynspg_ts=F)
43                                                     ! of external steps             (lk_dynspg_ts=T)
[4292]44      !
45      INTEGER  ::   ji, jj, jk   ! dummy loop indices
46      REAL(wp) ::   zt, zramp    ! local scalar
[12127]47      REAL(wp) ::   zt_offset   
[4292]48      REAL(wp), DIMENSION(nb_harmo) ::   zwt 
49      !!----------------------------------------------------------------------     
50      !
51      !                               ! tide pulsation at model time step (or sub-time-step)
[12127]52      zt = REAL( kt - kt_tide, wp ) * rdt
[4292]53      !
[12127]54      zt_offset = 0._wp
55      IF( PRESENT( pt_offset ) )   zt_offset = pt_offset
[4292]56      !
[5913]57      IF( PRESENT( kit ) )   THEN
[12127]58         zt = zt + ( REAL( kit, wp ) +  zt_offset - 1._wp ) * rdt / REAL( nn_baro, wp )
[4292]59      ELSE
[12127]60         zt = zt + zt_offset * rdt
[4292]61      ENDIF
62      !
63      zwt(:) = omega_tide(:) * zt
[2952]64
[4292]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
[12127]72         IF( PRESENT( kit ) )   zt = zt + ( REAL( kit, wp ) + zt_offset -1._wp ) * rdt / REAL( nn_baro, wp )
[4292]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
[2952]78
79  !!======================================================================
80
81END MODULE updtide
Note: See TracBrowser for help on using the repository browser.