File Coverage

blib/lib/Astro/Coord/ECI/TLE/Iridium.pm
Criterion Covered Total %
statement 351 388 90.4
branch 77 130 59.2
condition 11 50 22.0
subroutine 47 52 90.3
pod 10 10 100.0
total 496 630 78.7


line stmt bran cond sub pod time code
1             =head1 NAME
2              
3             Astro::Coord::ECI::TLE::Iridium - Compute behavior of Iridium satellites
4              
5             =head1 SYNOPSIS
6              
7             The following is a semi-brief script to calculate Iridium flares. You
8             will need to substitute your own location where indicated.
9              
10             use Astro::SpaceTrack;
11             use Astro::Coord::ECI;
12             use Astro::Coord::ECI::TLE;
13             use Astro::Coord::ECI::Utils qw{deg2rad rad2deg};
14              
15             # 1600 Pennsylvania Avenue, Washington DC, USA
16             my $your_north_latitude_in_degrees = 38.898748;
17             my $your_east_longitude_in_degrees = -77.037684;
18             my $your_height_above_sea_level_in_meters = 16.68;
19            
20             # Create object representing the observers' location.
21             # Note that the input to geodetic() is latitude north
22             # and longitude west, in RADIANS, and height above sea
23             # level in KILOMETERS.
24            
25             my $loc = Astro::Coord::ECI->geodetic (
26             deg2rad ($your_north_latitude_in_degrees),
27             deg2rad ($your_east_longitude_in_degrees),
28             $your_height_above_sea_level_in_meters/1000);
29            
30             # Get all the Iridium data from CelesTrak; it is direct-
31             # fetched, so no password is needed.
32            
33             my $st = Astro::SpaceTrack->new (direct => 1);
34             my $data = $st->celestrak ('iridium');
35             $data->is_success or die $data->status_line;
36            
37             # Parse the fetched data, yielding Iridium objects.
38            
39             my @sats = Astro::Coord::ECI::TLE->parse ($data->content);
40            
41             # We want flares for the next 2 days. In order to try to
42             # duplicate http://www.heavens-above.com/ as closely as
43             # possible, we throw away daytime flares dimmer than -6,
44             # and nighttime flares dimmer than -1. We also calculate
45             # flares for spares, and assume night is any time the Sun
46             # is below the horizon.
47            
48             my $start = time ();
49             my $finish = $start + 2 * 86400;
50             my @flares;
51             my %mag_limit = (am => -1, day => -6, pm => -1);
52             foreach my $irid (@sats) {
53             $irid->can_flare (1) or next;
54             $irid->set (twilight => 0);
55             foreach my $flare ($irid->flare ($loc, $start, $finish)) {
56             $flare->{magnitude} <= $mag_limit{$flare->{type}}
57             and push @flares, $flare;
58             }
59             }
60             print <
61             Date/Time Satellite Elevation Azimuth Magnitude
62             eod
63             foreach my $flare (sort {$a->{time} <=> $b->{time}} @flares) {
64            
65             # If we wanted to make use of the Iridium object that
66             # produced the flare (e.g. to get apparant equatorial
67             # coordinates) we would need to set the time first.
68             ## $flare->{body}->universal ($flare->{time});
69            
70             # The returned angles are in radians, so we need to
71             # convert back to degrees.
72            
73             printf "%s %-15s %9.1f %9.1f %5.1f\n",
74             scalar localtime $flare->{time},
75             $flare->{body}->get ('name'),
76             rad2deg ($flare->{elevation}),
77             rad2deg ($flare->{azimuth}),
78             $flare->{magnitude};
79             }
80              
81             =head1 NOTICE -- IRIDIUM SUPPORT
82              
83             As of early 2017 the flaring Iridium satellites are being taken out of
84             service, to be replaced by non-flaring Iridium Next satellites. Once the
85             flaring Iridium satellites are out of service, I plan to deprecate and
86             remove all functionality relating to the acquisition of Iridium status.
87              
88             I have not yet decided on the disposition of
89             L. My
90             thought at the moment is that it will be moved to its own package rather
91             than deleted, because the flare functionality may be of historical
92             interest. By the same reasoning, the TLE parsing logic in
93             L will remain able to
94             rebless satellites as Iridium, but the canned status will be 'tumbling'.
95              
96             =head1 DESCRIPTION
97              
98             This class is a subclass of
99             L, representing
100             original-design Iridium satellites. This class will probably B work
101             for the Iridium Next satellites, which are being launched starting early
102             2017.
103              
104             The C<< Astro::Coord::ECI::TLE->parse() >> method makes use of
105             built-in data to determine which satellites to rebless into this class,
106             based on the object's NORAD SATCAT ID. This internal data can be
107             modified using the Astro::Coord::ECI::TLE->status method to correct
108             errors or for historical research. It is also possible to get an Iridium
109             object by calling $tle->rebless (iridium => {status => $status})
110             directly.
111              
112             What this subclass adds is the ability to generate information on
113             Iridium flares (or glints, as they are also called). Members of this
114             class are considered capable of generating flares based on their status,
115             as follows:
116              
117             0 => in service
118             1 => spare (may or may not flare)
119             2 => failed - no predictable flares.
120              
121             CelesTrak-style statuses ('+', 'S', and '-' respectively) are accepted
122             on input. See L method
123             iridium_status for a way to get current Iridium constellation status.
124              
125             =head2 Methods
126              
127             This class adds the following public methods:
128              
129             =over
130              
131             =cut
132              
133             package Astro::Coord::ECI::TLE::Iridium;
134              
135 3     3   260150 use strict;
  3         19  
  3         81  
136 3     3   13 use warnings;
  3         6  
  3         81  
137              
138 3     3   13 use base qw{ Astro::Coord::ECI::TLE };
  3         5  
  3         1647  
139              
140             our $VERSION = '0.131';
141              
142 3     3   107084 use Astro::Coord::ECI::Utils 0.091 qw{:all};
  3         71  
  3         1037  
143 3     3   21 use Carp;
  3         7  
  3         143  
144 3     3   14 use POSIX qw{floor strftime}; # For debugging
  3         5  
  3         18  
145              
146 3     3   228 use constant ATTRIBUTE_KEY => '_sub_TLE_Iridium';
  3         6  
  3         167  
147 3     3   15 use constant DEFAULT_MAX_MIRROR_ANGLE => deg2rad (10);
  3         4  
  3         27  
148 3     3   186 use constant MMAAREA => 1.88 * .86; # Area of MMA, in square meters.
  3         6  
  3         147  
149 3     3   16 use constant MMAPHI => deg2rad (-130); # The MMAs are at an angle of
  3         5  
  3         13  
150             # 40 degrees to the axis, so
151             # we need to lay them back 130
152             # degrees (90 + 40) to make
153             # them "flat".
154 3     3   159 use constant TWOPIOVER3 => TWOPI / 3; # 120 degrees, in radians.
  3         5  
  3         125  
155              
156 3     3   15 use constant BODY_STATUS_IS_OPERATIONAL => 0;
  3         14  
  3         137  
157 3     3   16 use constant BODY_STATUS_IS_SPARE => 1;
  3         6  
  3         123  
158 3     3   24 use constant BODY_STATUS_IS_TUMBLING => 2;
  3         6  
  3         147  
159 3     3   17 use constant BODY_STATUS_IS_DECAYED => 3;
  3         12  
  3         2644  
