orbits-0.3: Types and functions for Kepler orbits.

Safe HaskellNone
LanguageHaskell2010

Physics.Orbit

Contents

Description

Types and functions for dealing with Kepler orbits.

Synopsis

The Orbit data type and dependencies

data Orbit a Source #

Data type defining an orbit parameterized by the type used to represent values

Constructors

Orbit 

Fields

Instances
Eq a => Eq (Orbit a) Source # 
Instance details

Defined in Physics.Orbit

Methods

(==) :: Orbit a -> Orbit a -> Bool #

(/=) :: Orbit a -> Orbit a -> Bool #

Show a => Show (Orbit a) Source # 
Instance details

Defined in Physics.Orbit

Methods

showsPrec :: Int -> Orbit a -> ShowS #

show :: Orbit a -> String #

showList :: [Orbit a] -> ShowS #

data InclinationSpecifier a Source #

Along with PeriapsisSpecifier the InclinationSpecifier describes orbital elements extra to its geometry.

Constructors

Inclined

The orbit does not lie exactly in the reference plane

Fields

  • longitudeOfAscendingNode :: !(Angle a)

    The longitude of the ascending node, Ω.

    The angle between the reference direction and the point where the orbiting body crosses the reference plane in the positive z direction.

  • inclination :: !(Angle a)

    The orbit's inclination, i.

    The angle between the reference plane and the orbital plane

NonInclined

The orbit lies in the reference plane

data PeriapsisSpecifier a Source #

Along with InclinationSpecifier the PeriapsisSpecifier describes orbital elements extra to its geometry.

Constructors

Eccentric

The orbit is not circular

Fields

Circular

The orbit has an eccentricity of 0 so the argumentOfPeriapsis is indeterminate.

Instances
Eq a => Eq (PeriapsisSpecifier a) Source # 
Instance details

Defined in Physics.Orbit

Show a => Show (PeriapsisSpecifier a) Source # 
Instance details

Defined in Physics.Orbit

data Classification Source #

What for the orbit's geometry takes. This is dependant only on the eccentricity, e >= 0, of the orbit.

Constructors

Elliptic

0 <= e < 1

This includes circular orbits.

Parabolic

e == 1

Hyperbolic

e > 1

Functions for dealing with orbits

Utilities

isValid :: (Ord a, Num a) => Orbit a -> Bool Source #

Return true is the orbit is valid and false if it is invalid. The behavior of all the other functions in this module is undefined when given an invalid orbit.

classify :: (Num a, Ord a) => Orbit a -> Classification Source #

classify is a funciton which returns the orbit's class.

Orbital elements

apoapsis :: (Fractional a, Ord a) => Orbit a -> Maybe (Distance a) Source #

Calculate the distance between the bodies when they are at their most distant. apoapsis returns Nothing when given a parabolic or hyperbolic orbit.

meanMotion :: (Floating a, Ord a) => Orbit a -> Quantity ((:/) Radian Second) a Source #

Calculate the mean motion, n, of an orbit

This is the rate of change of the mean anomaly with respect to time.

period :: (Floating a, Ord a) => Orbit a -> Maybe (Time a) Source #

Calculate the orbital period, p, of an elliptic orbit.

period returns Nothing if given a parabolic or hyperbolic orbit.

arealVelocity :: (Ord a, Floating a) => Orbit a -> Quantity ((:/) ((:^) Meter (Succ (Succ Zero))) Second) a Source #

Calculate the areal velocity, A, of the orbit.

The areal velocity is the area swept out by the line between the orbiting body and the primary per second.

Geometry

semiMajorAxis :: (Fractional a, Ord a) => Orbit a -> Maybe (Distance a) Source #

Calculate the semi-major axis, a, of the Orbit. Returns Nothing when given a parabolic orbit for which there is no semi-major axis. Note that the semi-major axis of a hyperbolic orbit is negative.

semiMinorAxis :: (Floating a, Ord a) => Orbit a -> Distance a Source #

