jord-0.6.0.0: Geographical Position Calculations

Copyright(c) 2018 Cedric Liegeois
LicenseBSD3
MaintainerCedric Liegeois <ofmooseandmen@yahoo.fr>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Geo.Jord.Frames

Contents

Description

Type and functions for working with delta vectors in different reference frames.

All functions are implemented using the vector-based approached described in Gade, K. (2010). A Non-singular Horizontal Position Representation

Synopsis

Reference Frames

class Frame a where Source #

class for reference frames.

Supported frames:

Minimal complete definition

rEF

Methods

rEF Source #

Arguments

:: a 
-> [Vector3d]

rotation matrix to transform vectors decomposed in frame a to vectors decomposed Earth-Fixed frame.

Instances
Frame FrameN Source #

R_EN: frame N to Earth

Instance details

Defined in Data.Geo.Jord.Frames

Methods

rEF :: FrameN -> [Vector3d] Source #

Frame FrameL Source #

R_EL: frame L to Earth

Instance details

Defined in Data.Geo.Jord.Frames

Methods

rEF :: FrameL -> [Vector3d] Source #

Frame FrameB Source #

R_EB: frame B to Earth

Instance details

Defined in Data.Geo.Jord.Frames

Methods

rEF :: FrameB -> [Vector3d] Source #

Body frame

data FrameB Source #

Body frame (typically of a vehicle).

  • Position: The origin is in the vehicle’s reference point.
  • Orientation: The x-axis points forward, the y-axis to the right (starboard) and the z-axis in the vehicle’s down direction.
  • Comments: The frame is fixed to the vehicle.
Instances
Eq FrameB Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

(==) :: FrameB -> FrameB -> Bool #

(/=) :: FrameB -> FrameB -> Bool #

Show FrameB Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Frame FrameB Source #

R_EB: frame B to Earth

Instance details

Defined in Data.Geo.Jord.Frames

Methods

rEF :: FrameB -> [Vector3d] Source #

yaw :: FrameB -> Angle Source #

body yaw angle (vertical axis).

pitch :: FrameB -> Angle Source #

body pitch angle (transverse axis).

roll :: FrameB -> Angle Source #

body roll angle (longitudinal axis).

frameB :: ETransform a => Angle -> Angle -> Angle -> a -> Earth -> FrameB Source #

FrameB from given yaw, pitch, roll, position (origin) and earth model.

Local frame

data FrameL Source #

Local level, Wander azimuth frame.

  • Position: The origin is directly beneath or above the vehicle (B), at Earth’s surface (surface of ellipsoid model).
  • Orientation: The z-axis is pointing down. Initially, the x-axis points towards north, and the y-axis points towards east, but as the vehicle moves they are not rotating about the z-axis (their angular velocity relative to the Earth has zero component along the z-axis). (Note: Any initial horizontal direction of the x- and y-axes is valid for L, but if the initial position is outside the poles, north and east are usually chosen for convenience.)
  • Comments: The L-frame is equal to the N-frame except for the rotation about the z-axis, which is always zero for this frame (relative to Earth). Hence, at a given time, the only difference between the frames is an angle between the x-axis of L and the north direction; this angle is called the wander azimuth angle. The L-frame is well suited for general calculations, as it is non-singular.
Instances
Eq FrameL Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

(==) :: FrameL -> FrameL -> Bool #

(/=) :: FrameL -> FrameL -> Bool #

Show FrameL Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Frame FrameL Source #

R_EL: frame L to Earth

Instance details

Defined in Data.Geo.Jord.Frames

Methods

rEF :: FrameL -> [Vector3d] Source #

wanderAzimuth :: FrameL -> Angle Source #

wander azimuth: angle between x-axis of the frame L and the north direction.

frameL :: ETransform a => Angle -> a -> Earth -> FrameL Source #

FrameL from given wander azimuth, position (origin) and earth model.

North-East-Down frame

data FrameN Source #

North-East-Down (local level) frame.

  • Position: The origin is directly beneath or above the vehicle (B), at Earth’s surface (surface of ellipsoid model).
  • Orientation: The x-axis points towards north, the y-axis points towards east (both are horizontal), and the z-axis is pointing down.
  • Comments: When moving relative to the Earth, the frame rotates about its z-axis to allow the x-axis to always point towards north. When getting close to the poles this rotation rate will increase, being infinite at the poles. The poles are thus singularities and the direction of the x- and y-axes are not defined here. Hence, this coordinate frame is not suitable for general calculations.
Instances
Eq FrameN Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

(==) :: FrameN -> FrameN -> Bool #

(/=) :: FrameN -> FrameN -> Bool #