160              
161             my %mutator = (
162             algorithm => sub {
163             my ( $self, $name, $value ) = @_;
164             my $method = "_flare_$value";
165             croak "Error - Unknown flare algorithm name $value"
166             unless $self->can ($method);
167             $self->{&ATTRIBUTE_KEY}{$name} = $value;
168             $self->{&ATTRIBUTE_KEY}{_algorithm_method} = $method;
169             },
170             status => \&_set_operational_status,
171             );
172             foreach my $key (qw{am day extinction max_mirror_angle pm status zone}) {
173             $mutator{$key} = sub {$_[0]->{&ATTRIBUTE_KEY}{$_[1]} = $_[2]};
174             }
175              
176             my %accessor = ();
177             foreach my $key (keys %mutator) {
178             $accessor{$key} ||= sub {$_[0]->{&ATTRIBUTE_KEY}{$_[1]}}
179             }
180              
181             my %static = ( # static values
182             algorithm => 'fixed',
183             am => 1,
184             day => 1,
185             extinction => 1,
186             intrinsic_magnitude => 7.0,
187             max_mirror_angle => DEFAULT_MAX_MIRROR_ANGLE,
188             pm => 1,
189             status => '',
190             zone => undef, # Offset from GMT, in seconds
191             );
192              
193             my %statatr = ( # for convenience of get() and put().
194             &ATTRIBUTE_KEY => \%static,
195             );
196              
197             __PACKAGE__->alias (iridium => __PACKAGE__);
198              
199             # Pre-compute the transform vectors for each of the three Main
200             # Mission Antennae, so that we do not have to repeatedly compute
201             # the sin and cos of the relevant angles. The transform we are
202             # doing is a rotation of theta radians about the Z axis (theta
203             # being Main Mission Antenna index * 2 * PI / 3) to face the
204             # MMA in the X direction, followed by a rotation of phi radians
205             # about the Y axis (phi being -130 degrees) to lay the MMA back
206             # into the X-Y plane.
207              
208             # Although we are using vector math for the actual operation, the
209             # transform vectors are derived using matrix math, with the
210             # resultant matrix being decomposed into the row vectors we need.
211             # The actual computation is to premultiply the theta transform
212             # matrix by the phi transform matrix:
213              
214             # +- -+ +- -+
215             # | cos(phi) 0 sin(phi) | | cos(theta) -sin(theta) 0 |
216             # | 0 1 0 | X | sin(theta) cos(theta) 0 |
217             # | -sin(phi) 0 cos(phi) | | 0 0 1 |
218             # +- -+ +- -+
219              
220             # +- -+
221             # | cos(theta) * cos(phi) -sin(theta) * cos(phi) sin(phi) |
222             # = | sin(theta) cos(theta) 0 |
223             # | -cos(theta) * sin(phi) sin(theta) * sin(phi) cos(phi) |
224             # +- -+
225              
226             my @transform_vector;
227             { # Begin local symbol block.
228             my $cosphi = cos (MMAPHI);
229             my $sinphi = sin (MMAPHI);
230              
231             foreach my $mma (0 .. 2) {
232             my $theta = $mma * TWOPIOVER3;
233             my $costheta = $theta ? cos ($theta) : 1;
234             my $sintheta = $theta ? sin ($theta) : 0;
235              
236             push @transform_vector,
237             [ [$costheta * $cosphi, - $sintheta * $cosphi, $sinphi],
238             [$sintheta, $costheta, 0],
239             [- $costheta * $sinphi, $sintheta * $sinphi, $cosphi],
240             ];
241             }
242             } # End local symbol block.
243              
244             # We also pre-compute the inverse transforms, to facilitate the
245             # recovery of the virtual image of the illuminating body.
246              
247             my @inverse_transform_vector =
248             map {scalar _invert_matrix_list (@$_)} @transform_vector;
249              
250             =item $tle->after_reblessing (\%attribs);
251              
252             This method supports reblessing into a subclass, with the argument
253             representing attributes that the subclass may wish to set. It is called
254             by rebless() and should not be called by the user.
255              
256             At this level of the inheritance hierarchy, it sets the status of the
257             object from the {status} key of the given hash. If this key is absent,
258             the object is assumed capable of generating flares.
259              
260             =cut
261              
262             {
263             # This seems to me to be a bit of a crock, but I can think of no
264             # other way to prevent the intrinsic_magnitude from being clobbered
265             # as not relevant to the class.
266             my %retain = map { $_ => 1 }
267             qw{ intrinsic_magnitude }, keys %mutator;
268              
269             sub after_reblessing {
270 8     8 1 4961 my ($self, $attrs) = @_;
271 8 100       21 if (defined $attrs) {
272 7         37 $attrs = {%$attrs};
273             } else {
274 1         2 $attrs = {};
275             }
276 8 50       25 HASH_REF eq ref $attrs or croak <<'EOD';
277             Error - The argument of after_reblessing(), if any, must be a hash
278             reference.
279             EOD
280 8         29 foreach my $key (keys %static) {
281 72 100       148 $attrs->{$key} = $static{$key} unless defined $attrs->{$key};
282             }
283 8         38 foreach my $key (keys %$attrs) {
284 107 100       177 delete $attrs->{$key} unless $retain{$key};
285             }
286 8         35 $self->set (%$attrs);
287 8         27 return;
288             }
289             }
290              
291             # see Astro::Coord::ECI->attribute ();
292              
293             sub attribute {
294 0     0 1 0 my ($self, $name) = @_;
295 0 0       0 return exists $accessor{$name} ?
296             __PACKAGE__ :
297             $self->SUPER::attribute ($name);
298             }
299              
300             =item $tle->before_reblessing ()
301              
302             This method supports reblessing into a subclass. It is intended to do
303             any cleanup the old class needs before reblessing into the new class. It
304             is called by rebless(), and should not be called by the user.
305              
306             At this level of the inheritance hierarchy, it removes the status
307             attribute.
308              
309             =cut
310              
311             sub before_reblessing {
312 5     5 1 193 my ($self) = @_;
313 5         21 delete $self->{&ATTRIBUTE_KEY};
314 5         9 return;
315             }
316              
317             =item $tle->can_flare ($spare);
318              
319             This method returns true (in the Perl sense) if the object is capable
320             of producing flares, and false otherwise. If the optional $spare
321             argument is true, spares are considered capable of flaring, otherwise
322             not. If C<$spare> is C<'all'>, then all objects are considered capable
323             of flaring.
324              
325             =cut
326              
327             sub can_flare {
328 8     8 1 913 my ( $self, $spare ) = @_;
329 8 100 100     32 defined $spare
330             and 'all' eq $spare
331             and return 1;
332 7         19 my $status = $self->get ('status');
333 7   66     47 return !$status || $spare && $status == $self->BODY_STATUS_IS_SPARE;
334             }
335              
336             =item @flares = $tle->flare ($sta, $start, $end);
337              
338             This method returns the list of flares produced by the given Iridium
339             satellite at the given station between the given start time and the
340             given end time. This list may be empty. If called in scalar context you
341             get the number of flares.
342              
343             All arguments are optional, with the defaults being
344              
345             $station = the 'station' attribute
346             $start = time()
347             $end = $start + 1 day
348              
349             Each flare is represented by a reference to an anonymous hash, with
350             elements as follows:
351              
352             angle => Mirror angle, radians
353             appulse => information about the position of the Sun
354             angle => distance from Sun to flare, radians
355             body => reference to the Sun object
356             area => Projected MMA area, square radians
357             azimuth => Azimuth of flare, radians
358             body => Reference to object producing flare
359             center => information about the center of the flare
360             body => location of the center of the flare
361             magnitude => estimated magnitude at the center
362             elevation => Elevation of flare, radians
363             magnitude => Estimated magnitude
364             mma => Flaring mma (0, 1, or 2)
365             range => Range to flare, kilometers
366             specular => True if specular reflection
367             station => reference to the observer's location
368             status => ''
369             type => Type of flare (see notes)
370             time => Time of flare
371             virtual_image => Location of virtual image
372              
373             Note that:
374              
375             * The time of the object passed in the {body} element is not
376             necessarily set to the time of the flare.
377              
378             * The {center}{body} element contains an Astro::Coord::ECI object
379             set to the location of the center of the flare at the given time.
380             The center is defined as the intersection of the plane of the
381             observer's horizon with the line from the virtual image of the
382             illuminating body through the flaring satellite.
383              
384             * The {mma} element indicates which Main Mission Antenna generated
385             the flare. The antennae are numbered clockwise (looking down on the
386             vehicle) from the front, so 0, 1, and 2 correspond to Heavens Above's
387             'Front', 'Right', and 'Left' respectively.
388              
389             * The {specular} element is actually the limb darkening factor if
390             applicable. Otherwise, it is 1 if the reflection is specular, and 0 if
391             not.
392              
393             * The {status} key is reserved for an explanation of why there is no
394             flare. When the hash is generated by the flare() method, this key will
395             always be false (in the Perl sense).
396              
397             * The {type} element contains 'day' if the flare occurs between the
398             beginning of twilight in the morning and the end of twilight in the
399             evening, 'am' if the flare is after midnight but not during the day,
400             and 'pm' if the flare is before midnight but not during the day.
401              
402             * The {virtual_image} element is an Astro::Coord::ECI object
403             representing the location of the virtual image of the illuminator
404             at the time of the flare.
405              
406             Why does this software produce different results than
407             L?
408              
409             The short answer is "I don't know, because I don't know how Heavens
410             Above gets their answers."
411              
412             In a little more detail, there appear to be several things going on:
413              
414             First, there appears to be no standard reference for how to calculate
415             the magnitude of a flare. This module calculates specular reflections
416             as though the sky were opaque, and the flaring Main Mission Antenna
417             were a window through to the virtual image of the Sun. Limb darkening
418             is taken into account, as is atmospheric extinction. Non-specular
419             flares are calculated by a fairly arbitrary equation whose coefficients
420             were fitted to visual flare magnitude estimates collected by Ron Lee
421             and made available on the Web by Randy John as part of his skysat
422             web site at C (missing; see
423             L). Atmospheric extinction
424             is also taken into account for the non-specular flares.
425              
426             Atmospheric extinction is calculated according to the article by Daniel
427             W. Green in the July 1992 issue of "International Comet Quarterly", and
428             available at L. Because
429             Heavens Above does not display flares dimmer than a certain magnitude
430             (-6 for day flares, and apparently 0 for night flares), it may not
431             display a flare that this code predicts. I have no information how
432             Heavens Above calculates magnitudes, but I find that this class gives
433             estimates about a magnitude brighter than Heavens Above at the dim end
434             of the scale.
435              
436             Second, I suspect that the positions and velocities calculated by
437             Astro::Coord::ECI::TLE differ slightly from those used by Heavens Above.
438             I do not know this, because I do not know what positions Heavens Above
439             uses, but there are slight differences among the results of all the
440             orbital propagation models I have looked at. All I can say about the
441             accuracy of Astro::Coord::ECI::TLE is that it duplicates the test data
442             given in "Spacetrack Report Number Three". But small differences are
443             important -- 0.1 degree at the satellite can make the difference between
444             seeing and not seeing a flare, and smaller differences can affect the
445             magnitude predictions, especially if they make the difference between
446             predicting a specular or non-specular flare. Occasionally I find that I
447             get very different results than Heavens Above, even when using orbital
448             data published on that web site.
449              
450             Third, Heavens Above issues predictions on satellites that my source
451             says are spares. I have skipped the spares by default because I do not
452             know that their attitudes are maintained to the requisite precision,
453             though perhaps they would be, to demonstrate that the spares are
454             functional. This software currently uses the Iridium status from
455             CelesTrak (L), since
456             it represents one-stop shopping, and Dr. Kelso has expressed the intent
457             to check with Iridium Satellite LLC monthly for status. Mike McCants'
458             "Status of Iridium Payloads" at
459             C (no longer
460             maintained) noted that flares may be unreliable for spares, so can_flare
461             () returns false for them. If this is not what you want, call can_flare
462             with a true value (e.g. C).
463              
464             Fourth, the Heavens Above definition of 'daytime' differs from mine.
465             Heavens Above does not document what their definition is, at least
466             not that I have found. My definition of daytime includes twilight,
467             which by default means the center of the Sun is less than 6 degrees
468             below the horizon. I know that, using that definition, this software
469             classifies some flares as daytime flares which Heavens Above classifies
470             as nighttime flares. It appears to me that Heavens Above considers it
471             night whenever the Sun is below the horizon.
472              
473             Fifth, the orbital elements used to make the prediction can differ.
474             I have occasionally seen Heavens Above using elements a day old,
475             versus the ones available from Space Track, and seen this difference
476             make a difference of six or eight seconds in the time of the flare.
477              
478             Sixth, this method takes no account of the decrease in magnitude that
479             would result from the Sun being extremely close to the horizon as seen
480             from the flaring satellite. I do not know whether Heavens Above does
481             this or not, but I have seen an instance where this code predicted a
482             flare but Heavens Above did not, where the observed flare was much
483             dimmer than this code predicted, and reddened. Subsequent calculations
484             put the Sun 0.1 degrees above the horizon as seen from the satellite.
485              
486             B that the algorithm used to calculate flares does not work at
487             latitudes beyond 85 degrees north or south, nor does it work for any
488             location that is not fixed to the Earth's surface. This may be fixed in
489             a future release. The chances of it being fixed in a future release will
490             be enhanced if someone claims to actually need it. This someone will be
491             invited to help test the new code.
492              
493             B that as of version 0.002_01 of this class, the 'backdate'
494             attribute determines whether a set of orbital elements can be used for
495             computations of flares before the epoch of the elements. If 'backdate'
496             is false and the start time passed to flare() is earlier than the epoch,
497             the start time is silently moved forward to the epoch. The initial
498             version of this functionality raised an exception if this adjustment
499             placed the start time after the end time, but as of version 0.003_01 of
500             this class, you simply get no flares if this happens.
501              
502             =cut
503              
504 3     3   37 use constant DTFMT => '%d-%b-%Y %H:%M:%S (GMT)';
  3         13  
  3         186  
