module Data.Geo.Jord.Kinematics
(
Track(..)
, Course
, Cpa
, cpaTime
, cpaDistance
, cpaPosition1
, cpaPosition2
, Intercept
, interceptTime
, interceptDistance
, interceptPosition
, interceptorBearing
, interceptorSpeed
, course
, position
, position84
, cpa
, cpa84
, intercept
, intercept84
, interceptBySpeed
, interceptBySpeed84
, interceptByTime
, interceptByTime84
) where
import Control.Applicative
import Data.Geo.Jord.Angle
import Data.Geo.Jord.AngularPosition
import Data.Geo.Jord.Duration
import Data.Geo.Jord.Earth
import Data.Geo.Jord.Geodetics
import Data.Geo.Jord.LatLong
import Data.Geo.Jord.Length
import Data.Geo.Jord.NVector
import Data.Geo.Jord.Quantity
import Data.Geo.Jord.Speed
import Data.Geo.Jord.Transformation
import Data.Geo.Jord.Vector3d
data Track a = Track
{ trackPos :: a
, trackBearing :: Angle
, trackSpeed :: Speed
} deriving (Eq, Show)
instance (NTransform a, Show a) => IsGreatCircle (Track a) where
greatCircleE t = greatCircleE (trackPos t, trackBearing t)
newtype Course =
Course Vector3d
deriving (Eq, Show)
instance IsVector3d Course where
vec (Course v) = v
data Cpa a = Cpa
{ cpaTime :: Duration
, cpaDistance :: Length
, cpaPosition1 :: a
, cpaPosition2 :: a
} deriving (Eq, Show)
data Intercept a = Intercept
{ interceptTime :: Duration
, interceptDistance :: Length
, interceptPosition :: a
, interceptorBearing :: Angle
, interceptorSpeed :: Speed
} deriving (Eq, Show)
course :: (NTransform a) => a -> Angle -> Course
course p b = Course (Vector3d (vz (head r)) (vz (r !! 1)) (vz (r !! 2)))
where
ll = nvectorToLatLong . pos . toNVector $ p
lat = latitude ll
lon = longitude ll
r = mdot (mdot (rz (negate' lon)) (ry lat)) (rx b)
position :: (NTransform a) => Track a -> Duration -> Length -> a
position (Track p0 b s) d = position' p0 s (course p0 b) (toSeconds d)
position84 :: (NTransform a) => Track a -> Duration -> a
position84 t d = position t d r84
cpa :: (Eq a, NTransform a) => Track a -> Track a -> Length -> Maybe (Cpa a)
cpa (Track p1 b1 s1) (Track p2 b2 s2) r
| p1 == p2 = Just (Cpa zero zero p1 p2)
| t < 0 = Nothing
| otherwise = Just (Cpa (seconds t) d cp1 cp2)
where
c1 = course p1 b1
c2 = course p2 b2
t = timeToCpa p1 c1 s1 p2 c2 s2 r
cp1 = position' p1 s1 c1 t r
cp2 = position' p2 s2 c2 t r
d = surfaceDistance cp1 cp2 r
cpa84 :: (Eq a, NTransform a) => Track a -> Track a -> Maybe (Cpa a)
cpa84 t1 t2 = cpa t1 t2 r84
intercept :: (Eq a, NTransform a) => Track a -> a -> Length -> Maybe (Intercept a)
intercept t@(Track tp tb ts) p r = interceptByTime t p (seconds d) r
where
ct0 = course tp tb
d = timeToIntercept tp ts ct0 p r
intercept84 :: (Eq a, NTransform a) => Track a -> a -> Maybe (Intercept a)
intercept84 t p = intercept t p r84
interceptBySpeed :: (Eq a, NTransform a) => Track a -> a -> Speed -> Length -> Maybe (Intercept a)
interceptBySpeed t@(Track tp tb ts) p s r = interceptByTime t p (seconds d) r
where
ct0 = course tp tb
d = timeToInterceptSpeed tp ts ct0 p s r
interceptBySpeed84 :: (Eq a, NTransform a) => Track a -> a -> Speed -> Maybe (Intercept a)
interceptBySpeed84 t p s = interceptBySpeed t p s r84
interceptByTime :: (Eq a, NTransform a) => Track a -> a -> Duration -> Length -> Maybe (Intercept a)
interceptByTime t p d r
| toMilliseconds d <= 0 = Nothing
| trackPos t == p = Nothing
| otherwise = fmap (\b -> Intercept d idist ipos b is) ib
where
ipos = position t d r
idist = surfaceDistance p ipos r
ib = initialBearing p ipos <|> initialBearing p (trackPos t)
is = metresPerSecond (toMetres idist / toSeconds d)
interceptByTime84 :: (Eq a, NTransform a) => Track a -> a -> Duration -> Maybe (Intercept a)
interceptByTime84 t p d = interceptByTime t p d r84
position' :: (NTransform a) => a -> Speed -> Course -> Double -> Length -> a
position' p0 s c sec r = fromNVector (nvectorHeight (nvector (vx v1) (vy v1) (vz v1)) h0)
where
nv0 = toNVector p0
v0 = vec . pos $nv0
h0 = height nv0
v1 = position'' v0 s (vec c) sec r
position'' :: Vector3d -> Speed -> Vector3d -> Double -> Length -> Vector3d
position'' v0 s c sec r = v1
where
w = toMetresPerSecond s / toMetres r
v1 = vadd (vscale v0 (cos (w * sec))) (vscale c (sin (w * sec)))
timeToCpa :: (NTransform a) => a -> Course -> Speed -> a -> Course -> Speed -> Length -> Double
timeToCpa p1 c1 s1 p2 c2 s2 r = cpaNrRec v10 c10 w1 v20 c20 w2 0 0
where
v10 = vec . pos . toNVector $ p1
c10 = vec c1
rm = toMetres r
w1 = toMetresPerSecond s1 / rm
v20 = vec . pos . toNVector $ p2
c20 = vec c2
w2 = toMetresPerSecond s2 / rm
timeToIntercept :: (NTransform a) => a -> Speed -> Course -> a -> Length -> Double
timeToIntercept p2 s2 c20 p1 r = intMinNrRec v10 v20 (vec c20) s2 w2 r s0 t0 0
where
v10 = vec . pos . toNVector $ p1
v20 = vec . pos . toNVector $ p2
s2mps = toMetresPerSecond s2
rm = toMetres r
w2 = s2mps / rm
s0 = ad v10 v20
t0 = rm * s0 / s2mps
timeToInterceptSpeed :: (NTransform a) => a -> Speed -> Course -> a -> Speed -> Length -> Double
timeToInterceptSpeed p2 s2 c20 p1 s1 r = intSpdNrRec v10 w1 v20 (vec c20) s2 w2 r s0 t0 0
where
v10 = vec . pos . toNVector $ p1
v20 = vec . pos . toNVector $ p2
s1mps = toMetresPerSecond s1
s2mps = toMetresPerSecond s2
rm = toMetres r
w2 = s2mps / rm
w1 = s1mps / rm
s0 = ad v10 v20
t0 = rm * s0 / s2mps
rx :: Angle -> [Vector3d]
rx a = [Vector3d 1 0 0, Vector3d 0 c s, Vector3d 0 (-s) c]
where
c = cos' a
s = sin' a
ry :: Angle -> [Vector3d]
ry a = [Vector3d c 0 (-s), Vector3d 0 1 0, Vector3d s 0 c]
where
c = cos' a
s = sin' a
rz :: Angle -> [Vector3d]
rz a = [Vector3d c s 0, Vector3d (-s) c 0, Vector3d 0 0 1]
where
c = cos' a
s = sin' a
cpaA :: Vector3d -> Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double
cpaA v10 c10 w1 v20 c20 w2 = negate (vdot (vscale v10 w1) c20 + vdot (vscale v20 w2) c10)
cpaB :: Vector3d -> Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double
cpaB v10 c10 w1 v20 c20 w2 = vdot (vscale c10 w1) v20 + vdot (vscale c20 w2) v10
cpaC :: Vector3d -> Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double
cpaC v10 c10 w1 v20 c20 w2 = negate (vdot (vscale v10 w1) v20 - vdot (vscale c20 w2) c10)
cpaD :: Vector3d -> Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double
cpaD v10 c10 w1 v20 c20 w2 = vdot (vscale c10 w1) c20 - vdot (vscale v20 w2) v10
cpaFt :: Double -> Double -> Double -> Double -> Double -> Double -> Double -> Double -> Double
cpaFt cw1t cw2t sw1t sw2t a b c d =
a * sw1t * sw2t + b * cw1t * cw2t + c * sw1t * cw2t + d * cw1t * sw2t
cpaDft ::
Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
cpaDft w1 w2 cw1t cw2t sw1t sw2t a b c d =
negate ((c * w2 + d * w1) * sw1t * sw2t) + (d * w2 + c * w1) * cw1t * cw2t +
(a * w2 - b * w1) * sw1t * cw2t -
(b * w2 - a * w1) * cw1t * sw2t
cpaStep :: Vector3d -> Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double -> Double
cpaStep v10 c10 w1 v20 c20 w2 t =
cpaFt cw1t cw2t sw1t sw2t a b c d / cpaDft w1 w2 cw1t cw2t sw1t sw2t a b c d
where
cw1t = cos (w1 * t)
cw2t = cos (w2 * t)
sw1t = sin (w1 * t)
sw2t = sin (w2 * t)
a = cpaA v10 c10 w1 v20 c20 w2
b = cpaB v10 c10 w1 v20 c20 w2
c = cpaC v10 c10 w1 v20 c20 w2
d = cpaD v10 c10 w1 v20 c20 w2
cpaNrRec ::
Vector3d -> Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double -> Int -> Double
cpaNrRec v10 c10 w1 v20 c20 w2 ti i
| i == 50 = -1.0
| abs fi < 1e-12 = ti1
| otherwise = cpaNrRec v10 c10 w1 v20 c20 w2 ti1 (i + 1)
where
fi = cpaStep v10 c10 w1 v20 c20 w2 ti
ti1 = ti - fi
intMinNrRec ::
Vector3d
-> Vector3d
-> Vector3d
-> Speed
-> Double
-> Length
-> Double
-> Double
-> Int
-> Double
intMinNrRec v10 v20 c20 s2 w2 r si ti i
| i == 50 = -1.0
| abs fi < 1e-12 = ti1
| otherwise = intMinNrRec v10 v20 c20 s2 w2 r si1 ti1 (i + 1)
where
fi = intMinStep v10 v20 c20 w2 si ti
ti1 = ti - fi
v2t = position'' v20 s2 c20 ti1 r
si1 = ad v10 v2t
intMinStep :: Vector3d -> Vector3d -> Vector3d -> Double -> Double -> Double -> Double
intMinStep v10 v20 c20 w2 s t =
dsdt s w2 v10v20 v10c20 sinw2t cosw2t / d2sdt2 s w2 v10v20 v10c20 sinw2t cosw2t
where
cosw2t = cos (w2 * t)
sinw2t = sin (w2 * t)
v10v20 = vdot v10 v20
v10c20 = vdot v10 c20
intSpdNrRec ::
Vector3d
-> Double
-> Vector3d
-> Vector3d
-> Speed
-> Double
-> Length
-> Double
-> Double
-> Int
-> Double
intSpdNrRec v10 w1 v20 c20 s2 w2 r si ti i
| i == 50 = -1.0
| abs fi < 1e-12 = ti1
| otherwise = intSpdNrRec v10 w1 v20 c20 s2 w2 r si1 ti1 (i + 1)
where
fi = intSpdStep v10 w1 v20 c20 w2 si ti
ti1 = ti - fi
v2t = position'' v20 s2 c20 ti1 r
si1 = ad v10 v2t
intSpdStep :: Vector3d -> Double -> Vector3d -> Vector3d -> Double -> Double -> Double -> Double
intSpdStep v10 w1 v20 c20 w2 s t = f / df
where
cosw2t = cos (w2 * t)
sinw2t = sin (w2 * t)
v10v20 = vdot v10 v20
v10c20 = vdot v10 c20
f = s / t - w1
df = (1.0 / t) * (dsdt s w2 v10v20 v10c20 sinw2t cosw2t - s / t)
dsdt :: Double -> Double -> Double -> Double -> Double -> Double -> Double
dsdt s w2 v10v20 v10c20 sinw2t cosw2t =
((-1.0) / sin s) * ((-w2) * (v10v20 * sinw2t - v10c20 * cosw2t))
d2sdt2 :: Double -> Double -> Double -> Double -> Double -> Double -> Double
d2sdt2 s w2 v10v20 v10c20 sinw2t cosw2t =
((-1.0) / sin s) * (cos s / (sins * sins) * x10d2x2dt2 * x10d2x2dt2 + x10d2x2dt2)
where
sins = sin s
x10d2x2dt2 = negate (w2 * w2) * (v10v20 * cosw2t + v10c20 * sinw2t)
ad :: Vector3d -> Vector3d -> Double
ad v1 v2 = atan2 (vnorm (vcross v1 v2)) (vdot v1 v2)