Copyright | (c) 2020 Cedric Liegeois |
---|---|
License | BSD3 |
Maintainer | Cedric Liegeois <ofmooseandmen@yahoo.fr> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Type and functions for working with delta vectors in different local reference frames: all frames are location dependent.
In order to use this module you should start with the following imports:
import Data.Geo.Jord.LocalFrames import Data.Geo.Jord.Position
All functions are implemented using the vector-based approached described in Gade, K. (2010). A Non-singular Horizontal Position Representation
Notes:
- The term Earth is used to be consistent with the paper. However any celestial body reference frame can be used.
- Though the API accept spherical models, doing so defeats the purpose of this module which is to find exact solutions. Prefer using ellipsoidal models.
Synopsis
- class LocalFrame a where
- data FrameB a
- yaw :: FrameB a -> Angle
- pitch :: FrameB a -> Angle
- roll :: FrameB a -> Angle
- bOrigin :: FrameB a -> Position a
- frameB :: Model a => Angle -> Angle -> Angle -> Position a -> FrameB a
- data FrameL a
- wanderAzimuth :: FrameL a -> Angle
- lOrigin :: FrameL a -> Position a
- frameL :: Model a => Angle -> Position a -> FrameL a
- data FrameN a
- nOrigin :: FrameN a -> Position a
- frameN :: Model a => Position a -> FrameN a
- data Delta
- delta :: Length -> Length -> Length -> Delta
- deltaMetres :: Double -> Double -> Double -> Delta
- dx :: Delta -> Length
- dy :: Delta -> Length
- dz :: Delta -> Length
- data Ned
- ned :: Length -> Length -> Length -> Ned
- nedMetres :: Double -> Double -> Double -> Ned
- north :: Ned -> Length
- east :: Ned -> Length
- down :: Ned -> Length
- bearing :: Ned -> Angle
- elevation :: Ned -> Angle
- slantRange :: Ned -> Length
- deltaBetween :: (LocalFrame a, Model b) => Position b -> Position b -> (Position b -> a) -> Delta
- nedBetween :: Model a => Position a -> Position a -> Ned
- target :: (LocalFrame a, Model b) => Position b -> (Position b -> a) -> Delta -> Position b
- targetN :: Model a => Position a -> Ned -> Position a
- module Data.Geo.Jord.Rotation
Local Reference frame
class LocalFrame a where Source #
class for local reference frames: a reference frame which is location dependant.
Supported frames:
:: a | |
-> [Vector3d] | rotation matrix to transform vectors decomposed in frame |
Instances
LocalFrame (FrameN a) Source # | R_EN: frame N to Earth |
LocalFrame (FrameL m) Source # | R_EL: frame L to Earth |
LocalFrame (FrameB a) Source # | R_EB: frame B to Earth |
Body frame
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.
frameB :: Model a => Angle -> Angle -> Angle -> Position a -> FrameB a Source #
FrameB
from given yaw, pitch, roll, position (origin).
Local level/wander azimuth frame
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.
wanderAzimuth :: FrameL a -> Angle Source #
wander azimuth: angle between x-axis of the frame L and the north direction.
frameL :: Model a => Angle -> Position a -> FrameL a Source #
FrameL
from given wander azimuth, position (origin).
North-East-Down frame
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.
Deltas
delta between position in one of the reference frames.
deltaMetres :: Double -> Double -> Double -> Delta Source #
Delta
from given x, y and z length in metres.
Delta in the north, east, down frame
North, east and down delta (thus in frame FrameN
).
nedMetres :: Double -> Double -> Double -> Ned Source #
Ned
from given north, east and down in metres.
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 :: (LocalFrame a, Model b) => Position b -> Position b -> (Position b -> a) -> Delta Source #
deltaBetween p1 p2 f
computes the exact Delta
between the two
positions p1
and p2
in local frame f
.
Examples
>>>
import Data.Geo.Jord.LocalFrames
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = wgs84Pos 1 2 (metres (-3))
>>>
let p2 = wgs84Pos 4 5 (metres (-6))
>>>
let w = decimalDegrees 5 -- wander azimuth
>>>
deltaBetween p1 p2 (frameL w)
Delta (Vector3d {vx = 359490.5782, vy = 302818.5225, vz = 17404.2714})
nedBetween :: Model a => Position a -> Position a -> Ned Source #
nedBetween p1 p2
computes the exact Ned
vector between the two
positions p1
and p2
, in north, east, and down.
Resulting 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.
This is equivalent to:
deltaBetween
p1 p2frameN
Examples
>>>
import Data.Geo.Jord.LocalFrames
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = wgs84Pos 1 2 (metres (-3))
>>>
let p2 = wgs84Pos 4 5 (metres (-6))
>>>
nedBetween p1 p2
Ned (Vector3d {vx = 331730.2348, vy = 332997.875, vz = 17404.2714})
target :: (LocalFrame a, Model b) => Position b -> (Position b -> a) -> Delta -> Position b Source #
target p0 f d
computes the target position from position p0
and delta d
in local frame f
.
Examples
>>>
import Data.Geo.Jord.LocalFrames
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p0 = wgs84Pos 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
49°41'30.486"N,3°28'52.561"E 6.0077m (WGS84)
targetN :: Model a => Position a -> Ned -> Position a Source #
targetN p0 d
computes the target position from position p0
and north, east, down d
.
This is equivalent to:
target
p0frameN
(Delta
d)
Examples
>>>
import Data.Geo.Jord.LocalFrames
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p0 = wgs84Pos 49.66618 3.45063 zero
>>>
targetN p0 (nedMeters 100 200 300)
49°40'1.485"N,3°27'12.242"E -299.9961m (WGS84)
re-exported for convenience
module Data.Geo.Jord.Rotation