jord-2.0.0.0: Geographical Position Calculations
Copyright(c) 2020 Cedric Liegeois
LicenseBSD3
MaintainerCedric Liegeois <ofmooseandmen@yahoo.fr>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Geo.Jord.Geodetic

Description

Geodetic coordinates of points in specified models (e.g. WGS84) and conversion functions between n-vectors and latitude/longitude.

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

See Earth Coordinates

In order to use this module you should start with the following imports:

import qualified Data.Geo.Jord.Geodetic as Geodetic
import qualified Data.Geo.Jord.Length as Length
import Data.Geo.Jord.Models
Synopsis

positions types

data HorizontalPosition a Source #

Geodetic coordinates (geodetic latitude, longitude as Angles) of an horizontal position in a specified Model.

The coordinates are also given as a n-vector: the normal vector to the surface. n-vector orientation: * z-axis points to the North Pole along the body's rotation axis, * x-axis points towards the point where latitude = longitude = 0

Note: at the poles all longitudes are equal, therefore a position with a latitude of 90° or -90° will have its longitude forcibly set to 0°.

The "show" instance gives position in degrees, minutes, seconds, milliseconds (Angle "show" instance), and the model (Model "show" instance).

The "eq" instance returns True if and only if, both positions have the same latitude, longitude and model. Note: two positions in different models may represent the same location but are not considered equal.

data Position a Source #

Geodetic coordinates (geodetic latitude, longitude as Angles and height as Length) of a position in a specified model.

The "show" instance gives position in degrees, minutes, seconds, milliseconds (HorizontalPosition "show" instance), height (Length "show" instance) and the model (Model "show" instance).

The "eq" instance returns True if and only if, both positions have the same horizontal coordinates and height.

see HorizontalPosition.

Instances

Instances details
Model a => Eq (Position a) Source # 
Instance details

Defined in Data.Geo.Jord.Geodetic

Methods

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

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

Model a => Show (Position a) Source # 
Instance details

Defined in Data.Geo.Jord.Geodetic

Methods

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

show :: Position a -> String #

showList :: [Position a] -> ShowS #

HasCoordinates (Position a) Source # 
Instance details

Defined in Data.Geo.Jord.Geodetic

class HasCoordinates a where Source #

class for data that provide coordinates.

Minimal complete definition

latitude, longitude, nvector

Methods

latitude Source #

Arguments

:: a 
-> Angle

geodetic latitude

decimalLatitude Source #

Arguments

:: a 
-> Double

geodetic latitude in decimal degrees

longitude Source #

Arguments

:: a 
-> Angle

longitude

decimalLongitude Source #

Arguments

:: a 
-> Double

longitude in decimal degrees

nvector Source #

Arguments

:: a 
-> V3

n-vector; normal vector to the surface of a celestial body.

height :: Model a => Position a -> Length Source #

height of given Position above the surface of the celestial body.

model :: Model a => HorizontalPosition a -> a Source #

model of given HorizontalPosition (e.g. WGS84).

model' :: Model a => Position a -> a Source #

model of given Position (e.g. WGS84).

Smart constructors

latLongPos :: Model a => Double -> Double -> a -> HorizontalPosition a Source #

HorizontalPosition from given geodetic latitude & longitude in decimal degrees in the given model.

Latitude & longitude values are first converted to Angle to ensure a consistent resolution with the rest of the API, then wrapped to their respective range.

latLongPos' :: Model a => Angle -> Angle -> a -> HorizontalPosition a Source #

HorizontalPosition from given geodetic latitude & longitude in the given model.

Latitude & longitude values are wrapped to their respective range.

latLongHeightPos :: Model a => Double -> Double -> Length -> a -> Position a Source #

Position from given geodetic latitude & longitude in decimal degrees and height in the given model

Latitude & longitude values are first converted to Angle to ensure a consistent resolution with the rest of the API, then wrapped to their respective range.

latLongHeightPos' :: Model a => Angle -> Angle -> Length -> a -> Position a Source #

Position from given geodetic latitude & longitude and height in the given model. Latitude & longitude values are wrapped to their respective range.

wgs84Pos :: Double -> Double -> HorizontalPosition WGS84 Source #

HorizontalPosition from given geodetic latitude & longitude in decimal degrees in the WGS84 datum.

Latitude & longitude values are first converted to Angle to ensure a consistent resolution with the rest of the API, then wrapped to their respective range.

This is equivalent to:

Geodetic.latLongPos lat lon WGS84