Show FrameN Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Frame FrameN Source #

R_EN: frame N to Earth

Instance details

Defined in Data.Geo.Jord.Frames

Methods

rEF :: FrameN -> [Vector3d] Source #

frameN :: ETransform a => a -> Earth -> FrameN Source #

FrameN from given position (origin) and earth model.

Deltas

data Delta Source #

delta between position in one of the reference frames.

Instances
Eq Delta Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

(==) :: Delta -> Delta -> Bool #

(/=) :: Delta -> Delta -> Bool #

Show Delta Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

showsPrec :: Int -> Delta -> ShowS #

show :: Delta -> String #

showList :: [Delta] -> ShowS #

delta :: Length -> Length -> Length -> Delta Source #

Delta from given x, y and z length.

deltaMetres :: Double -> Double -> Double -> Delta Source #

Delta from given x, y and z length in metres.

dx :: Delta -> Length Source #

x component of given Delta.

dy :: Delta -> Length Source #

y component of given Delta.

dz :: Delta -> Length Source #

z component of given Delta.

Delta in the north, east, down frame

data Ned Source #

North, east and down delta (thus in frame FrameN).

Instances
Eq Ned Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

(==) :: Ned -> Ned -> Bool #

(/=) :: Ned -> Ned -> Bool #

Show Ned Source # 
Instance details

Defined in Data.Geo.Jord.Frames

Methods

showsPrec :: Int -> Ned -> ShowS #

show :: Ned -> String #

showList :: [Ned] -> ShowS #

ned :: Length -> Length -> Length -> Ned Source #

Ned from given north, east and down.

nedMetres :: Double -> Double -> Double -> Ned Source #

Ned from given north, east and down in metres.

north :: Ned -> Length Source #

North component of given Ned.

east :: Ned -> Length Source #

East component of given Ned.

down :: Ned -> Length Source #

Down component of given Ned.

bearing :: Ned -> Angle Source #

bearing v computes the bearing in compass angle of the NED vector v from north.

Compass angles are clockwise angles from true north: 0 = north, 90 = east, 180 = south, 270 = west.

elevation :: Ned -> Angle Source #

elevation v computes the elevation of the NED vector v from horizontal (ie tangent to ellipsoid surface).

slantRange :: Ned -> Length Source #

slantRange v computes the distance from origin in the local system of the NED vector v.

Calculations

deltaBetween :: (ETransform a, Frame c) => a -> a -> (a -> Earth -> c) -> Earth -> Delta Source #

deltaBetween p1 p2 f e computes the exact Delta between the two positions p1 and p2 in frame f using earth model e.

    let p1 = decimalLatLongHeight 1 2 (metres (-3))
    let p2 = decimalLatLongHeight 4 5 (metres (-6))
    let w = decimalDegrees 5 -- wander azimuth
    let d = deltaBetween p1 p2 (frameL w) wgs84
    d = deltaMetres 359490.579 302818.523 17404.272

nedBetween :: ETransform a => a -> a -> Earth -> Ned Source #

nedBetween p1 p2 e computes the exact Ned vector between the two positions p1 and p2, in north, east, and down using earth model e.

Produced Ned delta is relative to p1: Due to the curvature of Earth and different directions to the North Pole, the north, east, and down directions will change (relative to Earth) for different places.

Position p1 must be outside the poles for the north and east directions to be defined.

    let p1 = decimalLatLongHeight 1 2 (metres (-3))
    let p2 = decimalLatLongHeight 4 5 (metres (-6))
    let d1 = nedBetween p1 p2 wgs84
    let d2 = deltaBetween p1 p2 frameN wgs84
    north d1 = dx d2
    east d1 = dy d2
    down d1 = dz d2

target :: (ETransform a, Frame c) => a -> (a -> Earth -> c) -> Delta -> Earth -> a Source #

target p0 f d e computes the target position from position p0 and delta d using in frame f and using earth model e.

    let p0 = decimalLatLongHeight 49.66618 3.45063 zero
    let y = decimalDegrees 10 -- yaw
    let r = decimalDegrees 20 -- roll
    let p = decimalDegrees 30 -- pitch
    let d = deltaMetres 3000 2000 100
    target p0 (frameB y r p) d wgs84 = decimalLatLongHeight 49.6918016 3.4812669 (metres 6.007)

targetN :: ETransform a => a -> Ned -> Earth -> a Source #

targetN p0 d e computes the target position from position p0 and north, east, down d using earth model e.

    let p0 = decimalLatLongHeight 49.66618 3.45063 zero
    targetN p0 (nedMeters 100 200 300) wgs84 = target p0 frameN (deltaMetres 100 200 300) wgs84