ROMS
Loading...
Searching...
No Matches
equilibrium_tide.F
Go to the documentation of this file.
1#include "cppdefs.h"
3#if defined TIDE_GENERATING_FORCES
4!
5!git $Id$
6!================================================== Hernan G. Arango ===
7! Copyright (c) 2002-2025 The ROMS Group John Wilkin !
8! Licensed under a MIT/X style license !
9! See License_ROMS.md !
10!=======================================================================
11! !
12! This module computes the equilibrium tide defined as the shape !
13! the sea surface (m) would assume if it were motionless and in !
14! equilibrium with the tide generating forces on a fluid planet. !
15! It is used to compute the tide generation force (TGF) terms for !
16! the pressure gradient. !
17! !
18! References: !
19! !
20! Arbic, B.K., Garner, S.T., Hallberg, R.W. and Simmons, H.L., 2004: !
21! The accuracy of surface elevations in forward global barotropic !
22! and baroclinic tide models. Deep Sea Research Part II: Topical !
23! Studies in Oceanography, 51(25-26), pp. 3069-3101. !
24! !
25! Arbic, B.K., Alford, M.H., Ansong, J.K., Buijsman, M.C., Ciotti, !
26! R.B., Farrar, J.T., Hallberg, R.W., Henze, C.E., Hill, C.N., !
27! Luecke, C.A. and Menemenlis, D., 2018: Primer on Global Internal !
28! Tide and Internal Gravity Wave Continuum Modeling in HYCOM and !
29! MITgcm. In: New Frontiers in Operational Oceanography, E. !
30! Chassignet, A. Pascual, J. Tintore and J. Verron (Eds.), GODAE !
31! OceanView, 307-392, doi: 10.17125/gov2018.ch13. !
32! !
33! Doodson, A.T. and Warburg, H.D., 1941: Admiralty Manual of Tides. !
34! His Majesty's Stationery Office, London, UK, 270 pp. !
35! !
36! Egbert, G.D. and Ray, R.D., 2017. Tidal prediction, J. Mar. Res., !
37! 75(3), pp.189-237. !
38! !
39!=======================================================================
40!
41 USE mod_kinds
42!
44 USE dateclock_mod, ONLY : datenum
45# ifdef DISTRIBUTE
47# endif
48 USE mod_param, ONLY : bounds, iadm, inlm, irpm, itlm, &
52!
53 implicit none
54!
55! Define equilibrium tide constituents structure.
56!
57 TYPE t_etide
58 real(r8) :: Afl ! product: amp*f*love
59 real(r8) :: amp ! amplitude (m)
60 real(r8) :: chi ! phase at Greenwich meridian (degrees)
61 real(r8) :: f ! f nodal factor (nondimensional)
62 real(r8) :: love ! tidal Love number factor
63 real(r8) :: nu ! nu nodal factor (degrees)
64 real(r8) :: omega ! frequency (1/s)
65 END TYPE t_etide
66!
67 TYPE (T_ETIDE) :: Q1 ! Q1 component, diurnal
68 TYPE (T_ETIDE) :: O1 ! O1 component, diurnal
69 TYPE (T_ETIDE) :: K1 ! K1 component, diurnal
70 TYPE (T_ETIDE) :: N2 ! N2 component, semi-diurnal
71 TYPE (T_ETIDE) :: M2 ! M2 component, semi-diurnal
72 TYPE (T_ETIDE) :: S2 ! S2 component, semi-diurnal
73 TYPE (T_ETIDE) :: K2 ! N2 component, semi-diurnal
74!
75 PUBLIC :: equilibrium_tide
76 PUBLIC :: harmonic_constituents
77!
78 CONTAINS
79!
80!***********************************************************************
81 SUBROUTINE equilibrium_tide (ng, tile, model)
82!***********************************************************************
83!
84 USE mod_grid
85 USE mod_ocean
86!
87! Imported variable declarations.
88!
89 integer, intent(in) :: ng, tile, model
90!
91! Local variable declarations.
92!
93 character (len=*), parameter :: MyFile = &
94 & __FILE__
95!
96# include "tile.h"
97!
98# ifdef PROFILE
99 CALL wclock_on (ng, inlm, 11, __line__, myfile)
100# endif
101 CALL equilibrium_tide_tile (ng, tile, model, &
102 & lbi, ubi, lbj, ubj, &
103 & grid(ng) % lonr, &
104 & grid(ng) % Cos2Lat, &
105 & grid(ng) % SinLat2, &
106# ifdef ADJOINT
107 & ocean(ng) % ad_eq_tide, &
108# endif
109# if defined TANGENT || defined TL_IOMS
110 & ocean(ng) % tl_eq_tide, &
111# endif
112 & ocean(ng) % eq_tide)
113# ifdef PROFILE
114 CALL wclock_off (ng, inlm, 11, __line__, myfile)
115# endif
116!
117 RETURN
118 END SUBROUTINE equilibrium_tide
119!
120!***********************************************************************
121 SUBROUTINE equilibrium_tide_tile (ng, tile, model, &
122 & LBi, UBi, LBj, UBj, &
123 & lonr, Cos2Lat, SinLat2, &
124# ifdef ADJOINT
125 & ad_eq_tide, &
126# endif
127# if defined TANGENT || defined TL_IOMS
128 & tl_eq_tide, &
129# endif
130 & eq_tide)
131!***********************************************************************
132!
133! Imported variables declarations.
134!
135 integer, intent(in) :: ng, tile, model
136 integer, intent(in) :: LBi, UBi, LBj, UBj
137!
138# ifdef ASSUMED_SHAPE
139 real(r8), intent(in) :: lonr(LBi:,LBj:)
140 real(r8), intent(in) :: SinLat2(LBi:,LBj:) ! SIN(2*latr)
141 real(r8), intent(in) :: Cos2Lat(LBi:,LBj:) ! COS2(latr)
142# ifdef ADJOINT
143 real(r8), intent(out) :: ad_eq_tide(LBi:,LBj:)
144# endif
145# if defined TANGENT || defined TL_IOMS
146 real(r8), intent(out) :: tl_eq_tide(LBi:,LBj:)
147# endif
148 real(r8), intent(out) :: eq_tide(LBi:,LBj:)
149# else
150 real(r8), intent(in) :: lonr(LBi:UBi,LBj:UBj)
151 real(r8), intent(in) :: SinLat2(LBi:UBi,LBj:UBj) ! SIN(2*latr)
152 real(r8), intent(in) :: Cos2Lat(LBi:UBi,LBj:UBj) ! COS2(latr)
153# ifdef ADJOINT
154 real(r8), intent(out) :: ad_eq_tide(LBi:UBi,LBj:UBj)
155# endif
156# if defined TANGENT || defined TL_IOMS
157 real(r8), intent(out) :: tl_eq_tide(LBi:UBi,LBj:UBj)
158# endif
159 real(r8), intent(out) :: eq_tide(LBi:UBi,LBj:UBj)
160# endif
161!
162! Local variables declarations.
163!
164 integer :: i, j
165!
166 real(dp) :: t_time_day, t_time_sec
167
168# include "set_bounds.h"
169!
170!-----------------------------------------------------------------------
171! Computes sea surface associated with the equilibrium tide
172!-----------------------------------------------------------------------
173!
174! Set equilibrium tide time in seconds. It can be negative if ROMS time
175! (seconds since reference date, Rclock%DateNumber) is earlier than the
176! date of zero phase (Rclock%tide_DateNumber) forcing tidal boundary
177! data. This zero phase date is set up when preparing the tidal NetCDF
178! file.
179!
180 t_time_sec=(rclock%DateNumber(2)+time(ng))- &
181 & rclock%tide_DateNumber(2)
182!
183! Compute astronomial equilibrium tide (m) with diurnal and semidiurnal
184! constituents. The long-period constituents and high-order harmonics
185! are neglected.
186!
187 DO j=jstrt,jendt
188 DO i=istrt,iendt
189 eq_tide(i,j)=q1%Afl*sinlat2(i,j)* &
190 & cos(q1%omega*t_time_sec+ &
191 & deg2rad*(lonr(i,j)+q1%chi+q1%nu))+ &
192 & o1%Afl*sinlat2(i,j)* &
193 & cos(o1%omega*t_time_sec+ &
194 & deg2rad*(lonr(i,j)+o1%chi+o1%nu))+ &
195 & k1%Afl*sinlat2(i,j)* &
196 & cos(k1%omega*t_time_sec+ &
197 & deg2rad*(lonr(i,j)+k1%chi+k1%nu))+ &
198 & n2%Afl*cos2lat(i,j)* &
199 & cos(n2%omega*t_time_sec+ &
200 & deg2rad*(2.0_r8*lonr(i,j)+n2%chi+n2%nu))+ &
201 & m2%Afl*cos2lat(i,j)* &
202 & cos(m2%omega*t_time_sec+ &
203 & deg2rad*(2.0_r8*lonr(i,j)+m2%chi+m2%nu))+ &
204 & s2%Afl*cos2lat(i,j)* &
205 & cos(s2%omega*t_time_sec+ &
206 & deg2rad*(2.0_r8*lonr(i,j)+s2%chi+s2%nu))+ &
207 & k2%Afl*cos2lat(i,j)* &
208 & cos(k2%omega*t_time_sec+ &
209 & deg2rad*(2.0_r8*lonr(i,j)+k2%chi+k2%nu))
210 END DO
211 END DO
212!
213 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
214 CALL exchange_r2d_tile (ng, tile, &
215 & lbi, ubi, lbj, ubj, &
216 & eq_tide)
217 END IF
218# ifdef DISTRIBUTE
219 CALL mp_exchange2d (ng, tile, inlm, 1, &
220 & lbi, ubi, lbj, ubj, &
221 & nghostpoints, &
222 & ewperiodic(ng), nsperiodic(ng), &
223 & eq_tide)
224# endif
225# ifdef ADJOINT
226!
227! Set adjoint of equilibrium tide.
228!
229 IF (model.eq.iadm) THEN
230 ad_eq_tide=0.0_r8
231 END IF
232# endif
233# if defined TANGENT || defined TL_IOMS
234!
235! Set tangent linear of equilibrium tide.
236!
237 IF ((model.eq.itlm).or.(model.eq.irpm)) THEN
238 tl_eq_tide=0.0_r8
239 END IF
240# endif
241!
242 RETURN
243 END SUBROUTINE equilibrium_tide_tile
244!
245!***********************************************************************
246 SUBROUTINE harmonic_constituents (Lnodal)
247!***********************************************************************
248!
249! Imported variables declarations.
250!
251 logical, intent(in) :: Lnodal ! Apply lunar nodal correction
252!
253! Local variables declarations.
254!
255 real(r8) :: N, T, h, p, s
256
257 real(dp) :: Astro_DateNumber(2) ! Jan 1, 2000 12:00:00
258!
259!-----------------------------------------------------------------------
260! Compute fundamental astronomical parameters. Adapted from Egbert and
261! Ray, 2017, Table 1.
262!-----------------------------------------------------------------------
263!
264! Set Egbert and Ray time reference for their astronomical parameters
265! (Table 1): days since 2000-01-01:12:00:00.
266!
267 CALL datenum (astro_datenumber, 2000, 1, 1, 12, 0, 0.0_dp)
268!
269! Terrestial time (in centuries) since tide reference date number. It
270! is set-up according to the chosen "tide_start" in standard input file
271! or the tidal forcing NetCDF file if found (default, recommended).
272!
273! Recall that the length of a year is 365.2425 days for the now called
274! Gregorian Calendar (corrected after 15 October 1582).
275!
276 t=(rclock%tide_DateNumber(1)-astro_datenumber(1))/36524.25_r8
277!
278! Mean longitude of the moon (Period = tropical month).
279!
280 s=218.316_r8+481267.8812_r8*t
281!
282! Mean longitude of the sun (Period = tropical year).
283!
284 h=280.466_r8+36000.7698_r8*t
285!
286! Mean longitude of lunar perigee (Period = 8.85 years).
287!
288 p=83.353_r8+4069.0137_r8*t
289!
290! Mean longitude of lunar node (Period = 18.6 years).
291!
292 n=-234.955_r8-1934.1363_r8*t ! degrees
293 n=n*deg2rad ! radians
294!
295!-----------------------------------------------------------------------
296! Compute the harmonic constituents of the equilibrium tide at
297! Greenwich. Adapted from Doodson and Warburg, 1941, Table 1.
298!-----------------------------------------------------------------------
299!
300! Nodal factors "f" and "nu" account for the slow modulation of the
301! tidal constituents due (principally) to the 18.6-year lunar nodal
302! cycle.
303!
304 IF (lnodal) THEN ! f nodal factor
305 o1%f=1.009_r8+0.187_r8*cos(n)-0.015_r8*cos(2.0_r8*n)
306 k1%f=1.006_r8+0.115_r8*cos(n)-0.009_r8*cos(2.0_r8*n)
307 m2%f=1.0_r8-0.037_r8*cos(n)
308 s2%f=1.0_r8
309 k2%f=1.024_r8+0.286_r8*cos(n)+0.008_r8*cos(2.0_r8*n)
310 ELSE
311 o1%f=1.0_r8
312 k1%f=1.0_r8
313 m2%f=1.0_r8
314 s2%f=1.0_r8
315 k2%f=1.0_r8
316 END IF
317 q1%f=o1%f
318 n2%f=m2%f
319!
320 IF (lnodal) THEN ! nu nodal factor
321 o1%nu=10.8_r8*sin(n)-1.3_r8*sin(2.0_r8*n)
322 k1%nu=-8.9_r8*sin(n)+0.7_r8*sin(2.0_r8*n)
323 m2%nu=-2.1_r8*sin(n)
324 s2%nu=0.0_r8
325 k2%nu=-17.7_r8*sin(n)+0.7_r8*sin(2.0_r8*n)
326 ELSE
327 o1%nu=0.0_r8
328 k1%nu=0.0_r8
329 m2%nu=0.0_r8
330 s2%nu=0.0_r8
331 k2%nu=0.0_r8
332 END IF
333 q1%nu=o1%nu
334 n2%nu=m2%nu
335!
336! Compute tidal constituent phase "chi" (degrees) at Greenwich meridian,
337! lambda = 0.
338!
339 q1%chi=h-3.0_r8*s+p-90.0_r8
340 o1%chi=h-2.0_r8*s-90.0_r8
341 k1%chi=h+90.0_r8
342 n2%chi=2.0_r8*h-3.0_r8*s+p
343 m2%chi=2.0_r8*h-2.0_r8*s
344 s2%chi=0.0_r8
345 k2%chi=2.0_r8*h
346!
347! Compute tidal constituent frequency (1/s).
348!
349 q1%omega=0.6495854e-4_r8
350 o1%omega=0.6759774e-4_r8
351 k1%omega=0.7292117e-4_r8
352 n2%omega=1.378797e-4_r8
353 m2%omega=1.405189e-4_r8
354 s2%omega=1.454441e-4_r8
355 k2%omega=1.458423e-4_r8
356!
357! Compute tidal constituent amplitude (m).
358!
359 q1%amp= 1.9273e-2_r8
360 o1%amp=10.0661e-2_r8
361 k1%amp=14.1565e-2_r8
362 n2%amp= 4.6397e-2_r8
363 m2%amp=24.2334e-2_r8
364 s2%amp=11.2743e-2_r8
365 k2%amp= 3.0684e-2_r8
366!
367! Compute tidal constituent Love number factors (1+k2-h2). The Love
368! number is defined as the ratio of the body tide to the height of
369! the static equilibrium tide.
370!
371 q1%love=0.695_r8
372 o1%love=0.695_r8
373 k1%love=0.736_r8
374 n2%love=0.693_r8
375 m2%love=0.693_r8
376 s2%love=0.693_r8
377 k2%love=0.693_r8
378!
379! Compute product of amp*f*love.
380!
381 q1%Afl=q1%amp*q1%f*q1%love
382 o1%Afl=o1%amp*o1%f*o1%love
383 k1%Afl=k1%amp*k1%f*k1%love
384 n2%Afl=n2%amp*n2%f*n2%love
385 m2%Afl=m2%amp*m2%f*m2%love
386 s2%Afl=s2%amp*s2%f*s2%love
387 k2%Afl=k2%amp*k2%f*k2%love
388!
389 RETURN
390 END SUBROUTINE harmonic_constituents
391#endif
392 END MODULE equilibrium_tide_mod
subroutine, public datenum(datenumber, year, month, day, hour, minutes, seconds)
Definition dateclock.F:243
subroutine exchange_r2d_tile(ng, tile, lbi, ubi, lbj, ubj, a)
type(t_grid), dimension(:), allocatable grid
Definition mod_grid.F:365
type(t_ocean), dimension(:), allocatable ocean
Definition mod_ocean.F:351
integer, parameter inlm
Definition mod_param.F:662
integer, parameter irpm
Definition mod_param.F:664
type(t_bounds), dimension(:), allocatable bounds
Definition mod_param.F:232
integer nghostpoints
Definition mod_param.F:710
integer, parameter iadm
Definition mod_param.F:665
integer, parameter itlm
Definition mod_param.F:663
logical lnodal
logical, dimension(:), allocatable ewperiodic
logical, dimension(:), allocatable nsperiodic
type(t_clock) rclock
real(dp), parameter deg2rad
real(dp), dimension(:), allocatable time
real(dp) tide_start
subroutine mp_exchange2d(ng, tile, model, nvar, lbi, ubi, lbj, ubj, nghost, ew_periodic, ns_periodic, a, b, c, d)
recursive subroutine wclock_off(ng, model, region, line, routine)
Definition timers.F:148
recursive subroutine wclock_on(ng, model, region, line, routine)
Definition timers.F:3