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.
sbctide.F90 in NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/SBC – NEMO

source: NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/SBC/sbctide.F90 @ 10811

Last change on this file since 10811 was 10811, checked in by smueller, 5 years ago

Replacement of the module variable used to store information about all available tidal components (variable Wave in module tide_mod) by an array used to store information about the selected components only (variable tide_components in module tide_mod), replacement of the corresponding initialisation subroutine, as well as related adjustments in various modules (bdytides, diaharm, sbctide, and tide_mod) and in one include file (tide.h90) (ticket #2194)

  • Property svn:keywords set to Id
File size: 3.2 KB
Line 
1MODULE sbctide
2   !!======================================================================
3   !!                       ***  MODULE  sbctide  ***
4   !! Initialization of tidal forcing
5   !!======================================================================
6   !! History :  9.0  !  2007  (O. Le Galloudec)  Original code
7   !!----------------------------------------------------------------------
8   USE oce            ! ocean dynamics and tracers variables
9   USE dom_oce        ! ocean space and time domain
10   USE phycst         ! physical constant
11   USE daymod         ! calandar
12   USE tide_mod       !
13   !
14   USE in_out_manager ! I/O units
15   USE iom            ! xIOs server
16   USE ioipsl         ! NetCDF IPSL library
17   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC sbc_tide
23 
24   !!----------------------------------------------------------------------
25   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
26   !! $Id$
27   !! Software governed by the CeCILL license (see ./LICENSE)
28   !!----------------------------------------------------------------------
29CONTAINS
30
31   SUBROUTINE sbc_tide( kt )
32      !!----------------------------------------------------------------------
33      !!                 ***  ROUTINE sbc_tide  ***
34      !!----------------------------------------------------------------------     
35      INTEGER, INTENT( in ) ::   kt     ! ocean time-step
36      INTEGER               ::   jk     ! dummy loop index
37      INTEGER               ::   nsec_day_orig     ! Temporary variable
38      !!----------------------------------------------------------------------
39     
40      IF( nsec_day == NINT(0.5_wp * rdt) .OR. kt == nit000 ) THEN      ! start a new day
41         !
42         !
43         IF( ln_read_load )THEN
44            IF ( kt == nit000 ) CALL tide_init_load
45            amp_pot(:,:,:) = amp_load(:,:,:)
46            phi_pot(:,:,:) = phi_load(:,:,:)
47         ELSE
48            amp_pot(:,:,:) = 0._wp
49            phi_pot(:,:,:) = 0._wp
50         ENDIF
51         pot_astro(:,:) = 0._wp
52         !
53         ! If the run does not start from midnight then need to initialise tides
54         ! at the start of the current day (only occurs when kt==nit000)
55         ! Temporarily set nsec_day to beginning of day.
56         nsec_day_orig = nsec_day
57         IF ( nsec_day /= NINT(0.5_wp * rdt) ) THEN
58            kt_tide = kt - (nsec_day - 0.5_wp * rdt)/rdt
59            nsec_day = NINT(0.5_wp * rdt)
60         ELSE
61            kt_tide = kt 
62         ENDIF
63         CALL tide_harmo( omega_tide, v0tide, utide, ftide, nb_harmo )
64         !
65         !
66         IF(lwp) THEN
67            WRITE(numout,*)
68            WRITE(numout,*) 'sbc_tide : Update of the components and (re)Init. the potential at kt=', kt
69            WRITE(numout,*) '~~~~~~~~ '
70            DO jk = 1, nb_harmo
71               WRITE(numout,*) tide_components(jk)%cname_tide, utide(jk), ftide(jk), v0tide(jk), omega_tide(jk)
72            END DO
73         ENDIF
74         !
75         IF( ln_tide_pot )   CALL tide_init_potential
76         !
77         ! Reset nsec_day
78         nsec_day = nsec_day_orig 
79      ENDIF
80      !
81   END SUBROUTINE sbc_tide
82
83  !!======================================================================
84END MODULE sbctide
Note: See TracBrowser for help on using the repository browser.