module Geodetics.Geodetic (
Geodetic (..),
readGroundPosition,
toLocal,
toWGS84,
antipode,
geometricalDistance,
geometricalDistanceSq,
groundDistance,
properAngle,
showAngle,
ECEF,
geoToEarth,
earthToGeo,
WGS84 (..)
) where
import Data.Char (chr)
import Data.Function
import Data.Maybe
import Data.Monoid
import Geodetics.Altitude
import Geodetics.Ellipsoids
import Geodetics.LatLongParser
import Numeric.Units.Dimensional.Prelude hiding ((.))
import Text.ParserCombinators.ReadP
import qualified Prelude as P
data (Ellipsoid e) => Geodetic e = Geodetic {
latitude, longitude :: Angle Double,
geoAlt :: Length Double,
ellipsoid :: e
}
instance (Ellipsoid e) => Show (Geodetic e) where
show g = concat [
showAngle (abs $ latitude g), " ", letter "SN" (latitude g), ", ",
showAngle (abs $ longitude g), " ", letter "WE" (longitude g), ", ",
show (altitude g), " ", show (ellipsoid g)]
where letter s n = [s !! (if n < _0 then 0 else 1)]
readGroundPosition :: (Ellipsoid e) => e -> String -> Maybe (Geodetic e)
readGroundPosition e str =
case map fst $ filter (null . snd) $ readP_to_S latLong str of
[] -> Nothing
(lat,long) : _ -> Just $ groundPosition $ Geodetic (lat *~ degree) (long *~ degree) undefined e
showAngle :: Angle Double -> String
showAngle a
| isNaN a1 = "NaN"
| isInfinite a1 = sgn ++ "Infinity"
| otherwise = concat [sgn, show d, [chr 0xB0, ' '],
show m, "' ",
show s, ".", dstr, "\"" ]
where
a1 = a /~ one
sgn = if a < _0 then "-" else ""
centisecs :: Integer
centisecs = P.abs $ P.round $ (a /~ degree) P.* 360000
(d, m1) = centisecs `P.divMod` 360000
(m, s1) = m1 `P.divMod` 6000
(s, ds) = s1 `P.divMod` 100
dstr = reverse $ take 2 $ reverse (show ds) ++ "00"
instance (Ellipsoid e) => HasAltitude (Geodetic e) where
altitude = geoAlt
setAltitude h g = g{geoAlt = h}
antipode :: (Ellipsoid e) => Geodetic e -> Geodetic e
antipode g = Geodetic lat long (geoAlt g) (ellipsoid g)
where
lat = negate $ latitude g
long' = longitude g - 180 *~ degree
long | long' < _0 = long' + 360 *~ degree
| otherwise = long'
geoToEarth :: (Ellipsoid e) => Geodetic e -> ECEF
geoToEarth geo = (
(n + h) * coslat * coslong,
(n + h) * coslat * sinlong,
(n * (_1 - eccentricity2 e) + h) * sinlat)
where
n = normal e $ latitude geo
e = ellipsoid geo
coslat = cos $ latitude geo
coslong = cos $ longitude geo
sinlat = sin $ latitude geo
sinlong = sin $ longitude geo
h = altitude geo
earthToGeo :: (Ellipsoid e) => e -> ECEF -> (Angle Double, Angle Double, Length Double)
earthToGeo e (x,y,z) = (phi, atan2 y x, sqrt (l ^ pos2 + p2) - norm)
where
p2 = x ^ pos2 + y ^ pos2
a = majorRadius e
a2 = a ^ pos2
e2 = eccentricity2 e
e4 = e2 ^ pos2
zeta = (_1-e2) * (z ^ pos2 / a2)
rho = (p2 / a2 + zeta - e4) / _6
rho2 = rho ^ pos2
rho3 = rho * rho2
s = e4 * zeta * p2 / (_4 * a2)
t = cbrt (s + rho3 + sqrt (s * (s + _2 * rho3)))
u = rho + t + rho2 / t
v = sqrt (u ^ pos2 + e4 * zeta)
w = e2 * (u + v - zeta) / (_2 * v)
kappa = _1 + e2 * (sqrt (u + v + w ^ pos2) + w) / (u + v)
phi = atan (kappa * z / sqrt p2)
norm = normal e phi
l = z + e2 * norm * sin phi
toLocal :: (Ellipsoid e1, Ellipsoid e2) => e2 -> Geodetic e1 -> Geodetic e2
toLocal e2 g = Geodetic lat lon alt e2
where
alt = altitude g
(lat, lon, _) = earthToGeo e2 $ applyHelmert h $ geoToEarth g
h = helmert (ellipsoid g) `mappend` inverseHelmert (helmert e2)
toWGS84 :: (Ellipsoid e) => Geodetic e -> Geodetic WGS84
toWGS84 g = Geodetic lat lon alt WGS84
where
alt = altitude g
(lat, lon, _) = earthToGeo WGS84 $ applyHelmert h $ geoToEarth g
h = helmert (ellipsoid g)
geometricalDistance :: (Ellipsoid e) => Geodetic e -> Geodetic e -> Length Double
geometricalDistance g1 g2 = sqrt $ geometricalDistanceSq g1 g2
geometricalDistanceSq :: (Ellipsoid e) => Geodetic e -> Geodetic e -> Area Double
geometricalDistanceSq g1 g2 = (x1-x2) ^ pos2 + (y1-y2) ^ pos2 + (z1-z2) ^ pos2
where
(x1,y1,z1) = geoToEarth g1
(x2,y2,z2) = geoToEarth g2
groundDistance :: (Ellipsoid e) => Geodetic e -> Geodetic e ->
Maybe (Length Double, Dimensionless Double, Dimensionless Double)
groundDistance p1 p2 = do
(_, (lambda, (cos2Alpha, delta, sinDelta, cosDelta, cos2DeltaM))) <-
listToMaybe $ dropWhile converging $ take 100 $ zip lambdas $ tail lambdas
let
uSq = cos2Alpha * (a^pos2 - b^pos2) / b^pos2
bigA = _1 + uSq/(16384*~one) * ((4096*~one) + uSq *
(((-768)*~one) + uSq * ((320*~one)
- (175*~one)*uSq)))
bigB = uSq/(1024*~one) * ((256*~one) +
uSq * (((-128)*~one) +
uSq * ((74*~one) - (47*~one)*uSq)))
deltaDelta =
bigB * sinDelta * (cos2DeltaM +
bigB/_4 * (cosDelta * (_2 * cos2DeltaM^pos2 - _1)
- bigB/_6 * cos2DeltaM * (_4 * sinDelta^pos2 - _3)
* (_4 * cos2DeltaM - _3)))
s = b * bigA * (delta - deltaDelta)
alpha1 = atan2(cosU2 * sin lambda) (cosU1 * sinU2 - sinU1 * cosU2 * cos lambda)
alpha2 = atan2(cosU1 * sin lambda) (cosU1 * sinU2 * cos lambda - sinU1 * cosU2)
return (s, alpha1, alpha2)
where
f = flattening $ ellipsoid p1
a = majorRadius $ ellipsoid p1
b = minorRadius $ ellipsoid p1
l = abs $ longitude p1 - longitude p2
u1 = atan ((_1-f) * tan (latitude p1))
u2 = atan ((_1-f) * tan (latitude p2))
sinU1 = sin u1
cosU1 = cos u1
sinU2 = sin u2
cosU2 = cos u2
nextLambda lambda = (lambda1, (cos2Alpha, delta, sinDelta, cosDelta, cos2DeltaM))
where
sinLambda = sin lambda
cosLambda = cos lambda
sinDelta = sqrt((cosU2 * sinLambda) ^ pos2 +
(cosU1 * sinU2 - sinU1 * cosU2 * cosLambda) ^ pos2)
cosDelta = sinU1 * sinU2 + cosU1 * cosU2 * cosLambda
delta = atan2 sinDelta cosDelta
sinAlpha = cosU1 * cosU2 * sinLambda / sinDelta
cos2Alpha = _1 - sinAlpha ^ pos2
cos2DeltaM = if cos2Alpha == _0
then _0
else cosDelta - _2 * sinU1 * sinU2 / cos2Alpha
c = f/(16 *~ one) * cos2Alpha * (_4 + f * (_4 - _3 * cos2Alpha))
lambda1 = l + (_1-c) * f * sinAlpha
* (delta + c * sinDelta
* (cos2DeltaM + c * cosDelta *(_2 * cos2DeltaM ^ pos2 - _1)))
lambdas = iterate (nextLambda . fst) (l, undefined)
converging ((l1,_),(l2,_)) = abs (l1 - l2) > (1e-14 *~ one)
properAngle :: Angle Double -> Angle Double
properAngle t
| r1 <= negate pi = r1 + pi2
| r1 > pi = r1 - pi2
| otherwise = r1
where
pf :: Double -> (Int, Double)
pf = properFraction
(_,r) = pf (t/pi2 /~ one)
r1 = (r *~ one) * pi2
pi2 = pi * _2