Calculate the semi-minor axis, b, of the Orbit. Like semiMajorAxis 'semiMinorAxis' o is negative when o is a hyperbolic orbit. In the case of a parabolic orbit semiMinorAxis returns 0m.

semiLatusRectum :: Num a => Orbit a -> Distance a Source #

Calculate the semiLatusRectum, l, of the Orbit

hyperbolicApproachAngle :: (Floating a, Ord a) => Orbit a -> Maybe (Angle a) Source #

Calculate the angle at which a body leaves the system when on a hyperbolic trajectory relative to the argument of periapsis. This is the limit of the true anomaly as time tends towards -infinity minus the argument of periapsis. The approach angle is in the closed range (-π..π/2).

This is the negation of the departure angle.

hyperbolicApproachAngle returns Nothing when given a non-hyperbolic orbit and -π when given a parabolic orbit.

hyperbolicDepartureAngle :: (Floating a, Ord a) => Orbit a -> Maybe (Angle a) Source #

Calculate the angle at which a body leaves the system when on an escape trajectory relative to the argument of periapsis. This is the limit of the true anomaly as time tends towards infinity minus the argument of periapsis. The departure angle is in the closed range (π/2..π).

This is the negation of the approach angle.

hyperbolicDepartureAngle returns Nothing when given an elliptic orbit and π when given a parabolic orbit.

Conversions

To time since periapse

timeAtMeanAnomaly :: (Floating a, Ord a) => Orbit a -> Angle a -> Time a Source #

Calculate the time since periapse, t, when the body has the given mean anomaly, M. M may be negative, indicating that the orbiting body has yet to reach periapse.

The sign of the time at mean anomaly M is the same as the sign of M.

The returned time is unbounded.

timeAtEccentricAnomaly :: (Floating a, Ord a) => Orbit a -> Angle a -> Maybe (Time a) Source #

Calculate the time since periapse, t, of an elliptic orbit when at eccentric anomaly E.

timeAtEccentricAnomaly returns Nothing if given a parabolic or hyperbolic orbit.

timeAtTrueAnomaly :: (Real a, Floating a) => Orbit a -> Angle a -> Maybe (Time a) Source #

Calculate the time since periapse given the true anomaly, ν, of an orbiting body.

To mean anomaly

meanAnomalyAtTime :: (Floating a, Ord a) => Orbit a -> Time a -> Angle a Source #

Calculate the mean anomaly, M, at the given time since periapse, t. t may be negative, indicating that the orbiting body has yet to reach periapse.

The sign of the mean anomaly at time t is the same as the sign of t.

The returned mean anomaly is unbounded.

meanAnomalyAtEccentricAnomaly :: (Floating a, Ord a) => Orbit a -> Angle a -> Maybe (Angle a) Source #

Calculate the mean anomaly, M, of an elliptic orbit when at eccentric anomaly E

meanAnomalyAtEccentricAnomaly returns Nothing if given a parabolic or hyperbolic orbit.

The number of orbits represented by the anomalies is preserved; i.e. M div 2π = E div

meanAnomalyAtTrueAnomaly :: (Real a, Floating a) => Orbit a -> Angle a -> Maybe (Angle a) Source #

Calculate the mean anomaly, M, of an orbiting body when at the given true anomaly, ν.

The number of orbits represented by the anomalies is preserved; i.e. M div 2π = ν div

Currently only implemented for elliptic orbits.

To eccentric anomaly

eccentricAnomalyAtTime :: (Converge [a], Floating a, Real a) => Orbit a -> Time a -> Maybe (Angle a) Source #

Calculate the eccentric anomaly, E, of an elliptic orbit at time t.

eccentricAnomalyAtTime returns Nothing when given a parabolic or hyperbolic orbit.

The number of orbits represented by the time is preserved; i.e. t div p = E div

eccentricAnomalyAtMeanAnomaly :: forall a. (Converge [a], Floating a, Real a) => Orbit a -> Angle a -> Maybe (Angle a) Source #

