3#if defined TIDE_GENERATING_FORCES
75 PUBLIC :: equilibrium_tide
76 PUBLIC :: harmonic_constituents
81 SUBROUTINE equilibrium_tide (ng, tile, model)
89 integer,
intent(in) :: ng, tile, model
93 character (len=*),
parameter :: MyFile = &
101 CALL equilibrium_tide_tile (ng, tile, model, &
102 & lbi, ubi, lbj, ubj, &
104 &
grid(ng) % Cos2Lat, &
105 &
grid(ng) % SinLat2, &
107 &
ocean(ng) % ad_eq_tide, &
109# if defined TANGENT || defined TL_IOMS
110 &
ocean(ng) % tl_eq_tide, &
112 &
ocean(ng) % eq_tide)
118 END SUBROUTINE equilibrium_tide
121 SUBROUTINE equilibrium_tide_tile (ng, tile, model, &
122 & LBi, UBi, LBj, UBj, &
123 & lonr, Cos2Lat, SinLat2, &
127# if defined TANGENT || defined TL_IOMS
135 integer,
intent(in) :: ng, tile, model
136 integer,
intent(in) :: LBi, UBi, LBj, UBj
139 real(r8),
intent(in) :: lonr(LBi:,LBj:)
140 real(r8),
intent(in) :: SinLat2(LBi:,LBj:)
141 real(r8),
intent(in) :: Cos2Lat(LBi:,LBj:)
143 real(r8),
intent(out) :: ad_eq_tide(LBi:,LBj:)
145# if defined TANGENT || defined TL_IOMS
146 real(r8),
intent(out) :: tl_eq_tide(LBi:,LBj:)
148 real(r8),
intent(out) :: eq_tide(LBi:,LBj:)
150 real(r8),
intent(in) :: lonr(LBi:UBi,LBj:UBj)
151 real(r8),
intent(in) :: SinLat2(LBi:UBi,LBj:UBj)
152 real(r8),
intent(in) :: Cos2Lat(LBi:UBi,LBj:UBj)
154 real(r8),
intent(out) :: ad_eq_tide(LBi:UBi,LBj:UBj)
156# if defined TANGENT || defined TL_IOMS
157 real(r8),
intent(out) :: tl_eq_tide(LBi:UBi,LBj:UBj)
159 real(r8),
intent(out) :: eq_tide(LBi:UBi,LBj:UBj)
166 real(dp) :: t_time_day, t_time_sec
168# include "set_bounds.h"
181 &
rclock%tide_DateNumber(2)
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))
215 & lbi, ubi, lbj, ubj, &
220 & lbi, ubi, lbj, ubj, &
229 IF (model.eq.
iadm)
THEN
233# if defined TANGENT || defined TL_IOMS
237 IF ((model.eq.
itlm).or.(model.eq.
irpm))
THEN
243 END SUBROUTINE equilibrium_tide_tile
246 SUBROUTINE harmonic_constituents (Lnodal)
251 logical,
intent(in) :: Lnodal
255 real(r8) :: N, T, h, p, s
257 real(dp) :: Astro_DateNumber(2)
267 CALL datenum (astro_datenumber, 2000, 1, 1, 12, 0, 0.0_dp)
276 t=(
rclock%tide_DateNumber(1)-astro_datenumber(1))/36524.25_r8
280 s=218.316_r8+481267.8812_r8*t
284 h=280.466_r8+36000.7698_r8*t
288 p=83.353_r8+4069.0137_r8*t
292 n=-234.955_r8-1934.1363_r8*t
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)
309 k2%f=1.024_r8+0.286_r8*cos(n)+0.008_r8*cos(2.0_r8*n)
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)
325 k2%nu=-17.7_r8*sin(n)+0.7_r8*sin(2.0_r8*n)
339 q1%chi=h-3.0_r8*s+p-90.0_r8
340 o1%chi=h-2.0_r8*s-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
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
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
390 END SUBROUTINE harmonic_constituents
subroutine, public datenum(datenumber, year, month, day, hour, minutes, seconds)
subroutine exchange_r2d_tile(ng, tile, lbi, ubi, lbj, ubj, a)
type(t_grid), dimension(:), allocatable grid
type(t_ocean), dimension(:), allocatable ocean
type(t_bounds), dimension(:), allocatable bounds
logical, dimension(:), allocatable ewperiodic
logical, dimension(:), allocatable nsperiodic
real(dp), parameter deg2rad
real(dp), dimension(:), allocatable time
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)
recursive subroutine wclock_on(ng, model, region, line, routine)