libTheSky
Routines to compute sky positions of Sun, Moon, planets and more
All Namespaces Files Functions Variables Pages
nutation.f90
Go to the documentation of this file.
1!> \file nutation.f90 Routines to compute nutation for libTheSky
2!!
3!! \todo Check difference in outcome between rev.198 and 199
4
5
6! Copyright (c) 2002-2025 Marc van der Sluys - Nikhef/Utrecht University - marc.vandersluys.nl
7!
8! This file is part of the libTheSky package,
9! see: https://libthesky.sf.net/
10!
11! This is free software: you can redistribute it and/or modify it under the terms of the
12! European Union Public Licence 1.2 (EUPL 1.2).
13!
14! This software is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY;
15! without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
16! See the EU Public Licence for more details.
17!
18! You should have received a copy of the European Union Public Licence along with this code.
19! If not, see <https://www.eupl.eu/1.2/en/>.
20
21
22!***********************************************************************************************************************************
23!> \brief Procedures for nutation
24
26 implicit none
27 save
28
29
30contains
31
32
33 !*********************************************************************************************************************************
34 !> \brief Calculate nutation - cheap routine from Meeus - as well as the mean obliquity of the ecliptic
35 !!
36 !! \param t Time in Julian Millennia since 2000.0 in dynamical time
37 !! \param dpsi Nutation in longitude (output)
38 !! \param eps0 Obliquity of the ecliptic (output)
39 !! \param deps Nutation in obliquity (output)
40 !!
41 !! \see
42 !! - IAU 1980 nutation model: Seidelmann (1981);
43 !! - Abbreviated by Meeus, Astronomical Algorithms, 1998, Ch. 22.
44
45 subroutine nutation(t, dpsi,eps0,deps)
46 use sufr_kinds, only: double
47 use sufr_constants, only: pi
49
50 implicit none
51 real(double), intent(in) :: t
52 real(double), intent(out) :: dpsi,eps0,deps
53 real(double) :: tjc,tjc2,tjc3,u, d,ms,mm,f,omg,tmpvar, nu(9,63), conv
54 integer :: i
55
56 tjc = t*10.d0 ! Julian Centuries since 2000.0 in dynamical time
57 tjc2 = tjc**2
58 tjc3 = tjc*tjc2
59
60 d = 5.19846946025d0 + 7771.37714617d0 *tjc - 3.340909d-5 *tjc2 + 9.2114446d-8 *tjc3 ! D in Meeus, p.144
61 ms = 6.24003588115d0 + 628.301956024d0 *tjc - 2.79776d-6 *tjc2 - 5.8177641733d-8 *tjc3 ! M in Meeus, p.144
62 mm = 2.3555483693d0 + 8328.69142288d0 *tjc + 1.517947757d-4 *tjc2 + 3.102807559d-7 *tjc3 ! M' in Meeus, p.144
63 f = 1.62790192912d0 + 8433.46615832d0 *tjc - 6.42717497d-5 *tjc2 + 5.3329949d-8 *tjc3 ! F in Meeus, p.144
64 omg = 2.18243858558d0 - 33.7570459367d0 *tjc + 3.6142278d-5 *tjc2 + 3.87850944888d-8 *tjc3 ! Omega in Meeus, p.144
65
66 dpsi=0.d0
67 deps=0.d0
68 nu = nutationdat
69 do i=1,63 ! Use data from the IAU1980 model (Seidelmann 1981; see nutation.dat)
70 tmpvar = nu(1,i)*d + nu(2,i)*ms + nu(3,i)*mm + nu(4,i)*f + nu(5,i)*omg
71 dpsi = dpsi + (nu(6,i) + nu(7,i)*tjc) * sin(tmpvar)
72 deps = deps + (nu(8,i) + nu(9,i)*tjc) * cos(tmpvar)
73 end do
74
75 conv = pi/(1.d4*3600.d0*180.d0) ! Convert from 0.0001" to radians
76 dpsi = dpsi*conv
77 deps = deps*conv
78
79
80 ! Add mean obliquity of the ecliptic:
81 ! eps0 = 0.409092804222d0 - 2.26965525d-4*tjc - 2.86d-9*tjc2 + 8.78967d-9*tjc3 ! Lieske et al, 1977
82
83 u = t/10.d0 ! Dynamical time since 2000 in units of 10,000 years
84 eps0 = 0.409092804222d0 - 0.022693789d0*u - 7.5146d-6*u*u + 0.0096926375d0*u**3 - 2.49097d-4*u**4 - 0.0012104343d0*u**5 - &
85 1.893197d-4*u**6 + 3.452d-5*u**7 + 1.3512d-4*u**8 + 2.8071d-5*u**9 + 1.1878d-5*u**10 ! Laskar, A&A 157 59 (1986), Tab.8.
86
87 end subroutine nutation
88 !*********************************************************************************************************************************
89
90
91 !*********************************************************************************************************************************
92 !> \brief Compute nutation using the IAU 2000 model. Add the mean obliquity of the ecliptic by Laskar (1986).
93 !!
94 !! \param jd Julian day of computation
95 !! \param dpsi_tot Total nutation in longitude (rad)
96 !! \param deps_tot Total nutation in obliquity (rad)
97 !! \param eps0 Mean obliquity of the ecliptic (rad; optional)
98 !!
99 !! \see http://geoweb.mit.edu/~tah/mhb2000/
100
101 subroutine nutation2000(jd, dpsi_tot, deps_tot, eps0)
102 use sufr_kinds, only: double
103 use sufr_constants, only: jd2000
104 implicit none
105
106 ! Subroutine to compute the complete MHB_2000 nutation series
107 ! with the associated corrections for planetary nutations,
108 ! the freely excited free-core-nutation (valid for 1979-2001.42),
109 ! the precession constant change and a rate of change of oblquity.)
110
111 ! USAGE:
112 ! call MHB_2000( jd, dpsi_ls, deps_ls, dpsi_plan, deps_plan,
113 ! . dpsi_fcn , deps_fcn , dPsi_prec, deps_prec,
114 ! . dpsi_tot , deps_tot )
115
116 ! where:
117 ! <jd> is the full julian date including fractional part of
118 ! of the day (REAL(DOUBLE) input)
119 ! <dpsi_ls> and <deps_ls> are the luni-solar nutation in
120 ! longitude and oblquity (mas) (REAL(DOUBLE) OUTPUT)
121 ! <dpsi_plan> and <deps_plan> are the contributions to the
122 ! nutations in longitude and obliquity due direct
123 ! planetary nutations and the perturbations of the
124 ! lunar and terrestrial orbits (mas). (REAL(DOUBLE) OUTPUT)
125 ! <dpsi_fcn> and <deps_fcn> are the contributions to the
126 ! nutations in longitude and obliquity due the free-
127 ! excitation of the Free-core-nutation (mas). These
128 ! values are valid for 1979-2000. (REAL(DOUBLE) OUTPUT)
129 ! <dpsi_prec> and <deps_prec> are the contributions to the
130 ! nutations in longitude and obliquity due changes in
131 ! the precession constant and rate of change of
132 ! obliquity (mas) (REAL(DOUBLE) OUTPUT).
133 ! <dpsi_tot> and <deps_tot> are the total nutations in longitude
134 ! and obliquity including the correction for the precession
135 ! constant (when precession is computed using the IAU 1976
136 ! precession constant), and are obtained by summing all
137 ! of the above corrections (mas) (REAL(DOUBLE) OUTPUT).
138
139 ! RESTRICTIONS: if <jd> is less than 2000000.0 this routine
140 ! assumes an MJD has been passed and the time
141 ! used will be converted to JD. A warning
142 ! message will be printed. See individual modules
143 ! for further restrictions.
144
145 ! PASSED VARIABLES
146 !
147 ! INPUT Values
148 ! jd - Time at which value needed. (jd + fraction of day)
149
150 ! OUTPUT Values
151 ! dpsi_ls and deps_ls - luni-solar nutation in
152 ! longitude and oblquity (mas) (REAL* OUTPUT)
153 ! dpsi_plan and deps_plan - contributions to the
154 ! nutations in longitude and obliquity due direct
155 ! planetary nutations and the perturbations of the
156 ! lunar and terrestrial orbits (mas). (REAL* OUTPUT)
157 ! dpsi_fcn and deps_fcn - contributions to the
158 ! nutations in longitude and obliquity due the free-
159 ! excitation of the Free-core-nutation (mas). These
160 ! values are valid for 1988-1994. (REAL* OUTPUT)
161 ! dpsi_prec and deps_prec - contributions to the
162 ! nutations in longitude and obliquity due changes in
163 ! the precession constant and rate of change of
164 ! obliquity (mas) (REAL* OUTPUT).
165 ! dpsi_tot and deps_tot - total nutations in longitude
166 ! and obliquity including the correction for the precession
167 ! constant (when precession is computed using the IAU 1976
168 ! precession constant), and are obtained by summing all
169 ! of the above corrections (mas) (REAL* OUTPUT).
170
171
172 real(double), intent(in) :: jd
173 real(double), intent(out) :: dpsi_tot, deps_tot
174 real(double), intent(out), optional :: eps0
175 real(double) :: dpsi_ls, deps_ls, dpsi_plan, deps_plan, dpsi_fcn , deps_fcn, dpsi_prec, deps_prec, pi, mas2r
176 real(double) :: u
177
178 !---------------------------------------------------------------
179
180 ! Call each of the routines needed for each contribution.
181
182 ! Luni-solar nutation
183 call ls_nut( jd, dpsi_ls, deps_ls )
184
185 ! Planetary nutation
186 call plan_nut ( jd, dpsi_plan, deps_plan )
187
188 ! Freely excited FCN (NOTE: No warning message is printed
189 ! if the JD is out of the range of 1979-2000)
190 call fcn_nut ( jd, dpsi_fcn , deps_fcn )
191
192 ! Precession and obliquity rate contributions (NOTE: IAU-1976
193 ! precession constant assumed to be used in the basic calculation
194 ! of precession).
195
196 call prec_nut( jd, dpsi_prec, deps_prec )
197
198 ! Now add up all of the terms to get the total nutation angles
199
200 dpsi_tot = dpsi_ls + dpsi_plan + dpsi_fcn + dpsi_prec
201 deps_tot = deps_ls + deps_plan + deps_fcn + deps_prec
202
203 ! Convert from mas to radians:
204 pi = 4*atan(1.d0)
205 mas2r = pi/(180.d0*3.6d6)
206 dpsi_tot = dpsi_tot*mas2r
207 deps_tot = deps_tot*mas2r
208
209
210 ! Add mean obliquity of the ecliptic:
211 if(present(eps0)) then
212 ! eps0 = 0.409092804222d0 - 2.26965525d-4*tjc - 2.86d-9*tjc2 + 8.78967d-9*tjc3 ! Lieske et al, 1977
213
214 u = (jd-jd2000)/3652500.d0 ! Dynamical time since 2000 in units of 10,000 years
215 eps0 = 0.409092804222d0 - 0.022693789d0*u - 7.5146d-6*u*u + 0.0096926375d0*u**3 - 2.49097d-4*u**4 - 0.0012104343d0*u**5 - &
216 1.893197d-4*u**6 + 3.452d-5*u**7 + 1.3512d-4*u**8 + 2.8071d-5*u**9 + 1.1878d-5*u**10 ! Laskar, A&A 157 59 (1986), Tab.8.
217 end if
218
219 end subroutine nutation2000
220 !*********************************************************************************************************************************
221
222
223
224
225
226
227
228
229
230 !TITLE LS_NUT
231
232 !*********************************************************************************************************************************
233 !> \brief Compute the MHB_2000 luni-solar contributions the nutations in longitude and obliquity.
234 !!
235 !! \param jd Julian day
236 !! \param dpsi_ls Nutation in longitude (milliarcsec)
237 !! \param deps_ls Nutation in obliquity (milliarcsec)
238
239 subroutine ls_nut( jd, dpsi_ls, deps_ls )
240 use sufr_kinds, only: double
241 implicit none
242
243 ! The MHB_2000 is based on:
244
245 ! (1) The Souchay and Kinoshita Rigid Earth nutation series
246 ! SKRE1997. There are many duplicate argument terms in this
247 ! series and all of these have been compacted in signle argument
248 ! terms.
249
250 ! (2) Value of the Retrograde FCN resonance factors from
251 ! the Mathews et al., 2000 , nutation formulation (full complex
252 ! estimates, and scaling parameter R from the same
253 ! theory.
254
255 ! (3) The effects of annual modulation of geodetic precession.
256 ! The correction applied is
257 ! 0 1 0 0 0 -0.150 (correction to in-phase nutation in
258 ! longitude).
259
260 ! (4) A prograde annual nutation has been estimated along with the
261 ! resonance coefficients. This probably reflects the influence of
262 ! S1 atmospheric tide.
263
264 ! (5) The free RFCN mode was estimated once every two years for the
265 ! data after 1984. (See values commented in eval_ls_nut. For the
266 ! last 6 years the values seem to be resonably stable.
267
268 ! (6) The new Simons et al., fundamental arguments are used in this
269 ! version. (The largest change from KSV_1995_1 was 0.007 mas for
270 ! semiannual nutation. All other changes, including the 18.6 year
271 ! nutation were 0.001-0.002 mas.)
272
273 ! REFERENCES:
274 ! NEW Version based on: Corrections and new developments in rigid Earth
275 ! nutation theory: Lunisolar influence including indirect planetary
276 ! effects, J. Souchay and H. Kinioshita, Astron. and Astrophys., 1995.
277 ! (Version here based on data files: SKRE1997.DPSI and SKRE1997.DEPS
278 ! and generated with ks_plan.f)
279 ! Souchay, J., and H. Kinoshita, Corrections and new developments in
280 ! rigid Earth nutation theory: I. Lunisolar influence including indirect
281 ! planetary effects, Astron. Astrophys., 312, 1017--1030, 1996.
282 ! Souchay, J., and H. Kinoshita, Corrections and new developments in
283 ! rigid Earth nutation theory: II. Influence of second-order geopotential
284 ! and direct planetray effect, Astron. Astrophys., 318, 639--652, 1997.
285 ! Souchay, J., B. Loysel, H, Kinoshita, and M. Folgueira, Corrections
286 ! and new developments in rigid Earth nutation theory: III. final tables
287 ! REN-2000 including crossed-nutation and spin-orbit coupling effects,
288 ! Astron. Astrophys. Suppl., 135, 111-131, 1999.
289 ! Kinoshita, H., and J. Souchay, The theory of the nutations for
290 ! the rigid Earth at the second order, Celes. Mech. and Dynam.
291 ! Astron., 48, 187--266, 1990.
292 ! Mathews, P. M., B. A. Buffett, and T. A. Herring, Modeling of Nutation-Precession:
293 ! Insights into the Earth's Interior and New Nonrigid Earth Nutation Series
294 ! to be submitted, J. Geophys. Res, 2000.
295 ! Simon, J. L., Bretagnon, P., Chapront, J., Chapront-Touze, M.,
296 ! Francou, G., Laskar, J., 1994, "Numerical Expressions for
297 ! Precession Formulae and Mean Elements for the Moon and
298 ! Planets," Astron. Astrophys., 282, pp. 663-683.
299
300
301
302 ! USAGE:
303 ! call ls_nut( jd, dpsi_ls, deps_ls )
304 ! where <jd> is a full julian date with fractional part
305 ! of the day added (REAL(DOUBLE) INPUT)
306 ! and <dpsi_ls> and <deps_ls> are the nutations
307 ! in longitude and obliquity in milliarcsec.
308 ! (REAL(DOUBLE) OUTPUT)
309
310 ! RESTRICTIONS: if <jd> is less than 2000000.0 this routine
311 ! assumes an MJD has been passed and the time
312 ! used will be converted to JD. A warning
313 ! message will be printed.
314
315 ! PASSED VARIABLES
316 !
317 ! INPUT Values
318 ! jd - Time at which value needed. (jd + fraction of day)
319
320 ! OUTPUT Values
321 ! dpsi_ls - The nutation in longitude (mas).
322 ! deps_ls - The nutation in obliquity (mas).
323
324
325
326 real(double), intent(in) :: jd
327 real(double), intent(out) :: dpsi_ls, deps_ls
328
329 ! LOCAL VARIABLES
330
331 ! epoch - Julian date (jd passed in unless the JD
332 ! appears to be an MJD in which case it is
333 ! converted to JD (2 400 000.5d0 added)
334 ! ls_arg(5) - The arguments for the Luni-solar nutations.
335 ! (l, l', F, D and Omega). All in Radians.
336
337
338 real(double) :: epoch, ls_arg(5)
339
340 !***** Check to make sure user passed JD and not MJD. Correct
341 ! problem and warn the user.
342 ! MvdS: remove this 'solution'
343 !if( jd .lt.2000000.0d0 ) then
344 ! write(*,100) jd
345 ! 100 format('**WARNING** MJD apparently passed to SD_COMP',
346 ! . ' Value (',F10.2,') converted to JD')
347 ! epoch = jd + 2 400 000.5d0
348 !else
349 ! epoch = jd
350 !end if
351
352 epoch = jd
353
354 !***** Get the fundamental arguments at this epoch
355
356 call ls_angles( epoch, ls_arg)
357
358 ! Now compute the luni-solare nutations by summing over all
359 ! terms in the series.
360
361 call eval_ls_nut( epoch, ls_arg, dpsi_ls, deps_ls )
362
363 end subroutine ls_nut
364 !*********************************************************************************************************************************
365
366
367
368
369
370
371
372
373
374 !TITLE LS_ANGLES
375
376 !*********************************************************************************************************************************
377 !> \brief compute the value of the fundamental argument for Brown's arguments.
378 !!
379 !! \param epoch Julian day for arguments (input)
380 !! \param ls_arg Brown's arguments (rad)
381
382 subroutine ls_angles( epoch, ls_arg )
383 use sufr_kinds, only: double
384 implicit none
385
386 ! Routine to compute the value of the fundamental argument
387 ! for Brown's arguments. Arguments based on the IERS
388 ! standards.
389
390 ! MOD TAH 960206: Changed arguments to use Simons et al., 1994
391 ! values:
392 ! Simon, J. L., Bretagnon, P., Chapront, J., Chapront-Touze, M.,
393 ! Francou, G., Laskar, J., 1994, "Numerical Expressions for
394 ! Precession Formulae and Mean Elements for the Moon and
395 ! Planets," Astron. Astrophys., 282, pp. 663-683.
396
397
398 ! PHYSICAL CONSTANTS
399
400 ! pi - Define here to full precision
401 ! rad_to_deg - Conversion from radians to degs.
402 ! DJ2000 - Julian date of J2000
403 ! sec360 - number of seconds in 360 degreees.
404
405
406 real(double) :: pi, rad_to_deg, DJ2000, sec360
407
408 parameter( pi = 3.1415926535897932d0 )
409 parameter( dj2000 = 2451545.d0 )
410 parameter( sec360 = 1296000.d0 )
411
412 ! Computed quanities
413 parameter( rad_to_deg = 180.d0 /pi )
414
415 !-------------------------------------------------------------------
416
417 ! PASSED VARIABLES
418
419 ! INPUT
420 ! epoch - Julian date for arguments (jd + fraction of day, REAL(DOUBLE))
421
422 ! OUTPUT
423 ! ls_arg(5) - Brown's arguments (radians, REAL(DOUBLE))
424
425
426 real(double), intent(in) :: epoch
427 real(double), intent(out) :: ls_arg(5)
428
429 ! LOCAL VARIABLES
430 ! cent - Julian centuries to DJ2000.
431 ! el,eld - Mean longitude of moon minus mean
432 ! - longitude of moon's perigee (arcsec)
433 ! elc(5) - Coefficients for computing el
434 ! elp,elpd - Mean longitude of the sun minus mean
435 ! - longitude of sun perigee (arcsec)
436 ! elpc(5) - Coeffiecents for computing elp
437 ! f,fd - Moon's mean longitude minus omega (sec)
438 ! fc(5) - Coefficients for computing f
439 ! d,dd - Mean elongation of the moon from the
440 ! - sun (arcsec)
441 ! dc(5) - coefficients for computing d
442 ! om,omd - longitude of the ascending node of the
443 ! - moon's mean orbit on the elliptic
444 ! - measured from the mean equinox of date
445 ! omc(5) - Coefficients for computing om.
446
447
448 real(double) :: cent, el, elc(5), elp, elpc(5), f, fc(5), d, dc(5), om, omc(5) ! ,eld , elpd ,fd ,dd ,omd
449
450 !**** DATA statements for the fundamental arguments.
451 ! Simons et al., 1994 values
452
453 data elc / -0.00024470d0, 0.051635d0, 31.8792d0, 1717915923.2178d0, 485868.249036d0/
454 data elpc / -0.00001149d0, +0.000136d0, -0.5532d0, 129596581.0481d0, 1287104.79305d0/
455 data fc / 0.00000417d0, -0.001037d0, -12.7512d0, 1739527262.8478d0, 335779.526232d0/
456 data dc / -0.00003169d0, 0.006593d0, -6.3706d0, 1602961601.2090d0, 1072260.70369d0/
457 ! MOD TAH MHB_2000: 960606: Replaced <Om> with expression from b.3 of
458 ! Simon et al., 1994 since b.3 is computed with new precession constant
459 ! (Only the rate changes).
460 data omc / -0.00005939d0, 0.007702d0, 7.4722d0, -6962890.5431d0, 450160.398036d0/
461
462
463 !**** Get the number of centuries to current time
464
465 cent = (epoch-dj2000) / 36525.d0
466
467 !**** Compute angular arguments and their time derivatives
468 ! New formulas adding in the higher order term.
469
470 el = elc(1) * cent**4 + elc(2) * cent**3 + elc(3) * cent**2 + elc(4) * cent + elc(5)
471 el = mod( el, sec360 )
472 !eld = 4.d0 * elc(1) * cent**3 + 3.d0 * elc(2) * cent**2 + 2.d0 * elc(3) * cent + elc(4)
473
474 elp = elpc(1) * cent**4 + elpc(2) * cent**3 + elpc(3) * cent**2 + elpc(4) * cent + elpc(5)
475 elp = mod( elp, sec360 )
476 !elpd = 4.d0 * elpc(1) * cent**3 + 3.d0 * elpc(2) * cent**2 + 2.d0 * elpc(3) * cent + elpc(4)
477
478 f = fc(1) * cent**4 + fc(2) * cent**3 + fc(3) * cent**2 + fc(4) * cent + fc(5)
479 f = mod( f, sec360 )
480 !fd = 4.d0 * fc(1) * cent**3 + 3.d0 * fc(2) * cent**2 + 2.d0 * fc(3) * cent + fc(4)
481
482 d = dc(1) * cent**4 + dc(2) * cent**3 + dc(3) * cent**2 + dc(4) * cent + dc(5)
483 d = mod( d, sec360 )
484 !dd = 4.d0 * dc(1) * cent**3 + 3.d0 * dc(2) * cent**2 + 2.d0 * dc(3) * cent + dc(4)
485
486 om = omc(1) * cent**4 + omc(2) * cent**3 + omc(3) * cent**2 + omc(4) * cent + omc(5)
487 om = mod( om, sec360 )
488 !omd = 4.d0 * omc(1) * cent**3 + 3.d0 * omc(2) * cent**2 + 2.d0 * omc(3) * cent + omc(4)
489
490
491
492 !**** Now save the values. Convert values from arcseconds to radians
493
494 ls_arg(1) = el / (3600.d0*rad_to_deg)
495 ls_arg(2) = elp/ (3600.d0*rad_to_deg)
496 ls_arg(3) = f / (3600.d0*rad_to_deg)
497 ls_arg(4) = d / (3600.d0*rad_to_deg)
498 ls_arg(5) = om / (3600.d0*rad_to_deg)
499
500 end subroutine ls_angles
501 !*********************************************************************************************************************************
502
503
504
505
506
507
508
509
510 !TITLE EVAL_LS_NUT
511
512 !*********************************************************************************************************************************
513 !> \brief Compute the nutations in longitude and obliquity by summing over all terms in the nutations series.
514 !!
515 !! \param epoch Julian day for arguments (input)
516 !! \param ls_arg Brown's arguments (input; rad)
517 !! \param dpsi_ls Nutation in longitude (output; milliarcsec)
518 !! \param deps_ls Nutation in obliquity (output; milliarcsec)
519
520 subroutine eval_ls_nut( epoch, ls_arg, dpsi_ls, deps_ls )
521 use sufr_kinds, only: double
522 implicit none
523
524 ! Routine to compute the nutations in longitude and obliquity
525 ! by summing over all terms in the nutations series.
526
527 ! NOTE: ls_angles must be called before routine.
528
529 ! PARAMETERS:
530
531 ! num_ls - Number of terms in the nutations series
532
533 integer :: num_ls
534
535 parameter( num_ls = 678)
536
537 ! DJ2000 - Julian date of J2000
538 ! pi - Pi.
539
540
541 real(double) :: pi, DJ2000
542
543 parameter( pi = 3.1415926535897932d0 )
544 parameter( dj2000 = 2451545.d0 )
545
546 ! PASSED PARAMETERS:
547
548 ! INPUT:
549 ! epoch - Julian date at which nutation angles are needed.
550 ! ls_arg(5) - Five arguments for the nutatoions (l,l',F,D and Om)
551 ! computed at the epoch that the nutations need to be
552 ! evaluated (rad) (REAL(DOUBLE))
553
554 ! OUTPUT:
555 ! dpsi_ls, deps_ls - nutations in longitude and obliquity (mas)
556 ! (REAL(DOUBLE))
557
558
559 real(double), intent(in) :: epoch, ls_arg(5)
560 real(double), intent(out) :: dpsi_ls, deps_ls
561
562 ! LOCAL VARIABLES:
563
564 ! i and j - Counters to loop over the coeffients and the argumemts
565
566
567 integer :: i,j
568
569 ! arg - Final summed argumemt for the nutations
570 ! contributions (rads)
571 ! cent - Number of centuries since J2000.
572 ! dpsi_lsu and deps_lsu - Nutations in longitude and oblquity
573 ! in micro-arc-sec (units that the data statements
574 ! are in)
575 ! carg, sarg -- Cosine and sine of arguments.
576
577
578 real(double) :: arg, cent, dpsi_lsu, deps_lsu, carg, sarg
579
580 ! RFCN Freq. -1.00231810920 cyc per sidreal day, Period 430.2082 solar days
581 ! Units now in 0.1 microarcsec
582 ! IX01-IX68(11,10) -- Invidual declarations of the coefficents
583 ! of the nutation series so no data statement has more than 10 lines
584 ! The first 5 values are the arguments for l lp F D Om
585 ! The remaining elements are:
586 ! 6 - Nutation in longitude psi (sin, uas)
587 ! 7 - dpsi/dt (uasec/cent)
588 ! 8 - Nutation in oblquity eps (cos, uas)
589 ! 9 - deps/dt (uas/cent)
590 ! 10 - Out-of-phase longitude (cos, uas)
591 ! 11 - Out-of-phase obliquity (sin, uas)
592
593 integer :: IX01(11,10), IX02(11,10), IX03(11,10), IX04(11,10), &
594 IX05(11,10), IX06(11,10), IX07(11,10), IX08(11,10), IX09(11,10), IX10(11,10), IX11(11,10), IX12(11,10), &
595 IX13(11,10), IX14(11,10), IX15(11,10), IX16(11,10), IX17(11,10), IX18(11,10), IX19(11,10), IX20(11,10), &
596 IX21(11,10), IX22(11,10), IX23(11,10), IX24(11,10), IX25(11,10), IX26(11,10), IX27(11,10), IX28(11,10), &
597 IX29(11,10), IX30(11,10), IX31(11,10), IX32(11,10), IX33(11,10), IX34(11,10), IX35(11,10), IX36(11,10), &
598 IX37(11,10), IX38(11,10), IX39(11,10), IX40(11,10), IX41(11,10), IX42(11,10), IX43(11,10), IX44(11,10), &
599 IX45(11,10), IX46(11,10), IX47(11,10), IX48(11,10), IX49(11,10), IX50(11,10), IX51(11,10), IX52(11,10), &
600 IX53(11,10), IX54(11,10), IX55(11,10), IX56(11,10), IX57(11,10), IX58(11,10), IX59(11,10), IX60(11,10), &
601 IX61(11,10), IX62(11,10), IX63(11,10), IX64(11,10), IX65(11,10), IX66(11,10), IX67(11,10), IX68(11, 8)
602
603 integer :: nutc_int(11,678)
604 equivalence(nutc_int(1, 1),ix01(1,1))
605 equivalence(nutc_int(1, 11),ix02(1,1))
606 equivalence(nutc_int(1, 21),ix03(1,1))
607 equivalence(nutc_int(1, 31),ix04(1,1))
608 equivalence(nutc_int(1, 41),ix05(1,1))
609 equivalence(nutc_int(1, 51),ix06(1,1))
610 equivalence(nutc_int(1, 61),ix07(1,1))
611 equivalence(nutc_int(1, 71),ix08(1,1))
612 equivalence(nutc_int(1, 81),ix09(1,1))
613 equivalence(nutc_int(1, 91),ix10(1,1))
614 equivalence(nutc_int(1,101),ix11(1,1))
615 equivalence(nutc_int(1,111),ix12(1,1))
616 equivalence(nutc_int(1,121),ix13(1,1))
617 equivalence(nutc_int(1,131),ix14(1,1))
618 equivalence(nutc_int(1,141),ix15(1,1))
619 equivalence(nutc_int(1,151),ix16(1,1))
620 equivalence(nutc_int(1,161),ix17(1,1))
621 equivalence(nutc_int(1,171),ix18(1,1))
622 equivalence(nutc_int(1,181),ix19(1,1))
623 equivalence(nutc_int(1,191),ix20(1,1))
624 equivalence(nutc_int(1,201),ix21(1,1))
625 equivalence(nutc_int(1,211),ix22(1,1))
626 equivalence(nutc_int(1,221),ix23(1,1))
627 equivalence(nutc_int(1,231),ix24(1,1))
628 equivalence(nutc_int(1,241),ix25(1,1))
629 equivalence(nutc_int(1,251),ix26(1,1))
630 equivalence(nutc_int(1,261),ix27(1,1))
631 equivalence(nutc_int(1,271),ix28(1,1))
632 equivalence(nutc_int(1,281),ix29(1,1))
633 equivalence(nutc_int(1,291),ix30(1,1))
634 equivalence(nutc_int(1,301),ix31(1,1))
635 equivalence(nutc_int(1,311),ix32(1,1))
636 equivalence(nutc_int(1,321),ix33(1,1))
637 equivalence(nutc_int(1,331),ix34(1,1))
638 equivalence(nutc_int(1,341),ix35(1,1))
639 equivalence(nutc_int(1,351),ix36(1,1))
640 equivalence(nutc_int(1,361),ix37(1,1))
641 equivalence(nutc_int(1,371),ix38(1,1))
642 equivalence(nutc_int(1,381),ix39(1,1))
643 equivalence(nutc_int(1,391),ix40(1,1))
644 equivalence(nutc_int(1,401),ix41(1,1))
645 equivalence(nutc_int(1,411),ix42(1,1))
646 equivalence(nutc_int(1,421),ix43(1,1))
647 equivalence(nutc_int(1,431),ix44(1,1))
648 equivalence(nutc_int(1,441),ix45(1,1))
649 equivalence(nutc_int(1,451),ix46(1,1))
650 equivalence(nutc_int(1,461),ix47(1,1))
651 equivalence(nutc_int(1,471),ix48(1,1))
652 equivalence(nutc_int(1,481),ix49(1,1))
653 equivalence(nutc_int(1,491),ix50(1,1))
654 equivalence(nutc_int(1,501),ix51(1,1))
655 equivalence(nutc_int(1,511),ix52(1,1))
656 equivalence(nutc_int(1,521),ix53(1,1))
657 equivalence(nutc_int(1,531),ix54(1,1))
658 equivalence(nutc_int(1,541),ix55(1,1))
659 equivalence(nutc_int(1,551),ix56(1,1))
660 equivalence(nutc_int(1,561),ix57(1,1))
661 equivalence(nutc_int(1,571),ix58(1,1))
662 equivalence(nutc_int(1,581),ix59(1,1))
663 equivalence(nutc_int(1,591),ix60(1,1))
664 equivalence(nutc_int(1,601),ix61(1,1))
665 equivalence(nutc_int(1,611),ix62(1,1))
666 equivalence(nutc_int(1,621),ix63(1,1))
667 equivalence(nutc_int(1,631),ix64(1,1))
668 equivalence(nutc_int(1,641),ix65(1,1))
669 equivalence(nutc_int(1,651),ix66(1,1))
670 equivalence(nutc_int(1,661),ix67(1,1))
671 equivalence(nutc_int(1,671),ix68(1,1))
672 data ix01/ 0, 0, 0, 0, 1,-172064161,-174666, 92052331, 9086, 33386, 15377, &
673 0, 0, 2, -2, 2, -13170906, -1675, 5730336, -3015,-13696, -4587, &
674 0, 0, 2, 0, 2, -2276413, -234, 978459, -485, 2796, 1374, &
675 0, 0, 0, 0, 2, 2074554, 207, -897492, 470, -698, -291, &
676 0, 1, 0, 0, 0, 1475877, -3633, 73871, -184, 11817, -1924, &
677 0, 1, 2, -2, 2, -516821, 1226, 224386, -677, -524, -174, &
678 1, 0, 0, 0, 0, 711159, 73, -6750, 0, -872, 358, &
679 0, 0, 2, 0, 1, -387298, -367, 200728, 18, 380, 318, &
680 1, 0, 2, 0, 2, -301461, -36, 129025, -63, 816, 367, &
681 0, -1, 2, -2, 2, 215829, -494, -95929, 299, 111, 132 /
682 data ix02/ 0, 0, 2, -2, 1, 128227, 137, -68982, -9, 181, 39, &
683 -1, 0, 2, 0, 2, 123457, 11, -53311, 32, 19, -4, &
684 -1, 0, 0, 2, 0, 156994, 10, -1235, 0, -168, 82, &
685 1, 0, 0, 0, 1, 63110, 63, -33228, 0, 27, -9, &
686 -1, 0, 0, 0, 1, -57976, -63, 31429, 0, -189, -75, &
687 -1, 0, 2, 2, 2, -59641, -11, 25543, -11, 149, 66, &
688 1, 0, 2, 0, 1, -51613, -42, 26366, 0, 129, 78, &
689 -2, 0, 2, 0, 1, 45893, 50, -24236, -10, 31, 20, &
690 0, 0, 0, 2, 0, 63384, 11, -1220, 0, -150, 29, &
691 0, 0, 2, 2, 2, -38571, -1, 16452, -11, 158, 68 /
692 data ix03/ 0, -2, 2, -2, 2, 32481, 0, -13870, 0, 0, 0, &
693 -2, 0, 0, 2, 0, -47722, 0, 477, 0, -18, -25, &
694 2, 0, 2, 0, 2, -31046, -1, 13238, -11, 131, 59, &
695 1, 0, 2, -2, 2, 28593, 0, -12338, 10, -1, -3, &
696 -1, 0, 2, 0, 1, 20441, 21, -10758, 0, 10, -3, &
697 2, 0, 0, 0, 0, 29243, 0, -609, 0, -74, 13, &
698 0, 0, 2, 0, 0, 25887, 0, -550, 0, -66, 11, &
699 0, 1, 0, 0, 1, -14053, -25, 8551, -2, 79, -45, &
700 -1, 0, 0, 2, 1, 15164, 10, -8001, 0, 11, -1, &
701 0, 2, 2, -2, 2, -15794, 72, 6850, -42, -16, -5 /
702 data ix04/ 0, 0, -2, 2, 0, 21783, 0, -167, 0, 13, 13, &
703 1, 0, 0, -2, 1, -12873, -10, 6953, 0, -37, -14, &
704 0, -1, 0, 0, 1, -12654, 11, 6415, 0, 63, 26, &
705 -1, 0, 2, 2, 1, -10204, 0, 5222, 0, 25, 15, &
706 0, 2, 0, 0, 0, 16707, -85, 168, -1, -10, 10, &
707 1, 0, 2, 2, 2, -7691, 0, 3268, 0, 44, 19, &
708 -2, 0, 2, 0, 0, -11024, 0, 104, 0, -14, 2, &
709 0, 1, 2, 0, 2, 7566, -21, -3250, 0, -11, -5, &
710 0, 0, 2, 2, 1, -6637, -11, 3353, 0, 25, 14, &
711 0, -1, 2, 0, 2, -7141, 21, 3070, 0, 8, 4 /
712 data ix05/ 0, 0, 0, 2, 1, -6302, -11, 3272, 0, 2, 4, &
713 1, 0, 2, -2, 1, 5800, 10, -3045, 0, 2, -1, &
714 2, 0, 2, -2, 2, 6443, 0, -2768, 0, -7, -4, &
715 -2, 0, 0, 2, 1, -5774, -11, 3041, 0, -15, -5, &
716 2, 0, 2, 0, 1, -5350, 0, 2695, 0, 21, 12, &
717 0, -1, 2, -2, 1, -4752, -11, 2719, 0, -3, -3, &
718 0, 0, 0, -2, 1, -4940, -11, 2720, 0, -21, -9, &
719 -1, -1, 0, 2, 0, 7350, 0, -51, 0, -8, 4, &
720 2, 0, 0, -2, 1, 4065, 0, -2206, 0, 6, 1, &
721 1, 0, 0, 2, 0, 6579, 0, -199, 0, -24, 2 /
722 data ix06/ 0, 1, 2, -2, 1, 3579, 0, -1900, 0, 5, 1, &
723 1, -1, 0, 0, 0, 4725, 0, -41, 0, -6, 3, &
724 -2, 0, 2, 0, 2, -3075, 0, 1313, 0, -2, -1, &
725 3, 0, 2, 0, 2, -2904, 0, 1233, 0, 15, 7, &
726 0, -1, 0, 2, 0, 4348, 0, -81, 0, -10, 2, &
727 1, -1, 2, 0, 2, -2878, 0, 1232, 0, 8, 4, &
728 0, 0, 0, 1, 0, -4230, 0, -20, 0, 5, -2, &
729 -1, -1, 2, 2, 2, -2819, 0, 1207, 0, 7, 3, &
730 -1, 0, 2, 0, 0, -4056, 0, 40, 0, 5, -2, &
731 0, -1, 2, 2, 2, -2647, 0, 1129, 0, 11, 5 /
732 data ix07/ -2, 0, 0, 0, 1, -2294, 0, 1266, 0, -10, -4, &
733 1, 1, 2, 0, 2, 2481, 0, -1062, 0, -7, -3, &
734 2, 0, 0, 0, 1, 2179, 0, -1129, 0, -2, -2, &
735 -1, 1, 0, 1, 0, 3276, 0, -9, 0, 1, 0, &
736 1, 1, 0, 0, 0, -3389, 0, 35, 0, 5, -2, &
737 1, 0, 2, 0, 0, 3339, 0, -107, 0, -13, 1, &
738 -1, 0, 2, -2, 1, -1987, 0, 1073, 0, -6, -2, &
739 1, 0, 0, 0, 2, -1981, 0, 854, 0, 0, 0, &
740 -1, 0, 0, 1, 0, 4026, 0, -553, 0, -353, -139, &
741 0, 0, 2, 1, 2, 1660, 0, -710, 0, -5, -2 /
742 data ix08/ -1, 0, 2, 4, 2, -1521, 0, 647, 0, 9, 4, &
743 -1, 1, 0, 1, 1, 1314, 0, -700, 0, 0, 0, &
744 0, -2, 2, -2, 1, -1283, 0, 672, 0, 0, 0, &
745 1, 0, 2, 2, 1, -1331, 0, 663, 0, 8, 4, &
746 -2, 0, 2, 2, 2, 1383, 0, -594, 0, -2, -2, &
747 -1, 0, 0, 0, 2, 1405, 0, -610, 0, 4, 2, &
748 1, 1, 2, -2, 2, 1290, 0, -556, 0, 0, 0, &
749 -2, 0, 2, 4, 2, -1214, 0, 518, 0, 5, 2, &
750 -1, 0, 4, 0, 2, 1146, 0, -490, 0, -3, -1, &
751 2, 0, 2, -2, 1, 1019, 0, -527, 0, -1, -1 /
752 data ix09/ 2, 0, 2, 2, 2, -1100, 0, 465, 0, 9, 4, &
753 1, 0, 0, 2, 1, -970, 0, 496, 0, 2, 1, &
754 3, 0, 0, 0, 0, 1575, 0, -50, 0, -6, 0, &
755 3, 0, 2, -2, 2, 934, 0, -399, 0, -3, -1, &
756 0, 0, 4, -2, 2, 922, 0, -395, 0, -1, -1, &
757 0, 1, 2, 0, 1, 815, 0, -422, 0, -1, -1, &
758 0, 0, -2, 2, 1, 834, 0, -440, 0, 2, 1, &
759 0, 0, 2, -2, 3, 1248, 0, -170, 0, 0, 1, &
760 -1, 0, 0, 4, 0, 1338, 0, -39, 0, -5, 0, &
761 2, 0, -2, 0, 1, 716, 0, -389, 0, -2, -1 /
762 data ix10/ -2, 0, 0, 4, 0, 1282, 0, -23, 0, -3, 1, &
763 -1, -1, 0, 2, 1, 742, 0, -391, 0, 1, 0, &
764 -1, 0, 0, 1, 1, 1020, 0, -495, 0, -25, -10, &
765 0, 1, 0, 0, 2, 715, 0, -326, 0, -4, 2, &
766 0, 0, -2, 0, 1, -666, 0, 369, 0, -3, -1, &
767 0, -1, 2, 0, 1, -667, 0, 346, 0, 1, 1, &
768 0, 0, 2, -1, 2, -704, 0, 304, 0, 0, 0, &
769 0, 0, 2, 4, 2, -694, 0, 294, 0, 5, 2, &
770 -2, -1, 0, 2, 0, -1014, 0, 4, 0, -1, -1, &
771 1, 1, 0, -2, 1, -585, 0, 316, 0, -2, -1 /
772 data ix11/ -1, 1, 0, 2, 0, -949, 0, 8, 0, 1, -1, &
773 -1, 1, 0, 1, 2, -595, 0, 258, 0, 0, 0, &
774 1, -1, 0, 0, 1, 528, 0, -279, 0, 0, 0, &
775 1, -1, 2, 2, 2, -590, 0, 252, 0, 4, 2, &
776 -1, 1, 2, 2, 2, 570, 0, -244, 0, -2, -1, &
777 3, 0, 2, 0, 1, -502, 0, 250, 0, 3, 2, &
778 0, 1, -2, 2, 0, -875, 0, 29, 0, 1, 0, &
779 -1, 0, 0, -2, 1, -492, 0, 275, 0, -3, -1, &
780 0, 1, 2, 2, 2, 535, 0, -228, 0, -2, -1, &
781 -1, -1, 2, 2, 1, -467, 0, 240, 0, 1, 1 /
782 data ix12/ 0, -1, 0, 0, 2, 591, 0, -253, 0, 0, 0, &
783 1, 0, 2, -4, 1, -453, 0, 244, 0, -1, -1, &
784 -1, 0, -2, 2, 0, 766, 0, 9, 0, 1, 0, &
785 0, -1, 2, 2, 1, -446, 0, 225, 0, 2, 1, &
786 2, -1, 2, 0, 2, -488, 0, 207, 0, 2, 1, &
787 0, 0, 0, 2, 2, -468, 0, 201, 0, 0, 0, &
788 1, -1, 2, 0, 1, -421, 0, 216, 0, 1, 1, &
789 -1, 1, 2, 0, 2, 463, 0, -200, 0, 0, 0, &
790 0, 1, 0, 2, 0, -673, 0, 14, 0, 2, 0, &
791 0, -1, -2, 2, 0, 658, 0, -2, 0, 0, 0 /
792 data ix13/ 0, 3, 2, -2, 2, -438, 0, 188, 0, 0, 0, &
793 0, 0, 0, 1, 1, -390, 0, 205, 0, 0, 0, &
794 -1, 0, 2, 2, 0, 639, -11, -19, 0, -2, 0, &
795 2, 1, 2, 0, 2, 412, 0, -176, 0, -2, -1, &
796 1, 1, 0, 0, 1, -361, 0, 189, 0, 0, 0, &
797 1, 1, 2, 0, 1, 360, 0, -185, 0, -1, -1, &
798 2, 0, 0, 2, 0, 588, 0, -24, 0, -3, 0, &
799 1, 0, -2, 2, 0, -578, 0, 5, 0, 1, 0, &
800 -1, 0, 0, 2, 2, -396, 0, 171, 0, 0, 0, &
801 0, 1, 0, 1, 0, 565, 0, -6, 0, -1, 0 /
802 data ix14/ 0, 1, 0, -2, 1, -335, 0, 184, 0, -1, -1, &
803 -1, 0, 2, -2, 2, 357, 0, -154, 0, 1, 0, &
804 0, 0, 0, -1, 1, 321, 0, -174, 0, 1, 0, &
805 -1, 1, 0, 0, 1, -301, 0, 162, 0, -1, 0, &
806 1, 0, 2, -1, 2, -334, 0, 144, 0, 0, 0, &
807 1, -1, 0, 2, 0, 493, 0, -15, 0, -2, 0, &
808 0, 0, 0, 4, 0, 494, 0, -19, 0, -2, 0, &
809 1, 0, 2, 1, 2, 337, 0, -143, 0, -1, -1, &
810 0, 0, 2, 1, 1, 280, 0, -144, 0, -1, 0, &
811 1, 0, 0, -2, 2, 309, 0, -134, 0, 1, 0 /
812 data ix15/ -1, 0, 2, 4, 1, -263, 0, 131, 0, 2, 1, &
813 1, 0, -2, 0, 1, 253, 0, -138, 0, 1, 0, &
814 1, 1, 2, -2, 1, 245, 0, -128, 0, 0, 0, &
815 0, 0, 2, 2, 0, 416, 0, -17, 0, -2, 0, &
816 -1, 0, 2, -1, 1, -229, 0, 128, 0, 0, 0, &
817 -2, 0, 2, 2, 1, 231, 0, -120, 0, 0, 0, &
818 4, 0, 2, 0, 2, -259, 0, 109, 0, 2, 1, &
819 2, -1, 0, 0, 0, 375, 0, -8, 0, -1, 0, &
820 2, 1, 2, -2, 2, 252, 0, -108, 0, 0, 0, &
821 0, 1, 2, 1, 2, -245, 0, 104, 0, 1, 0 /
822 data ix16/ 1, 0, 4, -2, 2, 243, 0, -104, 0, -1, 0, &
823 -1, -1, 0, 0, 1, 208, 0, -112, 0, 1, 0, &
824 0, 1, 0, 2, 1, 199, 0, -102, 0, 0, 0, &
825 -2, 0, 2, 4, 1, -208, 0, 105, 0, 1, 0, &
826 2, 0, 2, 0, 0, 335, 0, -14, 0, -2, 0, &
827 1, 0, 0, 1, 0, -325, 0, 7, 0, 1, 0, &
828 -1, 0, 0, 4, 1, -187, 0, 96, 0, 0, 0, &
829 -1, 0, 4, 0, 1, 197, 0, -100, 0, -1, 0, &
830 2, 0, 2, 2, 1, -192, 0, 94, 0, 2, 1, &
831 0, 0, 2, -3, 2, -188, 0, 83, 0, 0, 0 /
832 data ix17/ -1, -2, 0, 2, 0, 276, 0, -2, 0, 0, 0, &
833 2, 1, 0, 0, 0, -286, 0, 6, 0, 1, 0, &
834 0, 0, 4, 0, 2, 186, 0, -79, 0, -1, 0, &
835 0, 0, 0, 0, 3, -219, 0, 43, 0, 0, 0, &
836 0, 3, 0, 0, 0, 276, 0, 2, 0, 0, 0, &
837 0, 0, 2, -4, 1, -153, 0, 84, 0, -1, 0, &
838 0, -1, 0, 2, 1, -156, 0, 81, 0, 0, 0, &
839 0, 0, 0, 4, 1, -154, 0, 78, 0, 1, 0, &
840 -1, -1, 2, 4, 2, -174, 0, 75, 0, 1, 0, &
841 1, 0, 2, 4, 2, -163, 0, 69, 0, 2, 1 /
842 data ix18/ -2, 2, 0, 2, 0, -228, 0, 1, 0, 0, 0, &
843 -2, -1, 2, 0, 1, 91, 0, -54, 0, -4, -2, &
844 -2, 0, 0, 2, 2, 175, 0, -75, 0, 0, 0, &
845 -1, -1, 2, 0, 2, -159, 0, 69, 0, 0, 0, &
846 0, 0, 4, -2, 1, 141, 0, -72, 0, 0, 0, &
847 3, 0, 2, -2, 1, 147, 0, -75, 0, 0, 0, &
848 -2, -1, 0, 2, 1, -132, 0, 69, 0, 0, 0, &
849 1, 0, 0, -1, 1, 159, 0, -54, 0, -28, 11, &
850 0, -2, 0, 2, 0, 213, 0, -4, 0, 0, 0, &
851 -2, 0, 0, 4, 1, 123, 0, -64, 0, 0, 0 /
852 data ix19/ -3, 0, 0, 0, 1, -118, 0, 66, 0, -1, 0, &
853 1, 1, 2, 2, 2, 144, 0, -61, 0, -1, 0, &
854 0, 0, 2, 4, 1, -121, 0, 60, 0, 1, 0, &
855 3, 0, 2, 2, 2, -134, 0, 56, 0, 1, 1, &
856 -1, 1, 2, -2, 1, -105, 0, 57, 0, 0, 0, &
857 2, 0, 0, -4, 1, -102, 0, 56, 0, 0, 0, &
858 0, 0, 0, -2, 2, 120, 0, -52, 0, 0, 0, &
859 2, 0, 2, -4, 1, 101, 0, -54, 0, 0, 0, &
860 -1, 1, 0, 2, 1, -113, 0, 59, 0, 0, 0, &
861 0, 0, 2, -1, 1, -106, 0, 61, 0, 0, 0 /
862 data ix20/ 0, -2, 2, 2, 2, -129, 0, 55, 0, 1, 0, &
863 2, 0, 0, 2, 1, -114, 0, 57, 0, 0, 0, &
864 4, 0, 2, -2, 2, 113, 0, -49, 0, -1, 0, &
865 2, 0, 0, -2, 2, -102, 0, 44, 0, 0, 0, &
866 0, 2, 0, 0, 1, -94, 0, 51, 0, 0, 0, &
867 1, 0, 0, -4, 1, -100, 0, 56, 0, -1, 0, &
868 0, 2, 2, -2, 1, 87, 0, -47, 0, 0, 0, &
869 -3, 0, 0, 4, 0, 161, 0, -1, 0, 0, 0, &
870 -1, 1, 2, 0, 1, 96, 0, -50, 0, 0, 0, &
871 -1, -1, 0, 4, 0, 151, 0, -5, 0, -1, 0 /
872 data ix21/ -1, -2, 2, 2, 2, -104, 0, 44, 0, 0, 0, &
873 -2, -1, 2, 4, 2, -110, 0, 48, 0, 0, 0, &
874 1, -1, 2, 2, 1, -100, 0, 50, 0, 1, 0, &
875 -2, 1, 0, 2, 0, 92, 0, 12, 0, -5, -2, &
876 -2, 1, 2, 0, 1, 82, 0, -45, 0, 0, 0, &
877 2, 1, 0, -2, 1, 82, 0, -45, 0, 0, 0, &
878 -3, 0, 2, 0, 1, -78, 0, 41, 0, 0, 0, &
879 -2, 0, 2, -2, 1, -77, 0, 43, 0, 0, 0, &
880 -1, 1, 0, 2, 2, 2, 0, 54, 0, 0, 0, &
881 0, -1, 2, -1, 2, 94, 0, -40, 0, 0, 0 /
882 data ix22/ -1, 0, 4, -2, 2, -93, 0, 40, 0, 0, 0, &
883 0, -2, 2, 0, 2, -83, 0, 40, 0, 10, -2, &
884 -1, 0, 2, 1, 2, 83, 0, -36, 0, 0, 0, &
885 2, 0, 0, 0, 2, -91, 0, 39, 0, 0, 0, &
886 0, 0, 2, 0, 3, 128, 0, -1, 0, 0, 0, &
887 -2, 0, 4, 0, 2, -79, 0, 34, 0, 0, 0, &
888 -1, 0, -2, 0, 1, -83, 0, 47, 0, 0, 0, &
889 -1, 1, 2, 2, 1, 84, 0, -44, 0, 0, 0, &
890 3, 0, 0, 0, 1, 83, 0, -43, 0, 0, 0, &
891 -1, 0, 2, 3, 2, 91, 0, -39, 0, 0, 0 /
892 data ix23/ 2, -1, 2, 0, 1, -77, 0, 39, 0, 0, 0, &
893 0, 1, 2, 2, 1, 84, 0, -43, 0, 0, 0, &
894 0, -1, 2, 4, 2, -92, 0, 39, 0, 1, 0, &
895 2, -1, 2, 2, 2, -92, 0, 39, 0, 1, 0, &
896 0, 2, -2, 2, 0, -94, 0, 0, 0, 0, 0, &
897 -1, -1, 2, -1, 1, 68, 0, -36, 0, 0, 0, &
898 0, -2, 0, 0, 1, -61, 0, 32, 0, 0, 0, &
899 1, 0, 2, -4, 2, 71, 0, -31, 0, 0, 0, &
900 1, -1, 0, -2, 1, 62, 0, -34, 0, 0, 0, &
901 -1, -1, 2, 0, 1, -63, 0, 33, 0, 0, 0 /
902 data ix24/ 1, -1, 2, -2, 2, -73, 0, 32, 0, 0, 0, &
903 -2, -1, 0, 4, 0, 115, 0, -2, 0, 0, 0, &
904 -1, 0, 0, 3, 0, -103, 0, 2, 0, 0, 0, &
905 -2, -1, 2, 2, 2, 63, 0, -28, 0, 0, 0, &
906 0, 2, 2, 0, 2, 74, 0, -32, 0, 0, 0, &
907 1, 1, 0, 2, 0, -103, 0, 3, 0, -3, -1, &
908 2, 0, 2, -1, 2, -69, 0, 30, 0, 0, 0, &
909 1, 0, 2, 1, 1, 57, 0, -29, 0, 0, 0, &
910 4, 0, 0, 0, 0, 94, 0, -4, 0, 0, 0, &
911 2, 1, 2, 0, 1, 64, 0, -33, 0, 0, 0 /
912 data ix25/ 3, -1, 2, 0, 2, -63, 0, 26, 0, 0, 0, &
913 -2, 2, 0, 2, 1, -38, 0, 20, 0, 0, 0, &
914 1, 0, 2, -3, 1, -43, 0, 24, 0, 0, 0, &
915 1, 1, 2, -4, 1, -45, 0, 23, 0, 0, 0, &
916 -1, -1, 2, -2, 1, 47, 0, -24, 0, 0, 0, &
917 0, -1, 0, -1, 1, -48, 0, 25, 0, 0, 0, &
918 0, -1, 0, -2, 1, 45, 0, -26, 0, 0, 0, &
919 -2, 0, 0, 0, 2, 56, 0, -25, 0, 0, 0, &
920 -2, 0, -2, 2, 0, 88, 0, 2, 0, 0, 0, &
921 -1, 0, -2, 4, 0, -75, 0, 0, 0, 0, 0 /
922 data ix26/ 1, -2, 0, 0, 0, 85, 0, 0, 0, 0, 0, &
923 0, 1, 0, 1, 1, 49, 0, -26, 0, 0, 0, &
924 -1, 2, 0, 2, 0, -74, 0, -1, 0, -3, -1, &
925 1, -1, 2, -2, 1, -39, 0, 21, 0, 0, 0, &
926 1, 2, 2, -2, 2, 45, 0, -20, 0, 0, 0, &
927 2, -1, 2, -2, 2, 51, 0, -22, 0, 0, 0, &
928 1, 0, 2, -1, 1, -40, 0, 21, 0, 0, 0, &
929 2, 1, 2, -2, 1, 41, 0, -21, 0, 0, 0, &
930 -2, 0, 0, -2, 1, -42, 0, 24, 0, 0, 0, &
931 1, -2, 2, 0, 2, -51, 0, 22, 0, 0, 0 /
932 data ix27/ 0, 1, 2, 1, 1, -42, 0, 22, 0, 0, 0, &
933 1, 0, 4, -2, 1, 39, 0, -21, 0, 0, 0, &
934 -2, 0, 4, 2, 2, 46, 0, -18, 0, 0, 0, &
935 1, 1, 2, 1, 2, -53, 0, 22, 0, 0, 0, &
936 1, 0, 0, 4, 0, 82, 0, -4, 0, 0, 0, &
937 1, 0, 2, 2, 0, 81, 0, -4, 0, -1, 0, &
938 2, 0, 2, 1, 2, 47, 0, -19, 0, 0, 0, &
939 3, 1, 2, 0, 2, 53, 0, -23, 0, 0, 0, &
940 4, 0, 2, 0, 1, -45, 0, 22, 0, 0, 0, &
941 -2, -1, 2, 0, 0, -44, 0, -2, 0, 0, 0 /
942 data ix28/ 0, 1, -2, 2, 1, -33, 0, 16, 0, 0, 0, &
943 1, 0, -2, 1, 0, -61, 0, 1, 0, 0, 0, &
944 0, -1, -2, 2, 1, 28, 0, -15, 0, 0, 0, &
945 2, -1, 0, -2, 1, -38, 0, 19, 0, 0, 0, &
946 -1, 0, 2, -1, 2, -33, 0, 21, 0, 0, 0, &
947 1, 0, 2, -3, 2, -60, 0, 0, 0, 0, 0, &
948 0, 1, 2, -2, 3, 48, 0, -10, 0, 0, 0, &
949 0, 0, 2, -3, 1, 27, 0, -14, 0, 0, 0, &
950 -1, 0, -2, 2, 1, 38, 0, -20, 0, 0, 0, &
951 0, 0, 2, -4, 2, 31, 0, -13, 0, 0, 0 /
952 data ix29/ -2, 1, 0, 0, 1, -29, 0, 15, 0, 0, 0, &
953 -1, 0, 0, -1, 1, 28, 0, -15, 0, 0, 0, &
954 2, 0, 2, -4, 2, -32, 0, 15, 0, 0, 0, &
955 0, 0, 4, -4, 4, 45, 0, -8, 0, 0, 0, &
956 0, 0, 4, -4, 2, -44, 0, 19, 0, 0, 0, &
957 -1, -2, 0, 2, 1, 28, 0, -15, 0, 0, 0, &
958 -2, 0, 0, 3, 0, -51, 0, 0, 0, 0, 0, &
959 1, 0, -2, 2, 1, -36, 0, 20, 0, 0, 0, &
960 -3, 0, 2, 2, 2, 44, 0, -19, 0, 0, 0, &
961 -3, 0, 2, 2, 1, 26, 0, -14, 0, 0, 0 /
962 data ix30/ -2, 0, 2, 2, 0, -60, 0, 2, 0, 0, 0, &
963 2, -1, 0, 0, 1, 35, 0, -18, 0, 0, 0, &
964 -2, 1, 2, 2, 2, -27, 0, 11, 0, 0, 0, &
965 1, 1, 0, 1, 0, 47, 0, -1, 0, 0, 0, &
966 0, 1, 4, -2, 2, 36, 0, -15, 0, 0, 0, &
967 -1, 1, 0, -2, 1, -36, 0, 20, 0, 0, 0, &
968 0, 0, 0, -4, 1, -35, 0, 19, 0, 0, 0, &
969 1, -1, 0, 2, 1, -37, 0, 19, 0, 0, 0, &
970 1, 1, 0, 2, 1, 32, 0, -16, 0, 0, 0, &
971 -1, 2, 2, 2, 2, 35, 0, -14, 0, 0, 0 /
972 data ix31/ 3, 1, 2, -2, 2, 32, 0, -13, 0, 0, 0, &
973 0, -1, 0, 4, 0, 65, 0, -2, 0, 0, 0, &
974 2, -1, 0, 2, 0, 47, 0, -1, 0, 0, 0, &
975 0, 0, 4, 0, 1, 32, 0, -16, 0, 0, 0, &
976 2, 0, 4, -2, 2, 37, 0, -16, 0, 0, 0, &
977 -1, -1, 2, 4, 1, -30, 0, 15, 0, 0, 0, &
978 1, 0, 0, 4, 1, -32, 0, 16, 0, 0, 0, &
979 1, -2, 2, 2, 2, -31, 0, 13, 0, 0, 0, &
980 0, 0, 2, 3, 2, 37, 0, -16, 0, 0, 0, &
981 -1, 1, 2, 4, 2, 31, 0, -13, 0, 0, 0 /
982 data ix32/ 3, 0, 0, 2, 0, 49, 0, -2, 0, 0, 0, &
983 -1, 0, 4, 2, 2, 32, 0, -13, 0, 0, 0, &
984 1, 1, 2, 2, 1, 23, 0, -12, 0, 0, 0, &
985 -2, 0, 2, 6, 2, -43, 0, 18, 0, 0, 0, &
986 2, 1, 2, 2, 2, 26, 0, -11, 0, 0, 0, &
987 -1, 0, 2, 6, 2, -32, 0, 14, 0, 0, 0, &
988 1, 0, 2, 4, 1, -29, 0, 14, 0, 0, 0, &
989 2, 0, 2, 4, 2, -27, 0, 12, 0, 0, 0, &
990 1, 1, -2, 1, 0, 30, 0, 0, 0, 0, 0, &
991 -3, 1, 2, 1, 2, -11, 0, 5, 0, 0, 0 /
992 data ix33/ 2, 0, -2, 0, 2, -21, 0, 10, 0, 0, 0, &
993 -1, 0, 0, 1, 2, -34, 0, 15, 0, 0, 0, &
994 -4, 0, 2, 2, 1, -10, 0, 6, 0, 0, 0, &
995 -1, -1, 0, 1, 0, -36, 0, 0, 0, 0, 0, &
996 0, 0, -2, 2, 2, -9, 0, 4, 0, 0, 0, &
997 1, 0, 0, -1, 2, -12, 0, 5, 0, 0, 0, &
998 0, -1, 2, -2, 3, -21, 0, 5, 0, 0, 0, &
999 -2, 1, 2, 0, 0, -29, 0, -1, 0, 0, 0, &
1000 0, 0, 2, -2, 4, -15, 0, 3, 0, 0, 0, &
1001 -2, -2, 0, 2, 0, -20, 0, 0, 0, 0, 0 /
1002 data ix34/ -2, 0, -2, 4, 0, 28, 0, 0, 0, 0, -2, &
1003 0, -2, -2, 2, 0, 17, 0, 0, 0, 0, 0, &
1004 1, 2, 0, -2, 1, -22, 0, 12, 0, 0, 0, &
1005 3, 0, 0, -4, 1, -14, 0, 7, 0, 0, 0, &
1006 -1, 1, 2, -2, 2, 24, 0, -11, 0, 0, 0, &
1007 1, -1, 2, -4, 1, 11, 0, -6, 0, 0, 0, &
1008 1, 1, 0, -2, 2, 14, 0, -6, 0, 0, 0, &
1009 -3, 0, 2, 0, 0, 24, 0, 0, 0, 0, 0, &
1010 -3, 0, 2, 0, 2, 18, 0, -8, 0, 0, 0, &
1011 -2, 0, 0, 1, 0, -38, 0, 0, 0, 0, 0 /
1012 data ix35/ 0, 0, -2, 1, 0, -31, 0, 0, 0, 0, 0, &
1013 -3, 0, 0, 2, 1, -16, 0, 8, 0, 0, 0, &
1014 -1, -1, -2, 2, 0, 29, 0, 0, 0, 0, 0, &
1015 0, 1, 2, -4, 1, -18, 0, 10, 0, 0, 0, &
1016 2, 1, 0, -4, 1, -10, 0, 5, 0, 0, 0, &
1017 0, 2, 0, -2, 1, -17, 0, 10, 0, 0, 0, &
1018 1, 0, 0, -3, 1, 9, 0, -4, 0, 0, 0, &
1019 -2, 0, 2, -2, 2, 16, 0, -6, 0, 0, 0, &
1020 -2, -1, 0, 0, 1, 22, 0, -12, 0, 0, 0, &
1021 -4, 0, 0, 2, 0, 20, 0, 0, 0, 0, 0 /
1022 data ix36/ 1, 1, 0, -4, 1, -13, 0, 6, 0, 0, 0, &
1023 -1, 0, 2, -4, 1, -17, 0, 9, 0, 0, 0, &
1024 0, 0, 4, -4, 1, -14, 0, 8, 0, 0, 0, &
1025 0, 3, 2, -2, 2, 0, 0, -7, 0, 0, 0, &
1026 -3, -1, 0, 4, 0, 14, 0, 0, 0, 0, 0, &
1027 -3, 0, 0, 4, 1, 19, 0, -10, 0, 0, 0, &
1028 1, -1, -2, 2, 0, -34, 0, 0, 0, 0, 0, &
1029 -1, -1, 0, 2, 2, -20, 0, 8, 0, 0, 0, &
1030 1, -2, 0, 0, 1, 9, 0, -5, 0, 0, 0, &
1031 1, -1, 0, 0, 2, -18, 0, 7, 0, 0, 0 /
1032 data ix37/ 0, 0, 0, 1, 2, 13, 0, -6, 0, 0, 0, &
1033 -1, -1, 2, 0, 0, 17, 0, 0, 0, 0, 0, &
1034 1, -2, 2, -2, 2, -12, 0, 5, 0, 0, 0, &
1035 0, -1, 2, -1, 1, 15, 0, -8, 0, 0, 0, &
1036 -1, 0, 2, 0, 3, -11, 0, 3, 0, 0, 0, &
1037 1, 1, 0, 0, 2, 13, 0, -5, 0, 0, 0, &
1038 -1, 1, 2, 0, 0, -18, 0, 0, 0, 0, 0, &
1039 1, 2, 0, 0, 0, -35, 0, 0, 0, 0, 0, &
1040 -1, 2, 2, 0, 2, 9, 0, -4, 0, 0, 0, &
1041 -1, 0, 4, -2, 1, -19, 0, 10, 0, 0, 0 /
1042 data ix38/ 3, 0, 2, -4, 2, -26, 0, 11, 0, 0, 0, &
1043 1, 2, 2, -2, 1, 8, 0, -4, 0, 0, 0, &
1044 1, 0, 4, -4, 2, -10, 0, 4, 0, 0, 0, &
1045 -2, -1, 0, 4, 1, 10, 0, -6, 0, 0, 0, &
1046 0, -1, 0, 2, 2, -21, 0, 9, 0, 0, 0, &
1047 -2, 1, 0, 4, 0, -15, 0, 0, 0, 0, 0, &
1048 -2, -1, 2, 2, 1, 9, 0, -5, 0, 0, 0, &
1049 2, 0, -2, 2, 0, -29, 0, 0, 0, 0, 0, &
1050 1, 0, 0, 1, 1, -19, 0, 10, 0, 0, 0, &
1051 0, 1, 0, 2, 2, 12, 0, -5, 0, 0, 0 /
1052 data ix39/ 1, -1, 2, -1, 2, 22, 0, -9, 0, 0, 0, &
1053 -2, 0, 4, 0, 1, -10, 0, 5, 0, 0, 0, &
1054 2, 1, 0, 0, 1, -20, 0, 11, 0, 0, 0, &
1055 0, 1, 2, 0, 0, -20, 0, 0, 0, 0, 0, &
1056 0, -1, 4, -2, 2, -17, 0, 7, 0, 0, 0, &
1057 0, 0, 4, -2, 4, 15, 0, -3, 0, 0, 0, &
1058 0, 2, 2, 0, 1, 8, 0, -4, 0, 0, 0, &
1059 -3, 0, 0, 6, 0, 14, 0, 0, 0, 0, 0, &
1060 -1, -1, 0, 4, 1, -12, 0, 6, 0, 0, 0, &
1061 1, -2, 0, 2, 0, 25, 0, 0, 0, 0, 0 /
1062 data ix40/ -1, 0, 0, 4, 2, -13, 0, 6, 0, 0, 0, &
1063 -1, -2, 2, 2, 1, -14, 0, 8, 0, 0, 0, &
1064 -1, 0, 0, -2, 2, 13, 0, -5, 0, 0, 0, &
1065 1, 0, -2, -2, 1, -17, 0, 9, 0, 0, 0, &
1066 0, 0, -2, -2, 1, -12, 0, 6, 0, 0, 0, &
1067 -2, 0, -2, 0, 1, -10, 0, 5, 0, 0, 0, &
1068 0, 0, 0, 3, 1, 10, 0, -6, 0, 0, 0, &
1069 0, 0, 0, 3, 0, -15, 0, 0, 0, 0, 0, &
1070 -1, 1, 0, 4, 0, -22, 0, 0, 0, 0, 0, &
1071 -1, -1, 2, 2, 0, 28, 0, -1, 0, 0, 0 /
1072 data ix41/ -2, 0, 2, 3, 2, 15, 0, -7, 0, 0, 0, &
1073 1, 0, 0, 2, 2, 23, 0, -10, 0, 0, 0, &
1074 0, -1, 2, 1, 2, 12, 0, -5, 0, 0, 0, &
1075 3, -1, 0, 0, 0, 29, 0, -1, 0, 0, 0, &
1076 2, 0, 0, 1, 0, -25, 0, 1, 0, 0, 0, &
1077 1, -1, 2, 0, 0, 22, 0, 0, 0, 0, 0, &
1078 0, 0, 2, 1, 0, -18, 0, 0, 0, 0, 0, &
1079 1, 0, 2, 0, 3, 15, 0, 3, 0, 0, 0, &
1080 3, 1, 0, 0, 0, -23, 0, 0, 0, 0, 0, &
1081 3, -1, 2, -2, 2, 12, 0, -5, 0, 0, 0 /
1082 data ix42/ 2, 0, 2, -1, 1, -8, 0, 4, 0, 0, 0, &
1083 1, 1, 2, 0, 0, -19, 0, 0, 0, 0, 0, &
1084 0, 0, 4, -1, 2, -10, 0, 4, 0, 0, 0, &
1085 1, 2, 2, 0, 2, 21, 0, -9, 0, 0, 0, &
1086 -2, 0, 0, 6, 0, 23, 0, -1, 0, 0, 0, &
1087 0, -1, 0, 4, 1, -16, 0, 8, 0, 0, 0, &
1088 -2, -1, 2, 4, 1, -19, 0, 9, 0, 0, 0, &
1089 0, -2, 2, 2, 1, -22, 0, 10, 0, 0, 0, &
1090 0, -1, 2, 2, 0, 27, 0, -1, 0, 0, 0, &
1091 -1, 0, 2, 3, 1, 16, 0, -8, 0, 0, 0 /
1092 data ix43/ -2, 1, 2, 4, 2, 19, 0, -8, 0, 0, 0, &
1093 2, 0, 0, 2, 2, 9, 0, -4, 0, 0, 0, &
1094 2, -2, 2, 0, 2, -9, 0, 4, 0, 0, 0, &
1095 -1, 1, 2, 3, 2, -9, 0, 4, 0, 0, 0, &
1096 3, 0, 2, -1, 2, -8, 0, 4, 0, 0, 0, &
1097 4, 0, 2, -2, 1, 18, 0, -9, 0, 0, 0, &
1098 -1, 0, 0, 6, 0, 16, 0, -1, 0, 0, 0, &
1099 -1, -2, 2, 4, 2, -10, 0, 4, 0, 0, 0, &
1100 -3, 0, 2, 6, 2, -23, 0, 9, 0, 0, 0, &
1101 -1, 0, 2, 4, 0, 16, 0, -1, 0, 0, 0 /
1102 data ix44/ 3, 0, 0, 2, 1, -12, 0, 6, 0, 0, 0, &
1103 3, -1, 2, 0, 1, -8, 0, 4, 0, 0, 0, &
1104 3, 0, 2, 0, 0, 30, 0, -2, 0, 0, 0, &
1105 1, 0, 4, 0, 2, 24, 0, -10, 0, 0, 0, &
1106 5, 0, 2, -2, 2, 10, 0, -4, 0, 0, 0, &
1107 0, -1, 2, 4, 1, -16, 0, 7, 0, 0, 0, &
1108 2, -1, 2, 2, 1, -16, 0, 7, 0, 0, 0, &
1109 0, 1, 2, 4, 2, 17, 0, -7, 0, 0, 0, &
1110 1, -1, 2, 4, 2, -24, 0, 10, 0, 0, 0, &
1111 3, -1, 2, 2, 2, -12, 0, 5, 0, 0, 0 /
1112 data ix45/ 3, 0, 2, 2, 1, -24, 0, 11, 0, 0, 0, &
1113 5, 0, 2, 0, 2, -23, 0, 9, 0, 0, 0, &
1114 0, 0, 2, 6, 2, -13, 0, 5, 0, 0, 0, &
1115 4, 0, 2, 2, 2, -15, 0, 7, 0, 0, 0, &
1116 0, -1, 1, -1, 1, 0, 0, 0, 0, -1988, -1679, &
1117 -1, 0, 1, 0, 3, 0, 0, 0, 0, -63, -27, &
1118 0, -2, 2, -2, 3, -4, 0, 0, 0, 0, 0, &
1119 1, 0, -1, 0, 1, 0, 0, 0, 0, 5, 4, &
1120 2, -2, 0, -2, 1, 5, 0, -3, 0, 0, 0, &
1121 -1, 0, 1, 0, 2, 0, 0, 0, 0, 364, 176 /
1122 data ix46/ -1, 0, 1, 0, 1, 0, 0, 0, 0, -1044, -891, &
1123 -1, -1, 2, -1, 2, -3, 0, 1, 0, 0, 0, &
1124 -2, 2, 0, 2, 2, 4, 0, -2, 0, 0, 0, &
1125 -1, 0, 1, 0, 0, 0, 0, 0, 0, 330, 0, &
1126 -4, 1, 2, 2, 2, 5, 0, -2, 0, 0, 0, &
1127 -3, 0, 2, 1, 1, 3, 0, -2, 0, 0, 0, &
1128 -2, -1, 2, 0, 2, -3, 0, 1, 0, 0, 0, &
1129 1, 0, -2, 1, 1, -5, 0, 2, 0, 0, 0, &
1130 2, -1, -2, 0, 1, 3, 0, -1, 0, 0, 0, &
1131 -4, 0, 2, 2, 0, 3, 0, 0, 0, 0, 0 /
1132 data ix47/ -3, 1, 0, 3, 0, 3, 0, 0, 0, 0, 0, &
1133 -1, 0, -1, 2, 0, 0, 0, 0, 0, 5, 0, &
1134 0, -2, 0, 0, 2, 0, 0, 1, 0, 0, 0, &
1135 0, -2, 0, 0, 2, 4, 0, -2, 0, 0, 0, &
1136 -3, 0, 0, 3, 0, 6, 0, 0, 0, 0, 0, &
1137 -2, -1, 0, 2, 2, 5, 0, -2, 0, 0, 0, &
1138 -1, 0, -2, 3, 0, -7, 0, 0, 0, 0, 0, &
1139 -4, 0, 0, 4, 0, -12, 0, 0, 0, 0, 0, &
1140 2, 1, -2, 0, 1, 5, 0, -3, 0, 0, 0, &
1141 2, -1, 0, -2, 2, 3, 0, -1, 0, 0, 0 /
1142 data ix48/ 0, 0, 1, -1, 0, -5, 0, 0, 0, 0, 0, &
1143 -1, 2, 0, 1, 0, 3, 0, 0, 0, 0, 0, &
1144 -2, 1, 2, 0, 2, -7, 0, 3, 0, 0, 0, &
1145 1, 1, 0, -1, 1, 7, 0, -4, 0, 0, 0, &
1146 1, 0, 1, -2, 1, 0, 0, 0, 0, -12, -10, &
1147 0, 2, 0, 0, 2, 4, 0, -2, 0, 0, 0, &
1148 1, -1, 2, -3, 1, 3, 0, -2, 0, 0, 0, &
1149 -1, 1, 2, -1, 1, -3, 0, 2, 0, 0, 0, &
1150 -2, 0, 4, -2, 2, -7, 0, 3, 0, 0, 0, &
1151 -2, 0, 4, -2, 1, -4, 0, 2, 0, 0, 0 /
1152 data ix49/ -2, -2, 0, 2, 1, -3, 0, 1, 0, 0, 0, &
1153 -2, 0, -2, 4, 0, 0, 0, 0, 0, 0, 0, &
1154 1, 2, 2, -4, 1, -3, 0, 1, 0, 0, 0, &
1155 1, 1, 2, -4, 2, 7, 0, -3, 0, 0, 0, &
1156 -1, 2, 2, -2, 1, -4, 0, 2, 0, 0, 0, &
1157 2, 0, 0, -3, 1, 4, 0, -2, 0, 0, 0, &
1158 -1, 2, 0, 0, 1, -5, 0, 3, 0, 0, 0, &
1159 0, 0, 0, -2, 0, 5, 0, 0, 0, 0, 0, &
1160 -1, -1, 2, -2, 2, -5, 0, 2, 0, 0, 0, &
1161 -1, 1, 0, 0, 2, 5, 0, -2, 0, 0, 0 /
1162 data ix50/ 0, 0, 0, -1, 2, -8, 0, 3, 0, 0, 0, &
1163 -2, 1, 0, 1, 0, 9, 0, 0, 0, 0, 0, &
1164 1, -2, 0, -2, 1, 6, 0, -3, 0, 0, 0, &
1165 1, 0, -2, 0, 2, -5, 0, 2, 0, 0, 0, &
1166 -3, 1, 0, 2, 0, 3, 0, 0, 0, 0, 0, &
1167 -1, 1, -2, 2, 0, -7, 0, 0, 0, 0, 0, &
1168 -1, -1, 0, 0, 2, -3, 0, 1, 0, 0, 0, &
1169 -3, 0, 0, 2, 0, 5, 0, 0, 0, 0, 0, &
1170 -3, -1, 0, 2, 0, 3, 0, 0, 0, 0, 0, &
1171 2, 0, 2, -6, 1, -3, 0, 2, 0, 0, 0 /
1172 data ix51/ 0, 1, 2, -4, 2, 4, 0, -2, 0, 0, 0, &
1173 2, 0, 0, -4, 2, 3, 0, -1, 0, 0, 0, &
1174 -2, 1, 2, -2, 1, -5, 0, 2, 0, 0, 0, &
1175 0, -1, 2, -4, 1, 4, 0, -2, 0, 0, 0, &
1176 0, 1, 0, -2, 2, 9, 0, -3, 0, 0, 0, &
1177 -1, 0, 0, -2, 0, 4, 0, 0, 0, 0, 0, &
1178 2, 0, -2, -2, 1, 4, 0, -2, 0, 0, 0, &
1179 -4, 0, 2, 0, 1, -3, 0, 2, 0, 0, 0, &
1180 -1, -1, 0, -1, 1, -4, 0, 2, 0, 0, 0, &
1181 0, 0, -2, 0, 2, 9, 0, -3, 0, 0, 0 /
1182 data ix52/ -3, 0, 0, 1, 0, -4, 0, 0, 0, 0, 0, &
1183 -1, 0, -2, 1, 0, -4, 0, 0, 0, 0, 0, &
1184 -2, 0, -2, 2, 1, 3, 0, -2, 0, 0, 0, &
1185 0, 0, -4, 2, 0, 8, 0, 0, 0, 0, 0, &
1186 -2, -1, -2, 2, 0, 3, 0, 0, 0, 0, 0, &
1187 1, 0, 2, -6, 1, -3, 0, 2, 0, 0, 0, &
1188 -1, 0, 2, -4, 2, 3, 0, -1, 0, 0, 0, &
1189 1, 0, 0, -4, 2, 3, 0, -1, 0, 0, 0, &
1190 2, 1, 2, -4, 2, -3, 0, 1, 0, 0, 0, &
1191 2, 1, 2, -4, 1, 6, 0, -3, 0, 0, 0 /
1192 data ix53/ 0, 1, 4, -4, 4, 3, 0, 0, 0, 0, 0, &
1193 0, 1, 4, -4, 2, -3, 0, 1, 0, 0, 0, &
1194 -1, -1, -2, 4, 0, -7, 0, 0, 0, 0, 0, &
1195 -1, -3, 0, 2, 0, 9, 0, 0, 0, 0, 0, &
1196 -1, 0, -2, 4, 1, -3, 0, 2, 0, 0, 0, &
1197 -2, -1, 0, 3, 0, -3, 0, 0, 0, 0, 0, &
1198 0, 0, -2, 3, 0, -4, 0, 0, 0, 0, 0, &
1199 -2, 0, 0, 3, 1, -5, 0, 3, 0, 0, 0, &
1200 0, -1, 0, 1, 0, -13, 0, 0, 0, 0, 0, &
1201 -3, 0, 2, 2, 0, -7, 0, 0, 0, 0, 0 /
1202 data ix54/ 1, 1, -2, 2, 0, 10, 0, 0, 0, 0, 0, &
1203 -1, 1, 0, 2, 2, 3, 0, -1, 0, 0, 0, &
1204 1, -2, 2, -2, 1, 10, 0, 6, 0, 13, -5, &
1205 0, 0, 1, 0, 2, 0, 0, 0, 0, 30, 14, &
1206 0, 0, 1, 0, 1, 0, 0, 0, 0, -162, -138, &
1207 0, 0, 1, 0, 0, 0, 0, 0, 0, 75, 0, &
1208 -1, 2, 0, 2, 1, -7, 0, 4, 0, 0, 0, &
1209 0, 0, 2, 0, 2, -4, 0, 2, 0, 0, 0, &
1210 -2, 0, 2, 0, 2, 4, 0, -2, 0, 0, 0, &
1211 2, 0, 0, -1, 1, 5, 0, -2, 0, 0, 0 /
1212 data ix55/ 3, 0, 0, -2, 1, 5, 0, -3, 0, 0, 0, &
1213 1, 0, 2, -2, 3, -3, 0, 0, 0, 0, 0, &
1214 1, 2, 0, 0, 1, -3, 0, 2, 0, 0, 0, &
1215 2, 0, 2, -3, 2, -4, 0, 2, 0, 0, 0, &
1216 -1, 1, 4, -2, 2, -5, 0, 2, 0, 0, 0, &
1217 -2, -2, 0, 4, 0, 6, 0, 0, 0, 0, 0, &
1218 0, -3, 0, 2, 0, 9, 0, 0, 0, 0, 0, &
1219 0, 0, -2, 4, 0, 5, 0, 0, 0, 0, 0, &
1220 -1, -1, 0, 3, 0, -7, 0, 0, 0, 0, 0, &
1221 -2, 0, 0, 4, 2, -3, 0, 1, 0, 0, 0 /
1222 data ix56/ -1, 0, 0, 3, 1, -4, 0, 2, 0, 0, 0, &
1223 2, -2, 0, 0, 0, 7, 0, 0, 0, 0, 0, &
1224 1, -1, 0, 1, 0, -4, 0, 0, 0, 0, 0, &
1225 -1, 0, 0, 2, 0, 4, 0, 0, 0, 0, 0, &
1226 0, -2, 2, 0, 1, -6, 0, 3, 0, -3, 1, &
1227 -1, 0, 1, 2, 1, 0, 0, 0, 0, -3, -2, &
1228 -1, 1, 0, 3, 0, 11, 0, 0, 0, 0, 0, &
1229 -1, -1, 2, 1, 2, 3, 0, -1, 0, 0, 0, &
1230 0, -1, 2, 0, 0, 11, 0, 0, 0, 0, 0, &
1231 -2, 1, 2, 2, 1, -3, 0, 2, 0, 0, 0 /
1232 data ix57/ 2, -2, 2, -2, 2, -1, 0, 3, 0, 3, -1, &
1233 1, 1, 0, 1, 1, 4, 0, -2, 0, 0, 0, &
1234 1, 0, 1, 0, 1, 0, 0, 0, 0, -13, -11, &
1235 1, 0, 1, 0, 0, 3, 0, 0, 0, 6, 0, &
1236 0, 2, 0, 2, 0, -7, 0, 0, 0, 0, 0, &
1237 2, -1, 2, -2, 1, 5, 0, -3, 0, 0, 0, &
1238 0, -1, 4, -2, 1, -3, 0, 1, 0, 0, 0, &
1239 0, 0, 4, -2, 3, 3, 0, 0, 0, 0, 0, &
1240 0, 1, 4, -2, 1, 5, 0, -3, 0, 0, 0, &
1241 4, 0, 2, -4, 2, -7, 0, 3, 0, 0, 0 /
1242 data ix58/ 2, 2, 2, -2, 2, 8, 0, -3, 0, 0, 0, &
1243 2, 0, 4, -4, 2, -4, 0, 2, 0, 0, 0, &
1244 -1, -2, 0, 4, 0, 11, 0, 0, 0, 0, 0, &
1245 -1, -3, 2, 2, 2, -3, 0, 1, 0, 0, 0, &
1246 -3, 0, 2, 4, 2, 3, 0, -1, 0, 0, 0, &
1247 -3, 0, 2, -2, 1, -4, 0, 2, 0, 0, 0, &
1248 -1, -1, 0, -2, 1, 8, 0, -4, 0, 0, 0, &
1249 -3, 0, 0, 0, 2, 3, 0, -1, 0, 0, 0, &
1250 -3, 0, -2, 2, 0, 11, 0, 0, 0, 0, 0, &
1251 0, 1, 0, -4, 1, -6, 0, 3, 0, 0, 0 /
1252 data ix59/ -2, 1, 0, -2, 1, -4, 0, 2, 0, 0, 0, &
1253 -4, 0, 0, 0, 1, -8, 0, 4, 0, 0, 0, &
1254 -1, 0, 0, -4, 1, -7, 0, 3, 0, 0, 0, &
1255 -3, 0, 0, -2, 1, -4, 0, 2, 0, 0, 0, &
1256 0, 0, 0, 3, 2, 3, 0, -1, 0, 0, 0, &
1257 -1, 1, 0, 4, 1, 6, 0, -3, 0, 0, 0, &
1258 1, -2, 2, 0, 1, -6, 0, 3, 0, 0, 0, &
1259 0, 1, 0, 3, 0, 6, 0, 0, 0, 0, 0, &
1260 -1, 0, 2, 2, 3, 6, 0, -1, 0, 0, 0, &
1261 0, 0, 2, 2, 2, 5, 0, -2, 0, 0, 0 /
1262 data ix60/ -2, 0, 2, 2, 2, -5, 0, 2, 0, 0, 0, &
1263 -1, 1, 2, 2, 0, -4, 0, 0, 0, 0, 0, &
1264 3, 0, 0, 0, 2, -4, 0, 2, 0, 0, 0, &
1265 2, 1, 0, 1, 0, 4, 0, 0, 0, 0, 0, &
1266 2, -1, 2, -1, 2, 6, 0, -3, 0, 0, 0, &
1267 0, 0, 2, 0, 1, -4, 0, 2, 0, 0, 0, &
1268 0, 0, 3, 0, 3, 0, 0, 0, 0, -26, -11, &
1269 0, 0, 3, 0, 2, 0, 0, 0, 0, -10, -5, &
1270 -1, 2, 2, 2, 1, 5, 0, -3, 0, 0, 0, &
1271 -1, 0, 4, 0, 0, -13, 0, 0, 0, 0, 0 /
1272 data ix61/ 1, 2, 2, 0, 1, 3, 0, -2, 0, 0, 0, &
1273 3, 1, 2, -2, 1, 4, 0, -2, 0, 0, 0, &
1274 1, 1, 4, -2, 2, 7, 0, -3, 0, 0, 0, &
1275 -2, -1, 0, 6, 0, 4, 0, 0, 0, 0, 0, &
1276 0, -2, 0, 4, 0, 5, 0, 0, 0, 0, 0, &
1277 -2, 0, 0, 6, 1, -3, 0, 2, 0, 0, 0, &
1278 -2, -2, 2, 4, 2, -6, 0, 2, 0, 0, 0, &
1279 0, -3, 2, 2, 2, -5, 0, 2, 0, 0, 0, &
1280 0, 0, 0, 4, 2, -7, 0, 3, 0, 0, 0, &
1281 -1, -1, 2, 3, 2, 5, 0, -2, 0, 0, 0 /
1282 data ix62/ -2, 0, 2, 4, 0, 13, 0, 0, 0, 0, 0, &
1283 2, -1, 0, 2, 1, -4, 0, 2, 0, 0, 0, &
1284 1, 0, 0, 3, 0, -3, 0, 0, 0, 0, 0, &
1285 0, 1, 0, 4, 1, 5, 0, -2, 0, 0, 0, &
1286 0, 1, 0, 4, 0, -11, 0, 0, 0, 0, 0, &
1287 1, -1, 2, 1, 2, 5, 0, -2, 0, 0, 0, &
1288 0, 0, 2, 2, 3, 4, 0, 0, 0, 0, 0, &
1289 1, 0, 2, 2, 2, 4, 0, -2, 0, 0, 0, &
1290 -1, 0, 2, 2, 2, -4, 0, 2, 0, 0, 0, &
1291 -2, 0, 4, 2, 1, 6, 0, -3, 0, 0, 0 /
1292 data ix63/ 2, 1, 0, 2, 1, 3, 0, -2, 0, 0, 0, &
1293 2, 1, 0, 2, 0, -12, 0, 0, 0, 0, 0, &
1294 2, -1, 2, 0, 0, 4, 0, 0, 0, 0, 0, &
1295 1, 0, 2, 1, 0, -3, 0, 0, 0, 0, 0, &
1296 0, 1, 2, 2, 0, -4, 0, 0, 0, 0, 0, &
1297 2, 0, 2, 0, 3, 3, 0, 0, 0, 0, 0, &
1298 3, 0, 2, 0, 2, 3, 0, -1, 0, 0, 0, &
1299 1, 0, 2, 0, 2, -3, 0, 1, 0, 0, 0, &
1300 1, 0, 3, 0, 3, 0, 0, 0, 0, -5, -2, &
1301 1, 1, 2, 1, 1, -7, 0, 4, 0, 0, 0 /
1302 data ix64/ 0, 2, 2, 2, 2, 6, 0, -3, 0, 0, 0, &
1303 2, 1, 2, 0, 0, -3, 0, 0, 0, 0, 0, &
1304 2, 0, 4, -2, 1, 5, 0, -3, 0, 0, 0, &
1305 4, 1, 2, -2, 2, 3, 0, -1, 0, 0, 0, &
1306 -1, -1, 0, 6, 0, 3, 0, 0, 0, 0, 0, &
1307 -3, -1, 2, 6, 2, -3, 0, 1, 0, 0, 0, &
1308 -1, 0, 0, 6, 1, -5, 0, 3, 0, 0, 0, &
1309 -3, 0, 2, 6, 1, -3, 0, 2, 0, 0, 0, &
1310 1, -1, 0, 4, 1, -3, 0, 2, 0, 0, 0, &
1311 1, -1, 0, 4, 0, 12, 0, 0, 0, 0, 0 /
1312 data ix65/ -2, 0, 2, 5, 2, 3, 0, -1, 0, 0, 0, &
1313 1, -2, 2, 2, 1, -4, 0, 2, 0, 0, 0, &
1314 3, -1, 0, 2, 0, 4, 0, 0, 0, 0, 0, &
1315 1, -1, 2, 2, 0, 6, 0, 0, 0, 0, 0, &
1316 0, 0, 2, 3, 1, 5, 0, -3, 0, 0, 0, &
1317 -1, 1, 2, 4, 1, 4, 0, -2, 0, 0, 0, &
1318 0, 1, 2, 3, 2, -6, 0, 3, 0, 0, 0, &
1319 -1, 0, 4, 2, 1, 4, 0, -2, 0, 0, 0, &
1320 2, 0, 2, 1, 1, 6, 0, -3, 0, 0, 0, &
1321 5, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0 /
1322 data ix66/ 2, 1, 2, 1, 2, -6, 0, 3, 0, 0, 0, &
1323 1, 0, 4, 0, 1, 3, 0, -2, 0, 0, 0, &
1324 3, 1, 2, 0, 1, 7, 0, -4, 0, 0, 0, &
1325 3, 0, 4, -2, 2, 4, 0, -2, 0, 0, 0, &
1326 -2, -1, 2, 6, 2, -5, 0, 2, 0, 0, 0, &
1327 0, 0, 0, 6, 0, 5, 0, 0, 0, 0, 0, &
1328 0, -2, 2, 4, 2, -6, 0, 3, 0, 0, 0, &
1329 -2, 0, 2, 6, 1, -6, 0, 3, 0, 0, 0, &
1330 2, 0, 0, 4, 1, -4, 0, 2, 0, 0, 0, &
1331 2, 0, 0, 4, 0, 10, 0, 0, 0, 0, 0 /
1332 data ix67/ 2, -2, 2, 2, 2, -4, 0, 2, 0, 0, 0, &
1333 0, 0, 2, 4, 0, 7, 0, 0, 0, 0, 0, &
1334 1, 0, 2, 3, 2, 7, 0, -3, 0, 0, 0, &
1335 4, 0, 0, 2, 0, 4, 0, 0, 0, 0, 0, &
1336 2, 0, 2, 2, 0, 11, 0, 0, 0, 0, 0, &
1337 0, 0, 4, 2, 2, 5, 0, -2, 0, 0, 0, &
1338 4, -1, 2, 0, 2, -6, 0, 2, 0, 0, 0, &
1339 3, 0, 2, 1, 2, 4, 0, -2, 0, 0, 0, &
1340 2, 1, 2, 2, 1, 3, 0, -2, 0, 0, 0, &
1341 4, 1, 2, 0, 2, 5, 0, -2, 0, 0, 0 /
1342 data ix68/ -1, -1, 2, 6, 2, -4, 0, 2, 0, 0, 0, &
1343 -1, 0, 2, 6, 1, -4, 0, 2, 0, 0, 0, &
1344 1, -1, 2, 4, 1, -3, 0, 2, 0, 0, 0, &
1345 1, 1, 2, 4, 2, 4, 0, -2, 0, 0, 0, &
1346 3, 1, 2, 2, 2, 3, 0, -1, 0, 0, 0, &
1347 5, 0, 2, 0, 1, -3, 0, 1, 0, 0, 0, &
1348 2, -1, 2, 4, 2, -3, 0, 1, 0, 0, 0, &
1349 2, 0, 2, 4, 1, -3, 0, 2, 0, 0, 0 /
1350
1351 !**** Initialize the values and sum over the series
1352
1353 dpsi_lsu = 0.0d0
1354 deps_lsu = 0.0d0
1355
1356 cent = (epoch-dj2000) / 36525.d0
1357
1358 do i = num_ls, 1, -1
1359
1360 ! Sum the mulitpliers by the arguments to the argument of
1361 ! nutation
1362 arg = 0.d0
1363 do j = 1,5
1364
1365 ! Sum into the argument for nutation.
1366 arg = arg + nutc_int(j,i)*ls_arg(j)
1367 end do
1368
1369 arg = mod(arg, 2.d0*pi)
1370 carg = cos(arg)
1371 sarg = sin(arg)
1372
1373 !**** Now add contributions to dpsi and deps
1374 dpsi_lsu = dpsi_lsu + (nutc_int( 6,i)+ nutc_int(7,i)*cent)*sarg + nutc_int(10,i)*carg
1375 deps_lsu = deps_lsu + (nutc_int( 8,i)+ nutc_int(9,i)*cent)*carg + nutc_int(11,i)*sarg
1376
1377 end do
1378
1379 ! Convert values from 0.1 micro-arc-sec to mill-arc-second
1380 dpsi_ls = dpsi_lsu * 1.d-4
1381 deps_ls = deps_lsu * 1.d-4
1382
1383 end subroutine eval_ls_nut
1384 !*********************************************************************************************************************************
1385
1386
1387
1388
1389
1390
1391
1392
1393 !TITLE OUT_PLAN_NUT
1394
1395 !*********************************************************************************************************************************
1396 !> \brief Write the planetary contribution to the nutations to stdout.
1397 !!
1398 subroutine out_plan_nut()
1399 use sufr_kinds, only: double
1400 implicit none
1401
1402 ! Routine to write the planetary contribution to the nutations
1403 ! to stdout.
1404 !
1405
1406 ! USAGE:
1407 ! call out_plan_nut
1408
1409 ! APPOXIMATIONS: The Oppolzer terms have not been added (should be
1410 ! < 0.005 mas), and
1411 ! Contributions from a non-rigid Earth have not been
1412 ! computed. For many of these terms the contribution
1413 ! arises from the perturbation of the Earth's orbit and
1414 ! therefore there will be not deformation effects.
1415
1416
1417 ! PASSED VARIABLES
1418 ! NONE
1419
1420 ! LOCAL VARIABLES
1421
1422 ! epoch - Dummy Julian date (used in call to plan_angles).
1423 ! plan_arg(14) - Values of the planetary arguments
1424 ! L, L', F, D, Om, Mercury, Venus, Earth, Mars,
1425 ! Jupiter, Saturn, Uranus, Uranus(?), pa. (rads)
1426 ! plan_rat(14) - Rates of changes of the planetary arguments
1427 ! (rad/year). Used to get periods for the
1428 ! terms.
1429 ! dpsi, deps - Dummy returns for nutations in long and oblquity.
1430
1431 real(double) :: epoch, plan_arg(14), plan_rat(14), dpsi, deps
1432
1433 !**** Set the epoch to a dummy value
1434
1435 epoch = 2400000.5d0
1436
1437 !***** Get the fundamental arguments at this epoch
1438
1439 call plan_angles( epoch, plan_arg, plan_rat)
1440
1441 ! Now compute the contributions of the planetery ntations by
1442 ! summing over the series.
1443
1444 call eval_plan_nut( plan_arg, plan_rat, dpsi, deps, 'NO ' )
1445
1446 end subroutine out_plan_nut
1447 !*********************************************************************************************************************************
1448
1449
1450
1451
1452
1453
1454
1455
1456 !TITLE PLAN_NUT
1457
1458 !*********************************************************************************************************************************
1459 !> \brief Compute the planetary contribution to the nutations.
1460 !!
1461 !! \param jd Julian day (input)
1462 !! \param dpsi Contribution to the nutation in longitude (output; mas)
1463 !! \param deps Contribution to the nutation in obliquity (output; mas)
1464
1465 subroutine plan_nut( jd, dpsi, deps )
1466 use sufr_kinds, only: double
1467 implicit none
1468
1469 ! Routine to compute the planetary contribution to the nutations.
1470 ! Coefficents from Tables XIV to XIX of Kinoshita, H. and J. Souchay,
1471 ! Nutations for the rigid Earth, Celes. Mech. and Dynam. Astron,
1472 !
1473 ! NEW Version based on: Corrections and new developments in rigid Earth
1474 ! nutation theory: Lunisolar influence including indirect planetary
1475 ! effects, J. Souchay and H. Kinioshita, Astron. and Astrophys., 1995.
1476 ! (Version here based on data files: SKRE1997.DPSI and SKRE1997.DEPS
1477 ! and generated with ks_plan_SKRE97.f)
1478
1479 ! Arguments based on Souchay, Loysel, Kinoshita, Folgueira, Corrections
1480 ! and new developments in rigid earth nutation theory, Aston. Astrophys.
1481 ! Suppl. Ser, 135, 111-131, (1999)
1482 !
1483
1484 ! USAGE:
1485 ! call plan_nut( jd, dpsi, deps )
1486 ! where <jd> is a full julian date with fractional part
1487 ! of the day added (REAL(DOUBLE) INPUT)
1488 ! and <dpsi> and <deps> are the contributions to the nutations
1489 ! in longitude and obliquity in milliarcsec.
1490 ! (REAL(DOUBLE) OUTPUT)
1491
1492 ! RESTRICTIONS: if <jd> is less than 2000000.0 this routine
1493 ! assumes an MJD has been passed and the time
1494 ! used will be converted to JD. A warning
1495 ! message will be printed.
1496 ! APPOXIMATIONS: The Oppolzer terms have not been added (should be
1497 ! < 0.005 mas), and
1498 ! Contributions from a non-rigid Earth have not been
1499 ! computed. For many of these terms the contribution
1500 ! arises from the perturbation of the Earth's orbit and
1501 ! therefore there will be not deformation effects.
1502
1503
1504 ! PASSED VARIABLES
1505 !
1506 ! INPUT Values
1507 ! jd - Time at which value needed. (jd + fraction of day)
1508
1509 ! OUTPUT Values
1510 ! dpsi - Contribution to the nutation in longitude (mas). Should
1511 ! be added to standard nutation in longitude values.
1512 ! deps - Contribution to the nutation in obliquity (mas). Should
1513 ! be added to standard nutation in obliquity values.
1514
1515 real(double), intent(in) :: jd
1516 real(double), intent(out) :: dpsi, deps
1517
1518 ! LOCAL VARIABLES
1519
1520 ! epoch - Julian date (jd passed in unless the JD
1521 ! appears to be an MJD in which case it is
1522 ! converted to JD (2 400 000.5d0 added)
1523 ! plan_arg(10) - Values of the planetary arguments (rads)
1524 ! plan_rat(14) - Rates of planetary arguments (rads/yr)
1525
1526 real(double) :: epoch, plan_arg(14), plan_rat(14)
1527
1528 !***** Check to make sure user passed JD and not MJD. Correct
1529 ! problem and warn the user.
1530 ! MvdS: remove this 'solution'
1531 !if( jd .lt.2000000.0d0 ) then
1532 ! write(*,100) jd
1533 ! 100 format('**WARNING** MJD apparently passed to SD_COMP',
1534 ! . ' Value (',F10.2,') converted to JD')
1535 ! epoch = jd + 2 400 000.5d0
1536 !else
1537 ! epoch = jd
1538 !end if
1539 epoch = jd
1540
1541 !***** Get the fundamental arguments at this epoch
1542
1543 call plan_angles( epoch, plan_arg, plan_rat)
1544
1545 ! Now compute the contributions of the planetery ntations by
1546 ! summing over the series.
1547
1548 call eval_plan_nut( plan_arg, plan_rat, dpsi, deps, 'NO ' )
1549
1550 end subroutine plan_nut
1551 !*********************************************************************************************************************************
1552
1553
1554
1555
1556
1557
1558
1559
1560
1561 !TITLE EVAL_PLAN_NUT
1562
1563 !*********************************************************************************************************************************
1564 !> \brief Compute the planetary nutations by summing over the KS1990 coefficients.
1565 !!
1566 !! \param plan_arg Planetary arguments including pa as given (KS1990) (input; rad)
1567 !! \param plan_rat Planetary argument rates (input; rad/yr)
1568 !! \param dpsi Contribution to nutations in longitude (output; mas)
1569 !! \param deps Contribution to nutations in obliquity (output; mas)
1570 !! \param out 'YES' to write data to stdout (input)
1571
1572 subroutine eval_plan_nut( plan_arg, plan_rat, dpsi, deps, out )
1573 use sufr_kinds, only: double
1574 implicit none
1575
1576 ! Routine to compute the planetary nutations by summing over the
1577 ! KS1990 coefficients. The coefficients and their arguments are
1578 ! saved here in are integers in micro-arc-seconds.
1579
1580 ! NOTE: plan_angles must be called before routine.
1581
1582 ! PARAMETERS:
1583
1584 ! num_plan - Number of contributions to the planetary nutations
1585
1586 integer :: num_plan
1587 parameter( num_plan = 687 )
1588
1589 real(double) :: pi
1590 parameter( pi = 3.1415926535897932d0 )
1591
1592 ! PASSED PARAMETERS:
1593
1594 ! INPUT:
1595 ! plan_arg(14) - 14 planetary arguments including pa as given
1596 ! (KS1990.) (rad)
1597 ! plan_rat(14) - 14 Planetary argument rates (rad/yr)
1598
1599 ! OUTPUT:
1600 ! dpsi, deps - Contributions to nutations in longitude and
1601 ! obliquity (mas).
1602
1603 real(double), intent(in) :: plan_arg(14), plan_rat(14)
1604 real(double), intent(out) :: dpsi, deps
1605
1606 character, intent(in) :: out*(*)
1607
1608 ! LOCAL VARIABLES:
1609
1610
1611 ! i and j - Counters to loop over the coeffients and the argumemts
1612
1613 integer :: i,j
1614
1615 ! arg - Final summed argumemt for the nutations contributions (rads)
1616 ! dargdt - Rate of change of the argument (rads/yr)
1617 ! period - Period of the nutation in days.
1618 ! amp - Total Amplitude of the planetary nutation. (To be used for
1619 ! sorting size)
1620 ! carg, sarg - cosine and sin of arguments.
1621
1622 real(double) :: arg, dargdt, period, amp, carg, sarg
1623
1624
1625 ! ks_plan: Series based on:skre97_rigid.plan
1626 ! IX01-IX69(18,10) - Integer values of the planetary arguments and
1627 ! values (0.1 micro-arc-seconds for values)
1628 integer :: IX01(18,10), IX02(18,10), IX03(18,10), IX04(18,10), IX05(18,10), IX06(18,10)
1629 integer :: IX07(18,10), IX08(18,10), IX09(18,10), IX10(18,10), IX11(18,10), IX12(18,10)
1630 integer :: IX13(18,10), IX14(18,10), IX15(18,10), IX16(18,10), IX17(18,10), IX18(18,10)
1631 integer :: IX19(18,10), IX20(18,10), IX21(18,10), IX22(18,10)
1632 integer :: IX23(18,10), IX24(18,10), IX25(18,10), IX26(18,10), IX27(18,10), IX28(18,10)
1633 integer :: IX29(18,10), IX30(18,10), IX31(18,10), IX32(18,10)
1634 integer :: IX33(18,10), IX34(18,10), IX35(18,10), IX36(18,10), IX37(18,10), IX38(18,10)
1635 integer :: IX39(18,10), IX40(18,10), IX41(18,10), IX42(18,10)
1636 integer :: IX43(18,10), IX44(18,10), IX45(18,10), IX46(18,10), IX47(18,10), IX48(18,10)
1637 integer :: IX49(18,10), IX50(18,10), IX51(18,10), IX52(18,10)
1638 integer :: IX53(18,10), IX54(18,10), IX55(18,10), IX56(18,10), IX57(18,10), IX58(18,10)
1639 integer :: IX59(18,10), IX60(18,10), IX61(18,10), IX62(18,10)
1640 integer :: IX63(18,10), IX64(18,10), IX65(18,10), IX66(18,10), IX67(18,10), IX68(18,10)
1641 integer :: IX69(18, 7)
1642
1643 integer :: Plan_int(18,687)
1644
1645
1646 equivalence(plan_int(1, 1),ix01)
1647 equivalence(plan_int(1, 11),ix02)
1648 equivalence(plan_int(1, 21),ix03)
1649 equivalence(plan_int(1, 31),ix04)
1650 equivalence(plan_int(1, 41),ix05)
1651 equivalence(plan_int(1, 51),ix06)
1652 equivalence(plan_int(1, 61),ix07)
1653 equivalence(plan_int(1, 71),ix08)
1654 equivalence(plan_int(1, 81),ix09)
1655 equivalence(plan_int(1, 91),ix10)
1656 equivalence(plan_int(1,101),ix11)
1657 equivalence(plan_int(1,111),ix12)
1658 equivalence(plan_int(1,121),ix13)
1659 equivalence(plan_int(1,131),ix14)
1660 equivalence(plan_int(1,141),ix15)
1661 equivalence(plan_int(1,151),ix16)
1662 equivalence(plan_int(1,161),ix17)
1663 equivalence(plan_int(1,171),ix18)
1664 equivalence(plan_int(1,181),ix19)
1665 equivalence(plan_int(1,191),ix20)
1666 equivalence(plan_int(1,201),ix21)
1667 equivalence(plan_int(1,211),ix22)
1668 equivalence(plan_int(1,221),ix23)
1669 equivalence(plan_int(1,231),ix24)
1670 equivalence(plan_int(1,241),ix25)
1671 equivalence(plan_int(1,251),ix26)
1672 equivalence(plan_int(1,261),ix27)
1673 equivalence(plan_int(1,271),ix28)
1674 equivalence(plan_int(1,281),ix29)
1675 equivalence(plan_int(1,291),ix30)
1676 equivalence(plan_int(1,301),ix31)
1677 equivalence(plan_int(1,311),ix32)
1678 equivalence(plan_int(1,321),ix33)
1679 equivalence(plan_int(1,331),ix34)
1680 equivalence(plan_int(1,341),ix35)
1681 equivalence(plan_int(1,351),ix36)
1682 equivalence(plan_int(1,361),ix37)
1683 equivalence(plan_int(1,371),ix38)
1684 equivalence(plan_int(1,381),ix39)
1685 equivalence(plan_int(1,391),ix40)
1686 equivalence(plan_int(1,401),ix41)
1687 equivalence(plan_int(1,411),ix42)
1688 equivalence(plan_int(1,421),ix43)
1689 equivalence(plan_int(1,431),ix44)
1690 equivalence(plan_int(1,441),ix45)
1691 equivalence(plan_int(1,451),ix46)
1692 equivalence(plan_int(1,461),ix47)
1693 equivalence(plan_int(1,471),ix48)
1694 equivalence(plan_int(1,481),ix49)
1695 equivalence(plan_int(1,491),ix50)
1696 equivalence(plan_int(1,501),ix51)
1697 equivalence(plan_int(1,511),ix52)
1698 equivalence(plan_int(1,521),ix53)
1699 equivalence(plan_int(1,531),ix54)
1700 equivalence(plan_int(1,541),ix55)
1701 equivalence(plan_int(1,551),ix56)
1702 equivalence(plan_int(1,561),ix57)
1703 equivalence(plan_int(1,571),ix58)
1704 equivalence(plan_int(1,581),ix59)
1705 equivalence(plan_int(1,591),ix60)
1706 equivalence(plan_int(1,601),ix61)
1707 equivalence(plan_int(1,611),ix62)
1708 equivalence(plan_int(1,621),ix63)
1709 equivalence(plan_int(1,631),ix64)
1710 equivalence(plan_int(1,641),ix65)
1711 equivalence(plan_int(1,651),ix66)
1712 equivalence(plan_int(1,661),ix67)
1713 equivalence(plan_int(1,671),ix68)
1714 equivalence(plan_int(1,681),ix69)
1715
1716 data ix01/ 0, 0, 0, 0, 0, 0, 0, 8, -16, 4, 5, 0, 0, 0, 1440, 0, 0, 0, &
1717 0, 0, 0, 0, 0, 0, 0, -8, 16, -4, -5, 0, 0, 2, 56, -117, -42, -40, &
1718 0, 0, 0, 0, 0, 0, 0, 8, -16, 4, 5, 0, 0, 2, 125, -43, 0, -54, &
1719 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -1, 2, 2, 0, 5, 0, 0, &
1720 0, 0, 0, 0, 0, 0, 0, -4, 8, -1, -5, 0, 0, 2, 3, -7, -3, 0, &
1721 0, 0, 0, 0, 0, 0, 0, 4, -8, 3, 0, 0, 0, 1, 3, 0, 0, -2, &
1722 0, 0, 1, -1, 1, 0, 0, 3, -8, 3, 0, 0, 0, 0, -114, 0, 0, 61, &
1723 -1, 0, 0, 0, 0, 0, 10, -3, 0, 0, 0, 0, 0, 0, -219, 89, 0, 0, &
1724 0, 0, 0, 0, 0, 0, 0, 0, 0, -2, 6, -3, 0, 2, -3, 0, 0, 0, &
1725 0, 0, 0, 0, 0, 0, 0, 4, -8, 3, 0, 0, 0, 0, -462, 1604, 0, 0 /
1726
1727 data ix02/ 0, 0, 1, -1, 1, 0, 0, -5, 8, -3, 0, 0, 0, 0, 99, 0, 0, -53, &
1728 0, 0, 0, 0, 0, 0, 0, -4, 8, -3, 0, 0, 0, 1, -3, 0, 0, 2, &
1729 0, 0, 0, 0, 0, 0, 0, 4, -8, 1, 5, 0, 0, 2, 0, 6, 2, 0, &
1730 0, 0, 0, 0, 0, 0, -5, 6, 4, 0, 0, 0, 0, 2, 3, 0, 0, 0, &
1731 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, -5, 0, 0, 2, -12, 0, 0, 0, &
1732 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, -5, 0, 0, 1, 14, -218, 117, 8, &
1733 0, 0, 1, -1, 1, 0, 0, -1, 0, 2, -5, 0, 0, 0, 31, -481, -257, -17, &
1734 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, -5, 0, 0, 0, -491, 128, 0, 0, &
1735 0, 0, 1, -1, 1, 0, 0, -1, 0, -2, 5, 0, 0, 0, -3084, 5123, 2735, 1647, &
1736 0, 0, 0, 0, 0, 0, 0, 0, 0, -2, 5, 0, 0, 1, -1444, 2409, -1286, -771 /
1737
1738 data ix03/ 0, 0, 0, 0, 0, 0, 0, 0, 0, -2, 5, 0, 0, 2, 11, -24, -11, -9, &
1739 2, 0, -1, -1, 0, 0, 0, 3, -7, 0, 0, 0, 0, 0, 26, -9, 0, 0, &
1740 1, 0, 0, -2, 0, 0, 19, -21, 3, 0, 0, 0, 0, 0, 103, -60, 0, 0, &
1741 0, 0, 1, -1, 1, 0, 2, -4, 0, -3, 0, 0, 0, 0, 0, -13, -7, 0, &
1742 1, 0, 0, -1, 1, 0, 0, -1, 0, 2, 0, 0, 0, 0, -26, -29, -16, 14, &
1743 0, 0, 1, -1, 1, 0, 0, -1, 0, -4, 10, 0, 0, 0, 9, -27, -14, -5, &
1744 -2, 0, 0, 2, 1, 0, 0, 2, 0, 0, -5, 0, 0, 0, 12, 0, 0, -6, &
1745 0, 0, 0, 0, 0, 0, 3, -7, 4, 0, 0, 0, 0, 0, -7, 0, 0, 0, &
1746 0, 0, -1, 1, 0, 0, 0, 1, 0, 1, -1, 0, 0, 0, 0, 24, 0, 0, &
1747 -2, 0, 0, 2, 1, 0, 0, 2, 0, -2, 0, 0, 0, 0, 284, 0, 0, -151 /
1748
1749 data ix04/ -1, 0, 0, 0, 0, 0, 18, -16, 0, 0, 0, 0, 0, 0, 226, 101, 0, 0, &
1750 -2, 0, 1, 1, 2, 0, 0, 1, 0, -2, 0, 0, 0, 0, 0, -8, -2, 0, &
1751 -1, 0, 1, -1, 1, 0, 18, -17, 0, 0, 0, 0, 0, 0, 0, -6, -3, 0, &
1752 -1, 0, 0, 1, 1, 0, 0, 2, -2, 0, 0, 0, 0, 0, 5, 0, 0, -3, &
1753 0, 0, 0, 0, 0, 0, -8, 13, 0, 0, 0, 0, 0, 2, -41, 175, 76, 17, &
1754 0, 0, 2, -2, 2, 0, -8, 11, 0, 0, 0, 0, 0, 0, 0, 15, 6, 0, &
1755 0, 0, 0, 0, 0, 0, -8, 13, 0, 0, 0, 0, 0, 1, 425, 212, -133, 269, &
1756 0, 0, 1, -1, 1, 0, -8, 12, 0, 0, 0, 0, 0, 0, 1200, 598, 319, -641, &
1757 0, 0, 0, 0, 0, 0, 8, -13, 0, 0, 0, 0, 0, 0, 235, 334, 0, 0, &
1758 0, 0, 1, -1, 1, 0, 8, -14, 0, 0, 0, 0, 0, 0, 11, -12, -7, -6 /
1759
1760 data ix05/ 0, 0, 0, 0, 0, 0, 8, -13, 0, 0, 0, 0, 0, 1, 5, -6, 3, 3, &
1761 -2, 0, 0, 2, 1, 0, 0, 2, 0, -4, 5, 0, 0, 0, -5, 0, 0, 3, &
1762 -2, 0, 0, 2, 2, 0, 3, -3, 0, 0, 0, 0, 0, 0, 6, 0, 0, -3, &
1763 -2, 0, 0, 2, 0, 0, 0, 2, 0, -3, 1, 0, 0, 0, 15, 0, 0, 0, &
1764 0, 0, 0, 0, 1, 0, 3, -5, 0, 2, 0, 0, 0, 0, 13, 0, 0, -7, &
1765 -2, 0, 0, 2, 0, 0, 0, 2, 0, -4, 3, 0, 0, 0, -6, -9, 0, 0, &
1766 0, 0, -1, 1, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 266, -78, 0, 0, &
1767 0, 0, 0, 0, 1, 0, 0, -1, 2, 0, 0, 0, 0, 0, -460, -435, -232, 246, &
1768 0, 0, 1, -1, 2, 0, 0, -2, 2, 0, 0, 0, 0, 0, 0, 15, 7, 0, &
1769 -1, 0, 1, 0, 1, 0, 3, -5, 0, 0, 0, 0, 0, 0, -3, 0, 0, 2 /
1770
1771 data ix06/ -1, 0, 0, 1, 0, 0, 3, -4, 0, 0, 0, 0, 0, 0, 0, 131, 0, 0, &
1772 -2, 0, 0, 2, 0, 0, 0, 2, 0, -2, -2, 0, 0, 0, 4, 0, 0, 0, &
1773 -2, 0, 2, 0, 2, 0, 0, -5, 9, 0, 0, 0, 0, 0, 0, 3, 0, 0, &
1774 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, 0, -1, 0, 0, 0, 4, 2, 0, &
1775 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 3, 0, 0, &
1776 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, 0, 0, 2, 0, -17, -19, -10, 9, &
1777 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 1, -9, -11, 6, -5, &
1778 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 2, -6, 0, 0, 3, &
1779 -1, 0, 0, 1, 0, 0, 0, 3, -4, 0, 0, 0, 0, 0, -16, 8, 0, 0, &
1780 0, 0, -1, 1, 0, 0, 0, 1, 0, 0, 2, 0, 0, 0, 0, 3, 0, 0 /
1781
1782 data ix07/ 0, 0, 1, -1, 2, 0, 0, -1, 0, 0, 2, 0, 0, 0, 11, 24, 11, -5, &
1783 0, 0, 0, 0, 1, 0, 0, -9, 17, 0, 0, 0, 0, 0, -3, -4, -2, 1, &
1784 0, 0, 0, 0, 2, 0, -3, 5, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, &
1785 0, 0, 1, -1, 1, 0, 0, -1, 0, -1, 2, 0, 0, 0, 0, -8, -4, 0, &
1786 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, -2, 0, 0, 0, 0, 3, 0, 0, &
1787 1, 0, 0, -2, 0, 0, 17, -16, 0, -2, 0, 0, 0, 0, 0, 5, 0, 0, &
1788 0, 0, 1, -1, 1, 0, 0, -1, 0, 1, -3, 0, 0, 0, 0, 3, 2, 0, &
1789 -2, 0, 0, 2, 1, 0, 0, 5, -6, 0, 0, 0, 0, 0, -6, 4, 2, 3, &
1790 0, 0, -2, 2, 0, 0, 0, 9, -13, 0, 0, 0, 0, 0, -3, -5, 0, 0, &
1791 0, 0, 1, -1, 2, 0, 0, -1, 0, 0, 1, 0, 0, 0, -5, 0, 0, 2 /
1792
1793 data ix08/ 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 4, 24, 13, -2, &
1794 0, 0, -1, 1, 0, 0, 0, 1, 0, 0, 1, 0, 0, 0, -42, 20, 0, 0, &
1795 0, 0, -2, 2, 0, 0, 5, -6, 0, 0, 0, 0, 0, 0, -10, 233, 0, 0, &
1796 0, 0, -1, 1, 1, 0, 5, -7, 0, 0, 0, 0, 0, 0, -3, 0, 0, 1, &
1797 -2, 0, 0, 2, 0, 0, 6, -8, 0, 0, 0, 0, 0, 0, 78, -18, 0, 0, &
1798 2, 0, 1, -3, 1, 0, -6, 7, 0, 0, 0, 0, 0, 0, 0, 3, 1, 0, &
1799 0, 0, 0, 0, 2, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, -3, -1, 0, &
1800 0, 0, -1, 1, 1, 0, 0, 1, 0, 1, 0, 0, 0, 0, 0, -4, -2, 1, &
1801 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, 0, 2, 0, 0, 0, -8, -4, -1, &
1802 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 1, 0, -5, 3, 0 /
1803
1804 data ix09/ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 2, -7, 0, 0, 3, &
1805 0, 0, 0, 0, 0, 0, 0, -8, 15, 0, 0, 0, 0, 2, -14, 8, 3, 6, &
1806 0, 0, 0, 0, 0, 0, 0, -8, 15, 0, 0, 0, 0, 1, 0, 8, -4, 0, &
1807 0, 0, 1, -1, 1, 0, 0, -9, 15, 0, 0, 0, 0, 0, 0, 19, 10, 0, &
1808 0, 0, 0, 0, 0, 0, 0, 8, -15, 0, 0, 0, 0, 0, 45, -22, 0, 0, &
1809 1, 0, -1, -1, 0, 0, 0, 8, -15, 0, 0, 0, 0, 0, -3, 0, 0, 0, &
1810 2, 0, 0, -2, 0, 0, 2, -5, 0, 0, 0, 0, 0, 0, 0, -3, 0, 0, &
1811 -2, 0, 0, 2, 0, 0, 0, 2, 0, -5, 5, 0, 0, 0, 0, 3, 0, 0, &
1812 2, 0, 0, -2, 1, 0, 0, -6, 8, 0, 0, 0, 0, 0, 3, 5, 3, -2, &
1813 2, 0, 0, -2, 1, 0, 0, -2, 0, 3, 0, 0, 0, 0, 89, -16, -9, -48 /
1814
1815 data ix10/ -2, 0, 1, 1, 0, 0, 0, 1, 0, -3, 0, 0, 0, 0, 0, 3, 0, 0, &
1816 -2, 0, 1, 1, 1, 0, 0, 1, 0, -3, 0, 0, 0, 0, -3, 7, 4, 2, &
1817 -2, 0, 0, 2, 0, 0, 0, 2, 0, -3, 0, 0, 0, 0, -349, -62, 0, 0, &
1818 -2, 0, 0, 2, 0, 0, 0, 6, -8, 0, 0, 0, 0, 0, -15, 22, 0, 0, &
1819 -2, 0, 0, 2, 0, 0, 0, 2, 0, -1, -5, 0, 0, 0, -3, 0, 0, 0, &
1820 -1, 0, 0, 1, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, -53, 0, 0, 0, &
1821 -1, 0, 1, 1, 1, 0, -20, 20, 0, 0, 0, 0, 0, 0, 5, 0, 0, -3, &
1822 1, 0, 0, -2, 0, 0, 20, -21, 0, 0, 0, 0, 0, 0, 0, -8, 0, 0, &
1823 0, 0, 0, 0, 1, 0, 0, 8, -15, 0, 0, 0, 0, 0, 15, -7, -4, -8, &
1824 0, 0, 2, -2, 1, 0, 0, -10, 15, 0, 0, 0, 0, 0, -3, 0, 0, 1 /
1825
1826 data ix11/ 0, 0, -1, 1, 0, 0, 0, 1, 0, 1, 0, 0, 0, 0, -21, -78, 0, 0, &
1827 0, 0, 0, 0, 1, 0, 0, 0, 0, 1, 0, 0, 0, 0, 20, -70, -37, -11, &
1828 0, 0, 1, -1, 2, 0, 0, -1, 0, 1, 0, 0, 0, 0, 0, 6, 3, 0, &
1829 0, 0, 1, -1, 1, 0, 0, -1, 0, -2, 4, 0, 0, 0, 5, 3, 2, -2, &
1830 2, 0, 0, -2, 1, 0, -6, 8, 0, 0, 0, 0, 0, 0, -17, -4, -2, 9, &
1831 0, 0, -2, 2, 1, 0, 5, -6, 0, 0, 0, 0, 0, 0, 0, 6, 3, 0, &
1832 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -1, 0, 0, 1, 32, 15, -8, 17, &
1833 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, -1, 0, 0, 0, 174, 84, 45, -93, &
1834 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 11, 56, 0, 0, &
1835 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, 1, 0, 0, 0, -66, -12, -6, 35 /
1836
1837 data ix12/ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 47, 8, 4, -25, &
1838 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 2, 0, 8, 4, 0, &
1839 0, 0, 2, -2, 1, 0, 0, -9, 13, 0, 0, 0, 0, 0, 10, -22, -12, -5, &
1840 0, 0, 0, 0, 1, 0, 0, 7, -13, 0, 0, 0, 0, 0, -3, 0, 0, 2, &
1841 -2, 0, 0, 2, 0, 0, 0, 5, -6, 0, 0, 0, 0, 0, -24, 12, 0, 0, &
1842 0, 0, 0, 0, 0, 0, 0, 9, -17, 0, 0, 0, 0, 0, 5, -6, 0, 0, &
1843 0, 0, 0, 0, 0, 0, 0, -9, 17, 0, 0, 0, 0, 2, 3, 0, 0, -2, &
1844 1, 0, 0, -1, 1, 0, 0, -3, 4, 0, 0, 0, 0, 0, 4, 3, 1, -2, &
1845 1, 0, 0, -1, 1, 0, -3, 4, 0, 0, 0, 0, 0, 0, 0, 29, 15, 0, &
1846 0, 0, 0, 0, 2, 0, 0, -1, 2, 0, 0, 0, 0, 0, -5, -4, -2, 2 /
1847
1848 data ix13/ 0, 0, -1, 1, 1, 0, 0, 0, 2, 0, 0, 0, 0, 0, 8, -3, -1, -5, &
1849 0, 0, -2, 2, 0, 1, 0, -2, 0, 0, 0, 0, 0, 0, 0, -3, 0, 0, &
1850 0, 0, 0, 0, 0, 0, 3, -5, 0, 2, 0, 0, 0, 0, 10, 0, 0, 0, &
1851 -2, 0, 0, 2, 1, 0, 0, 2, 0, -3, 1, 0, 0, 0, 3, 0, 0, -2, &
1852 -2, 0, 0, 2, 1, 0, 3, -3, 0, 0, 0, 0, 0, 0, -5, 0, 0, 3, &
1853 0, 0, 0, 0, 1, 0, 8, -13, 0, 0, 0, 0, 0, 0, 46, 66, 35, -25, &
1854 0, 0, -1, 1, 0, 0, 8, -12, 0, 0, 0, 0, 0, 0, -14, 7, 0, 0, &
1855 0, 0, 2, -2, 1, 0, -8, 11, 0, 0, 0, 0, 0, 0, 0, 3, 2, 0, &
1856 -1, 0, 0, 1, 0, 0, 0, 2, -2, 0, 0, 0, 0, 0, -5, 0, 0, 0, &
1857 -1, 0, 0, 0, 1, 0, 18, -16, 0, 0, 0, 0, 0, 0, -68, -34, -18, 36 /
1858
1859 data ix14/ 0, 0, 1, -1, 1, 0, 0, -1, 0, -1, 1, 0, 0, 0, 0, 14, 7, 0, &
1860 0, 0, 0, 0, 1, 0, 3, -7, 4, 0, 0, 0, 0, 0, 10, -6, -3, -5, &
1861 -2, 0, 1, 1, 1, 0, 0, -3, 7, 0, 0, 0, 0, 0, -5, -4, -2, 3, &
1862 0, 0, 1, -1, 2, 0, 0, -1, 0, -2, 5, 0, 0, 0, -3, 5, 2, 1, &
1863 0, 0, 0, 0, 1, 0, 0, 0, 0, -2, 5, 0, 0, 0, 76, 17, 9, -41, &
1864 0, 0, 0, 0, 1, 0, 0, -4, 8, -3, 0, 0, 0, 0, 84, 298, 159, -45, &
1865 1, 0, 0, 0, 1, 0, -10, 3, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, &
1866 0, 0, 2, -2, 1, 0, 0, -2, 0, 0, 0, 0, 0, 0, -3, 0, 0, 2, &
1867 -1, 0, 0, 0, 1, 0, 10, -3, 0, 0, 0, 0, 0, 0, -3, 0, 0, 1, &
1868 0, 0, 0, 0, 1, 0, 0, 4, -8, 3, 0, 0, 0, 0, -82, 292, 156, 44 /
1869
1870 data ix15/ 0, 0, 0, 0, 1, 0, 0, 0, 0, 2, -5, 0, 0, 0, -73, 17, 9, 39, &
1871 0, 0, -1, 1, 0, 0, 0, 1, 0, 2, -5, 0, 0, 0, -9, -16, 0, 0, &
1872 2, 0, -1, -1, 1, 0, 0, 3, -7, 0, 0, 0, 0, 0, 3, 0, -1, -2, &
1873 -2, 0, 0, 2, 0, 0, 0, 2, 0, 0, -5, 0, 0, 0, -3, 0, 0, 0, &
1874 0, 0, 0, 0, 1, 0, -3, 7, -4, 0, 0, 0, 0, 0, -9, -5, -3, 5, &
1875 -2, 0, 0, 2, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, -439, 0, 0, 0, &
1876 1, 0, 0, 0, 1, 0, -18, 16, 0, 0, 0, 0, 0, 0, 57, -28, -15, -30, &
1877 -2, 0, 1, 1, 1, 0, 0, 1, 0, -2, 0, 0, 0, 0, 0, -6, -3, 0, &
1878 0, 0, 1, -1, 2, 0, -8, 12, 0, 0, 0, 0, 0, 0, -4, 0, 0, 2, &
1879 0, 0, 0, 0, 1, 0, -8, 13, 0, 0, 0, 0, 0, 0, -40, 57, 30, 21 /
1880
1881 data ix16/ 0, 0, 0, 0, 0, 0, 0, 1, -2, 0, 0, 0, 0, 1, 23, 7, 3, -13, &
1882 0, 0, 1, -1, 1, 0, 0, 0, -2, 0, 0, 0, 0, 0, 273, 80, 43, -146, &
1883 0, 0, 0, 0, 0, 0, 0, 1, -2, 0, 0, 0, 0, 0, -449, 430, 0, 0, &
1884 0, 0, 1, -1, 1, 0, 0, -2, 2, 0, 0, 0, 0, 0, -8, -47, -25, 4, &
1885 0, 0, 0, 0, 0, 0, 0, -1, 2, 0, 0, 0, 0, 1, 6, 47, 25, -3, &
1886 -1, 0, 0, 1, 1, 0, 3, -4, 0, 0, 0, 0, 0, 0, 0, 23, 13, 0, &
1887 -1, 0, 0, 1, 1, 0, 0, 3, -4, 0, 0, 0, 0, 0, -3, 0, 0, 2, &
1888 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, -2, 0, 0, 0, 3, -4, -2, -2, &
1889 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, 2, 0, 0, 0, -48, -110, -59, 26, &
1890 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 1, 51, 114, 61, -27 /
1891
1892 data ix17/ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 2, -133, 0, 0, 57, &
1893 0, 0, 1, -1, 0, 0, 3, -6, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, &
1894 0, 0, 0, 0, 1, 0, -3, 5, 0, 0, 0, 0, 0, 0, -21, -6, -3, 11, &
1895 0, 0, 1, -1, 2, 0, -3, 4, 0, 0, 0, 0, 0, 0, 0, -3, -1, 0, &
1896 0, 0, 0, 0, 1, 0, 0, -2, 4, 0, 0, 0, 0, 0, -11, -21, -11, 6, &
1897 0, 0, 2, -2, 1, 0, -5, 6, 0, 0, 0, 0, 0, 0, -18, -436, -233, 9, &
1898 0, 0, -1, 1, 0, 0, 5, -7, 0, 0, 0, 0, 0, 0, 35, -7, 0, 0, &
1899 0, 0, 0, 0, 1, 0, 5, -8, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0, &
1900 -2, 0, 0, 2, 1, 0, 6, -8, 0, 0, 0, 0, 0, 0, 11, -3, -1, -6, &
1901 0, 0, 0, 0, 1, 0, 0, -8, 15, 0, 0, 0, 0, 0, -5, -3, -1, 3 /
1902
1903 data ix18/ -2, 0, 0, 2, 1, 0, 0, 2, 0, -3, 0, 0, 0, 0, -53, -9, -5, 28, &
1904 -2, 0, 0, 2, 1, 0, 0, 6, -8, 0, 0, 0, 0, 0, 0, 3, 2, 1, &
1905 1, 0, 0, -1, 1, 0, 0, -1, 0, 1, 0, 0, 0, 0, 4, 0, 0, -2, &
1906 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, -5, 0, 0, 0, 0, -4, 0, 0, &
1907 0, 0, 1, -1, 1, 0, 0, -1, 0, -1, 0, 0, 0, 0, -50, 194, 103, 27, &
1908 0, 0, 0, 0, 0, 0, 0, 0, 0, -1, 0, 0, 0, 1, -13, 52, 28, 7, &
1909 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, -91, 248, 0, 0, &
1910 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 1, 6, 49, 26, -3, &
1911 0, 0, 1, -1, 1, 0, 0, -1, 0, 1, 0, 0, 0, 0, -6, -47, -25, 3, &
1912 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 5, 3, 0 /
1913
1914 data ix19/ 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 2, 52, 23, 10, -23, &
1915 0, 0, 1, -1, 2, 0, 0, -1, 0, 0, -1, 0, 0, 0, -3, 0, 0, 1, &
1916 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, -1, 0, 0, 0, 0, 5, 3, 0, &
1917 0, 0, -1, 1, 0, 0, 0, 1, 0, 0, -1, 0, 0, 0, -4, 0, 0, 0, &
1918 0, 0, 0, 0, 0, 0, 0, -7, 13, 0, 0, 0, 0, 2, -4, 8, 3, 2, &
1919 0, 0, 0, 0, 0, 0, 0, 7, -13, 0, 0, 0, 0, 0, 10, 0, 0, 0, &
1920 2, 0, 0, -2, 1, 0, 0, -5, 6, 0, 0, 0, 0, 0, 3, 0, 0, -2, &
1921 0, 0, 2, -2, 1, 0, 0, -8, 11, 0, 0, 0, 0, 0, 0, 8, 4, 0, &
1922 0, 0, 2, -2, 1, -1, 0, 2, 0, 0, 0, 0, 0, 0, 0, 8, 4, 1, &
1923 -2, 0, 0, 2, 0, 0, 0, 4, -4, 0, 0, 0, 0, 0, -4, 0, 0, 0 /
1924
1925 data ix20/ 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, -2, 0, 0, 0, -4, 0, 0, 0, &
1926 0, 0, 1, -1, 1, 0, 0, -1, 0, 0, 3, 0, 0, 0, -8, 4, 2, 4, &
1927 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 1, 8, -4, -2, -4, &
1928 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 2, 0, 15, 7, 0, &
1929 -2, 0, 0, 2, 0, 0, 3, -3, 0, 0, 0, 0, 0, 0, -138, 0, 0, 0, &
1930 0, 0, 0, 0, 2, 0, 0, -4, 8, -3, 0, 0, 0, 0, 0, -7, -3, 0, &
1931 0, 0, 0, 0, 2, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, -7, -3, 0, &
1932 2, 0, 0, -2, 1, 0, 0, -2, 0, 2, 0, 0, 0, 0, 54, 0, 0, -29, &
1933 0, 0, 1, -1, 2, 0, 0, -1, 0, 2, 0, 0, 0, 0, 0, 10, 4, 0, &
1934 0, 0, 1, -1, 2, 0, 0, 0, -2, 0, 0, 0, 0, 0, -7, 0, 0, 3 /
1935
1936 data ix21/ 0, 0, 0, 0, 1, 0, 0, 1, -2, 0, 0, 0, 0, 0, -37, 35, 19, 20, &
1937 0, 0, -1, 1, 0, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, 4, 0, 0, &
1938 0, 0, -1, 1, 0, 0, 0, 1, 0, 0, -2, 0, 0, 0, -4, 9, 0, 0, &
1939 0, 0, 2, -2, 1, 0, 0, -2, 0, 0, 2, 0, 0, 0, 8, 0, 0, -4, &
1940 0, 0, 1, -1, 1, 0, 3, -6, 0, 0, 0, 0, 0, 0, -9, -14, -8, 5, &
1941 0, 0, 0, 0, 0, 0, 3, -5, 0, 0, 0, 0, 0, 1, -3, -9, -5, 3, &
1942 0, 0, 0, 0, 0, 0, 3, -5, 0, 0, 0, 0, 0, 0, -145, 47, 0, 0, &
1943 0, 0, 1, -1, 1, 0, -3, 4, 0, 0, 0, 0, 0, 0, -10, 40, 21, 5, &
1944 0, 0, 0, 0, 0, 0, -3, 5, 0, 0, 0, 0, 0, 1, 11, -49, -26, -7, &
1945 0, 0, 0, 0, 0, 0, -3, 5, 0, 0, 0, 0, 0, 2, -2150, 0, 0, 932 /
1946
1947 data ix22/ 0, 0, 2, -2, 2, 0, -3, 3, 0, 0, 0, 0, 0, 0, -12, 0, 0, 5, &
1948 0, 0, 0, 0, 0, 0, -3, 5, 0, 0, 0, 0, 0, 2, 85, 0, 0, -37, &
1949 0, 0, 0, 0, 0, 0, 0, 2, -4, 0, 0, 0, 0, 1, 4, 0, 0, -2, &
1950 0, 0, 1, -1, 1, 0, 0, 1, -4, 0, 0, 0, 0, 0, 3, 0, 0, -2, &
1951 0, 0, 0, 0, 0, 0, 0, 2, -4, 0, 0, 0, 0, 0, -86, 153, 0, 0, &
1952 0, 0, 0, 0, 0, 0, 0, -2, 4, 0, 0, 0, 0, 1, -6, 9, 5, 3, &
1953 0, 0, 1, -1, 1, 0, 0, -3, 4, 0, 0, 0, 0, 0, 9, -13, -7, -5, &
1954 0, 0, 0, 0, 0, 0, 0, -2, 4, 0, 0, 0, 0, 1, -8, 12, 6, 4, &
1955 0, 0, 0, 0, 0, 0, 0, -2, 4, 0, 0, 0, 0, 2, -51, 0, 0, 22, &
1956 0, 0, 0, 0, 0, 0, -5, 8, 0, 0, 0, 0, 0, 2, -11, -268, -116, 5 /
1957
1958 data ix23/ 0, 0, 2, -2, 2, 0, -5, 6, 0, 0, 0, 0, 0, 0, 0, 12, 5, 0, &
1959 0, 0, 0, 0, 0, 0, -5, 8, 0, 0, 0, 0, 0, 2, 0, 7, 3, 0, &
1960 0, 0, 0, 0, 0, 0, -5, 8, 0, 0, 0, 0, 0, 1, 31, 6, 3, -17, &
1961 0, 0, 1, -1, 1, 0, -5, 7, 0, 0, 0, 0, 0, 0, 140, 27, 14, -75, &
1962 0, 0, 0, 0, 0, 0, -5, 8, 0, 0, 0, 0, 0, 1, 57, 11, 6, -30, &
1963 0, 0, 0, 0, 0, 0, 5, -8, 0, 0, 0, 0, 0, 0, -14, -39, 0, 0, &
1964 0, 0, 1, -1, 2, 0, 0, -1, 0, -1, 0, 0, 0, 0, 0, -6, -2, 0, &
1965 0, 0, 0, 0, 1, 0, 0, 0, 0, -1, 0, 0, 0, 0, 4, 15, 8, -2, &
1966 0, 0, -1, 1, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, 0, 4, 0, 0, &
1967 0, 0, 2, -2, 1, 0, 0, -2, 0, 1, 0, 0, 0, 0, -3, 0, 0, 1 /
1968
1969 data ix24/ 0, 0, 0, 0, 0, 0, 0, -6, 11, 0, 0, 0, 0, 2, 0, 11, 5, 0, &
1970 0, 0, 0, 0, 0, 0, 0, 6, -11, 0, 0, 0, 0, 0, 9, 6, 0, 0, &
1971 0, 0, 0, 0, 0, -1, 0, 4, 0, 0, 0, 0, 0, 2, -4, 10, 4, 2, &
1972 0, 0, 0, 0, 0, 1, 0, -4, 0, 0, 0, 0, 0, 0, 5, 3, 0, 0, &
1973 2, 0, 0, -2, 1, 0, -3, 3, 0, 0, 0, 0, 0, 0, 16, 0, 0, -9, &
1974 -2, 0, 0, 2, 0, 0, 0, 2, 0, 0, -2, 0, 0, 0, -3, 0, 0, 0, &
1975 0, 0, 2, -2, 1, 0, 0, -7, 9, 0, 0, 0, 0, 0, 0, 3, 2, -1, &
1976 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, -5, 0, 0, 2, 7, 0, 0, -3, &
1977 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, -25, 22, 0, 0, &
1978 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 1, 42, 223, 119, -22 /
1979
1980 data ix25/ 0, 0, 1, -1, 1, 0, 0, -1, 0, 2, 0, 0, 0, 0, -27, -143, -77, 14, &
1981 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 1, 9, 49, 26, -5, &
1982 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 2, -1166, 0, 0, 505, &
1983 0, 0, 2, -2, 2, 0, 0, -2, 0, 2, 0, 0, 0, 0, -5, 0, 0, 2, &
1984 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 2, -6, 0, 0, 3, &
1985 0, 0, 0, 0, 1, 0, 3, -5, 0, 0, 0, 0, 0, 0, -8, 0, 1, 4, &
1986 0, 0, -1, 1, 0, 0, 3, -4, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, &
1987 0, 0, 2, -2, 1, 0, -3, 3, 0, 0, 0, 0, 0, 0, 117, 0, 0, -63, &
1988 0, 0, 0, 0, 1, 0, 0, 2, -4, 0, 0, 0, 0, 0, -4, 8, 4, 2, &
1989 0, 0, 2, -2, 1, 0, 0, -4, 4, 0, 0, 0, 0, 0, 3, 0, 0, -2 /
1990
1991 data ix26/ 0, 0, 1, -1, 2, 0, -5, 7, 0, 0, 0, 0, 0, 0, -5, 0, 0, 2, &
1992 0, 0, 0, 0, 0, 0, 0, 3, -6, 0, 0, 0, 0, 0, 0, 31, 0, 0, &
1993 0, 0, 0, 0, 0, 0, 0, -3, 6, 0, 0, 0, 0, 1, -5, 0, 1, 3, &
1994 0, 0, 1, -1, 1, 0, 0, -4, 6, 0, 0, 0, 0, 0, 4, 0, 0, -2, &
1995 0, 0, 0, 0, 0, 0, 0, -3, 6, 0, 0, 0, 0, 1, -4, 0, 0, 2, &
1996 0, 0, 0, 0, 0, 0, 0, -3, 6, 0, 0, 0, 0, 2, -24, -13, -6, 10, &
1997 0, 0, -1, 1, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, &
1998 0, 0, 0, 0, 1, 0, 2, -3, 0, 0, 0, 0, 0, 0, 0, -32, -17, 0, &
1999 0, 0, 0, 0, 0, 0, 0, -5, 9, 0, 0, 0, 0, 2, 8, 12, 5, -3, &
2000 0, 0, 0, 0, 0, 0, 0, -5, 9, 0, 0, 0, 0, 1, 3, 0, 0, -1 /
2001
2002 data ix27/ 0, 0, 0, 0, 0, 0, 0, 5, -9, 0, 0, 0, 0, 0, 7, 13, 0, 0, &
2003 0, 0, -1, 1, 0, 0, 0, 1, 0, -2, 0, 0, 0, 0, -3, 16, 0, 0, &
2004 0, 0, 2, -2, 1, 0, 0, -2, 0, 2, 0, 0, 0, 0, 50, 0, 0, -27, &
2005 -2, 0, 1, 1, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, -5, -3, 0, &
2006 0, 0, -2, 2, 0, 0, 3, -3, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, &
2007 0, 0, 0, 0, 0, 0, -6, 10, 0, 0, 0, 0, 0, 1, 0, 5, 3, 1, &
2008 0, 0, 0, 0, 0, 0, -6, 10, 0, 0, 0, 0, 0, 2, 24, 5, 2, -11, &
2009 0, 0, 0, 0, 0, 0, -2, 3, 0, 0, 0, 0, 0, 2, 5, -11, -5, -2, &
2010 0, 0, 0, 0, 0, 0, -2, 3, 0, 0, 0, 0, 0, 1, 30, -3, -2, -16, &
2011 0, 0, 1, -1, 1, 0, -2, 2, 0, 0, 0, 0, 0, 0, 18, 0, 0, -9 /
2012
2013 data ix28/ 0, 0, 0, 0, 0, 0, 2, -3, 0, 0, 0, 0, 0, 0, 8, 614, 0, 0, &
2014 0, 0, 0, 0, 0, 0, 2, -3, 0, 0, 0, 0, 0, 1, 3, -3, -1, -2, &
2015 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 1, 6, 17, 9, -3, &
2016 0, 0, 1, -1, 1, 0, 0, -1, 0, 3, 0, 0, 0, 0, -3, -9, -5, 2, &
2017 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 1, 0, 6, 3, -1, &
2018 0, 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 2, -127, 21, 9, 55, &
2019 0, 0, 0, 0, 0, 0, 0, 4, -8, 0, 0, 0, 0, 0, 3, 5, 0, 0, &
2020 0, 0, 0, 0, 0, 0, 0, -4, 8, 0, 0, 0, 0, 2, -6, -10, -4, 3, &
2021 0, 0, -2, 2, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, 5, 0, 0, 0, &
2022 0, 0, 0, 0, 0, 0, 0, -4, 7, 0, 0, 0, 0, 2, 16, 9, 4, -7 /
2023
2024 data ix29/ 0, 0, 0, 0, 0, 0, 0, -4, 7, 0, 0, 0, 0, 1, 3, 0, 0, -2, &
2025 0, 0, 0, 0, 0, 0, 0, 4, -7, 0, 0, 0, 0, 0, 0, 22, 0, 0, &
2026 0, 0, 0, 0, 1, 0, -2, 3, 0, 0, 0, 0, 0, 0, 0, 19, 10, 0, &
2027 0, 0, 2, -2, 1, 0, 0, -2, 0, 3, 0, 0, 0, 0, 7, 0, 0, -4, &
2028 0, 0, 0, 0, 0, 0, 0, -5, 10, 0, 0, 0, 0, 2, 0, -5, -2, 0, &
2029 0, 0, 0, 0, 1, 0, -1, 2, 0, 0, 0, 0, 0, 0, 0, 3, 1, 0, &
2030 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 2, -9, 3, 1, 4, &
2031 0, 0, 0, 0, 0, 0, 0, -3, 5, 0, 0, 0, 0, 2, 17, 0, 0, -7, &
2032 0, 0, 0, 0, 0, 0, 0, -3, 5, 0, 0, 0, 0, 1, 0, -3, -2, -1, &
2033 0, 0, 0, 0, 0, 0, 0, 3, -5, 0, 0, 0, 0, 0, -20, 34, 0, 0 /
2034
2035 data ix30/ 0, 0, 0, 0, 0, 0, 1, -2, 0, 0, 0, 0, 0, 1, -10, 0, 1, 5, &
2036 0, 0, 1, -1, 1, 0, 1, -3, 0, 0, 0, 0, 0, 0, -4, 0, 0, 2, &
2037 0, 0, 0, 0, 0, 0, 1, -2, 0, 0, 0, 0, 0, 0, 22, -87, 0, 0, &
2038 0, 0, 0, 0, 0, 0, -1, 2, 0, 0, 0, 0, 0, 1, -4, 0, 0, 2, &
2039 0, 0, 0, 0, 0, 0, -1, 2, 0, 0, 0, 0, 0, 2, -3, -6, -2, 1, &
2040 0, 0, 0, 0, 0, 0, -7, 11, 0, 0, 0, 0, 0, 2, -16, -3, -1, 7, &
2041 0, 0, 0, 0, 0, 0, -7, 11, 0, 0, 0, 0, 0, 1, 0, -3, -2, 0, &
2042 0, 0, -2, 2, 0, 0, 4, -4, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, &
2043 0, 0, 0, 0, 0, 0, 0, 2, -3, 0, 0, 0, 0, 0, -68, 39, 0, 0, &
2044 0, 0, 2, -2, 1, 0, -4, 4, 0, 0, 0, 0, 0, 0, 27, 0, 0, -14 /
2045
2046 data ix31/ 0, 0, -1, 1, 0, 0, 4, -5, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, &
2047 0, 0, 0, 0, 0, 0, 0, 1, -1, 0, 0, 0, 0, 0, -25, 0, 0, 0, &
2048 0, 0, 0, 0, 0, 0, -4, 7, 0, 0, 0, 0, 0, 1, -12, -3, -2, 6, &
2049 0, 0, 1, -1, 1, 0, -4, 6, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, &
2050 0, 0, 0, 0, 0, 0, -4, 7, 0, 0, 0, 0, 0, 2, 3, 66, 29, -1, &
2051 0, 0, 0, 0, 0, 0, -4, 6, 0, 0, 0, 0, 0, 2, 490, 0, 0, -213, &
2052 0, 0, 0, 0, 0, 0, -4, 6, 0, 0, 0, 0, 0, 1, -22, 93, 49, 12, &
2053 0, 0, 1, -1, 1, 0, -4, 5, 0, 0, 0, 0, 0, 0, -7, 28, 15, 4, &
2054 0, 0, 0, 0, 0, 0, -4, 6, 0, 0, 0, 0, 0, 1, -3, 13, 7, 2, &
2055 0, 0, 0, 0, 0, 0, 4, -6, 0, 0, 0, 0, 0, 0, -46, 14, 0, 0 /
2056
2057 data ix32/ -2, 0, 0, 2, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, -5, 0, 0, 0, &
2058 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 2, 1, 0, 0, &
2059 0, 0, -1, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, -3, 0, 0, &
2060 0, 0, 0, 0, 1, 0, 1, -1, 0, 0, 0, 0, 0, 0, -28, 0, 0, 15, &
2061 0, 0, 0, 0, 0, 0, 0, -1, 0, 5, 0, 0, 0, 2, 5, 0, 0, -2, &
2062 0, 0, 0, 0, 0, 0, 0, 1, -3, 0, 0, 0, 0, 0, 0, 3, 0, 0, &
2063 0, 0, 0, 0, 0, 0, 0, -1, 3, 0, 0, 0, 0, 2, -11, 0, 0, 5, &
2064 0, 0, 0, 0, 0, 0, 0, -7, 12, 0, 0, 0, 0, 2, 0, 3, 1, 0, &
2065 0, 0, 0, 0, 0, 0, -1, 1, 0, 0, 0, 0, 0, 2, -3, 0, 0, 1, &
2066 0, 0, 0, 0, 0, 0, -1, 1, 0, 0, 0, 0, 0, 1, 25, 106, 57, -13 /
2067
2068 data ix33/ 0, 0, 1, -1, 1, 0, -1, 0, 0, 0, 0, 0, 0, 0, 5, 21, 11, -3, &
2069 0, 0, 0, 0, 0, 0, 1, -1, 0, 0, 0, 0, 0, 0, 1485, 0, 0, 0, &
2070 0, 0, 0, 0, 0, 0, 1, -1, 0, 0, 0, 0, 0, 1, -7, -32, -17, 4, &
2071 0, 0, 1, -1, 1, 0, 1, -2, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0, &
2072 0, 0, 0, 0, 0, 0, 0, -2, 5, 0, 0, 0, 0, 2, -6, -3, -2, 3, &
2073 0, 0, 0, 0, 0, 0, 0, -1, 0, 4, 0, 0, 0, 2, 30, -6, -2, -13, &
2074 0, 0, 0, 0, 0, 0, 0, 1, 0, -4, 0, 0, 0, 0, -4, 4, 0, 0, &
2075 0, 0, 0, 0, 1, 0, -1, 1, 0, 0, 0, 0, 0, 0, -19, 0, 0, 10, &
2076 0, 0, 0, 0, 0, 0, 0, -6, 10, 0, 0, 0, 0, 2, 0, 4, 2, -1, &
2077 0, 0, 0, 0, 0, 0, 0, -6, 10, 0, 0, 0, 0, 0, 0, 3, 0, 0 /
2078
2079 data ix34/ 0, 0, 2, -2, 1, 0, 0, -3, 0, 3, 0, 0, 0, 0, 4, 0, 0, -2, &
2080 0, 0, 0, 0, 0, 0, 0, -3, 7, 0, 0, 0, 0, 2, 0, -3, -1, 0, &
2081 -2, 0, 0, 2, 0, 0, 4, -4, 0, 0, 0, 0, 0, 0, -3, 0, 0, 0, &
2082 0, 0, 0, 0, 0, 0, 0, -5, 8, 0, 0, 0, 0, 2, 5, 3, 1, -2, &
2083 0, 0, 0, 0, 0, 0, 0, 5, -8, 0, 0, 0, 0, 0, 0, 11, 0, 0, &
2084 0, 0, 0, 0, 0, 0, 0, -1, 0, 3, 0, 0, 0, 2, 118, 0, 0, -52, &
2085 0, 0, 0, 0, 0, 0, 0, -1, 0, 3, 0, 0, 0, 1, 0, -5, -3, 0, &
2086 0, 0, 0, 0, 0, 0, 0, 1, 0, -3, 0, 0, 0, 0, -28, 36, 0, 0, &
2087 0, 0, 0, 0, 0, 0, 2, -4, 0, 0, 0, 0, 0, 0, 5, -5, 0, 0, &
2088 0, 0, 0, 0, 0, 0, -2, 4, 0, 0, 0, 0, 0, 1, 14, -59, -31, -8 /
2089
2090 data ix35/ 0, 0, 1, -1, 1, 0, -2, 3, 0, 0, 0, 0, 0, 0, 0, 9, 5, 1, &
2091 0, 0, 0, 0, 0, 0, -2, 4, 0, 0, 0, 0, 0, 2, -458, 0, 0, 198, &
2092 0, 0, 0, 0, 0, 0, -6, 9, 0, 0, 0, 0, 0, 2, 0, -45, -20, 0, &
2093 0, 0, 0, 0, 0, 0, -6, 9, 0, 0, 0, 0, 0, 1, 9, 0, 0, -5, &
2094 0, 0, 0, 0, 0, 0, 6, -9, 0, 0, 0, 0, 0, 0, 0, -3, 0, 0, &
2095 0, 0, 0, 0, 1, 0, 0, 1, 0, -2, 0, 0, 0, 0, 0, -4, -2, -1, &
2096 0, 0, 2, -2, 1, 0, -2, 2, 0, 0, 0, 0, 0, 0, 11, 0, 0, -6, &
2097 0, 0, 0, 0, 0, 0, 0, -4, 6, 0, 0, 0, 0, 2, 6, 0, 0, -2, &
2098 0, 0, 0, 0, 0, 0, 0, 4, -6, 0, 0, 0, 0, 0, -16, 23, 0, 0, &
2099 0, 0, 0, 0, 1, 0, 3, -4, 0, 0, 0, 0, 0, 0, 0, -4, -2, 0 /
2100
2101 data ix36/ 0, 0, 0, 0, 0, 0, 0, -1, 0, 2, 0, 0, 0, 2, -5, 0, 0, 2, &
2102 0, 0, 0, 0, 0, 0, 0, 1, 0, -2, 0, 0, 0, 0, -166, 269, 0, 0, &
2103 0, 0, 0, 0, 1, 0, 0, 1, 0, -1, 0, 0, 0, 0, 15, 0, 0, -8, &
2104 0, 0, 0, 0, 0, 0, -5, 9, 0, 0, 0, 0, 0, 2, 10, 0, 0, -4, &
2105 0, 0, 0, 0, 0, 0, 0, 3, -4, 0, 0, 0, 0, 0, -78, 45, 0, 0, &
2106 0, 0, 0, 0, 0, 0, -3, 4, 0, 0, 0, 0, 0, 2, 0, -5, -2, 0, &
2107 0, 0, 0, 0, 0, 0, -3, 4, 0, 0, 0, 0, 0, 1, 7, 0, 0, -4, &
2108 0, 0, 0, 0, 0, 0, 3, -4, 0, 0, 0, 0, 0, 0, -5, 328, 0, 0, &
2109 0, 0, 0, 0, 0, 0, 3, -4, 0, 0, 0, 0, 0, 1, 3, 0, 0, -2, &
2110 0, 0, 0, 0, 1, 0, 0, 2, -2, 0, 0, 0, 0, 0, 5, 0, 0, -2 /
2111
2112 data ix37/ 0, 0, 0, 0, 1, 0, 0, -1, 0, 2, 0, 0, 0, 0, 0, 3, 1, 0, &
2113 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, -3, 0, 0, 0, -3, 0, 0, 0, &
2114 0, 0, 0, 0, 0, 0, 0, 1, 0, 1, -5, 0, 0, 0, -3, 0, 0, 0, &
2115 0, 0, 0, 0, 0, 0, 0, -1, 0, 1, 0, 0, 0, 1, 0, -4, -2, 0, &
2116 0, 0, 0, 0, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, -1223, -26, 0, 0, &
2117 0, 0, 0, 0, 0, 0, 0, 1, 0, -1, 0, 0, 0, 1, 0, 7, 3, 0, &
2118 0, 0, 0, 0, 0, 0, 0, 1, 0, -3, 5, 0, 0, 0, 3, 0, 0, 0, &
2119 0, 0, 0, 0, 1, 0, -3, 4, 0, 0, 0, 0, 0, 0, 0, 3, 2, 0, &
2120 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, -2, 0, 0, 0, -6, 20, 0, 0, &
2121 0, 0, 0, 0, 0, 0, 0, 2, -2, 0, 0, 0, 0, 0, -368, 0, 0, 0 /
2122
2123 data ix38/ 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, -1, 0, 0, 0, -75, 0, 0, 0, &
2124 0, 0, 0, 0, 1, 0, 0, -1, 0, 1, 0, 0, 0, 0, 11, 0, 0, -6, &
2125 0, 0, 0, 0, 1, 0, 0, -2, 2, 0, 0, 0, 0, 0, 3, 0, 0, -2, &
2126 0, 0, 0, 0, 0, 0, -8, 14, 0, 0, 0, 0, 0, 2, -3, 0, 0, 1, &
2127 0, 0, 0, 0, 0, 0, 0, 1, 0, 2, -5, 0, 0, 0, -13, -30, 0, 0, &
2128 0, 0, 0, 0, 0, 0, 0, 5, -8, 3, 0, 0, 0, 0, 21, 3, 0, 0, &
2129 0, 0, 0, 0, 0, 0, 0, 5, -8, 3, 0, 0, 0, 2, -3, 0, 0, 1, &
2130 0, 0, 0, 0, 0, 0, 0, -1, 0, 0, 0, 0, 0, 1, -4, 0, 0, 2, &
2131 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 8, -27, 0, 0, &
2132 0, 0, 0, 0, 0, 0, 0, 3, -8, 3, 0, 0, 0, 0, -19, -11, 0, 0 /
2133
2134 data ix39/ 0, 0, 0, 0, 0, 0, 0, -3, 8, -3, 0, 0, 0, 2, -4, 0, 0, 2, &
2135 0, 0, 0, 0, 0, 0, 0, 1, 0, -2, 5, 0, 0, 2, 0, 5, 2, 0, &
2136 0, 0, 0, 0, 0, 0, -8, 12, 0, 0, 0, 0, 0, 2, -6, 0, 0, 2, &
2137 0, 0, 0, 0, 0, 0, -8, 12, 0, 0, 0, 0, 0, 0, -8, 0, 0, 0, &
2138 0, 0, 0, 0, 0, 0, 0, 1, 0, 1, -2, 0, 0, 0, -1, 0, 0, 0, &
2139 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 0, 0, 2, -14, 0, 0, 6, &
2140 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 6, 0, 0, 0, &
2141 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 2, -74, 0, 0, 32, &
2142 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 2, 0, 0, 2, 0, -3, -1, 0, &
2143 0, 0, 2, -2, 1, 0, -5, 5, 0, 0, 0, 0, 0, 0, 4, 0, 0, -2 /
2144
2145 data ix40/ 0, 0, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 0, 8, 11, 0, 0, &
2146 0, 0, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 1, 0, 3, 2, 0, &
2147 0, 0, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 2, -262, 0, 0, 114, &
2148 0, 0, 0, 0, 0, 0, 3, -6, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, &
2149 0, 0, 0, 0, 0, 0, -3, 6, 0, 0, 0, 0, 0, 1, -7, 0, 0, 4, &
2150 0, 0, 0, 0, 0, 0, -3, 6, 0, 0, 0, 0, 0, 2, 0, -27, -12, 0, &
2151 0, 0, 0, 0, 0, 0, 0, -1, 4, 0, 0, 0, 0, 2, -19, -8, -4, 8, &
2152 0, 0, 0, 0, 0, 0, -5, 7, 0, 0, 0, 0, 0, 2, 202, 0, 0, -87, &
2153 0, 0, 0, 0, 0, 0, -5, 7, 0, 0, 0, 0, 0, 1, -8, 35, 19, 5, &
2154 0, 0, 1, -1, 1, 0, -5, 6, 0, 0, 0, 0, 0, 0, 0, 4, 2, 0 /
2155
2156 data ix41/ 0, 0, 0, 0, 0, 0, 5, -7, 0, 0, 0, 0, 0, 0, 16, -5, 0, 0, &
2157 0, 0, 2, -2, 1, 0, 0, -1, 0, 1, 0, 0, 0, 0, 5, 0, 0, -3, &
2158 0, 0, 0, 0, 0, 0, 0, -1, 0, 1, 0, 0, 0, 0, 0, -3, 0, 0, &
2159 0, 0, 0, 0, 0, -1, 0, 3, 0, 0, 0, 0, 0, 2, 1, 0, 0, 0, &
2160 0, 0, 0, 0, 0, 0, 0, 1, 0, 2, 0, 0, 0, 2, -35, -48, -21, 15, &
2161 0, 0, 0, 0, 0, 0, 0, -2, 6, 0, 0, 0, 0, 2, -3, -5, -2, 1, &
2162 0, 0, 0, 0, 1, 0, 2, -2, 0, 0, 0, 0, 0, 0, 6, 0, 0, -3, &
2163 0, 0, 0, 0, 0, 0, 0, -6, 9, 0, 0, 0, 0, 2, 3, 0, 0, -1, &
2164 0, 0, 0, 0, 0, 0, 0, 6, -9, 0, 0, 0, 0, 0, 0, -5, 0, 0, &
2165 0, 0, 0, 0, 0, 0, -2, 2, 0, 0, 0, 0, 0, 1, 12, 55, 29, -6 /
2166
2167 data ix42/ 0, 0, 1, -1, 1, 0, -2, 1, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0, &
2168 0, 0, 0, 0, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, -598, 0, 0, 0, &
2169 0, 0, 0, 0, 0, 0, 2, -2, 0, 0, 0, 0, 0, 1, -3, -13, -7, 1, &
2170 0, 0, 0, 0, 0, 0, 0, 1, 0, 3, 0, 0, 0, 2, -5, -7, -3, 2, &
2171 0, 0, 0, 0, 0, 0, 0, -5, 7, 0, 0, 0, 0, 2, 3, 0, 0, -1, &
2172 0, 0, 0, 0, 0, 0, 0, 5, -7, 0, 0, 0, 0, 0, 5, -7, 0, 0, &
2173 0, 0, 0, 0, 1, 0, -2, 2, 0, 0, 0, 0, 0, 0, 4, 0, 0, -2, &
2174 0, 0, 0, 0, 0, 0, 0, 4, -5, 0, 0, 0, 0, 0, 16, -6, 0, 0, &
2175 0, 0, 0, 0, 0, 0, 1, -3, 0, 0, 0, 0, 0, 0, 8, -3, 0, 0, &
2176 0, 0, 0, 0, 0, 0, -1, 3, 0, 0, 0, 0, 0, 1, 8, -31, -16, -4 /
2177
2178 data ix43/ 0, 0, 1, -1, 1, 0, -1, 2, 0, 0, 0, 0, 0, 0, 0, 3, 1, 0, &
2179 0, 0, 0, 0, 0, 0, -1, 3, 0, 0, 0, 0, 0, 2, 113, 0, 0, -49, &
2180 0, 0, 0, 0, 0, 0, -7, 10, 0, 0, 0, 0, 0, 2, 0, -24, -10, 0, &
2181 0, 0, 0, 0, 0, 0, -7, 10, 0, 0, 0, 0, 0, 1, 4, 0, 0, -2, &
2182 0, 0, 0, 0, 0, 0, 0, 3, -3, 0, 0, 0, 0, 0, 27, 0, 0, 0, &
2183 0, 0, 0, 0, 0, 0, -4, 8, 0, 0, 0, 0, 0, 2, -3, 0, 0, 1, &
2184 0, 0, 0, 0, 0, 0, -4, 5, 0, 0, 0, 0, 0, 2, 0, -4, -2, 0, &
2185 0, 0, 0, 0, 0, 0, -4, 5, 0, 0, 0, 0, 0, 1, 5, 0, 0, -2, &
2186 0, 0, 0, 0, 0, 0, 4, -5, 0, 0, 0, 0, 0, 0, 0, -3, 0, 0, &
2187 0, 0, 0, 0, 0, 0, 0, 1, 1, 0, 0, 0, 0, 2, -13, 0, 0, 6 /
2188
2189 data ix44/ 0, 0, 0, 0, 0, 0, 0, -2, 0, 5, 0, 0, 0, 2, 5, 0, 0, -2, &
2190 0, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 2, -18, -10, -4, 8, &
2191 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, -4, -28, 0, 0, &
2192 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 2, -5, 6, 3, 2, &
2193 0, 0, 0, 0, 0, 0, -9, 13, 0, 0, 0, 0, 0, 2, -3, 0, 0, 1, &
2194 0, 0, 0, 0, 0, 0, 0, -1, 5, 0, 0, 0, 0, 2, -5, -9, -4, 2, &
2195 0, 0, 0, 0, 0, 0, 0, -2, 0, 4, 0, 0, 0, 2, 17, 0, 0, -7, &
2196 0, 0, 0, 0, 0, 0, 0, 2, 0, -4, 0, 0, 0, 0, 11, 4, 0, 0, &
2197 0, 0, 0, 0, 0, 0, 0, -2, 7, 0, 0, 0, 0, 2, 0, -6, -2, 0, &
2198 0, 0, 0, 0, 0, 0, 0, 2, 0, -3, 0, 0, 0, 0, 83, 15, 0, 0 /
2199
2200 data ix45/ 0, 0, 0, 0, 0, 0, -2, 5, 0, 0, 0, 0, 0, 1, -4, 0, 0, 2, &
2201 0, 0, 0, 0, 0, 0, -2, 5, 0, 0, 0, 0, 0, 2, 0, -114, -49, 0, &
2202 0, 0, 0, 0, 0, 0, -6, 8, 0, 0, 0, 0, 0, 2, 117, 0, 0, -51, &
2203 0, 0, 0, 0, 0, 0, -6, 8, 0, 0, 0, 0, 0, 1, -5, 19, 10, 2, &
2204 0, 0, 0, 0, 0, 0, 6, -8, 0, 0, 0, 0, 0, 0, -3, 0, 0, 0, &
2205 0, 0, 0, 0, 1, 0, 0, 2, 0, -2, 0, 0, 0, 0, -3, 0, 0, 2, &
2206 0, 0, 0, 0, 0, 0, 0, -3, 9, 0, 0, 0, 0, 2, 0, -3, -1, 0, &
2207 0, 0, 0, 0, 0, 0, 0, 5, -6, 0, 0, 0, 0, 0, 3, 0, 0, 0, &
2208 0, 0, 0, 0, 0, 0, 0, 5, -6, 0, 0, 0, 0, 2, 0, -6, -2, 0, &
2209 0, 0, 0, 0, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, 393, 3, 0, 0 /
2210
2211 data ix46/ 0, 0, 0, 0, 0, 0, 0, 2, 0, -2, 0, 0, 0, 1, -4, 21, 11, 2, &
2212 0, 0, 0, 0, 0, 0, 0, 2, 0, -2, 0, 0, 0, 2, -6, 0, -1, 3, &
2213 0, 0, 0, 0, 0, 0, -5, 10, 0, 0, 0, 0, 0, 2, -3, 8, 4, 1, &
2214 0, 0, 0, 0, 0, 0, 0, 4, -4, 0, 0, 0, 0, 0, 8, 0, 0, 0, &
2215 0, 0, 0, 0, 0, 0, 0, 4, -4, 0, 0, 0, 0, 2, 18, -29, -13, -8, &
2216 0, 0, 0, 0, 0, 0, -3, 3, 0, 0, 0, 0, 0, 1, 8, 34, 18, -4, &
2217 0, 0, 0, 0, 0, 0, 3, -3, 0, 0, 0, 0, 0, 0, 89, 0, 0, 0, &
2218 0, 0, 0, 0, 0, 0, 3, -3, 0, 0, 0, 0, 0, 1, 3, 12, 6, -1, &
2219 0, 0, 0, 0, 0, 0, 3, -3, 0, 0, 0, 0, 0, 2, 54, -15, -7, -24, &
2220 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, -3, 0, 0, 0, 0, 3, 0, 0 /
2221
2222 data ix47/ 0, 0, 0, 0, 0, 0, 0, -5, 13, 0, 0, 0, 0, 2, 3, 0, 0, -1, &
2223 0, 0, 0, 0, 0, 0, 0, 2, 0, -1, 0, 0, 0, 0, 0, 35, 0, 0, &
2224 0, 0, 0, 0, 0, 0, 0, 2, 0, -1, 0, 0, 0, 2, -154, -30, -13, 67, &
2225 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, -2, 0, 0, 0, 15, 0, 0, 0, &
2226 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, -2, 0, 0, 1, 0, 4, 2, 0, &
2227 0, 0, 0, 0, 0, 0, 0, 3, -2, 0, 0, 0, 0, 0, 0, 9, 0, 0, &
2228 0, 0, 0, 0, 0, 0, 0, 3, -2, 0, 0, 0, 0, 2, 80, -71, -31, -35, &
2229 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, -1, 0, 0, 2, 0, -20, -9, 0, &
2230 0, 0, 0, 0, 0, 0, 0, -6, 15, 0, 0, 0, 0, 2, 11, 5, 2, -5, &
2231 0, 0, 0, 0, 0, 0, -8, 15, 0, 0, 0, 0, 0, 2, 61, -96, -42, -27 /
2232
2233 data ix48/ 0, 0, 0, 0, 0, 0, -3, 9, -4, 0, 0, 0, 0, 2, 14, 9, 4, -6, &
2234 0, 0, 0, 0, 0, 0, 0, 2, 0, 2, -5, 0, 0, 2, -11, -6, -3, 5, &
2235 0, 0, 0, 0, 0, 0, 0, -2, 8, -1, -5, 0, 0, 2, 0, -3, -1, 0, &
2236 0, 0, 0, 0, 0, 0, 0, 6, -8, 3, 0, 0, 0, 2, 123, -415, -180, -53, &
2237 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, -35, &
2238 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, -5, 0, 0, 0, &
2239 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 1, 7, -32, -17, -4, &
2240 0, 0, 1, -1, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, -9, -5, 0, &
2241 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 1, 0, -4, 2, 0, &
2242 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 2, -89, 0, 0, 38 /
2243
2244 data ix49/ 0, 0, 0, 0, 0, 0, 0, -6, 16, -4, -5, 0, 0, 2, 0, -86, -19, -6, &
2245 0, 0, 0, 0, 0, 0, 0, -2, 8, -3, 0, 0, 0, 2, 0, 0, -19, 6, &
2246 0, 0, 0, 0, 0, 0, 0, -2, 8, -3, 0, 0, 0, 2, -123, -416, -180, 53, &
2247 0, 0, 0, 0, 0, 0, 0, 6, -8, 1, 5, 0, 0, 2, 0, -3, -1, 0, &
2248 0, 0, 0, 0, 0, 0, 0, 2, 0, -2, 5, 0, 0, 2, 12, -6, -3, -5, &
2249 0, 0, 0, 0, 0, 0, 3, -5, 4, 0, 0, 0, 0, 2, -13, 9, 4, 6, &
2250 0, 0, 0, 0, 0, 0, -8, 11, 0, 0, 0, 0, 0, 2, 0, -15, -7, 0, &
2251 0, 0, 0, 0, 0, 0, -8, 11, 0, 0, 0, 0, 0, 1, 3, 0, 0, -1, &
2252 0, 0, 0, 0, 0, 0, -8, 11, 0, 0, 0, 0, 0, 2, -62, -97, -42, 27, &
2253 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 2, -11, 5, 2, 5 /
2254
2255 data ix50/ 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 1, 0, 0, 2, 0, -19, -8, 0, &
2256 0, 0, 0, 0, 0, 0, 3, -3, 0, 2, 0, 0, 0, 2, -3, 0, 0, 1, &
2257 0, 0, 2, -2, 1, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, 4, 2, 0, &
2258 0, 0, 1, -1, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, &
2259 0, 0, 2, -2, 1, 0, 0, -4, 8, -3, 0, 0, 0, 0, 0, 4, 2, 0, &
2260 0, 0, 0, 0, 0, 0, 0, 1, 2, 0, 0, 0, 0, 2, -85, -70, -31, 37, &
2261 0, 0, 0, 0, 0, 0, 0, 2, 0, 1, 0, 0, 0, 2, 163, -12, -5, -72, &
2262 0, 0, 0, 0, 0, 0, -3, 7, 0, 0, 0, 0, 0, 2, -63, -16, -7, 28, &
2263 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 2, -21, -32, -14, 9, &
2264 0, 0, 0, 0, 0, 0, -5, 6, 0, 0, 0, 0, 0, 2, 0, -3, -1, 0 /
2265
2266 data ix51/ 0, 0, 0, 0, 0, 0, -5, 6, 0, 0, 0, 0, 0, 1, 3, 0, 0, -2, &
2267 0, 0, 0, 0, 0, 0, 5, -6, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, &
2268 0, 0, 0, 0, 0, 0, 5, -6, 0, 0, 0, 0, 0, 2, 3, 10, 4, -1, &
2269 0, 0, 0, 0, 0, 0, 0, 2, 0, 2, 0, 0, 0, 2, 3, 0, 0, -1, &
2270 0, 0, 0, 0, 0, 0, 0, -1, 6, 0, 0, 0, 0, 2, 0, -7, -3, 0, &
2271 0, 0, 0, 0, 0, 0, 0, 7, -9, 0, 0, 0, 0, 2, 0, -4, -2, 0, &
2272 0, 0, 0, 0, 0, 0, 2, -1, 0, 0, 0, 0, 0, 0, 6, 19, 0, 0, &
2273 0, 0, 0, 0, 0, 0, 2, -1, 0, 0, 0, 0, 0, 2, 5, -173, -75, -2, &
2274 0, 0, 0, 0, 0, 0, 0, 6, -7, 0, 0, 0, 0, 2, 0, -7, -3, 0, &
2275 0, 0, 0, 0, 0, 0, 0, 5, -5, 0, 0, 0, 0, 2, 7, -12, -5, -3 /
2276
2277 data ix52/ 0, 0, 0, 0, 0, 0, -1, 4, 0, 0, 0, 0, 0, 1, -3, 0, 0, 2, &
2278 0, 0, 0, 0, 0, 0, -1, 4, 0, 0, 0, 0, 0, 2, 3, -4, -2, -1, &
2279 0, 0, 0, 0, 0, 0, -7, 9, 0, 0, 0, 0, 0, 2, 74, 0, 0, -32, &
2280 0, 0, 0, 0, 0, 0, -7, 9, 0, 0, 0, 0, 0, 1, -3, 12, 6, 2, &
2281 0, 0, 0, 0, 0, 0, 0, 4, -3, 0, 0, 0, 0, 2, 26, -14, -6, -11, &
2282 0, 0, 0, 0, 0, 0, 0, 3, -1, 0, 0, 0, 0, 2, 19, 0, 0, -8, &
2283 0, 0, 0, 0, 0, 0, -4, 4, 0, 0, 0, 0, 0, 1, 6, 24, 13, -3, &
2284 0, 0, 0, 0, 0, 0, 4, -4, 0, 0, 0, 0, 0, 0, 83, 0, 0, 0, &
2285 0, 0, 0, 0, 0, 0, 4, -4, 0, 0, 0, 0, 0, 1, 0, -10, -5, 0, &
2286 0, 0, 0, 0, 0, 0, 4, -4, 0, 0, 0, 0, 0, 2, 11, -3, -1, -5 /
2287
2288 data ix53/ 0, 0, 0, 0, 0, 0, 0, 2, 1, 0, 0, 0, 0, 2, 3, 0, 1, -1, &
2289 0, 0, 0, 0, 0, 0, 0, -3, 0, 5, 0, 0, 0, 2, 3, 0, 0, -1, &
2290 0, 0, 0, 0, 0, 0, 1, 1, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, &
2291 0, 0, 0, 0, 0, 0, 1, 1, 0, 0, 0, 0, 0, 1, 5, -23, -12, -3, &
2292 0, 0, 0, 0, 0, 0, 1, 1, 0, 0, 0, 0, 0, 2, -339, 0, 0, 147, &
2293 0, 0, 0, 0, 0, 0, -9, 12, 0, 0, 0, 0, 0, 2, 0, -10, -5, 0, &
2294 0, 0, 0, 0, 0, 0, 0, 3, 0, -4, 0, 0, 0, 0, 5, 0, 0, 0, &
2295 0, 0, 2, -2, 1, 0, 1, -1, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, &
2296 0, 0, 0, 0, 0, 0, 0, 7, -8, 0, 0, 0, 0, 2, 0, -4, -2, 0, &
2297 0, 0, 0, 0, 0, 0, 0, 3, 0, -3, 0, 0, 0, 0, 18, -3, 0, 0 /
2298
2299 data ix54/ 0, 0, 0, 0, 0, 0, 0, 3, 0, -3, 0, 0, 0, 2, 9, -11, -5, -4, &
2300 0, 0, 0, 0, 0, 0, -2, 6, 0, 0, 0, 0, 0, 2, -8, 0, 0, 4, &
2301 0, 0, 0, 0, 0, 0, -6, 7, 0, 0, 0, 0, 0, 1, 3, 0, 0, -1, &
2302 0, 0, 0, 0, 0, 0, 6, -7, 0, 0, 0, 0, 0, 0, 0, 9, 0, 0, &
2303 0, 0, 0, 0, 0, 0, 0, 6, -6, 0, 0, 0, 0, 2, 6, -9, -4, -2, &
2304 0, 0, 0, 0, 0, 0, 0, 3, 0, -2, 0, 0, 0, 0, -4, -12, 0, 0, &
2305 0, 0, 0, 0, 0, 0, 0, 3, 0, -2, 0, 0, 0, 2, 67, -91, -39, -29, &
2306 0, 0, 0, 0, 0, 0, 0, 5, -4, 0, 0, 0, 0, 2, 30, -18, -8, -13, &
2307 0, 0, 0, 0, 0, 0, 3, -2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, &
2308 0, 0, 0, 0, 0, 0, 3, -2, 0, 0, 0, 0, 0, 2, 0, -114, -50, 0 /
2309
2310 data ix55/ 0, 0, 0, 0, 0, 0, 0, 3, 0, -1, 0, 0, 0, 2, 0, 0, 0, 23, &
2311 0, 0, 0, 0, 0, 0, 0, 3, 0, -1, 0, 0, 0, 2, 517, 16, 7, -224, &
2312 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, -2, 0, 0, 2, 0, -7, -3, 0, &
2313 0, 0, 0, 0, 0, 0, 0, 4, -2, 0, 0, 0, 0, 2, 143, -3, -1, -62, &
2314 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, 0, 0, 2, 29, 0, 0, -13, &
2315 0, 0, 2, -2, 1, 0, 0, 1, 0, -1, 0, 0, 0, 0, -4, 0, 0, 2, &
2316 0, 0, 0, 0, 0, 0, -8, 16, 0, 0, 0, 0, 0, 2, -6, 0, 0, 3, &
2317 0, 0, 0, 0, 0, 0, 0, 3, 0, 2, -5, 0, 0, 2, 5, 12, 5, -2, &
2318 0, 0, 0, 0, 0, 0, 0, 7, -8, 3, 0, 0, 0, 2, -25, 0, 0, 11, &
2319 0, 0, 0, 0, 0, 0, 0, -5, 16, -4, -5, 0, 0, 2, -3, 0, 0, 1 /
2320
2321 data ix56/ 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 2, 0, 4, 2, 0, &
2322 0, 0, 0, 0, 0, 0, 0, -1, 8, -3, 0, 0, 0, 2, -22, 12, 5, 10, &
2323 0, 0, 0, 0, 0, 0, -8, 10, 0, 0, 0, 0, 0, 2, 50, 0, 0, -22, &
2324 0, 0, 0, 0, 0, 0, -8, 10, 0, 0, 0, 0, 0, 1, 0, 7, 4, 0, &
2325 0, 0, 0, 0, 0, 0, -8, 10, 0, 0, 0, 0, 0, 2, 0, 3, 1, 0, &
2326 0, 0, 0, 0, 0, 0, 0, 2, 2, 0, 0, 0, 0, 2, -4, 4, 2, 2, &
2327 0, 0, 0, 0, 0, 0, 0, 3, 0, 1, 0, 0, 0, 2, -5, -11, -5, 2, &
2328 0, 0, 0, 0, 0, 0, -3, 8, 0, 0, 0, 0, 0, 2, 0, 4, 2, 0, &
2329 0, 0, 0, 0, 0, 0, -5, 5, 0, 0, 0, 0, 0, 1, 4, 17, 9, -2, &
2330 0, 0, 0, 0, 0, 0, 5, -5, 0, 0, 0, 0, 0, 0, 59, 0, 0, 0 /
2331
2332 data ix57/ 0, 0, 0, 0, 0, 0, 5, -5, 0, 0, 0, 0, 0, 1, 0, -4, -2, 0, &
2333 0, 0, 0, 0, 0, 0, 5, -5, 0, 0, 0, 0, 0, 2, -8, 0, 0, 4, &
2334 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, -3, 0, 0, 0, &
2335 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 1, 4, -15, -8, -2, &
2336 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 2, 370, -8, 0, -160, &
2337 0, 0, 0, 0, 0, 0, 0, 7, -7, 0, 0, 0, 0, 2, 0, 0, -3, 0, &
2338 0, 0, 0, 0, 0, 0, 0, 7, -7, 0, 0, 0, 0, 2, 0, 3, 1, 0, &
2339 0, 0, 0, 0, 0, 0, 0, 6, -5, 0, 0, 0, 0, 2, -6, 3, 1, 3, &
2340 0, 0, 0, 0, 0, 0, 7, -8, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, &
2341 0, 0, 0, 0, 0, 0, 0, 5, -3, 0, 0, 0, 0, 2, -10, 0, 0, 4 /
2342
2343 data ix58/ 0, 0, 0, 0, 0, 0, 4, -3, 0, 0, 0, 0, 0, 2, 0, 9, 4, 0, &
2344 0, 0, 0, 0, 0, 0, 1, 2, 0, 0, 0, 0, 0, 2, 4, 17, 7, -2, &
2345 0, 0, 0, 0, 0, 0, -9, 11, 0, 0, 0, 0, 0, 2, 34, 0, 0, -15, &
2346 0, 0, 0, 0, 0, 0, -9, 11, 0, 0, 0, 0, 0, 1, 0, 5, 3, 0, &
2347 0, 0, 0, 0, 0, 0, 0, 4, 0, -4, 0, 0, 0, 2, -5, 0, 0, 2, &
2348 0, 0, 0, 0, 0, 0, 0, 4, 0, -3, 0, 0, 0, 2, -37, -7, -3, 16, &
2349 0, 0, 0, 0, 0, 0, -6, 6, 0, 0, 0, 0, 0, 1, 3, 13, 7, -2, &
2350 0, 0, 0, 0, 0, 0, 6, -6, 0, 0, 0, 0, 0, 0, 40, 0, 0, 0, &
2351 0, 0, 0, 0, 0, 0, 6, -6, 0, 0, 0, 0, 0, 1, 0, -3, -2, 0, &
2352 0, 0, 0, 0, 0, 0, 0, 4, 0, -2, 0, 0, 0, 2, -184, -3, -1, 80 /
2353
2354 data ix59/ 0, 0, 0, 0, 0, 0, 0, 6, -4, 0, 0, 0, 0, 2, -3, 0, 0, 1, &
2355 0, 0, 0, 0, 0, 0, 3, -1, 0, 0, 0, 0, 0, 0, -3, 0, 0, 0, &
2356 0, 0, 0, 0, 0, 0, 3, -1, 0, 0, 0, 0, 0, 1, 0, -10, -6, -1, &
2357 0, 0, 0, 0, 0, 0, 3, -1, 0, 0, 0, 0, 0, 2, 31, -6, 0, -13, &
2358 0, 0, 0, 0, 0, 0, 0, 4, 0, -1, 0, 0, 0, 2, -3, -32, -14, 1, &
2359 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, -2, 0, 0, 2, -7, 0, 0, 3, &
2360 0, 0, 0, 0, 0, 0, 0, 5, -2, 0, 0, 0, 0, 2, 0, -8, -4, 0, &
2361 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 0, 0, 3, -4, 0, 0, &
2362 0, 0, 0, 0, 0, 0, 8, -9, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, &
2363 0, 0, 0, 0, 0, 0, 5, -4, 0, 0, 0, 0, 0, 2, 0, 3, 1, 0 /
2364
2365 data ix60/ 0, 0, 0, 0, 0, 0, 2, 1, 0, 0, 0, 0, 0, 2, 19, -23, -10, 2, &
2366 0, 0, 0, 0, 0, 0, 2, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, -10, &
2367 0, 0, 0, 0, 0, 0, 2, 1, 0, 0, 0, 0, 0, 1, 0, 3, 2, 0, &
2368 0, 0, 0, 0, 0, 0, -7, 7, 0, 0, 0, 0, 0, 1, 0, 9, 5, -1, &
2369 0, 0, 0, 0, 0, 0, 7, -7, 0, 0, 0, 0, 0, 0, 28, 0, 0, 0, &
2370 0, 0, 0, 0, 0, 0, 4, -2, 0, 0, 0, 0, 0, 1, 0, -7, -4, 0, &
2371 0, 0, 0, 0, 0, 0, 4, -2, 0, 0, 0, 0, 0, 2, 8, -4, 0, -4, &
2372 0, 0, 0, 0, 0, 0, 4, -2, 0, 0, 0, 0, 0, 0, 0, 0, -2, 0, &
2373 0, 0, 0, 0, 0, 0, 4, -2, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, &
2374 0, 0, 0, 0, 0, 0, 0, 5, 0, -4, 0, 0, 0, 2, -3, 0, 0, 1 /
2375
2376 data ix61/ 0, 0, 0, 0, 0, 0, 0, 5, 0, -3, 0, 0, 0, 2, -9, 0, 1, 4, &
2377 0, 0, 0, 0, 0, 0, 0, 5, 0, -2, 0, 0, 0, 2, 3, 12, 5, -1, &
2378 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, 0, 0, 0, 2, 17, -3, -1, 0, &
2379 0, 0, 0, 0, 0, 0, -8, 8, 0, 0, 0, 0, 0, 1, 0, 7, 4, 0, &
2380 0, 0, 0, 0, 0, 0, 8, -8, 0, 0, 0, 0, 0, 0, 19, 0, 0, 0, &
2381 0, 0, 0, 0, 0, 0, 5, -3, 0, 0, 0, 0, 0, 1, 0, -5, -3, 0, &
2382 0, 0, 0, 0, 0, 0, 5, -3, 0, 0, 0, 0, 0, 2, 14, -3, 0, -1, &
2383 0, 0, 0, 0, 0, 0, -9, 9, 0, 0, 0, 0, 0, 1, 0, 0, -1, 0, &
2384 0, 0, 0, 0, 0, 0, -9, 9, 0, 0, 0, 0, 0, 1, 0, 0, 0, -5, &
2385 0, 0, 0, 0, 0, 0, -9, 9, 0, 0, 0, 0, 0, 1, 0, 5, 3, 0 /
2386
2387 data ix62/ 0, 0, 0, 0, 0, 0, 9, -9, 0, 0, 0, 0, 0, 0, 13, 0, 0, 0, &
2388 0, 0, 0, 0, 0, 0, 6, -4, 0, 0, 0, 0, 0, 1, 0, -3, -2, 0, &
2389 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 2, 2, 9, 4, 3, &
2390 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, -4, &
2391 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, &
2392 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 1, 0, 4, 2, 0, &
2393 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 2, 6, 0, 0, -3, &
2394 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, &
2395 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 1, 0, 3, 1, 0, &
2396 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 2, 5, 0, 0, -2 /
2397
2398 data ix63/ 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 3, 0, 0, -1, &
2399 1, 0, 0, -2, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, -3, 0, 0, 0, &
2400 1, 0, 0, -2, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, &
2401 1, 0, 0, -2, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, 7, 0, 0, 0, &
2402 1, 0, 0, -2, 0, 0, 1, -1, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, &
2403 -1, 0, 0, 0, 0, 0, 3, -3, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, &
2404 -1, 0, 0, 0, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, 6, 0, 0, 0, &
2405 -1, 0, 0, 2, 0, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, -4, 0, 0, &
2406 1, 0, 0, -2, 0, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, -4, 0, 0, &
2407 -2, 0, 0, 2, 0, 0, 0, 4, -8, 3, 0, 0, 0, 0, 5, 0, 0, 0 /
2408
2409 data ix64/ -1, 0, 0, 0, 0, 0, 0, 2, 0, -3, 0, 0, 0, 0, -3, 0, 0, 0, &
2410 -1, 0, 0, 0, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, 4, 0, 0, 0, &
2411 -1, 0, 0, 0, 0, 0, 1, -1, 0, 0, 0, 0, 0, 0, -5, 0, 0, 0, &
2412 -1, 0, 0, 2, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, 4, 0, 0, 0, &
2413 1, 0, -1, 1, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 3, 0, 0, &
2414 -1, 0, 0, 2, 0, 0, 0, 2, 0, -3, 0, 0, 0, 0, 13, 0, 0, 0, &
2415 -2, 0, 0, 0, 0, 0, 0, 2, 0, -3, 0, 0, 0, 0, 21, 11, 0, 0, &
2416 1, 0, 0, 0, 0, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, -5, 0, 0, &
2417 -1, 0, 1, -1, 1, 0, 0, -1, 0, 0, 0, 0, 0, 0, 0, -5, -2, 0, &
2418 1, 0, 1, -1, 1, 0, 0, -1, 0, 0, 0, 0, 0, 0, 0, 5, 3, 0 /
2419
2420 data ix65/ -1, 0, 0, 0, 0, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, -5, 0, 0, &
2421 -1, 0, 0, 2, 1, 0, 0, 2, 0, -2, 0, 0, 0, 0, -3, 0, 0, 2, &
2422 0, 0, 0, 0, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, 20, 10, 0, 0, &
2423 -1, 0, 0, 2, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, -34, 0, 0, 0, &
2424 -1, 0, 0, 2, 0, 0, 3, -3, 0, 0, 0, 0, 0, 0, -19, 0, 0, 0, &
2425 1, 0, 0, -2, 1, 0, 0, -2, 0, 2, 0, 0, 0, 0, 3, 0, 0, -2, &
2426 1, 0, 2, -2, 2, 0, -3, 3, 0, 0, 0, 0, 0, 0, -3, 0, 0, 1, &
2427 1, 0, 2, -2, 2, 0, 0, -2, 0, 2, 0, 0, 0, 0, -6, 0, 0, 3, &
2428 1, 0, 0, 0, 0, 0, 1, -1, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, &
2429 1, 0, 0, 0, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, 3, 0, 0, 0 /
2430
2431 data ix66/ 0, 0, 0, -2, 0, 0, 2, -2, 0, 0, 0, 0, 0, 0, 3, 0, 0, 0, &
2432 0, 0, 0, -2, 0, 0, 0, 1, 0, -1, 0, 0, 0, 0, 4, 0, 0, 0, &
2433 0, 0, 2, 0, 2, 0, -2, 2, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, &
2434 0, 0, 2, 0, 2, 0, 0, -1, 0, 1, 0, 0, 0, 0, 6, 0, 0, -3, &
2435 0, 0, 2, 0, 2, 0, -1, 1, 0, 0, 0, 0, 0, 0, -8, 0, 0, 3, &
2436 0, 0, 2, 0, 2, 0, -2, 3, 0, 0, 0, 0, 0, 0, 0, 3, 1, 0, &
2437 0, 0, 0, 2, 0, 0, 0, 2, 0, -2, 0, 0, 0, 0, -3, 0, 0, 0, &
2438 0, 0, 1, 1, 2, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, -3, -2, 0, &
2439 1, 0, 2, 0, 2, 0, 0, 1, 0, 0, 0, 0, 0, 0, 126, -63, -27, -55, &
2440 -1, 0, 2, 0, 2, 0, 10, -3, 0, 0, 0, 0, 0, 0, -5, 0, 1, 2 /
2441
2442 data ix67/ 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, -3, 28, 15, 2, &
2443 1, 0, 2, 0, 2, 0, 0, 1, 0, 0, 0, 0, 0, 0, 5, 0, 1, -2, &
2444 0, 0, 2, 0, 2, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, 9, 4, 1, &
2445 0, 0, 2, 0, 2, 0, 0, -4, 8, -3, 0, 0, 0, 0, 0, 9, 4, -1, &
2446 -1, 0, 2, 0, 2, 0, 0, -4, 8, -3, 0, 0, 0, 0, -126, -63, -27, 55, &
2447 2, 0, 2, -2, 2, 0, 0, -2, 0, 3, 0, 0, 0, 0, 3, 0, 0, -1, &
2448 1, 0, 2, 0, 1, 0, 0, -2, 0, 3, 0, 0, 0, 0, 21, -11, -6, -11, &
2449 0, 0, 1, 1, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, &
2450 -1, 0, 2, 0, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, -21, -11, -6, 11, &
2451 -2, 0, 2, 2, 2, 0, 0, 2, 0, -2, 0, 0, 0, 0, -3, 0, 0, 1 /
2452
2453 data ix68/ 0, 0, 2, 0, 2, 0, 2, -3, 0, 0, 0, 0, 0, 0, 0, 3, 1, 0, &
2454 0, 0, 2, 0, 2, 0, 1, -1, 0, 0, 0, 0, 0, 0, 8, 0, 0, -4, &
2455 0, 0, 2, 0, 2, 0, 0, 1, 0, -1, 0, 0, 0, 0, -6, 0, 0, 3, &
2456 0, 0, 2, 0, 2, 0, 2, -2, 0, 0, 0, 0, 0, 0, -3, 0, 0, 1, &
2457 -1, 0, 2, 2, 2, 0, 0, -1, 0, 1, 0, 0, 0, 0, 3, 0, 0, -1, &
2458 1, 0, 2, 0, 2, 0, -1, 1, 0, 0, 0, 0, 0, 0, -3, 0, 0, 1, &
2459 -1, 0, 2, 2, 2, 0, 0, 2, 0, -3, 0, 0, 0, 0, -5, 0, 0, 2, &
2460 2, 0, 2, 0, 2, 0, 0, 2, 0, -3, 0, 0, 0, 0, 24, -12, -5, -11, &
2461 1, 0, 2, 0, 2, 0, 0, -4, 8, -3, 0, 0, 0, 0, 0, 3, 1, 0, &
2462 1, 0, 2, 0, 2, 0, 0, 4, -8, 3, 0, 0, 0, 0, 0, 3, 1, 0 /
2463
2464 data ix69/ 1, 0, 1, 1, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 3, 2, 0, &
2465 0, 0, 2, 0, 2, 0, 0, 1, 0, 0, 0, 0, 0, 0, -24, -12, -5, 10, &
2466 2, 0, 2, 0, 1, 0, 0, 1, 0, 0, 0, 0, 0, 0, 4, 0, -1, -2, &
2467 -1, 0, 2, 2, 2, 0, 0, 2, 0, -2, 0, 0, 0, 0, 13, 0, 0, -6, &
2468 -1, 0, 2, 2, 2, 0, 3, -3, 0, 0, 0, 0, 0, 0, 7, 0, 0, -3, &
2469 1, 0, 2, 0, 2, 0, 1, -1, 0, 0, 0, 0, 0, 0, 3, 0, 0, -1, &
2470 0, 0, 2, 2, 2, 0, 0, 2, 0, -2, 0, 0, 0, 0, 3, 0, 0, -1 /
2471
2472
2473 !**** Initialize the values and sum over the series
2474
2475 dpsi = 0.0d0
2476 deps = 0.0d0
2477
2478 do i = num_plan, 1, -1
2479
2480 ! Sum the mulitpliers by the arguments to the argument of
2481 ! nutation
2482 arg = 0.d0
2483 dargdt = 0.d0
2484 do j = 1,14
2485
2486 ! Planetary values
2487 arg = arg + plan_int(j,i)*plan_arg(j)
2488 dargdt = dargdt + plan_int(j,i)*plan_rat(j)
2489 end do
2490
2491 arg = mod(arg, 2.d0*pi)
2492 carg = cos(arg)
2493 sarg = sin(arg)
2494 ! MOD TAH 010819: Removed the d4 from the period since rates
2495 ! are now in rads/yr rather than rads/1.d4 yrs.
2496 ! Output period is in Julian days.
2497 period = (2*pi/dargdt)*365.25d0
2498
2499 !**** Now add contributions to dpsi and deps
2500 dpsi = dpsi + (plan_int(15,i)*sarg + plan_int(16,i)*carg) * 1.d-4
2501 deps = deps + (plan_int(17,i)*sarg + plan_int(18,i)*carg) * 1.d-4
2502
2503 if( out(1:3).eq.'YES' ) then
2504 amp = sqrt( ( dble(plan_int(15,i)**2 + plan_int(16,i)**2)*0.4d0**2 + plan_int(17,i)**2 + plan_int(18,i)**2) * 1.d-8 )
2505 write(*,175) i, (plan_int(j,i), j=1,14), period, (plan_int(j,i)*1.d-4, j=15,18), amp
2506175 format(i4,14(1x,i3),1x,f11.2,1x,2(f8.4,1x,f8.4,2x), 1x,f8.4)
2507 end if
2508
2509 end do
2510
2511 end subroutine eval_plan_nut
2512 !*********************************************************************************************************************************
2513
2514
2515
2516
2517
2518
2519
2520
2521 !TITLE 'PLAN_ANGLES'
2522
2523 !*********************************************************************************************************************************
2524 !> \brief Compute of planetary arguments for planetary nutation.
2525 !!
2526 !! \param epoch Julian day (input)
2527 !! \param plan_arg Planetary arguments for longtitudes of L, L', F, D, Om, Mercury, Ven, Ear, Mar, Jup, Sat, Ura, Ura(?), pa.
2528 !! \param plan_rat Planetary argument rates (rads/year)
2529 !!
2530 subroutine plan_angles( epoch, plan_arg, plan_rat )
2531 use sufr_kinds, only: double
2532 implicit none
2533
2534
2535 ! Routine to compute of planetary arguments for planetary
2536 ! nutation. The longitudes of the major planets is computed
2537 ! according to:
2538 !
2539 ! Arguments based on Souchay, Loysel, Kinoshita, Folgueira, Corrections
2540 ! and new developments in rigid earth nutation theory, Aston. Astrophys.
2541 ! Suppl. Ser, 135, 111-131, (1999)
2542 !
2543
2544
2545
2546 ! PHYSICAL CONSTANTS NEEDED FOR SD_COMP
2547
2548 ! pi - Define here to full precision
2549 ! DJ2000 - Julian date of J2000
2550
2551 !real(double), parameter :: pi = 3.1415926535897932d0
2552 real(double), parameter :: DJ2000 = 2451545.d0
2553
2554
2555 ! PASSED VARIABLES
2556
2557 ! INPUT
2558 ! epoch - Julian date plus fraction of a day
2559 !
2560 ! OUTPUT
2561 ! plan_arg(14) - Planetary arguments for longtitudes of
2562 ! L, L', F, D, Om, Mercury, Venus, Earth, Mars,
2563 ! Jupiter, Saturn, Uranus, Uranus(?), pa.
2564 ! plan_rat(14) - Planetary argument rates (rads/year)
2565
2566 real(double), intent(in) :: epoch
2567 real(double), intent(out) :: plan_arg(14), plan_rat(14)
2568
2569 ! LOCAL VARIABLES
2570 ! cent - Centuries since J2000.
2571 ! nl - Mecurcy longitude (rads)
2572 ! nlc(2) - coefficients for computing nl
2573 ! vl - Venus longitude (rads)
2574 ! vlc(2) - coefficients for computing vl
2575 ! tl - Earth longitude (rads)
2576 ! tlc(2) - coefficients for computing tl
2577 ! ml - Mars longitude (rads)
2578 ! mlc(2) - coefficients for computing ml
2579 ! jl - Jupliter longitude (rads)
2580 ! jlc(2) - coefficients for computing jl
2581 ! sl - Saturn longitude (rads)
2582 ! slc(2) - coefficients for computing sl
2583 ! ul - Uranus longitude (rads)
2584 ! ulc(2) - coefficients for computing ul
2585 ! xl - Neptune longitude (rads)
2586 ! xlc(2) - coefficients for compulting xl
2587 ! lm - Mean longitude of moon minus mean longitude
2588 ! of perigee (rads)
2589 ! lmc(2) - Coefficients for computing lm
2590 ! sl - Sun longitude (rads)
2591 ! slc(2) - coefficients for computing sl
2592 ! Fr - Moon's mean longitude minus Om (rad)
2593 ! Frc(2) - Coefficients for computing Fr
2594 ! Dr - Mean elongation of the Moon from the Sun (rads)
2595 ! drc(2) - Coefficients for computing dc
2596 ! Om - Longitude of the ascending node of the moon's
2597 ! mean orbit on the elliptic (rad)
2598 ! Omc(2) - Coefficients for computing Om
2599 ! pa - pa (rads)
2600 ! pac(2) - Coefficients for computing pa from KS1990.
2601 ! (Values converted from rates and acceleration
2602 ! in 1000's year to centuries).
2603
2604 real(double) :: cent, nl, nlc(2), vl, vlc(2), tl, tlc(2), ml, mlc(2), &
2605 jl, jlc(2), sl, slc(2), ul, ulc(2), xl, xlc(2), &
2606 pa, pac(2), Dr, drc(2), Fr, frc(2), &
2607 lm, lmc(2), ls, lsc(2), Om, Omc(2)
2608
2609 data nlc / 4.402608842d0, 2608.7903141574d0 /
2610 data vlc / 3.176146697d0, 1021.3285546211d0 /
2611 data tlc / 1.753470314d0, 628.3075849991d0 /
2612 data mlc / 6.203480913d0, 334.0612426700d0 /
2613 data jlc / 0.599546497d0, 52.9690962641d0 /
2614 data slc / 0.874016757d0, 21.3299104960d0 /
2615 data ulc / 5.481293871d0, 7.4781598567d0 /
2616 data xlc / 5.321159000d0, 3.8127774000d0 /
2617 data lmc / 2.355555980d0, 8328.6914269554d0 /
2618 data lsc / 6.240060130d0, 628.301955d0 /
2619 data frc / 1.627905234d0, 8433.466158131d0 /
2620 data drc / 5.198466741d0, 7771.3771468121d0 /
2621 data omc / 2.182439200d0, -33.757045d0 /
2622 data pac / 0.2438175d-1, 0.000538691d-2 /
2623
2624 !***** Get number of Centuries since J2000
2625
2626 cent = (epoch-dj2000) / 36525.d0
2627
2628 ! Compute arguments
2629 nl = nlc(1) + nlc(2)*cent
2630 vl = vlc(1) + vlc(2)*cent
2631 tl = tlc(1) + tlc(2)*cent
2632 ml = mlc(1) + mlc(2)*cent
2633 jl = jlc(1) + jlc(2)*cent
2634 sl = slc(1) + slc(2)*cent
2635 ul = ulc(1) + ulc(2)*cent
2636 xl = xlc(1) + xlc(2)*cent
2637 lm = lmc(1) + lmc(2)*cent
2638 ls = lsc(1) + lsc(2)*cent
2639 fr = frc(1) + frc(2)*cent
2640 dr = drc(1) + drc(2)*cent
2641 om = omc(1) + omc(2)*cent
2642 pa = pac(1)*cent + pac(2)*cent**2
2643
2644 !**** Now save the values
2645 plan_arg( 1) = lm
2646 plan_arg( 2) = ls
2647 plan_arg( 3) = fr
2648 plan_arg( 4) = dr
2649 plan_arg( 5) = om
2650 plan_arg( 6) = nl
2651 plan_arg( 7) = vl
2652 plan_arg( 8) = tl
2653 plan_arg( 9) = ml
2654 plan_arg(10) = jl
2655 plan_arg(11) = sl
2656 plan_arg(12) = ul
2657 plan_arg(13) = xl
2658 plan_arg(14) = pa
2659
2660 !**** Now save the rates (useful if periods are wanted)
2661 ! MOD TAH 010819: Changed *100.d0 to /100.d0 to make rates
2662 ! in radians/year rather than radians/10000 year. Also
2663 ! need to correct period calculation in eval_plan_nut
2664 plan_rat( 1) = lmc(2)/100.d0
2665 plan_rat( 2) = lsc(2)/100.d0
2666 plan_rat( 3) = frc(2)/100.d0
2667 plan_rat( 4) = drc(2)/100.d0
2668 plan_rat( 5) = omc(2)/100.d0
2669 plan_rat( 6) = nlc(2)/100.d0
2670 plan_rat( 7) = vlc(2)/100.d0
2671 plan_rat( 8) = tlc(2)/100.d0
2672 plan_rat( 9) = mlc(2)/100.d0
2673 plan_rat(10) = jlc(2)/100.d0
2674 plan_rat(11) = slc(2)/100.d0
2675 plan_rat(12) = ulc(2)/100.d0
2676 plan_rat(13) = xlc(2)/100.d0
2677 plan_rat(14) = pac(1)/100.d0 + 2*pac(2)*cent/100.d0
2678
2679
2680 end subroutine plan_angles
2681 !*********************************************************************************************************************************
2682
2683
2684
2685
2686
2687
2688
2689
2690
2691
2692 !TITLE FCN_NUT
2693
2694 !*********************************************************************************************************************************
2695 !> \brief Compute the consttributions of the freely excited FCN mode to the nutations in longitude and obliquity.
2696 !!
2697 !! \param jd Julian day (input)
2698 !! \param dpsi_fcn Contribution to the nutation in longitude (output; milliarcsec)
2699 !! \param deps_fcn Contribution to the nutation in obliquity (output; milliarcsec)
2700 !!
2701 subroutine fcn_nut ( jd, dpsi_fcn, deps_fcn )
2702 use sufr_kinds, only: double
2703 implicit none
2704
2705 ! Routine to compute the consttributions of the freely excited
2706 ! FCN mode to the nutations in longitude and obliquity.
2707
2708 ! USAGE:
2709 ! call fcn_nut( jd, dpsi_fcn, deps_fcn )
2710 ! where <jd> is a full julian date with fractional part
2711 ! of the day added (REAL(DOUBLE) INPUT)
2712 ! and <dpsi_fcn> and <deps_fcn> are the contributions to the nutations
2713 ! in longitude and obliquity in milliarcsec.
2714 ! (REAL(DOUBLE) OUTPUT)
2715
2716 ! RESTRICTIONS: if <jd> is less than 2000000.0 this routine
2717 ! assumes an MJD has been passed and the time
2718 ! used will be converted to JD. A warning
2719 ! message will be printed.
2720
2721 ! RESTRICTIONS: This term represents as free excitation mode and
2722 ! therefore will change with time (in much the same
2723 ! way that the Chandler Wobble changes). The
2724 ! frequency of the FCN used here is accurate, but
2725 ! coefficients used will depend on time. The values
2726 ! are interpolated over the 1979-2000 interval with
2727 ! the first or last values being used outside of these
2728 ! times.
2729
2730 ! PARAMETERS:
2731
2732 ! DJ2000 - Julian date of J2000
2733 ! solar_to_sidereal - Conversion from solar days to sidereal
2734 ! days.
2735 ! num_fcn - Number of FCN amplitudes (linear interpolation between
2736 ! values).
2737
2738
2739 real(double) :: DJ2000, pi, solar_to_sidereal
2740
2741 integer :: num_fcn
2742
2743 parameter( pi = 3.1415926535897932d0 )
2744 parameter( dj2000 = 2451545.d0 )
2745 parameter( solar_to_sidereal = 1.00273790935d0 )
2746 parameter( num_fcn = 11 )
2747
2748 ! PASSED VARIABLES
2749 !
2750 ! INPUT Values
2751 ! jd - Time at which value needed. (jd + fraction of day)
2752
2753 ! OUTPUT Values
2754 ! dpsi_fcn - Contribution to the nutation in longitude (mas). Should
2755 ! be added to standard nutation in longitude values.
2756 ! deps_fcn - Contribution to the nutation in obliquity (mas). Should
2757 ! be added to standard nutation in obliquity values.
2758
2759
2760 real(double), intent(in) :: jd
2761 real(double), intent(out) :: dpsi_fcn, deps_fcn
2762
2763 ! LOCAL VARIABLES
2764
2765 ! epoch - Julian date (jd passed in unless the JD
2766 ! appears to be an MJD in which case it is
2767 ! converted to JD (2 400 000.5d0 added)
2768
2769 ! fcn_freq - Freqency of the FCN mode (cycles per sidreal day).
2770 ! fcn_arg - Argument for the fcn mode computed from J2000 (rad).
2771 ! fcn_tabl(2, num_fcn) - Amplitude for the fcn free exciation. These
2772 ! are converted to nutation in longitude and obliquity. (mas)
2773 ! fcn_ampl(2) - Interpolated FCN amplitude (mas)
2774 ! fcn_jd(num_fcn) - Starting epochs for the fcn amplitudes (JD). These
2775 ! epochs are the midpoints of the intervals overwhich the
2776 ! FCN free terms have been estimated.
2777 ! sine - Sine of the mean obliquity of the ecliptic. (A constant
2778 ! value can be used here since the changes are small for
2779 ! this constribtion i.e., between 1980 and 2000 the error
2780 ! in the nutation in longitude is only 0.05 micro-arc-sec.
2781 ! Values based on 8438.14059" at J2000 (IERS 2000 Conventions)
2782 ! dt - Time difference between epoch and tabular interval (days)
2783 ! dt_tab - Time difference in tables values.
2784 ! dfcn_amp(2) - Change in FCN amplitude between tabular points (mas)
2785
2786
2787 real(double) :: epoch, fcn_freq, fcn_arg, fcn_ampl(2), fcn_tabl(2,num_fcn), sine, fcn_jd(num_fcn), dt, dt_tab, dfcn_amp(2)
2788
2789 ! i - A counter used in do loop to find the correct pair of
2790 ! amplitudes to use
2791
2792 integer :: i
2793
2794 data fcn_freq / -1.00231810920d0 /
2795
2796 ! FCN estimated values (by time range, peicewise linear function)
2797 ! Node date Cos +- Sin +-
2798 ! 1979/ 1/ 1 -0.0620 0.1256 -0.1346 0.1293 mas
2799 ! 1984/ 1/ 1 0.0447 0.0302 -0.1679 0.0309 mas
2800 ! 1986/ 1/ 1 0.2406 0.0163 -0.2759 0.0159 mas
2801 ! 1988/ 1/ 1 0.1183 0.0127 -0.2163 0.0128 mas
2802 ! 1990/ 1/ 1 0.0479 0.0084 -0.1965 0.0083 mas
2803 ! 1992/ 1/ 1 -0.0796 0.0071 -0.1321 0.0071 mas
2804 ! 1994/ 1/ 1 -0.0075 0.0057 -0.1150 0.0057 mas
2805 ! 1996/ 1/ 1 -0.0128 0.0058 -0.0998 0.0058 mas
2806 ! 1998/ 1/ 1 -0.0263 0.0059 -0.1122 0.0059 mas
2807 ! 2000/ 1/ 1 0.0519 0.0071 0.0081 0.0070 mas
2808 ! 2001/ 6/ 1 0.2100 0.0162 0.1401 0.0163 mas
2809
2810 ! These are the estimated values with their standard deviations.
2811 ! Due to the large standard deviation of thr 1979 node, we replace
2812 ! its value with the 1984 value, thus maintaining a constant amplitude
2813 ! between 1979 and 1984.
2814
2815 ! Time dependent values
2816 data fcn_jd / 2443874.5d0, 2445700.5d0, 2446431.5d0, 2447161.5d0, 2447892.5d0, 2448622.5d0, &
2817 2449353.5d0, 2450083.5d0, 2450814.5d0, 2451544.5d0, 2452061.5d0 /
2818
2819
2820 data fcn_tabl / -0.062d0, -0.135d0, 0.045d0, -0.168d0, 0.241d0, -0.276d0, 0.118d0, -0.216d0, &
2821 0.048d0, -0.197d0, -0.080d0, -0.132d0, -0.007d0, -0.115d0, -0.013d0, -0.100d0, &
2822 -0.026d0, -0.112d0, 0.052d0, 0.008d0, 0.210d0, 0.140d0 /
2823
2824 data sine / 0.3977769687d0 /
2825
2826 fcn_ampl(1:2) = 0.d0
2827
2828 !***** Check to make sure user passed JD and not MJD. Correct
2829 ! problem and warn the user.
2830 ! MvdS: remove this 'solution'
2831 !if( jd .lt.2000000.0d0 ) then
2832 ! write(*,100) jd
2833 ! 100 format('**WARNING** MJD apparently passed to FCN_NUT',
2834 ! . ' Value (',F10.2,') converted to JD')
2835 ! epoch = jd + 2 400 000.5d0
2836 !else
2837 ! epoch = jd
2838 !end if
2839 epoch = jd
2840
2841 !**** Find out which table values we should use.
2842 if( epoch.le.fcn_jd(1) ) then
2843 fcn_ampl(1) = fcn_tabl(1,1)
2844 fcn_ampl(2) = fcn_tabl(2,1)
2845 else if( epoch.ge. fcn_jd(num_fcn) ) then
2846 fcn_ampl(1) = fcn_tabl(1,num_fcn)
2847 fcn_ampl(2) = fcn_tabl(2,num_fcn)
2848 else
2849 do i = 1, num_fcn-1
2850 if( epoch.ge.fcn_jd(i) .and. epoch.lt.fcn_jd(i+1) ) then
2851 dt = epoch - fcn_jd(i)
2852 dt_tab = fcn_jd(i+1) - fcn_jd(i)
2853 dfcn_amp(1) = fcn_tabl(1,i+1) - fcn_tabl(1,i)
2854 dfcn_amp(2) = fcn_tabl(2,i+1) - fcn_tabl(2,i)
2855 fcn_ampl(1) = fcn_tabl(1,i) + (dfcn_amp(1)/dt_tab)*dt
2856 fcn_ampl(2) = fcn_tabl(2,i) + (dfcn_amp(2)/dt_tab)*dt
2857 end if
2858 end do
2859 end if
2860
2861
2862 !***** Get the argument for the FCN mode at this times
2863
2864 fcn_arg = -2*pi*(1.d0+fcn_freq)*solar_to_sidereal*(epoch-dj2000)
2865
2866 dpsi_fcn = (-fcn_ampl(1)*sin(fcn_arg) + fcn_ampl(2)*cos(fcn_arg))/sine
2867
2868 deps_fcn = (-fcn_ampl(1)*cos(fcn_arg) - fcn_ampl(2)*sin(fcn_arg))
2869
2870 end subroutine fcn_nut
2871 !*********************************************************************************************************************************
2872
2873
2874
2875
2876
2877
2878
2879
2880
2881
2882 !TITLE PREC_NUT
2883
2884 !*********************************************************************************************************************************
2885 !> \brief Evaluate the corrections to the nutations in longitude and obliquity due to the corrections to the
2886 !! IAU-1976 Luni-solar precession constant and the secular rate of change of the obliquity of the ecliptic.
2887 !!
2888 !! \param jd Julian day (input)
2889 !! \param dpsi_prec Contribution to the nutation in longitude (output; mas)
2890 !! \param deps_prec Contribution to the nutation in obliquity (output; mas)
2891
2892 subroutine prec_nut( jd, dpsi_prec, deps_prec )
2893 use sufr_kinds, only: double
2894 implicit none
2895
2896 ! Routine to evaluate the corrections to the nutations in longitude
2897 ! and obliquity due to the corrections to the IAU-1976 Luni-solar
2898 ! precession constant and the secular rate of change of the obliquity
2899 ! of the ecliptic.
2900
2901 ! PARAMETERS:
2902
2903 ! DJ2000 - Julian date of J2000
2904
2905
2906 real(double) :: DJ2000
2907
2908 parameter( dj2000 = 2451545.d0 )
2909
2910 ! PASSED VARIABLES
2911 !
2912 ! INPUT Values
2913 ! jd - Time at which value needed. (jd + fraction of day)
2914
2915 ! OUTPUT Values
2916 ! dpsi_prec - Contribution to the nutation in longitude (mas). Should
2917 ! be added to standard nutation in longitude values. Value
2918 ! valid only when the IAU-1976 precession constant used to
2919 ! compute the transformation to mean system.
2920 ! deps_prec - Contribution to the nutation in obliquity (mas). Should
2921 ! be added to standard nutation in obliquity values.
2922
2923
2924 real(double), intent(in) :: jd
2925 real(double), intent(out) :: dpsi_prec, deps_prec
2926
2927 ! LOCAL VARIABLES
2928
2929 ! epoch - Julian date (jd passed in unless the JD
2930 ! appears to be an MJD in which case it is
2931 ! converted to JD (2 400 000.5d0 added)
2932 ! cent - Number of Julian centuries since J2000.0
2933 ! DpsiDt - Correction to precession constant as a
2934 ! linear rate of change of nutation in
2935 ! longitude. (arc-second/century)
2936 ! DepsDt - Correction to rate of change of oblquity
2937 ! (arc-second/century)
2938
2939
2940
2941 real(double) :: epoch, cent, DpsiDt, DepsDt
2942 !
2943 ! Theoretical estimaate of adjustment to precession constant is
2944 ! -0.29965 "/cent; estimate is -0.29965 +- 0.0004 "/cent.
2945
2946 data dpsidt / -0.29965d0 /
2947 data depsdt / -0.02524d0 /
2948
2949 !***** Check to make sure user passed JD and not MJD. Correct
2950 ! problem and warn the user.
2951 ! MvdS: remove this 'solution'
2952 !if( jd .lt.2000000.0d0 ) then
2953 ! write(*,100) jd
2954 ! 100 format('**WARNING** MJD apparently passed to SD_COMP',
2955 ! . ' Value (',F10.2,') converted to JD')
2956 ! epoch = jd + 2 400 000.5d0
2957 !else
2958 ! epoch = jd
2959 !end if
2960 epoch = jd
2961
2962 !**** Compute the number of centuries
2963
2964 cent = (epoch - dj2000)/36525.d0
2965
2966 dpsi_prec = dpsidt*cent*1000.d0
2967 deps_prec = depsdt*cent*1000.d0
2968
2969 end subroutine prec_nut
2970 !*********************************************************************************************************************************
2971
2972
2973
2974
2975
2976
2977
2978
2979
2980
2981
2982 !TITLE ls_iau76
2983
2984 !*********************************************************************************************************************************
2985 !> \brief Compute the value of the fundamental argument for Brown's arguments.
2986 !!
2987 !! \param epoch Julian day (input)
2988 !! \param ls_arg Brown's arguments (output; rad)
2989
2990 subroutine ls_iau76( epoch, ls_arg )
2991 use sufr_kinds, only: double
2992 implicit none
2993
2994 ! Routine to compute the value of the fundamental argument
2995 ! for Brown's arguments. Arguments based on the IERS
2996 ! standards.
2997
2998 ! PHYSICAL CONSTANTS
2999
3000 ! pi - Define here to full precision
3001 ! rad_to_deg - Conversion from radians to degs.
3002 ! DJ2000 - Julian date of J2000
3003 ! sec360 - number of seconds in 360 degreees.
3004
3005
3006 real(double) :: pi, rad_to_deg, DJ2000, sec360
3007
3008 parameter( pi = 3.1415926535897932d0 )
3009 parameter( dj2000 = 2451545.d0 )
3010 parameter( sec360 = 1296000.d0 )
3011
3012 ! Computed quanities
3013 parameter( rad_to_deg = 180.d0 /pi )
3014
3015 !-------------------------------------------------------------------
3016
3017 ! PASSED VARIABLES
3018
3019 ! INPUT
3020 ! epoch - Julian date for arguments (jd + fraction of day, REAL(DOUBLE))
3021
3022 ! OUTPUT
3023 ! ls_arg(5) - Brown's arguments (radians, REAL(DOUBLE))
3024
3025
3026 real(double), intent(in) :: epoch
3027 real(double), intent(out) :: ls_arg(5)
3028
3029 ! LOCAL VARIABLES
3030 ! cent - Julian centuries to DJ2000.
3031 ! el,eld - Mean longitude of moon minus mean
3032 ! - longitude of moon's perigee (arcsec)
3033 ! elc(5) - Coefficients for computing el
3034 ! elp,elpd - Mean longitude of the sun minus mean
3035 ! - longitude of sun perigee (arcsec)
3036 ! elpc(5) - Coeffiecents for computing elp
3037 ! f,fd - Moon's mean longitude minus omega (sec)
3038 ! fc(5) - Coefficients for computing f
3039 ! d,dd - Mean elongation of the moon from the
3040 ! - sun (arcsec)
3041 ! dc(5) - coefficients for computing d
3042 ! om,omd - longitude of the ascending node of the
3043 ! - moon's mean orbit on the elliptic
3044 ! - measured from the mean equinox of date
3045 ! omc(5) - Coefficients for computing om.
3046
3047
3048 real(double) :: cent, el, elc(5), elp, elpc(5), f, fc(5), d, dc(5), om, omc(5) ! ,eld , elpd ,fd ,dd ,omd
3049
3050 !**** DATA statements for the fundamental arguments.
3051
3052 data elc / 0.064d0, 31.310d0, 715922.633d0, 485866.733d0, 1325.0d0 /
3053 data elpc / -0.012d0, -0.577d0, 1292581.224d0, 1287099.804d0, 99.0d0 /
3054 data fc / 0.011d0, -13.257d0, 295263.137d0, 335778.877d0, 1342.0d0 /
3055 data dc / 0.019d0, -6.891d0, 1105601.328d0, 1072261.307d0, 1236.0d0 /
3056 data omc / 0.008d0, 7.455d0, -482890.539d0, 450160.280d0, -5.0d0 /
3057
3058 !**** Get the number of centuries to current time
3059
3060 cent = (epoch-dj2000) / 36525.d0
3061
3062 !**** Compute angular arguments
3063 el = elc(1) * cent**3 + elc(2) * cent**2 + elc(3) * cent + elc(4) + mod( elc(5) * cent, 1.d0 ) * sec360
3064 el = mod( el, sec360 )
3065 !eld = 3.d0 * elc(1) * cent**2 + 2.d0 * elc(2) * cent + elc(3) + elc(5) * sec360
3066
3067 elp = elpc(1) * cent**3 + elpc(2) * cent**2 + elpc(3) * cent + elpc(4) + mod( elpc(5) * cent, 1.d0 ) * sec360
3068 elp = mod( elp, sec360 )
3069 !elpd = 3.d0 * elpc(1) * cent**2 + 2.d0 * elpc(2) * cent + elpc(3) + elpc(5) * sec360
3070
3071 f = fc(1) * cent**3 + fc(2) * cent**2 + fc(3) * cent + fc(4) + mod( fc(5) * cent, 1.d0 ) * sec360
3072 f = mod( f, sec360 )
3073 !fd = 3.d0 * fc(1) * cent**2 + 2.d0 * fc(2) * cent + fc(3) + fc(5) * sec360
3074
3075 d = dc(1) * cent**3 + dc(2) * cent**2 + dc(3) * cent + dc(4) + mod( dc(5) * cent, 1.d0 ) * sec360
3076 d = mod( d, sec360 )
3077 !dd = 3.d0 * dc(1) * cent**2 + 2.d0 * dc(2) * cent + dc(3) + dc(5) * sec360
3078
3079 om = omc(1) * cent**3 + omc(2) * cent**2 + omc(3) * cent + omc(4) + mod( omc(5) * cent, 1.d0 ) * sec360
3080 om = mod( om, sec360 )
3081 !omd = 3.d0 * omc(1) * cent**2 + 2.d0 * omc(2) * cent + omc(3) + omc(5) * sec360
3082
3083
3084 !**** Now save the values. Convert values from arcseconds to radians
3085
3086 ls_arg(1) = el / (3600.d0*rad_to_deg)
3087 ls_arg(2) = elp/ (3600.d0*rad_to_deg)
3088 ls_arg(3) = f / (3600.d0*rad_to_deg)
3089 ls_arg(4) = d / (3600.d0*rad_to_deg)
3090 ls_arg(5) = om / (3600.d0*rad_to_deg)
3091
3092 end subroutine ls_iau76
3093 !*********************************************************************************************************************************
3094
3095
3096end module thesky_nutation
3097!***********************************************************************************************************************************
3098
Constants used in libTheSky.
Definition modules.f90:23
real(double), dimension(9, 63) nutationdat
Data for simple nutation function.
Definition modules.f90:44
Procedures for nutation.
Definition nutation.f90:25
subroutine ls_angles(epoch, ls_arg)
compute the value of the fundamental argument for Brown's arguments.
Definition nutation.f90:383
subroutine fcn_nut(jd, dpsi_fcn, deps_fcn)
Compute the consttributions of the freely excited FCN mode to the nutations in longitude and obliquit...
subroutine eval_plan_nut(plan_arg, plan_rat, dpsi, deps, out)
Compute the planetary nutations by summing over the KS1990 coefficients.
subroutine plan_nut(jd, dpsi, deps)
Compute the planetary contribution to the nutations.
subroutine nutation(t, dpsi, eps0, deps)
Calculate nutation - cheap routine from Meeus - as well as the mean obliquity of the ecliptic.
Definition nutation.f90:46
subroutine ls_nut(jd, dpsi_ls, deps_ls)
Compute the MHB_2000 luni-solar contributions the nutations in longitude and obliquity.
Definition nutation.f90:240
subroutine eval_ls_nut(epoch, ls_arg, dpsi_ls, deps_ls)
Compute the nutations in longitude and obliquity by summing over all terms in the nutations series.
Definition nutation.f90:521
subroutine prec_nut(jd, dpsi_prec, deps_prec)
Evaluate the corrections to the nutations in longitude and obliquity due to the corrections to the IA...
subroutine nutation2000(jd, dpsi_tot, deps_tot, eps0)
Compute nutation using the IAU 2000 model. Add the mean obliquity of the ecliptic by Laskar (1986).
Definition nutation.f90:102
subroutine ls_iau76(epoch, ls_arg)
Compute the value of the fundamental argument for Brown's arguments.
subroutine plan_angles(epoch, plan_arg, plan_rat)
Compute of planetary arguments for planetary nutation.
subroutine out_plan_nut()
Write the planetary contribution to the nutations to stdout.