Calculate the eccentric anomaly, E, of an elliptic orbit when at mean anomaly M. This function is considerably slower than most other conversion functions as it uses an iterative method as no closed form solution exists.

The number of orbits represented by the anomalies is preserved; i.e. M div 2π = E div

eccentricAnomalyAtMeanAnomaly returns Nothing when given a parabolic or hyperbolic orbit.

eccentricAnomalyAtMeanAnomalyFloat :: Orbit Float -> Angle Float -> Maybe (Angle Float) Source #

eccentricAnomalyAtMeanAnomaly specialized to Float.

This function is used to calculate the initial guess for eccentricAnomalyAtMeanAnomaly.

eccentricAnomalyAtTrueAnomaly :: (Floating a, Real a) => Orbit a -> Angle a -> Maybe (Angle a) Source #

Calculate the eccentric anomaly, E, of an orbiting body when it has true anomaly, ν.

The number of orbits represented by the anomalies is preserved; i.e. ν div 2π = E div

Returns Nothing if given a parabolic or hyperbolic orbit.

To true anomaly

trueAnomalyAtTime :: (Converge [a], RealFloat a) => Orbit a -> Time a -> Maybe (Angle a) Source #

Calculate the true anomaly, ν, of a body at time since periapse, t.

trueAnomalyAtMeanAnomaly :: (Converge [a], RealFloat a) => Orbit a -> Angle a -> Maybe (Angle a) Source #

Calculate the true anomaly, ν, of an orbiting body when it has the given mean anomaly, _M.

trueAnomalyAtEccentricAnomaly Source #

Arguments

:: RealFloat a 
=> Orbit a

An elliptic orbit

-> Angle a

The eccentric anomaly _E

-> Maybe (Angle a)

The true anomaly, ν

Calculate the true anomaly, ν, of an orbiting body when it has the given eccentric anomaly, _E.

The number of orbits represented by the anomalies is preserved; i.e. ν div 2π = E div

Unit synonyms

type Time = Quantity Second Source #

A measure in seconds.

type Distance = Quantity Meter Source #

A measure in meters.

type Speed = Quantity ((:*) Meter ((:^) Second (Pred Zero))) Source #

A measure in meters per second.

type Mass = Quantity ((:@) Kilo Gram) Source #

A measure in kilograms.

type Angle = Quantity Radian Source #

A measure in radians.

type Unitless = Quantity Number Source #

A unitless measure.

Reexported from CReal

class Converge a #

If a type is an instance of Converge then it represents a stream of values which are increasingly accurate approximations of a desired value

Minimal complete definition

converge, convergeErr

Instances
Eq a => Converge [a]

Every list of equatable values is an instance of Converge. converge returns the first element which is equal to the succeeding element in the list. If the list ends before the sequence converges the last value is returned.

Instance details

Defined in Data.CReal.Converge

Associated Types

type Element [a] :: Type #

Methods

converge :: [a] -> Maybe (Element [a]) #

convergeErr :: (Element [a] -> Element [a]) -> [a] -> Maybe (Element [a]) #

Converge [CReal n]

The overlapping instance for CReal n has a slightly different behavior. The instance for Eq will cause converge to return a value when the list converges to within 2^-n (due to the Eq instance for CReal n) despite the precision the value is requested at by the surrounding computation. This instance will return a value approximated to the correct precision.

It's important to note when the error function reaches zero this function behaves like converge as it's not possible to determine the precision at which the error function should be evaluated at.

Find where log x = π using Newton's method

>>> let initialGuess = 1
>>> let improve x = x - x * (log x - pi)
>>> let Just y = converge (iterate improve initialGuess)
>>> showAtPrecision 10 y
"23.1406"
>>> showAtPrecision 50 y
"23.1406926327792686"
Instance details

Defined in Data.CReal.Converge

Associated Types

type Element [CReal n] :: Type #

Methods

converge :: [CReal n] -> Maybe (Element [CReal n]) #

convergeErr :: (Element [CReal n] -> Element [CReal n]) -> [CReal n] -> Maybe (Element [CReal n]) #