505 3     3   17 use constant DAY_TOLERANCE => deg2rad (2); # Distance Sun moves in 8 minutes.
  3         6  
  3         10  
506 3     3   143 use constant AM_START_LIMIT => 86400 - 480; # 8 minutes before midnight.
  3         5  
  3         133  
507 3     3   16 use constant AM_END_LIMIT => 43200 + 480; # 8 minutes after noon.
  3         5  
  3         168  
508 3     3   18 use constant PM_START_LIMIT => 43200 - 480; # 8 minutes before noon.
  3         3  
  3         146  
509 3     3   16 use constant PM_END_LIMIT => 480; # 8 minutes after midnight.
  3         6  
  3         6632  
510              
511             sub flare {
512 2     2 1 113 my ( $self, @args ) = __default_station( @_ );
513 2         58 my $method = $self->{&ATTRIBUTE_KEY}{_algorithm_method};
514 2         8 return $self->$method (@args);
515             }
516              
517             # Called as $self->$method()
518             sub _flare_fixed { ## no critic (ProhibitUnusedPrivateSubroutines)
519 2     2   4 my $self = shift;
520 2         4 my $station = shift;
521             {
522 2         3 local $@;
  2         12  
523 2 50       8 __instance( $station, 'Astro::Coord::ECI' ) or croak <
524             Error - The station must be a subclass of Astro::Coord::ECI.
525             eod
526             }
527 2   33     28 my $start = shift || time ();
528 2   33     13 my $end = shift || $start + SECSPERDAY;
529 2 50       8 $end >= $start or croak <
530             Error - End time must be after start time.
531             eod
532              
533 2         21 $start = $self->max_effective_date($start);
534 2 50       34 $start > $end and return;
535              
536 2         2 my @flares;
537 2         6 my $illum = $self->get ('illum');
538 2         18 my $horizon = $self->get ('horizon');
539 2         34 my $twilight = $self->get ('twilight');
540 2         31 my $sun = $self->get( 'sun' );
541              
542 2         74 my %want = (
543             am => $self->get ('am'),
544             day => $self->get ('day'),
545             pm => $self->get ('pm'),
546             );
547 2   33     16 my $check_time = !($want{am} && $want{day} && $want{pm});
548 2         5 my $day_limit = $twilight - DAY_TOLERANCE;
549 2         4 my $night_limit = $twilight + DAY_TOLERANCE;
550 2         15 my $illum_tolerance = deg2rad (15);
551              
552             # We assume our observing location is fixed on the surface of the
553             # Earth, and take advantage of the fact that an Iridium orbit is
554             # very nearly polar. We use these to calculate the intervals
555             # between successive passes through the observer's latitude, since
556             # the satellite is visible then if ever.
557              
558             ### CAVEAT: The typical orbital inclination of an Iridium satellite
559             ### is about 85 degrees. So this algorithm only works between
560             ### latitudes 85 north and 85 south.
561              
562 2         19 my $satlat = ($self->universal ($start)->geodetic ())[0];
563 2         26 my $zdot = ($self->eci)[5];
564 2         44 my $stalat = ($station->geodetic ())[0];
565 2         59 my $period = $self->period;
566 2         37 my $angular_velocity = TWOPI / $period;
567 2 0       12 my ($time, $asc) = ($zdot > 0 ?
    50          
    50          
568             $satlat < $stalat ? (($stalat - $satlat) / $angular_velocity, 1) :
569             ((PI - $stalat - $satlat) / $angular_velocity, 0) :
570             $satlat < $stalat ?
571             ((PI + $stalat + $satlat) / $angular_velocity, 1) :
572             (($satlat - $stalat) / $angular_velocity, 0));
573 2         4 $time += $start;
574 2         8 my @deltas = (
575             (PIOVER2 + $stalat) * 2 / $angular_velocity,
576             (PIOVER2 - $stalat) * 2 / $angular_velocity,
577             );
578              
579             # At this point the time represents (approximately, because our
580             # calculated period is a little scant) a moment when the
581             # satellite crosses the observer's latitude.
582              
583             # Pick up a copy of our max mirror angle so we don't have to call
584             # get () repeatedly.
585              
586 2         5 my $max_mirror_angle = $self->get ('max_mirror_angle');
587              
588             # While this time is less than our end time ...
589              
590 2         11 while ($time < $end) {
591              
592             # Calculate location of satellite.
593              
594 66         172 $self->universal ($time);
595 66         13686 my ($satlat, $satlon, $satalt) = $self->geodetic;
596              
597             # Correct time to put satellite at same latitude as station.
598              
599 66 100       664 $time += ($asc ? $stalat - $satlat : $satlat - $stalat)
600             / $angular_velocity;
601 66         120 ($satlat, $satlon, $satalt) = $self->universal ($time)->geodetic;
602              
603             # Calculate whether satellite is above horizon.
604              
605 66         662 my ( undef, $elev, $rng ) = $station->azel_offset( $self, 0 );
606 66 100       3613 $elev > $horizon or next;
607              
608             # Check whether we are interested in this potential flare, based
609             # on whether it might be during the day, or am, or pm.
610              
611 4 50 0     12 $check_time and (eval {
612 0         0 my $sun_elev = ($station->azel ($sun->universal ($time)))[1];
613 0 0 0     0 ($want{day} && $sun_elev > $day_limit) and return 1;
614 0 0 0     0 (($want{am} || $want{pm}) && $sun_elev < $night_limit) or return 0;
      0        
615 0         0 my @local_time = $self->_time_in_zone( $time );
616 0         0 my $time_of_day = ($local_time[2] * 60 + $local_time[1]) * 60
617             + $local_time[0];
618 0 0 0     0 ($want{am} && ($time_of_day > AM_START_LIMIT ||
      0        
619             $time_of_day < AM_END_LIMIT)) and return 1;
620 0 0 0     0 ($want{pm} && ($time_of_day > PM_START_LIMIT ||
      0        
621             $time_of_day < PM_END_LIMIT)) and return 1;
622 0         0 0;
623             } || next);
624              
625             # Calculate whether the satellite is illuminated.
626              
627             ## my $lit = ($self->azel ($illum->universal ($time)))[1] >=
628 4 50       20 ($self->azel ($illum->universal ($time)))[1] >=
629             $self->dip () - $illum_tolerance or next;
630              
631             # For our screening to work we need to know the maximum angular
632             # distance we can travel in 30 seconds. This is the arc tangent
633             # of the velocity over the range
634              
635 4         170 my (undef, undef, undef, $xdot, $ydot, $zdot) = $self->eci ();
636 4         88 my $max_angle = atan2 (
637             sqrt ($xdot * $xdot + $ydot * $ydot + $zdot * $zdot), $rng)
638             * 30;
639 4         10 $max_angle += $max_mirror_angle; # Take into account near misses.
640              
641             # Iterate over a period of 16 minutes centered on our current
642             # time, calculating the location of the reflection of the sun
643             # versus the satellite, as seen by the observer.
644              
645 4         9 my @flare_potential = ([], [], []); # Flare-potential data by MMA.
646 4         13 foreach my $deltat (-8 .. 8) {
647 68         261 my $time = $deltat * 60 + $time;
648              
649             # See if the satellite is illuminated at this time.
650             # TODO This code may need some slop; specifically we might want to
651             # assume the Sun is higher than it actually is by $max_angle.
652              
653 68 100       162 ($self->universal ($time)->azel ($illum->universal ($time)))[1] >=
654             $self->dip () or next;
655              
656             # Transform the relevant coordinates into a coordinate system
657             # in which the axis of the satellite is along the Z axis (with
658             # the Earth in the negative Z direction) and the direction of
659             # motion (and hence one of the Main Mission Antennae) is along
660             # the X axis. The method returns Math::VectorReal objects
661             # corresponding to all inputs, including '$self'.
662              
663 64         2278 my ( $illum_vector, $station_vector ) =
664             $self->_flare_transform_coords_list (
665             $illum, $station->universal( $time ) );
666              
667             # Now we do a second iteration over the Main Mission Antennae,
668             # checking for the position of the Sun's reflection.
669              
670 64         121 foreach my $mma (0 .. 2) {
671              
672             # We clone the sun and the station, and then calculate the angle
673             # between the satellite and the reflection of the Sun, as seen by
674             # the observer. We skip to the next antenna if no reflection is
675             # generated.
676              
677 192         323 my $illum_vector = [@$illum_vector];
678 192         296 my $station_vector = [@$station_vector];
679             next unless defined (
680 192 100       317 my $angle = _flare_calculate_angle_list(
681             $mma, $illum_vector, $station_vector ) );
682              
683             # Save the angle, time, and cloned station for subsequent
684             # analysis.
685              
686 64         430 push @{$flare_potential[$mma]},
  64         181  
687             [$angle, $time, $illum_vector, $station_vector];
688              
689             # End of iterating over Main Mission Antennae.
690              
691             }
692              
693             # End of iterating over 16 minute period centered on current
694             # time.
695              
696             }
697              
698             # Now iterate over each MMA to calculate its flare, if any.
699              
700             MMA_LOOP:
701 4         12 foreach my $mma (0 .. 2) {
702              
703             # Find the best possibility for a flare. If none, or the angle is
704             # more than the max possible, ignore this antenna.
705              
706 12 100       17 next if @{$flare_potential[$mma]} < 2;
  12         94  
707 8         14 my @flare_approx;
708 8         12 do { # Begin local symbol block
709 8         12 my $inx = 0;
710 8         27 my $angle = $flare_potential[$mma][$inx][0];
711 8         13 foreach (1 .. @{$flare_potential[$mma]} - 1) {
  8         22  
712 56 100       104 next unless $flare_potential[$mma][$_][0] < $angle;
713 10         16 $inx = $_;
714 10         23 $angle = $flare_potential[$mma][$_][0];
715             }
716 8 100       22 next if $angle > $max_angle;
717              
718             # If the best potential is at the beginning or end of the list,
719             # calculate the entrance (or exit) of the flare so we have a
720             # starting point for out approximations. Note that we used to
721             # just abandon the calculation in these cases.
722              
723 6 50       19 if ($inx == 0) {
    100          
724 0         0 unshift @{$flare_potential[$mma]},
  0         0  
725             $self->_flare_entrance ($illum, $station, $mma,
726             $flare_potential[$mma][$inx][1] - 60,
727             $flare_potential[$mma][$inx][1]);
728 0         0 $inx++;
729 6         18 } elsif ($inx == @{$flare_potential[$mma]} - 1) {
730 2         4 push @{$flare_potential[$mma]},
  2         12  
731             $self->_flare_entrance ($illum, $station, $mma,
732             $flare_potential[$mma][$inx][1] + 60,
733             $flare_potential[$mma][$inx][1]);
734             }
735 6         27 @flare_approx = ($flare_potential[$mma][$inx - 1],
736             $flare_potential[$mma][$inx + 1]);
737             }; # End local symbol block;
738              
739             # Use successive approximation to find the time of minimum
740             # angle. We can not use a linear split-the-difference search,
741             # because the behavior is too far from linear. So we fudge by
742             # taking the second- and third-closest angles found, and working
743             # inward from them. We also use a weighted average of the two
744             # previously-used times to prevent converging so fast we jump
745             # over the point we are trying to find.
746              
747 6         23 while (abs ($flare_approx[1][1] - $flare_approx[0][1]) > .1) {
748              
749             # Calculate the next time to try as a weighted average of the
750             # previous two approximations, with the worse approximation
751             # having three times the weight of the better one. This prevents
752             # us from converging so fast we miss the true minimum. Yes, this
753             # is ad-hocery. I tried weighting the 'wrong' flare twice as
754             # much, but still missed the maximum sometimes. This was more
755             # obvious on daytime flares, where if you miss the peak the
756             # flare is probably not specular.
757              
758             ## my $time = ($flare_approx[1][1] * 2 + $flare_approx[0][1]) / 3;
759 148         262 my $time = ($flare_approx[1][1] * 3 + $flare_approx[0][1]) / 4;
760             #### my $time = ($flare_approx[1][1] * 6 + $flare_approx[0][1]) / 7;
761              
762             # Transform the relevant coordinates into a coordinate system
763             # in which the axis of the satellite is along the Z axis (with
764             # the Earth in the negative Z direction) and the direction of
765             # motion (and hence one of the Main Mission Antennae) is along
766             # the X axis.
767              
768 148         385 my ( $illum_vector, $station_vector ) =
769             $self->universal( $time )->
770             _flare_transform_coords_list(
771             $illum->universal( $time ),
772             $station->universal( $time ) );
773              
774             # Calculate the angle between the satellite and the reflection
775             # of the Sun, as seen by the observer.
776              
777 148         303 my $angle = _flare_calculate_angle_list(
778             $mma, $illum_vector, $station_vector );
779 148 50       948 defined $angle or next MMA_LOOP;
780              
781             # Store the data in our approximation list, in order by angle.
782              
783 148         221 pop @flare_approx;
784 148         579 splice @flare_approx, $angle >= $flare_approx[0][0], 0,
785             [$angle, $time, $illum_vector, $station_vector];
786              
787             # End of successive approximation of time of minimum angle.
788              
789             }
790              
791             # Pull the (potential) flare data off the approximation list.
792              
793             my ($angle, $time, $illum_vector, $station_vector) =
794 6         16 @{$flare_approx[0]};
  6         19  
795              
796             # Skip it if the mirror angle is greater than the max.
797              
798 6 100       23 next if $angle > $max_mirror_angle;
799              
800             # All our approximations may have left us with a satellite which
801             # is not quite lit. This happened with Iridium 32 (OID 24945) on
802             # Feb 03 2007 at 07:45:19 PM. So we check for illumination one
803             # last time.
804             # TODO: this calculation should be performed not on the position
805             # of the Sun, but on the actual point on the Sun which is
806             # reflected to the observer. It looks now like it needs to be done
807             # in _flare_calculate_angle_list().
808              
809 4 50       13 ($self->universal ($time)->azel ($illum->universal ($time)))[1] >=
810             $self->dip () or next;
811              
812             # Calculate all the flare data.
813              
814 4         158 my $flare = $self->_flare_char_list ($station, $mma, $angle,
815             $time, $illum_vector, $station_vector);
816              
817             # Stash the data.
818              
819             push @flares, $flare
820 4 50 33     52 if !$flare->{status} && $want{$flare->{type}};
821              
822             # End of iteration over each MMA to calculate its flare.
823              
824             }
825              
826             # Compute the next approxiate crossing of the observer's
827             # latitude.
828              
829             } continue {
830 66         118 $time += $deltas[$asc];
831 66         161 $asc = 1 - $asc;
832             }
833              
834 2         42 return @flares;
835              
836             }
837              
838             # [$angle, $time, $illum_vector, $station_vector] =
839             # $self->_flare_entrance ($illum, $station, $mma, $start,
840             # $end);
841              
842             # Given that a flare is in progress at the end time and not at
843             # the start time, computes the start of the flare. Can be used
844             # for exit by reversing the times.
845              
846             sub _flare_entrance {
847 2     2   7 my ($self, $illum, $station, $mma, $start, $end) = @_;
848 2         3 my $output;
849             # my $time = find_first_true (
850             find_first_true (
851             $start, $end,
852             sub {
853 12     12   162 $self->universal ($_[0]);
854 12         2583 my ( $illum_vector, $station_vector ) =
855             $self->_flare_transform_coords_list(
856             $illum->universal( $_[0] ),
857             $station->universal( $_[0] ) );
858 12 100       27 if ( defined ( my $angle = _flare_calculate_angle_list(
859             $mma, $illum_vector, $station_vector ) ) ) {
860 6         100 $output = [$angle, $_[0], $illum_vector, $station_vector];
861 6         16 1;
862             } else {
863 6         13 0;
864             }
865 2         29 });
866 2   0     27 $output ||= do { # Can happen if end is entrance.
      33        
867             $self->universal ($end);
868             my ( $illum_vector, $station_vector ) =
869             $self->_flare_transform_coords_list(
870             $illum->universal( $end ),
871             $station->universal( $end) );
872             my $angle = _flare_calculate_angle_list(
873             $mma, $illum_vector, $station_vector );
874             defined $angle ?
875             [$angle, $end, $illum_vector, $station_vector] :
876             undef;
877             } || confess <
878             Programming error - No entrance found by _flare_entrance.
879             @{[join ' - ', grep {$_} map {$self->get ($_)} qw{name id}]}
880             \$mma = $mma
881             \$start = $start = @{[scalar localtime $start]}
882             \$end = $end = @{[scalar localtime $end]}
883             eod
884 2         5 return $output;
885             }
886              
887             # @vectors = $tle->_flare_transform_coords_list( $eci ....)
888             #
889             # This private method transforms the coordinates of the $tle
890             # object and all $eci objects passed in, so that the $tle
891             # object is at the origin of a coordinate system whose
892             # X axis is along the velocity vector of the $tle object, the
893             # Y axis is perpendicular to the plane of the orbit, and the
894             # Z axis is perpendicular to both of these, and therefore
895             # nominally "up and down", with the center of the Earth in the
896             # - Z direction. The objects are not modified, instead
897             # list references (containing the position vectors)
898             # corresponding to all arguments (except the invocant) are
899             # returned.
900              
901             sub _flare_transform_coords_list {
902 228     228   76304 my ( $self, @args ) = @_;
903 228         435 my @ref = $self->eci();
904 228         4926 my $X = vector_unitize( [@ref[3 .. 5]] );
905 228         5670 my $Y = vector_cross_product( vector_unitize( [ @ref[0 .. 2]] ), $X );
906 228         6358 my $Z = vector_cross_product( $X, $Y );
907 228         2029 my @coord = ($X, $Y, $Z);
908 228         275 my @rslt;
909 228         358 foreach my $loc (@args) {
910 456         3910 my @eci = $loc->eci();
911 456         28441 my @pos = map { $eci[$_] - $ref[$_] } 0 .. 2;
  1368         2195  
912             push @rslt, [
913 456         688 map { vector_dot_product( \@pos, $coord[$_] ) } 0 .. 2
  1368         14027  
914             ];
915             }
916 228         3831 return @rslt;
917             }
918              
919             # @original = $tle->_flare_transform_coords_inverse_list( @vectors )
920             #
921             # This private method is the inverse (almost) of
922             # _flare_transform_coords_list(). The weasel word is because it
923             # returns array references representing the ECI position vectors,
924             # rather than Astro::Coord::ECI objects.
925              
926             sub _flare_transform_coords_inverse_list {
927 8     8   22 my ( $self, @args ) = @_;
928 8         20 my @ref = $self->eci();
929 8         197 my $X = vector_unitize( [@ref[3 .. 5]] );
930 8         205 my $Y = vector_cross_product( vector_unitize( [ @ref[0 .. 2]] ), $X );
931 8         242 my $Z = vector_cross_product( $X, $Y );
932 8         71 my @coord = _invert_matrix_list($X, $Y, $Z);
933 8         13 my @rslt;
934 8         16 foreach my $loc (@args) {
935             push @rslt, [
936 8         20 map { vector_dot_product( $loc, $coord[$_] ) + $ref[$_] } 0 .. 2
  24         241  
937             ];
938             }
939 8         134 return @rslt;
940             }
941              
942             # $angle = _flare_calculate_angle_list($mma, $illum, $station)
943              
944             # This private subroutine calculates the angle between the
945             # satellite and the reflection of the Sun in the given Main
946             # Mission Antenna as seen from the observing station. $illum and
947             # $station are list reverences generated by
948             # _flare_transform_coords_list(). The satellite position is not
949             # needed because in this coordinate system it is [0, 0, 0]
950              
951             # A reflection can only occur if both the Sun and the observer
952             # are in front of the antenna (i.e. have positive Z coordinates
953             # after transforming everything so that the plane of the MMA is
954             # the X-Y axis). If there is no reflection, undef is returned.
955              
956             sub _flare_calculate_angle_list {
957 364     364   523 my ( $mma, $illum, $station ) = @_;
958              
959             # Rotate the objects so that the Main Mission Antenna of interest
960             # lies in the X-Y plane, facing in the +Z direction.
961              
962 364         458 my @eci;
963 364         576 foreach my $inx (0 .. 2) {
964 1092         10695 $eci[$inx] = vector_dot_product ($illum, $transform_vector[$mma][$inx])
965             }
966 364 100       5283 return unless $eci[2] > 0;
967 274         377 $eci[2] = - $eci[2];
968 274         477 $illum = [$eci[0], $eci[1], $eci[2]];
969 274         405 foreach my $inx (0 .. 2) {
970 822         7934 $eci[$inx] = vector_dot_product ($station, $transform_vector[$mma][$inx])
971             }
972 274 100       3889 return unless $eci[2] > 0;
973 222         389 $station = [$eci[0], $eci[1], $eci[2]];
974              
975             # Now calculate the angle between the illumination source and the
976             # observer as seen by the observer.
977              
978 222         455 return _list_angle( $station, $illum, [ 0, 0, 0 ] );
979             }
980              
981             # $hash_ref = $iridium->_flare_char_list (...)
982             #
983             # Calculate the characteristics of the flare of the given body.
984             # The arguments are as follows:
985             #
986             # $station => the object representing the observer.
987             # $mma => the flaring Main Mission Antenna (0 .. 2).
988             # $angle => the previously-calculated mirror angle.
989             # $time => the time of the flare.
990             # $illum_vector => the previously-calculated vector to the
991             # illuminating body (satellite = [0, 0, 0]).
992             # $station_vector => the previously-calculated vector to the
993             # observer (satellite = [0, 0, 0])
994              
995             sub _flare_char_list {
996              
997 8     8   23 my ($self, $station, $mma, $angle, $time, $illum_vector, $station_vector) = @_;
998              
999             # Skip it if the flare is not above the horizon.
1000              
1001 8         25 my ($azim, $elev) = $station->azel ($self->universal ($time));
1002 8         699 my $horizon = $self->get ('horizon');
1003 8 50       138 if ($elev < $horizon) {
1004 0         0 return _make_status (sprintf (
1005             'Satellite %.2f degrees below horizon', rad2deg ($horizon - $elev)));
1006             }
1007              
1008             # Retrieve the illuminating body information.
1009              
1010 8         20 my $illum = $self->get ('illum');
1011 8         81 my $illum_radius = $illum->get ('diameter') / 2;
1012              
1013             # Retrieve missing station information.
1014              
1015 8         195 my $height = ($station->geodetic)[2];
1016              
1017             # And any odds and ends we might need.
1018              
1019 8         189 my $sun = $self->get( 'sun' );
1020 8         184 my $twilight = $self->get ('twilight');
1021 8         126 my $atm_extinct = $self->get ('extinction');
1022              
1023             # Calculate the range to the satellite, and to the reflection of
1024             # the Sun, from the observer.
1025              
1026 8         20 my $sat_range = vector_magnitude ($station_vector);
1027 8         131 my $illum_range = vector_magnitude ([
1028             $illum_vector->[0] - $station_vector->[0],
1029             $illum_vector->[1] - $station_vector->[1],
1030             $illum_vector->[2] - $station_vector->[2],
1031             ]);
1032              
1033             # Calculate the projected area of the MMA of interest, in square
1034             # radians.
1035              
1036 8         127 my $sat_area = abs ($station_vector->[2]) / $sat_range * MMAAREA
1037             / 1e6 / ($sat_range * $sat_range);
1038              
1039             # As a side effect, we calculate omega, the angle from the center
1040             # of the Sun to the edge, as seen by the observer.
1041              
1042 8         16 my $illum_omega = $illum_radius / $illum_range;
1043 8         16 my $illum_area = PI * $illum_omega * $illum_omega;
1044              
1045             # Calculate the magnitude of the illuminating body at the point
1046             # reflected by the Main Mission Antenna.
1047              
1048 8         28 my ($point_magnitude, $limb_darkening, $central_magnitude) =
1049             $illum->magnitude ($angle, $illum_omega);
1050              
1051             # Calculate the reduction in magnitude due to the fact that the
1052             # projected area of the main mission antenna is smaller than the
1053             # projected area of the Sun.
1054              
1055 8         355 my $area_correction =
1056             intensity_to_magnitude ($sat_area / $illum_area);
1057              
1058             # Calculate the dead-center flare magnitude as the central
1059             # magnitude of the Sun plus the delta caused by the fact that the
1060             # projected area of the main mission antenna is smaller than the
1061             # area of the sun.
1062              
1063 8         42 my $central_mag = $central_magnitude + $area_correction;
1064              
1065             # And for the test case, I got -8.0. Amazing.
1066              
1067             # Calculate the atmospheric extinction of the flare.
1068              
1069 8 50       31 my $extinction = $atm_extinct ?
1070             atmospheric_extinction ($elev, $height) : 0;
1071              
1072             # The following off-axis magnitude calculation is the result of
1073             # normalizing Ron Lee's magnitude data (made available by Randy
1074             # John in various forms at http://home.comcast.net/~skysat/ ) for
1075             # a projected Main Mission Antenna area of 1e-12 square radians
1076             # and zero atmospheric extinction. A logarithmic correlation was
1077             # suggested by Rob Matson (author of IRIDFLAR) at
1078             # http://www.satobs.org/seesat/Apr-1998/0175.html . I tried a
1079             # couple other possibilities, but ended up most satisfied (or
1080             # least unsatisfied) with a linear regression on
1081             # ln (8 - magnitude), with the 8 picked because it was the
1082             # maximum possible magnitude.
1083             # Maybe I could have done better with a larger arbitrary
1084             # constant, since the data sags a bit in the middle versus the
1085             # regression line, but there is a fair amount of scatter anyway.
1086              
1087             # All this means that the calculation is
1088             # mag = 8 - exp (-5.1306 * angle_in_radians + 2.4128) +
1089             # intensity_to_magnitude (area / 1e-12) +
1090             # atmospheric_refraction (elevation, height)
1091             # The R-squared for this is .563.
1092              
1093             # There are several possible sources of error:
1094              
1095             # * My mirror angle is defined slightly different than Randy
1096             # John's. Mine is the angle between the satellite and the
1097             # virtual image of the Sun as seen by the observer. His is the
1098             # angle between the actual reflection and a central specular
1099             # reflection, which I take to be 180 degrees minus the angle
1100             # between the Sun and the observer as seen from the satellite.
1101             # This makes my angle slightly smaller than his, the difference
1102             # being the angle between the observer and the satellite as
1103             # seen from the Sun, something on the order of 0.01 degrees or
1104             # less. This is probably not directly a source of error (since
1105             # I used my own calculation of mirror angle), but needs to be
1106             # taken into account when evaluating the other sources of
1107             # error.
1108              
1109             # * My calculated mirror angles are different than Randy John's
1110             # by an amount which is typically about a tenth of a degree,
1111             # but which can be on the order of a couple degrees. Since I
1112             # do not currently have any Wintel hardware, I can not tell
1113             # how much of this is difference in calculation and how much
1114             # is difference in orbital elements.
1115              
1116             # * The error between the visually estimated magnitudes and the
1117             # actual magnitudes is unknown. In theory, visual estimates are
1118             # fairly good given a number of nearby comparison stars of
1119             # magnitudes near the body to be estimated. How the ephemeral
1120             # nature of the flares affects the accuracy of this process is
1121             # not known to me. What happens with magnitudes brighter than
1122             # about -1, where there are no comparison objects available is
1123             # also unknown, as is the actual methodology of making the
1124             # estimates.
1125              
1126             # Note to me: the current estimate was done with
1127             # perl process.pl -quiet -specular -radians -constant 8
1128             # The previous was done with
1129             # perl process.pl -specular -radians, but the correlation was
1130             # done in a spreadsheet (normalized2.ods)
1131              
1132 3     3   29 use constant OFF_AXIS_FACTOR => -5.1306; # Was -3.9246
  3         7  
  3         196  
1133 3     3   21 use constant OFF_AXIS_CONST => 2.4128; # Was 2.60
  3         6  
  3         153  
1134 3     3   16 use constant OFF_AXIS_STD_AREA => 1e-12;
  3         6  
  3         143  
1135 3     3   18 use constant OFF_BASE_MAG => 8; # Was 10
  3         4  
  3         8384  
1136              
1137 8         130 my $off_axis_mag = OFF_BASE_MAG -
1138             exp ($angle * OFF_AXIS_FACTOR + OFF_AXIS_CONST) +
1139             intensity_to_magnitude ($sat_area / OFF_AXIS_STD_AREA) +
1140             $extinction;
1141 8 50       52 my $flare_mag = $limb_darkening > 0 ? do {
1142 0         0 my $specular_mag = $point_magnitude + $area_correction +
1143             $extinction;
1144 0         0 min ($specular_mag, $off_axis_mag) } : $off_axis_mag;
1145              
1146             # Compute the flare type (am, day, or pm)
1147              
1148 8         24 my $sun_elev = ($station->azel ($sun->universal ($time)))[1];
1149 8 50       1773 my $flare_type = $sun_elev >= $twilight ? 'day' :
    100          
1150             ( $self->_time_in_zone( $time ) )[2] > 12 ? 'pm' : 'am';
1151              
1152             # Compute the angle from the Sun to the flare.
1153              
1154 8         30 my $sun_angle = $station->angle ($sun, $self);
1155              
1156             # Wikipedia gives the following analytical expression for the
1157             # inversion of a 3 x 3 matrix at
1158             # http://en.wikipedia.org/wiki/Matrix_inversion
1159             # Given
1160             #
1161             # +- -+
1162             # | a b c |
1163             # A = | d e f |
1164             # | g h i |
1165             # + -+
1166             #
1167             # the inverse is
1168             #
1169             # +- -+
1170             # 1 | ei-fh ch-bi bf-ce |
1171             # A'= --- | fg-di ai-cg cd-af |
1172             # |A| | dh-eg bg-ah ae-bd |
1173             # +- -+
1174             #
1175             # where the determinant |A| = a(ei - fh) - b(di - fg) + c(dh - eg)
1176             # and the matrix is singuar if |A| == 0
1177             #
1178             # I can then undo the rotations by premultiplying the inverse
1179             # matrices in the reverse order, and add back the location of
1180             # the Iridium satellite to get the location of the virtual image
1181             # in ECI coordinates.
1182              
1183             # Compute the location of the virtual image of the illuminator,
1184             # in ECI coordinates:
1185              
1186 8         1095 my ($virtual_image, $image_vector) = do {
1187              
1188             # Recover the position of the virtual image of the illuminator. We
1189             # calculated this before, but never saved it.
1190              
1191             my $image_vector = [
1192 8         57 map { vector_dot_product( $illum_vector,
  24         257  
1193             $transform_vector[$mma][$_] ) } 0 .. 2
1194             ];
1195 8         129 $image_vector->[2] = - $image_vector->[2];
1196              
1197             # Undo the rotations that placed the MMA of interest in the X-Y
1198             # plane.
1199              
1200             $image_vector = [
1201 8         17 map { vector_dot_product( $image_vector,
  24         264  
1202             $inverse_transform_vector[$mma][$_] ) } 0 .. 2
1203             ];
1204              
1205             # Transform from satellite-local coordinates to ECI coordinates.
1206              
1207 8         129 ( $image_vector ) = $self->_flare_transform_coords_inverse_list(
1208             $image_vector );
1209              
1210             # Manufacture an object representing the virtual image, and a vector
1211             # represnting same for use in calculating the flare sub-point.
1212              
1213 8         24 ( Astro::Coord::ECI->universal( $time )->eci( @{ $image_vector } ),
  8         696  
1214             $image_vector );
1215             };
1216              
1217             # Compute the distance to the flare center.
1218              
1219             # For the calculation, consider the Earth flat, and consider the
1220             # center of the flare at the given time to be the point where the
1221             # line from the virtual image of the Sun through the satellite
1222             # intersects the plane.
1223              
1224             # Per http://mathforum.org/library/drmath/view/55094.html
1225             # you can consider the plane defined as a point A (the observer)
1226             # and a normal vector N (toward the zenith), and the line
1227             # to be defined by point P (Iridium) and vector V (= Q - P, with
1228             # Q being the virtual image of the Sun). Then the intersection X
1229             # is given by
1230             #
1231             # (A - P) dot N
1232             # X = P + ------------- (Q - P)
1233             # (Q - P) dot N
1234             #
1235             # I have A (observer), P (Iridium), and Q (virtual image of Sun),
1236             # so all I need is N. This I can get by rotating a unit vector by
1237             # the longitude, then by the geodetic latitude. The distance is
1238             # | X - A |, and the direction is the azimuth of X from A, which
1239             # the azel() method will give me.
1240             #
1241              
1242 8         284 my $sub_vector = do {
1243 8         28 my $a = [($station->eci ())[0 .. 2]];
1244 8         369 my $p = [($self->eci ())[0 .. 2]];
1245 8         162 my $q = $image_vector;
1246 8         19 my @n = $station->geodetic ();
1247 8         171 $n[2] += 1;
1248 8         22 my $n = [(Astro::Coord::ECI->geodetic (@n)
1249             ->universal ($time)->eci ())[0 .. 2]];
1250 8         2935 $n = [$n->[0] - $a->[0], $n->[1] - $a->[1], $n->[2] - $a->[2]];
1251 8         25 my $q_p = [$q->[0] - $p->[0], $q->[1] - $p->[1], $q->[2] - $p->[2]];
1252 8         28 my $k = vector_dot_product ([$a->[0] - $p->[0], $a->[1] - $p->[1], $a->[2] - $p->[2]], $n) /
1253             vector_dot_product ($q_p, $n);
1254 8         270 [$q_p->[0] * $k + $p->[0], $q_p->[1] * $k + $p->[1], $q_p->[2] * $k + $p->[2]];
1255             };
1256 8         24 my $sub_point = Astro::Coord::ECI->new(
1257             station => $station )->universal( $time )->eci( @$sub_vector );
1258              
1259             # Stash the data.
1260              
1261 8         1334 my %rslt = (
1262             angle => $angle, # Mirror angle, radians
1263             appulse => { # Relationship of flare to Sun
1264             angle => $sun_angle, # Angle from flare to Sun
1265             body => $sun, # Reference to Sun
1266             },
1267             area => $sat_area, # Projected MMA area, square radians
1268             azimuth => $azim, # Azimuth of flare
1269             body => $self, # Reference to flaring body
1270             center => { # Information on flare center
1271             body => $sub_point, # Location of center
1272             magnitude => $central_mag, # Predicted magnitude at center
1273             },
1274             elevation => $elev, # Elevation of flare
1275             magnitude => $flare_mag, # Estimated magnitude
1276             mma => $mma, # Flaring mma (0, 1, or 2)
1277             range => $sat_range, # Range to satellite, kilometers
1278             specular => $limb_darkening, # True if specular
1279             station => $station, # Observer's location
1280             status => '', # True if below horizon or not illum
1281             time => $time, # Time of flare
1282             type => $flare_type, # Flare type ('am', 'day', 'pm')
1283             virtual_image => $virtual_image, # Virtual image of illum.
1284             );
1285              
1286 8 50       40 return wantarray ? %rslt : \%rslt;
1287             }
1288              
1289             # $ainv = _invert_matrix_list ($a)
1290              
1291             # This subroutine takes a reference to a list of three list
1292             # references, considers them as a matrix, and inverts that
1293             # matrix, returning a reference to the list of list references
1294             # that represents the inverted matrix. If called in list context,
1295             # it returns the list itself. You can also pass the three input
1296             # list references as a list.
1297              
1298             sub _invert_matrix_list {
1299 17     17   37 my @args = @_;
1300 17 50       28 confess <<'EOD' unless (grep { ARRAY_REF eq ref $_ } @args) == 3;
  51         131  
1301             Programming error -- _invert_matrix_list takes as its arguments three
1302             list references.
1303             EOD
1304 17         26 my ($a, $b, $c) = @{$args[0]};
  17         35  
1305 17         30 my ($d, $e, $f) = @{$args[1]};
  17         31  
1306 17         21 my ($g, $h, $i) = @{$args[2]};
  17         31  
1307 17         46 my $ei_fh = $e * $i - $f * $h;
1308 17         37 my $fg_di = $f * $g - $d * $i;
1309 17         32 my $dh_eg = $d * $h - $e * $g;
1310 17         43 my $A = $a * $ei_fh + $b * $fg_di + $c * $dh_eg;
1311 17 50       38 confess <
1312             Programming error -- You are trying to invert a singular matrix. This
1313             should not happen since our purpose is to undo a rotation.
1314             eod
1315 17         109 my @inv = (
1316             [$ei_fh / $A, ($c * $h - $b * $i) / $A, ($b * $f - $c * $e) / $A],
1317             [$fg_di / $A, ($a * $i - $c * $g) / $A, ($c * $d - $a * $f) / $A],
1318             [$dh_eg / $A, ($b * $g - $a * $h) / $A, ($a * $e - $b * $d) / $A],
1319             );
1320 17 100       59 return wantarray ? @inv : \@inv;
1321             }
1322              
1323             # $a = _list_angle ($A, $B, $C)
1324             #
1325             # This subroutine takes as input three list references, which are
1326             # assumed to define the coordinates of the vertices of a
1327             # triangle. The angle of the first vertex is computed (in
1328             # radians) by the law of cosines, and returned.
1329              
1330             sub _list_angle {
1331 222     222   301 my $A = shift;
1332 222         265 my $B = shift;
1333 222         265 my $C = shift;
1334              
1335 222         422 my $a = distsq ($B, $C);
1336 222         4002 my $b = distsq ($A, $C);
1337 222         3556 my $c = distsq ($A, $B);
1338              
1339 222         3726 return acos (($b + $c - $a) / sqrt (4 * $b * $c));
1340             }
1341              
1342             =item $value = $tle->get ($name);
1343              
1344             This method returns the value of the given attribute. Attributes other
1345             than 'status' are delegated to the parent.
1346              
1347             =cut
1348              
1349             sub get {
1350 1072     1072 1 147777 my $self = shift;
1351 1072         1509 my $name = shift;
1352              
1353 1072 100       1898 if (!$accessor{$name}) {
    50          
1354 1045         2198 return $self->SUPER::get ($name);
1355             } elsif (ref $self) {
1356 27         67 return $accessor{$name}->($self, $name);
1357             } else {
1358 0         0 return $accessor{$name}->(\%statatr, $name);
1359             }
1360             }
1361              
1362             # $status = _make_status ($message);
1363              
1364             # This subroutine returns a reference to a hash with key 'status'
1365             # containing the given message. In list context it returns the
1366             # hash itself.
1367              
1368             sub _make_status {
1369 8     8   24 my %stat = (status => @_);
1370 8 50       24 return wantarray ? %stat : \%stat;
1371             }
1372              
1373             =item $mag = $tle->magnitude( $station );
1374              
1375             This override of the superclass' method method returns the magnitude of
1376             the body as seen from the given station at the body's currently-set
1377             time. If no C<$station> is specified, the object's C<'station'>
1378             attribute is used. If that is not set, and exception is thrown.
1379              
1380             This method calls the superclass' C, and returns C
1381             if the superclass does. Otherwise it adds to the magnitude of the body
1382             itself the magnitude of any flare in progress, and returns the result.
1383              
1384             =cut
1385              
1386             sub magnitude {
1387 4     4 1 932 my ( $self, $sta ) = __default_station( @_ );
1388 4 50       127 defined( my $mag = $self->SUPER::magnitude( $sta ) )
1389             or return undef; ## no critic (ProhibitExplicitReturnUndef)
1390 4         2086 my $time = $self->universal();
1391 12         23 my @flare = grep { defined }
1392 4         58 map { $_->{magnitude} }
  12         25  
1393             $self->reflection( $sta, $time );
1394             @flare
1395 4 50       49 and $mag = add_magnitudes( $mag, @flare );
1396 4         64 return $mag;
1397             }
1398              
1399             =item @data = $tle->reflection ($station, $time)
1400              
1401             This method returns a list of references to hashes containing the same
1402             data as returned for a flare, calculated for the given observer and time
1403             for all Main Mission Antennae. If C<$time> is C, the current time
1404             setting of the invocant is used. If C<$station> is C the current
1405             C attribute is used. Note the following differences from the
1406             flare() hash:
1407              
1408             If the hash contains a 'status' key which is true (in the Perl sense),
1409             no reflection occurred, and the content of the key is a message saying
1410             why not. If the 'mma' key exists in addition to the 'status' key, the
1411             failure applies only to that MMA, and other MMAs may possibly generate a
1412             reflection. If the 'mma' key does not exist, then the satellite is
1413             either not illuminated or below the horizon for the given observer, and
1414             the @data list will contain only a single entry.
1415              
1416             Other than (maybe) 'mma', no other keys should be assumed to exist if
1417             the 'status' key is true.
1418              
1419             If called in scalar context, a reference to the \@data list is returned.
1420              
1421             B that prior to 0.061_01 the C<$time> argument defaulted to the
1422             current time. This behavior was undocumented, and therefore I felt free
1423             to change it.
1424              
1425             =cut
1426              
1427             sub reflection {
1428 4     4 1 13 my ( $self, $station, $time ) = __default_station( @_ );
1429 4         106 my $method = "_reflection_$self->{&ATTRIBUTE_KEY}{algorithm}";
1430 4         16 return $self->$method( $station, $time );
1431             }
1432              
1433             # Called as $self->$method, above
1434             sub _reflection_fixed { ## no critic (ProhibitUnusedPrivateSubroutines)
1435 4     4   11 my ( $self, $station, $time ) = @_;
1436 4 50       11 defined $time
1437             or $time = $self->universal();
1438 4         17 my $debug = $self->get ('debug');
1439 4         35 my $illum = $self->get ('illum')->universal ($time);
1440              
1441             # Calculate whether satellite is above horizon.
1442              
1443 4         88 my (undef, $elev) = $station->universal ($time)->
1444             azel_offset( $self->universal ($time), 0 );
1445 4 50       305 return scalar _make_status (
1446             sprintf ('Satellite %.2f degrees below horizon', rad2deg (-$elev)))
1447             unless $elev >= 0;
1448              
1449             # Calculate whether the satellite is illuminated.
1450              
1451 4         15 my $lit = ($self->azel ($illum->universal ($time)))[1] - $self->dip ();
1452 4 50       154 return scalar _make_status (
1453             sprintf ('Satellite fails to be illuminated by %.2f degrees',
1454             rad2deg (-$lit)))
1455             unless $lit >= 0;
1456              
1457             # Transform the relevant coordinates into a coordinate system
1458             # in which the axis of the satellite is along the Z axis (with
1459             # the Earth in the negative Z direction) and the direction of
1460             # motion (and hence one of the Main Mission Antennae) is along
1461             # the X axis.
1462              
1463 4         18 my ( $illum_vector, $station_vector ) =
1464             $self->_flare_transform_coords_list( $illum, $station );
1465              
1466 4         7 my @rslt;
1467              
1468 4         10 foreach my $mma (0 .. 2) {
1469              
1470             # We calculate
1471             # the angle between the satellite and the reflection of the Sun,
1472             # as seen by the observer. We skip to the next antenna if no
1473             # reflection is generated.
1474              
1475 12         39 my $angle = _flare_calculate_angle_list(
1476             $mma, $illum_vector, $station_vector );
1477 12 50       47 warn <
1478 0 0       0 MMA $mma Angle: @{[defined $angle ? rad2deg ($angle) . ' degrees' :
1479             'undefined']}
1480             eod
1481 12 100       38 push @rslt, defined $angle ?
1482             scalar $self->_flare_char_list ($station, $mma, $angle, $time,
1483             $illum_vector, $station_vector) :
1484             scalar _make_status ('Geometry does not allow reflection',
1485             mma => $mma);
1486             }
1487              
1488 4 50       20 return wantarray ? @rslt : \@rslt;
1489             }
1490              
1491             =item $tle->set ($name => $value ...)
1492              
1493             This method sets the value of the given attribute (or attributes).
1494             Attributes other than 'status' are delegated to the parent.
1495              
1496             =cut
1497              
1498             sub set {
1499 14     14 1 1596 my ($self, @args) = @_;
1500 14         35 while (@args) {
1501 78         351 my $name = shift @args;
1502 78         94 my $value = shift @args;
1503 78 100       184 if (!$mutator{$name}) {
    50          
1504 13         43 $self->SUPER::set ($name, $value);
1505             } elsif (ref $self) {
1506 65         119 $mutator{$name}->($self, $name, $value);
1507             } else {
1508 0         0 $mutator{$name}->(\%statatr, $name, $value);
1509             }
1510             }
1511 14         253 return $self;
1512             }
1513              
1514             # For use of -am and -pm
1515             {
1516             my $date_time_available = eval {
1517             load_module( 'DateTime' );
1518             load_module( 'DateTime::TimeZone' );
1519             1;
1520             };
1521              
1522             sub _time_in_zone {
1523 4     4   13 my ( $self, $time ) = @_;
1524              
1525 4 50       9 defined( my $zone = $self->get( 'zone' ) )
1526             or return localtime $time;
1527              
1528 4 50       32 looks_like_number( $zone )
1529             and return gmtime( $zone * 3600 + $time );
1530              
1531 0 0       0 if ( $date_time_available ) {
1532              
1533 0         0 my $dt = DateTime->from_epoch(
1534             epoch => $time,
1535             time_zone => $zone,
1536             );
1537              
1538 0         0 my @localtime = map { $dt->$_() } qw{ second minute hour day
  0         0  
1539             month_0 year day_of_week_0 day_of_year_0 is_dst };
1540 0         0 $localtime[5] -= 1900;
1541 0         0 return @localtime;
1542              
1543             } else {
1544              
1545 0         0 local $ENV{TZ} = $zone;
1546 0         0 return localtime $time;
1547              
1548             }
1549             }
1550             }
1551              
1552             sub __parse_name {
1553 1     1   16 my ( $self, $name ) = @_;
1554 1 50 33     5 defined $name
1555             and $name =~ s/ \s* [[] ( \S ) []] \s* \z //smx
1556             and $self->_set_operational_status( status => $1 );
1557 1         7 return $self->SUPER::__parse_name( $name );
1558             }
1559              
1560             {
1561             my @encode_status;
1562             $encode_status[BODY_STATUS_IS_OPERATIONAL] = '+';
1563             $encode_status[BODY_STATUS_IS_SPARE] = 'S';
1564             $encode_status[BODY_STATUS_IS_TUMBLING] = '-';
1565             $encode_status[BODY_STATUS_IS_DECAYED] = 'D';
1566              
1567             sub __encode_operational_status {
1568             ## my ( $self, $name, $status ) = @_;
1569 0     0   0 my ( $self, undef, $status ) = @_; # Name unused
1570 0 0       0 defined $status
1571             or $status = $self->get( 'status' );
1572 0 0       0 defined $encode_status[ $status ]
1573             or return BODY_STATUS_IS_TUMBLING;
1574 0         0 return $encode_status[ $status ];
1575             }
1576             }
1577              
1578             {
1579              
1580             my %status_map = (
1581             BODY_STATUS_IS_OPERATIONAL() => BODY_STATUS_IS_OPERATIONAL,
1582             '' => BODY_STATUS_IS_OPERATIONAL,
1583             '+' => BODY_STATUS_IS_OPERATIONAL,
1584             BODY_STATUS_IS_SPARE() => BODY_STATUS_IS_SPARE,
1585             '?' => BODY_STATUS_IS_SPARE,
1586             'S' => BODY_STATUS_IS_SPARE,
1587             's' => BODY_STATUS_IS_SPARE,
1588             'D' => BODY_STATUS_IS_DECAYED,
1589             'd' => BODY_STATUS_IS_DECAYED,
1590             BODY_STATUS_IS_TUMBLING() => BODY_STATUS_IS_TUMBLING,
1591             BODY_STATUS_IS_DECAYED() => BODY_STATUS_IS_DECAYED,
1592             );
1593              
1594             sub __decode_operational_status {
1595 295     295   44582 my ( $value ) = @_;
1596 295 50       472 defined $value
1597             or return BODY_STATUS_IS_OPERATIONAL;;
1598 295 100       541 defined $status_map{$value}
1599             or return BODY_STATUS_IS_TUMBLING;
1600 199         354 return $status_map{$value};
1601             }
1602             }
1603              
1604             sub _set_operational_status {
1605 0     0     my ( $self, $name, $value ) = @_;
1606 0           $self->{&ATTRIBUTE_KEY}{$name} = __decode_operational_status( $value );
1607 0           return $self;
1608             }
1609              
1610             {
1611             my %json_map = (
1612             operational_status => \&__encode_operational_status,
1613             );
1614              
1615             sub TO_JSON {
1616 0     0 1   my ( $self ) = @_;
1617 0           return $self->__to_json(
1618             \%json_map,
1619             $self->SUPER::TO_JSON(),
1620             );
1621             }
1622             }
1623              
1624             # All Iridium Classic satellites.
1625             #
1626             # Generated by Astro::SpaceTrack
1627             # $ tools/all_iridium_classic -iridium -indent=0
1628             # on Mon Jun 29 12:08:42 2020 GMT
1629             #
1630             # The following static method is UNSUPPORTED, and exists solely for the
1631             # benefit of xt/author/iridium_status.t. It may be modified or revoked
1632             # at any time.
1633 0     0     sub __iridium_status_as_of { return( qw{ 7 16 11 29 5 2020 } ) }
1634              
1635             __PACKAGE__->status( clear => 'iridium' );
1636             __PACKAGE__->status( add => 24792, iridium => 'D', 'Iridium 8', 'Decayed 2017-11-24' );
1637             __PACKAGE__->status( add => 24793, iridium => '-', 'Iridium 7', 'Tumbling' );
1638             __PACKAGE__->status( add => 24794, iridium => 'D', 'Iridium 6', 'Decayed 2017-12-23' );
1639             __PACKAGE__->status( add => 24795, iridium => '-', 'Iridium 5', 'Tumbling' );
1640             __PACKAGE__->status( add => 24796, iridium => '-', 'Iridium 4', 'Tumbling' );
1641             __PACKAGE__->status( add => 24836, iridium => '-', 'Iridium 914', 'Tumbling' );
1642             __PACKAGE__->status( add => 24837, iridium => 'D', 'Iridium 12', 'Decayed 2018-09-02' );
1643             __PACKAGE__->status( add => 24838, iridium => 'D', 'Iridium 9', 'Decayed 2003-03-11' );
1644             __PACKAGE__->status( add => 24839, iridium => 'D', 'Iridium 10', 'Decayed 2018-10-06' );
1645             __PACKAGE__->status( add => 24840, iridium => 'D', 'Iridium 13', 'Decayed 2018-04-29' );
1646             __PACKAGE__->status( add => 24841, iridium => '-', 'Iridium 16', 'Tumbling' );
1647             __PACKAGE__->status( add => 24842, iridium => '-', 'Iridium 911', 'Tumbling' );
1648             __PACKAGE__->status( add => 24869, iridium => 'D', 'Iridium 15', 'Decayed 2018-10-14' );
1649             __PACKAGE__->status( add => 24870, iridium => '-', 'Iridium 17', 'Tumbling' );
1650             __PACKAGE__->status( add => 24871, iridium => '-', 'Iridium 920', 'Tumbling' );
1651             __PACKAGE__->status( add => 24872, iridium => 'D', 'Iridium 18', 'Decayed 2018-08-19' );
1652             __PACKAGE__->status( add => 24873, iridium => '-', 'Iridium 921', 'Tumbling' );
1653             __PACKAGE__->status( add => 24903, iridium => '-', 'Iridium 26', 'Tumbling' );
1654             __PACKAGE__->status( add => 24904, iridium => 'D', 'Iridium 25', 'Decayed 2018-05-14' );
1655             __PACKAGE__->status( add => 24905, iridium => 'D', 'Iridium 46', 'Decayed 2019-05-11' );
1656             __PACKAGE__->status( add => 24906, iridium => 'D', 'Iridium 23', 'Decayed 2018-03-28' );
1657             __PACKAGE__->status( add => 24907, iridium => '-', 'Iridium 22', 'Tumbling' );
1658             __PACKAGE__->status( add => 24925, iridium => '-', 'Dummy mass 1', 'Tumbling' );
1659             __PACKAGE__->status( add => 24926, iridium => '-', 'Dummy mass 2', 'Tumbling' );
1660             __PACKAGE__->status( add => 24944, iridium => '-', 'Iridium 29', 'Tumbling' );
1661             __PACKAGE__->status( add => 24945, iridium => 'D', 'Iridium 32', 'Decayed 2019-03-10' );
1662             __PACKAGE__->status( add => 24946, iridium => '-', 'Iridium 33', 'Tumbling' );
1663             __PACKAGE__->status( add => 24947, iridium => 'D', 'Iridium 27', 'Decayed 2002-02-01' );
1664             __PACKAGE__->status( add => 24948, iridium => '-', 'Iridium 28', 'Tumbling' );
1665             __PACKAGE__->status( add => 24949, iridium => 'D', 'Iridium 30', 'Decayed 2017-09-28' );
1666             __PACKAGE__->status( add => 24950, iridium => 'D', 'Iridium 31', 'Decayed 2018-12-20' );
1667             __PACKAGE__->status( add => 24965, iridium => 'D', 'Iridium 19', 'Decayed 2018-04-07' );
1668             __PACKAGE__->status( add => 24966, iridium => 'D', 'Iridium 35', 'Decayed 2018-12-26' );
1669             __PACKAGE__->status( add => 24967, iridium => '-', 'Iridium 36', 'Tumbling' );
1670             __PACKAGE__->status( add => 24968, iridium => 'D', 'Iridium 37', 'Decayed 2018-05-26' );
1671             __PACKAGE__->status( add => 24969, iridium => 'D', 'Iridium 34', 'Decayed 2018-01-08' );
1672             __PACKAGE__->status( add => 25039, iridium => 'D', 'Iridium 43', 'Decayed 2018-02-11' );
1673             __PACKAGE__->status( add => 25040, iridium => 'D', 'Iridium 41', 'Decayed 2018-07-28' );
1674             __PACKAGE__->status( add => 25041, iridium => 'D', 'Iridium 40', 'Decayed 2018-09-23' );
1675             __PACKAGE__->status( add => 25042, iridium => '-', 'Iridium 39', 'Tumbling' );
1676             __PACKAGE__->status( add => 25043, iridium => '-', 'Iridium 38', 'Tumbling' );
1677             __PACKAGE__->status( add => 25077, iridium => '-', 'Iridium 42', 'Tumbling' );
1678             __PACKAGE__->status( add => 25078, iridium => '-', 'Iridium 44', 'Tumbling' );
1679             __PACKAGE__->status( add => 25104, iridium => '-', 'Iridium 45', 'Tumbling' );
1680             __PACKAGE__->status( add => 25105, iridium => '-', 'Iridium 24', 'Tumbling' );
1681             __PACKAGE__->status( add => 25106, iridium => 'D', 'Iridium 47', 'Decayed 2018-09-01' );
1682             __PACKAGE__->status( add => 25107, iridium => 'D', 'Iridium 48', 'Decayed 2001-05-05' );
1683             __PACKAGE__->status( add => 25108, iridium => 'D', 'Iridium 49', 'Decayed 2018-02-13' );
1684             __PACKAGE__->status( add => 25169, iridium => 'D', 'Iridium 52', 'Decayed 2018-11-05' );
1685             __PACKAGE__->status( add => 25170, iridium => 'D', 'Iridium 56', 'Decayed 2018-10-11' );
1686             __PACKAGE__->status( add => 25171, iridium => 'D', 'Iridium 54', 'Decayed 2019-05-11' );
1687             __PACKAGE__->status( add => 25172, iridium => 'D', 'Iridium 50', 'Decayed 2018-09-23' );
1688             __PACKAGE__->status( add => 25173, iridium => 'D', 'Iridium 53', 'Decayed 2018-09-30' );
1689             __PACKAGE__->status( add => 25262, iridium => '-', 'Iridium 51', 'Tumbling' );
1690             __PACKAGE__->status( add => 25263, iridium => 'D', 'Iridium 61', 'Decayed 2019-07-23' );
1691             __PACKAGE__->status( add => 25272, iridium => 'D', 'Iridium 55', 'Decayed 2019-03-31' );
1692             __PACKAGE__->status( add => 25273, iridium => '-', 'Iridium 57', 'Tumbling' );
1693             __PACKAGE__->status( add => 25274, iridium => 'D', 'Iridium 58', 'Decayed 2019-04-07' );
1694             __PACKAGE__->status( add => 25275, iridium => 'D', 'Iridium 59', 'Decayed 2019-03-11' );
1695             __PACKAGE__->status( add => 25276, iridium => 'D', 'Iridium 60', 'Decayed 2019-03-17' );
1696             __PACKAGE__->status( add => 25285, iridium => 'D', 'Iridium 62', 'Decayed 2018-11-07' );
1697             __PACKAGE__->status( add => 25286, iridium => '-', 'Iridium 63', 'Tumbling' );
1698             __PACKAGE__->status( add => 25287, iridium => 'D', 'Iridium 64', 'Decayed 2019-04-01' );
1699             __PACKAGE__->status( add => 25288, iridium => 'D', 'Iridium 65', 'Decayed 2018-07-19' );
1700             __PACKAGE__->status( add => 25289, iridium => 'D', 'Iridium 66', 'Decayed 2018-08-23' );
1701             __PACKAGE__->status( add => 25290, iridium => 'D', 'Iridium 67', 'Decayed 2018-07-02' );
1702             __PACKAGE__->status( add => 25291, iridium => 'D', 'Iridium 68', 'Decayed 2018-06-06' );
1703             __PACKAGE__->status( add => 25319, iridium => '-', 'Iridium 69', 'Tumbling' );
1704             __PACKAGE__->status( add => 25320, iridium => '-', 'Iridium 71', 'Tumbling' );
1705             __PACKAGE__->status( add => 25342, iridium => 'D', 'Iridium 70', 'Decayed 2018-10-11' );
1706             __PACKAGE__->status( add => 25343, iridium => 'D', 'Iridium 72', 'Decayed 2018-05-14' );
1707             __PACKAGE__->status( add => 25344, iridium => '-', 'Iridium 73', 'Tumbling' );
1708             __PACKAGE__->status( add => 25345, iridium => 'D', 'Iridium 74', 'Decayed 2017-06-11' );
1709             __PACKAGE__->status( add => 25346, iridium => 'D', 'Iridium 75', 'Decayed 2018-07-10' );
1710             __PACKAGE__->status( add => 25431, iridium => 'D', 'Iridium 3', 'Decayed 2018-02-08' );
1711             __PACKAGE__->status( add => 25432, iridium => 'D', 'Iridium 76', 'Decayed 2018-08-28' );
1712             __PACKAGE__->status( add => 25467, iridium => '-', 'Iridium 82', 'Tumbling' );
1713             __PACKAGE__->status( add => 25468, iridium => 'D', 'Iridium 81', 'Decayed 2018-07-17' );
1714             __PACKAGE__->status( add => 25469, iridium => 'D', 'Iridium 80', 'Decayed 2018-08-12' );
1715             __PACKAGE__->status( add => 25470, iridium => 'D', 'Iridium 79', 'Decayed 2000-11-29' );
1716             __PACKAGE__->status( add => 25471, iridium => 'D', 'Iridium 77', 'Decayed 2017-09-22' );
1717             __PACKAGE__->status( add => 25527, iridium => '-', 'Iridium 2', 'Tumbling' );
1718             __PACKAGE__->status( add => 25528, iridium => 'D', 'Iridium 86', 'Decayed 2018-10-05' );
1719             __PACKAGE__->status( add => 25529, iridium => 'D', 'Iridium 85', 'Decayed 2000-12-30' );
1720             __PACKAGE__->status( add => 25530, iridium => 'D', 'Iridium 84', 'Decayed 2018-11-04' );
1721             __PACKAGE__->status( add => 25531, iridium => 'D', 'Iridium 83', 'Decayed 2018-11-05' );
1722             __PACKAGE__->status( add => 25577, iridium => 'D', 'Iridium 20', 'Decayed 2018-10-22' );
1723             __PACKAGE__->status( add => 25578, iridium => 'D', 'Iridium 11', 'Decayed 2018-10-22' );
1724             __PACKAGE__->status( add => 25777, iridium => 'D', 'Iridium 14', 'Decayed 2019-03-15' );
1725             __PACKAGE__->status( add => 25778, iridium => 'D', 'Iridium 21', 'Decayed 2018-05-24' );
1726             __PACKAGE__->status( add => 27372, iridium => 'D', 'Iridium 91', 'Decayed 2019-03-13' );
1727             __PACKAGE__->status( add => 27373, iridium => 'D', 'Iridium 90', 'Decayed 2019-01-23' );
1728             __PACKAGE__->status( add => 27374, iridium => 'D', 'Iridium 94', 'Decayed 2018-04-18' );
1729             __PACKAGE__->status( add => 27375, iridium => 'D', 'Iridium 95', 'Decayed 2019-03-25' );
1730             __PACKAGE__->status( add => 27376, iridium => '-', 'Iridium 96', 'SpaceTrack' );
1731             __PACKAGE__->status( add => 27450, iridium => 'D', 'Iridium 97', 'Decayed 2019-12-27' );
1732             __PACKAGE__->status( add => 27451, iridium => 'D', 'Iridium 98', 'Decayed 2018-08-24' );
1733              
1734             # Summary:
1735             # Operational [+]: 0
1736             # Spare [S]: 0
1737             # Tumbling [-]: 32
1738             # Decayed [D]: 65
1739              
1740             1;
1741              
1742             __END__