geodetics-0.0.2: Terrestrial coordinate systems and associated calculations.

Safe HaskellNone

Geodetics.Ellipsoids

Contents

Description

An Ellipsoid is a reasonable best fit for the surface of the Earth over some defined area. WGS84 is the standard used for the whole of the Earth. Other Ellipsoids are considered a best fit for some specific area.

Synopsis

Helmert transform between geodetic reference systems

data Helmert Source

The 7 parameter Helmert transformation. The monoid instance allows composition.

inverseHelmert :: Helmert -> HelmertSource

The inverse of a Helmert transformation.

type ECEF = Vec3 (Length Double)Source

Earth-centred, Earth-fixed coordinates as a vector. The origin and axes are not defined: use with caution.

applyHelmert :: Helmert -> ECEF -> ECEFSource

Apply a Helmert transformation to earth-centered coordinates.

Ellipsoid models of the Geoid

class (Show a, Eq a) => Ellipsoid a whereSource

An Ellipsoid is defined by the major radius and the inverse flattening (which define its shape), and its Helmert transform relative to WGS84 (which defines its position and orientation).

The inclusion of the Helmert parameters relative to WGS84 actually make this a Terrestrial Reference Frame (TRF), but the term Ellipsoid will be used in this library for readability.

Minimum definition: majorRadius, flatR & helmert.

Laws:

 helmertToWGS84 = applyHelmert . helmert
 helmertFromWGS84 e . helmertToWGS84 e = id

Methods

majorRadius :: a -> Length DoubleSource

flatRSource

Arguments

:: a 
-> Dimensionless Double

Inverse of the flattening.

helmert :: a -> HelmertSource

helmertToWSG84Source

Arguments

:: a 
-> ECEF 
-> ECEF

The Helmert transform that will convert a position wrt this ellipsoid into a position wrt WGS84.

helmertFromWSG84Source

Arguments

:: a 
-> ECEF 
-> ECEF

And its inverse.

data WGS84 Source

The WGS84 geoid, major radius 6378137.0 meters, flattening = 1 / 298.257223563 as defined in "Technical Manual DMA TM 8358.1 - Datums, Ellipsoids, Grids, and Grid Reference Systems" at the National Geospatial-Intelligence Agency (NGA).

The WGS84 has a special place in this library as the standard Ellipsoid against which all others are defined.

Constructors

WGS84 

data LocalEllipsoid Source

Ellipsoids other than WGS84, used within a defined geographical area where they are a better fit to the local geoid. Can also be used for historical ellipsoids.

The Show instance just returns the name. Creating two different local ellipsoids with the same name is a Bad Thing.

flattening :: Ellipsoid e => e -> Dimensionless DoubleSource

Flattening (f) of an ellipsoid.

minorRadius :: Ellipsoid e => e -> Length DoubleSource

The minor radius of an ellipsoid.

eccentricity2 :: Ellipsoid e => e -> Dimensionless DoubleSource

The eccentricity squared of an ellipsoid.

eccentricity'2 :: Ellipsoid e => e -> Dimensionless DoubleSource

The second eccentricity squared of an ellipsoid.

Auxiliary latitudes and related Values

normal :: Ellipsoid e => e -> Angle Double -> Length DoubleSource

Distance from the surface at the specified latitude to the axis of the Earth straight down. Also known as the radius of curvature in the prime vertical, and often denoted N.

latitudeRadius :: Ellipsoid e => e -> Angle Double -> Length DoubleSource

Radius of the circle of latitude: the distance from a point at that latitude to the axis of the Earth.

meridianRadius :: Ellipsoid e => e -> Angle Double -> Length DoubleSource

Radius of curvature in the meridian at the specified latitude. Often denoted M.

primeVerticalRadius :: Ellipsoid e => e -> Angle Double -> Length DoubleSource

Radius of curvature of the ellipsoid perpendicular to the meridian at the specified latitude.

isometricLatitude :: Ellipsoid e => e -> Angle Double -> Angle DoubleSource

The isometric latitude. The isometric latitude is conventionally denoted by ψ (not to be confused with the geocentric latitude): it is used in the development of the ellipsoidal versions of the normal Mercator projection and the Transverse Mercator projection. The name isometric arises from the fact that at any point on the ellipsoid equal increments of ψ and longitude λ give rise to equal distance displacements along the meridians and parallels respectively.

Tiny linear algebra library for 3D vectors

type Vec3 a = (a, a, a)Source

3d vector as (X,Y,Z).

type Matrix3 a = Vec3 (Vec3 a)Source

3x3 transform matrix for Vec3.

add3 :: Num a => Vec3 (Quantity d a) -> Vec3 (Quantity d a) -> Vec3 (Quantity d a)Source

Add two vectors

scale3 :: (Num a, Mul d d' d'') => Vec3 (Dimensional DQuantity d a) -> Dimensional DQuantity d' a -> Vec3 (Dimensional DQuantity d'' a)Source

Multiply a vector by a scalar.

negate3 :: Num a => Vec3 (Quantity d a) -> Vec3 (Quantity d a)Source

Negation of a vector.

transform3 :: (Num a, Mul d d' d'') => Matrix3 (Dimensional DQuantity d a) -> Vec3 (Dimensional DQuantity d' a) -> Vec3 (Dimensional DQuantity d'' a)Source

Multiply a matrix by a vector in the Dimensional type system.

invert3 :: (Fractional a, Mul d d d2, Mul d2 d d3, Div d2 d3 d1') => Matrix3 (Dimensional DQuantity d a) -> Matrix3 (Dimensional DQuantity d1' a)Source

Inverse of a 3x3 matrix.

trans3 :: Matrix3 a -> Matrix3 aSource

Transpose of a 3x3 matrix.

dot3 :: (Num a, Mul d1 d2 d3) => Vec3 (Dimensional DQuantity d1 a) -> Vec3 (Dimensional DQuantity d2 a) -> Dimensional DQuantity d3 aSource

Dot product of two vectors

cross3 :: (Num a, Mul d1 d2 d3) => Vec3 (Dimensional DQuantity d1 a) -> Vec3 (Dimensional DQuantity d2 a) -> Vec3 (Dimensional DQuantity d3 a)Source

Cross product of two vectors