wgs84Pos' :: Angle -> Angle -> HorizontalPosition WGS84 Source #

HorizontalPosition from given geodetic latitude & longitude and height in the WGS84 datum.

Latitude & longitude values are wrapped to their respective range.

This is equivalent to:

Geodetic.latLongPos' lat lon WGS84

s84Pos :: Double -> Double -> HorizontalPosition S84 Source #

HorizontalPosition from given latitude & longitude in decimal degrees in the spherical datum derived from WGS84.

Latitude & longitude values are first converted to Angle to ensure a consistent resolution with the rest of the API, then wrapped to their respective range.

This is equivalent to:

Geodetic.latLongPos lat lon S84

s84Pos' :: Angle -> Angle -> HorizontalPosition S84 Source #

Position from given latitude & longitude in the spherical datum derived from WGS84.

Latitude & longitude values are wrapped to their respective range.

This is equivalent to:

Geodetic.latLongPos' lat lon h S84

nvectorPos :: Model a => Double -> Double -> Double -> a -> HorizontalPosition a Source #

Position from given n-vector (x, y, z coordinates) in the given model.

(x, y, z) will be converted first to latitude & longitude to ensure a consistent resolution with the rest of the API.

This is equivalent to:

Geodetic.nvectorPos' (Math3d.vec3 x y z)

nvectorPos' :: Model a => V3 -> a -> HorizontalPosition a Source #

HorizontalPosition from given n-vector (x, y, z coordinates) in the given model.

(x, y, z) will be converted first to latitude & longitude to ensure a consistent resolution with the rest of the API.

nvectorHeightPos :: Model a => Double -> Double -> Double -> Length -> a -> Position a Source #

Position from given n-vector (x, y, z coordinates) and height in the given model.

(x, y, z) will be converted first to latitude & longitude to ensure a consistent resolution with the rest of the API. This is equivalent to:

Geodetic.nvectorHeightPos' (Math3d.vec3 x y z) h

nvectorHeightPos' :: Model a => V3 -> Length -> a -> Position a Source #

Position from given n-vector (x, y, z coordinates) and height in the given model.

(x, y, z) will be converted first to latitude & longitude to ensure a consistent resolution with the rest of the API.

Read/Show positions

readHorizontalPosition :: Model a => String -> a -> Maybe (HorizontalPosition a) Source #

Reads an 'HorizontalPosition, from the given string using horizontalPosition, for example:

>>> Geodetic.readHorizontalPosition "55°36'21''N 013°00'02''E" WGS84
Just 55°36'21.000"N,13°0'2.000"E (WGS84)

horizontalPosition :: Model a => a -> ReadP (HorizontalPosition a) Source #

Parses and returns a HorizontalPosition.

Supported formats:

  • DD(MM)(SS)[N|S]DDD(MM)(SS)[E|W] - e.g. 553621N0130002E or 0116S03649E or 47N122W
  • Angle[N|S] Angle[E|W] - e.g. 55°36'21''N 13°0'02''E or 11°16'S 36°49'E or 47°N 122°W

readPosition :: Model a => String -> a -> Maybe (Position a) Source #

Reads a Position from the given string using position, for example:

>>> Geodetic.readPosition "55°36'21''N 013°00'02''E 1500m" WGS84
Just 55°36'21.000"N,13°0'2.000"E 1500.0m (WGS84)

position :: Model a => a -> ReadP (Position a) Source #

Parses and returns a Position: the beginning of the string is parsed by horizontalPosition and additionally the string may end by a valid Length.

n-vector conversions

nvectorFromLatLong :: (Angle, Angle) -> V3 Source #

nvectorFromLatLong ll returns n-vector equivalent to the given (latitude, longitude) pair ll.

nvectorToLatLong :: V3 -> (Angle, Angle) Source #

nvectorToLatLong nv returns (latitude, longitude) pair equivalent to the given n-vector nv. Latitude is always in [-90°, 90°] and longitude in [-180°, 180°].

Misc.

antipode :: Model a => HorizontalPosition a -> HorizontalPosition a Source #

antipode p computes the antipodal position of p: the position which is diametrically opposite to p.

antipode' :: Model a => Position a -> Position a Source #

antipode p computes the antipodal position of p: the position which is diametrically opposite to p at the same height.

northPole :: Model a => a -> HorizontalPosition a Source #

Horizontal position of the North Pole in the given model.

southPole :: Model a => a -> HorizontalPosition a Source #

Horizontal position of the South Pole in the given model.