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.
tide_mod.F90 in NEMO/branches/NERC/NEMO_4.0.4_CO9_package_tides/src/OCE/SBC – NEMO

source: NEMO/branches/NERC/NEMO_4.0.4_CO9_package_tides/src/OCE/SBC/tide_mod.F90 @ 14266

Last change on this file since 14266 was 14266, checked in by dbyrne, 3 years ago

Long period tide forcing, variable love number, new nodal equation 20 added

File size: 15.9 KB
Line 
1MODULE tide_mod
2   !!======================================================================
3   !!                       ***  MODULE  tide_mod  ***
4   !! Compute nodal modulations corrections and pulsations
5   !!======================================================================
6   !! History :  1.0  !  2007  (O. Le Galloudec)  Original code
7   !!----------------------------------------------------------------------
8   USE dom_oce        ! ocean space and time domain
9   USE phycst         ! physical constant
10   USE daymod         ! calendar
11
12   IMPLICIT NONE
13   PRIVATE
14
15   PUBLIC   tide_harmo       ! called by tideini and diaharm modules
16   PUBLIC   tide_init_Wave   ! called by tideini and diaharm modules
17
18   ! davbyr: increase maximum number of harmonics from 19 to 34
19   INTEGER, PUBLIC, PARAMETER ::   jpmax_harmo = 34   !: maximum number of harmonic
20
21   TYPE, PUBLIC ::    tide
22      CHARACTER(LEN=4) ::   cname_tide
23      REAL(wp)         ::   equitide
24      INTEGER          ::   nutide
25      INTEGER          ::   nt, ns, nh, np, np1, shift
26      INTEGER          ::   nksi, nnu0, nnu1, nnu2, R
27      INTEGER          ::   nformula
28   END TYPE tide
29
30   TYPE(tide), PUBLIC, DIMENSION(jpmax_harmo) ::   Wave   !:
31
32   REAL(wp) ::   sh_T, sh_s, sh_h, sh_p, sh_p1             ! astronomic angles
33   REAL(wp) ::   sh_xi, sh_nu, sh_nuprim, sh_nusec, sh_R   !
34   REAL(wp) ::   sh_I, sh_x1ra, sh_N                       !
35
36   !!----------------------------------------------------------------------
37   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
38   !! $Id$
39   !! Software governed by the CeCILL license (see ./LICENSE)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE tide_init_Wave
44#     include "tide.h90"
45   END SUBROUTINE tide_init_Wave
46
47
48   SUBROUTINE tide_harmo( pomega, pvt, put , pcor, ktide ,kc)
49      !!----------------------------------------------------------------------
50      !!----------------------------------------------------------------------
51      INTEGER , DIMENSION(kc), INTENT(in ) ::   ktide            ! Indice of tidal constituents
52      INTEGER                , INTENT(in ) ::   kc               ! Total number of tidal constituents
53      REAL(wp), DIMENSION(kc), INTENT(out) ::   pomega           ! pulsation in radians/s
54      REAL(wp), DIMENSION(kc), INTENT(out) ::   pvt, put, pcor   !
55      !!----------------------------------------------------------------------
56      !
57      CALL astronomic_angle
58      CALL tide_pulse( pomega, ktide ,kc )
59      CALL tide_vuf  ( pvt, put, pcor, ktide ,kc )
60      !
61   END SUBROUTINE tide_harmo
62
63
64   SUBROUTINE astronomic_angle
65      !!----------------------------------------------------------------------
66      !!  tj is time elapsed since 1st January 1900, 0 hour, counted in julian
67      !!  century (e.g. time in days divide by 36525)
68      !!----------------------------------------------------------------------
69      REAL(wp) ::   cosI, p, q, t2, t4, sin2I, s2, tgI2, P1, sh_tgn2, at1, at2
70      REAL(wp) ::   zqy , zsy, zday, zdj, zhfrac
71      !!----------------------------------------------------------------------
72      !
73      zqy = AINT( (nyear-1901.)/4. )
74      zsy = nyear - 1900.
75      !
76      zdj  = dayjul( nyear, nmonth, nday )
77      zday = zdj + zqy - 1.
78      !
79      zhfrac = nsec_day / 3600.
80      !
81      !----------------------------------------------------------------------
82      !  Sh_n Longitude of ascending lunar node
83      !----------------------------------------------------------------------
84      sh_N=(259.1560564-19.328185764*zsy-.0529539336*zday-.0022064139*zhfrac)*rad
85      !----------------------------------------------------------------------
86      ! T mean solar angle (Greenwhich time)
87      !----------------------------------------------------------------------
88      sh_T=(180.+zhfrac*(360./24.))*rad
89      !----------------------------------------------------------------------
90      ! h mean solar Longitude
91      !----------------------------------------------------------------------
92      sh_h=(280.1895014-.238724988*zsy+.9856473288*zday+.0410686387*zhfrac)*rad
93      !----------------------------------------------------------------------
94      ! s mean lunar Longitude
95      !----------------------------------------------------------------------
96      sh_s=(277.0256206+129.38482032*zsy+13.176396768*zday+.549016532*zhfrac)*rad
97      !----------------------------------------------------------------------
98      ! p1 Longitude of solar perigee
99      !----------------------------------------------------------------------
100      sh_p1=(281.2208569+.01717836*zsy+.000047064*zday+.000001961*zhfrac)*rad
101      !----------------------------------------------------------------------
102      ! p Longitude of lunar perigee
103      !----------------------------------------------------------------------
104      sh_p=(334.3837214+40.66246584*zsy+.111404016*zday+.004641834*zhfrac)*rad
105
106      sh_N = MOD( sh_N ,2*rpi )
107      sh_s = MOD( sh_s ,2*rpi )
108      sh_h = MOD( sh_h, 2*rpi )
109      sh_p = MOD( sh_p, 2*rpi )
110      sh_p1= MOD( sh_p1,2*rpi )
111
112      cosI = 0.913694997 -0.035692561 *cos(sh_N)
113
114      sh_I = ACOS( cosI )
115
116      sin2I   = sin(sh_I)
117      sh_tgn2 = tan(sh_N/2.0)
118
119      at1=atan(1.01883*sh_tgn2)
120      at2=atan(0.64412*sh_tgn2)
121
122      sh_xi=-at1-at2+sh_N
123
124      IF( sh_N > rpi )   sh_xi=sh_xi-2.0*rpi
125
126      sh_nu = at1 - at2
127
128      !----------------------------------------------------------------------
129      ! For constituents l2 k1 k2
130      !----------------------------------------------------------------------
131
132      tgI2 = tan(sh_I/2.0)
133      P1   = sh_p-sh_xi
134
135      t2 = tgI2*tgI2
136      t4 = t2*t2
137      sh_x1ra = sqrt( 1.0-12.0*t2*cos(2.0*P1)+36.0*t4 )
138
139      p = sin(2.0*P1)
140      q = 1.0/(6.0*t2)-cos(2.0*P1)
141      sh_R = atan(p/q)
142
143      p = sin(2.0*sh_I)*sin(sh_nu)
144      q = sin(2.0*sh_I)*cos(sh_nu)+0.3347
145      sh_nuprim = atan(p/q)
146
147      s2 = sin(sh_I)*sin(sh_I)
148      p  = s2*sin(2.0*sh_nu)
149      q  = s2*cos(2.0*sh_nu)+0.0727
150      sh_nusec = 0.5*atan(p/q)
151      !
152   END SUBROUTINE astronomic_angle
153
154
155   SUBROUTINE tide_pulse( pomega, ktide ,kc )
156      !!----------------------------------------------------------------------
157      !!                     ***  ROUTINE tide_pulse  ***
158      !!                     
159      !! ** Purpose : Compute tidal frequencies
160      !!----------------------------------------------------------------------
161      INTEGER                , INTENT(in ) ::   kc       ! Total number of tidal constituents
162      INTEGER , DIMENSION(kc), INTENT(in ) ::   ktide    ! Indice of tidal constituents
163      REAL(wp), DIMENSION(kc), INTENT(out) ::   pomega   ! pulsation in radians/s
164      !
165      INTEGER  ::   jh
166      REAL(wp) ::   zscale
167      REAL(wp) ::   zomega_T =  13149000.0_wp
168      REAL(wp) ::   zomega_s =    481267.892_wp
169      REAL(wp) ::   zomega_h =     36000.76892_wp
170      REAL(wp) ::   zomega_p =      4069.0322056_wp
171      REAL(wp) ::   zomega_n =      1934.1423972_wp
172      REAL(wp) ::   zomega_p1=         1.719175_wp
173      !!----------------------------------------------------------------------
174      !
175      zscale =  rad / ( 36525._wp * 86400._wp ) 
176      !
177      DO jh = 1, kc
178         pomega(jh) = (  zomega_T * Wave( ktide(jh) )%nT   &
179            &          + zomega_s * Wave( ktide(jh) )%ns   &
180            &          + zomega_h * Wave( ktide(jh) )%nh   &
181            &          + zomega_p * Wave( ktide(jh) )%np   &
182            &          + zomega_p1* Wave( ktide(jh) )%np1  ) * zscale
183      END DO
184      !
185   END SUBROUTINE tide_pulse
186
187
188   SUBROUTINE tide_vuf( pvt, put, pcor, ktide ,kc )
189      !!----------------------------------------------------------------------
190      !!                     ***  ROUTINE tide_vuf  ***
191      !!                     
192      !! ** Purpose : Compute nodal modulation corrections
193      !!
194      !! ** Outputs : vt: Phase of tidal potential relative to Greenwich (radians)
195      !!              ut: Phase correction u due to nodal motion (radians)
196      !!              ft: Nodal correction factor
197      !!----------------------------------------------------------------------
198      INTEGER                , INTENT(in ) ::   kc               ! Total number of tidal constituents
199      INTEGER , DIMENSION(kc), INTENT(in ) ::   ktide            ! Indice of tidal constituents
200      REAL(wp), DIMENSION(kc), INTENT(out) ::   pvt, put, pcor   !
201      !
202      INTEGER ::   jh   ! dummy loop index
203      !!----------------------------------------------------------------------
204      !
205      DO jh = 1, kc
206         !  Phase of the tidal potential relative to the Greenwhich
207         !  meridian (e.g. the position of the fictuous celestial body). Units are radian:
208         pvt(jh) = sh_T * Wave( ktide(jh) )%nT    &
209            &    + sh_s * Wave( ktide(jh) )%ns    &
210            &    + sh_h * Wave( ktide(jh) )%nh    &
211            &    + sh_p * Wave( ktide(jh) )%np    &
212            &    + sh_p1* Wave( ktide(jh) )%np1   &
213            &    +        Wave( ktide(jh) )%shift * rad
214         !
215         !  Phase correction u due to nodal motion. Units are radian:
216         put(jh) = sh_xi     * Wave( ktide(jh) )%nksi   &
217            &    + sh_nu     * Wave( ktide(jh) )%nnu0   &
218            &    + sh_nuprim * Wave( ktide(jh) )%nnu1   &
219            &    + sh_nusec  * Wave( ktide(jh) )%nnu2   &
220            &    + sh_R      * Wave( ktide(jh) )%R
221
222         !  Nodal correction factor:
223         pcor(jh) = nodal_factort( Wave( ktide(jh) )%nformula )
224      END DO
225      !
226   END SUBROUTINE tide_vuf
227
228
229   RECURSIVE FUNCTION nodal_factort( kformula ) RESULT( zf )
230      !!----------------------------------------------------------------------
231      !!----------------------------------------------------------------------
232      INTEGER, INTENT(in) :: kformula
233      !
234      REAL(wp) :: zf
235      REAL(wp) :: zs, zf1, zf2
236      !!----------------------------------------------------------------------
237      !
238      SELECT CASE( kformula )
239      !
240      CASE( 0 )                  !==  formule 0, solar waves
241         zf = 1.0
242         !
243      CASE( 1 )                  !==  formule 1, compound waves (78 x 78)
244         zf=nodal_factort(78)
245         zf = zf * zf
246         !
247      CASE ( 2 )                 !==  formule 2, compound waves (78 x 0)  ===  (78)
248       zf1= nodal_factort(78)
249       zf = nodal_factort( 0)
250       zf = zf1 * zf
251       !
252      CASE ( 4 )                 !==  formule 4,  compound waves (78 x 235)
253         zf1 = nodal_factort( 78)
254         zf  = nodal_factort(235)
255         zf  = zf1 * zf
256         !
257      CASE ( 5 )                 !==  formule 5,  compound waves (78 *78 x 235)
258         zf1 = nodal_factort( 78)
259         zf  = nodal_factort(235)
260         zf  = zf * zf1 * zf1
261         !
262      CASE ( 6 )                 !==  formule 6,  compound waves (78 *78 x 0)
263         zf1 = nodal_factort(78)
264         zf  = nodal_factort( 0)
265         zf  = zf * zf1 * zf1 
266         !
267      CASE( 7 )                  !==  formule 7, compound waves (75 x 75)
268         zf = nodal_factort(75)
269         zf = zf * zf
270         !
271      CASE( 8 )                  !==  formule 8,  compound waves (78 x 0 x 235)
272         zf  = nodal_factort( 78)
273         zf1 = nodal_factort(  0)
274         zf2 = nodal_factort(235)
275         zf  = zf * zf1 * zf2
276         !
277      CASE( 9 )                  !==  formule 9,  compound waves (78 x 0 x 227)
278         zf  = nodal_factort( 78)
279         zf1 = nodal_factort(  0)
280         zf2 = nodal_factort(227)
281         zf  = zf * zf1 * zf2
282         !
283      CASE( 10 )                 !==  formule 10,  compound waves (78 x 227)
284         zf  = nodal_factort( 78)
285         zf1 = nodal_factort(227)
286         zf  = zf * zf1
287         !
288      CASE( 11 )                 !==  formule 11,  compound waves (75 x 0)
289!!gm bug???? zf 2 fois !
290         zf = nodal_factort(75)
291         zf1 = nodal_factort( 0)
292         zf = zf * zf1
293         !
294      CASE( 12 )                 !==  formule 12,  compound waves (78 x 78 x 78 x 0)
295         zf1 = nodal_factort(78)
296         zf  = nodal_factort( 0)
297         zf  = zf * zf1 * zf1 * zf1
298         !
299      CASE( 13 )                 !==  formule 13, compound waves (78 x 75)
300         zf1 = nodal_factort(78)
301         zf  = nodal_factort(75)
302         zf  = zf * zf1
303         !
304      CASE( 14 )                 !==  formule 14, compound waves (235 x 0)  ===  (235)
305         zf  = nodal_factort(235)
306         zf1 = nodal_factort(  0)
307         zf  = zf * zf1
308         !
309      CASE( 15 )                 !==  formule 15, compound waves (235 x 75)
310         zf  = nodal_factort(235)
311         zf1 = nodal_factort( 75)
312         zf  = zf * zf1
313         !
314      CASE( 16 )                 !==  formule 16, compound waves (78 x 0 x 0)  ===  (78)
315         zf  = nodal_factort(78)
316         zf1 = nodal_factort( 0)
317         zf  = zf * zf1 * zf1
318         !
319      CASE( 17 )                 !==  formule 17,  compound waves (227 x 0)
320         zf1 = nodal_factort(227)
321         zf  = nodal_factort(  0)
322         zf  = zf * zf1
323         !
324      CASE( 18 )                 !==  formule 18,  compound waves (78 x 78 x 78 )
325         zf1 = nodal_factort(78)
326         zf  = zf1 * zf1 * zf1
327         !
328      CASE( 19 )                 !==  formule 19, compound waves (78 x 0 x 0 x 0)  ===  (78)
329!!gm bug2 ==>>>   here identical to formule 16,  a third multiplication by zf1 is missing
330         zf  = nodal_factort(78)
331         zf1 = nodal_factort( 0)
332         zf = zf * zf1 * zf1
333         !
334         
335      !--- davbyr 11/2017
336      CASE( 20 )                 !==  formule 20,  compound waves ( 78 x 78 x 78 x 78 )
337         zf1 = nodal_factort(78)
338         zf  = zf1 * zf1 * zf1 * zf1
339      !--- END davbyr
340      CASE( 73 )                 !==  formule 73
341         zs = sin(sh_I)
342         zf = (2./3.-zs*zs)/0.5021
343         !
344      CASE( 74 )                 !==  formule 74
345         zs = sin(sh_I)
346         zf = zs * zs / 0.1578
347         !
348      CASE( 75 )                 !==  formule 75
349         zs = cos(sh_I/2)
350         zf = sin(sh_I) * zs * zs / 0.3800
351         !
352      CASE( 76 )                 !==  formule 76
353         zf = sin(2*sh_I) / 0.7214
354         !
355      CASE( 77 )                 !==  formule 77
356         zs = sin(sh_I/2)
357         zf = sin(sh_I) * zs * zs / 0.0164
358         !
359      CASE( 78 )                 !==  formule 78
360         zs = cos(sh_I/2)
361         zf = zs * zs * zs * zs / 0.9154
362         !
363      CASE( 79 )                 !==  formule 79
364         zs = sin(sh_I)
365         zf = zs * zs / 0.1565
366         !
367      CASE( 144 )                !==  formule 144
368         zs = sin(sh_I/2)
369         zf = ( 1-10*zs*zs+15*zs*zs*zs*zs ) * cos(sh_I/2) / 0.5873
370         !
371      CASE( 149 )                !==  formule 149
372         zs = cos(sh_I/2)
373         zf = zs*zs*zs*zs*zs*zs / 0.8758
374         !
375      CASE( 215 )                !==  formule 215
376         zs = cos(sh_I/2)
377         zf = zs*zs*zs*zs / 0.9154 * sh_x1ra
378         !
379      CASE( 227 )                !==  formule 227
380         zs = sin(2*sh_I)
381         zf = sqrt( 0.8965*zs*zs+0.6001*zs*cos (sh_nu)+0.1006 )
382         !
383      CASE ( 235 )               !==  formule 235
384         zs = sin(sh_I)
385         zf = sqrt( 19.0444*zs*zs*zs*zs + 2.7702*zs*zs*cos(2*sh_nu) + .0981 )
386         !
387      END SELECT
388      !
389   END FUNCTION nodal_factort
390
391
392   FUNCTION dayjul( kyr, kmonth, kday )
393      !!----------------------------------------------------------------------
394      !!  *** THIS ROUTINE COMPUTES THE JULIAN DAY (AS A REAL VARIABLE)
395      !!----------------------------------------------------------------------
396      INTEGER,INTENT(in) ::   kyr, kmonth, kday
397      !
398      INTEGER,DIMENSION(12) ::  idayt, idays
399      INTEGER  ::   inc, ji
400      REAL(wp) ::   dayjul, zyq
401      !
402      DATA idayt/0.,31.,59.,90.,120.,151.,181.,212.,243.,273.,304.,334./
403      !!----------------------------------------------------------------------
404      !
405      idays(1) = 0.
406      idays(2) = 31.
407      inc = 0.
408      zyq = MOD( kyr-1900. , 4. )
409      IF( zyq == 0.)   inc = 1.
410      DO ji = 3, 12
411         idays(ji)=idayt(ji)+inc
412      END DO
413      dayjul = idays(kmonth) + kday
414      !
415   END FUNCTION dayjul
416
417   !!======================================================================
418END MODULE tide_mod
Note: See TracBrowser for help on using the repository browser.