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 @ 10822

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

Addition of a new type (tide_harmonics in module tide_mod), two replacements of four separate arrays for the storage of oscillation parameters by one array of variables of this new type (in modules diaharm and tide_mod), and related adjustments in various modules (bdytides, diaharm, sbctides, and tide_mod) (ticket #2194)

  • Property svn:keywords set to Id
File size: 3.3 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(tide_components, tide_harmonics) ! Update oscillation parameters of tidal components
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_harmonics(jk)%cname_tide, tide_harmonics(jk)%u, &
72                  &            tide_harmonics(jk)%f,tide_harmonics(jk)%v0, tide_harmonics(jk)%omega
73            END DO
74         ENDIF
75         !
76         IF( ln_tide_pot )   CALL tide_init_potential
77         !
78         ! Reset nsec_day
79         nsec_day = nsec_day_orig 
80      ENDIF
81      !
82   END SUBROUTINE sbc_tide
83
84  !!======================================================================
85END MODULE sbctide
Note: See TracBrowser for help on using the repository browser.