module Data.Geo.Jord.Kinematics
(
Track(..)
, Course
, Cpa
, cpaTime
, cpaDistance
, cpaPosition1
, cpaPosition2
, Intercept
, interceptTime
, interceptDistance
, interceptPosition
, interceptorBearing
, interceptorSpeed
, course
, positionAfter
, trackPositionAfter
, cpa
, intercept
, interceptBySpeed
, interceptByTime
, module Data.Geo.Jord.Duration
, module Data.Geo.Jord.Speed
) where
import Control.Applicative ((<|>))
import Data.Maybe (fromJust, isNothing)
import Data.Geo.Jord.Duration
import Data.Geo.Jord.GreatCircle
import Data.Geo.Jord.Internal
import Data.Geo.Jord.Position
import Data.Geo.Jord.Speed
data Track a =
Track
{ trackPosition :: Position a
, trackBearing :: Angle
, trackSpeed :: Speed
}
deriving (Eq, Show)
newtype Course =
Course Vector3d
deriving (Eq, Show)
data Cpa a =
Cpa
{ cpaTime :: Duration
, cpaDistance :: Length
, cpaPosition1 :: Position a
, cpaPosition2 :: Position a
}
deriving (Eq, Show)
data Intercept a =
Intercept
{ interceptTime :: Duration
, interceptDistance :: Length
, interceptPosition :: Position a
, interceptorBearing :: Angle
, interceptorSpeed :: Speed
}
deriving (Eq, Show)
course :: (Spherical a) => Position a -> Angle -> Course
course p b = Course (Vector3d (vz (head r)) (vz (r !! 1)) (vz (r !! 2)))
where
lat = latitude p
lon = longitude p
r = mdot (mdot (rz (negate' lon)) (ry lat)) (rx b)
positionAfter :: (Spherical a) => Position a -> Angle -> Speed -> Duration -> Position a
positionAfter p b s d = position' p (course p b) s (toSeconds d)
positionAfter' :: (Spherical a) => Position a -> Course -> Speed -> Duration -> Position a
positionAfter' p c s d = position' p c s (toSeconds d)
trackPositionAfter :: (Spherical a) => Track a -> Duration -> Position a
trackPositionAfter (Track p b s) = positionAfter' p (course p b) s
cpa :: (Spherical a) => Track a -> Track a -> Maybe (Cpa a)
cpa (Track p1 b1 s1) (Track p2 b2 s2)
| llEq 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
cp1 = position' p1 c1 s1 t
cp2 = position' p2 c2 s2 t
d = surfaceDistance cp1 cp2
intercept :: (Spherical a) => Track a -> Position a -> Maybe (Intercept a)
intercept t p = interceptByTime t p (seconds (timeToIntercept t p))
interceptBySpeed :: (Spherical a) => Track a -> Position a -> Speed -> Maybe (Intercept a)
interceptBySpeed t p s
| isNothing minInt = Nothing
| fmap interceptorSpeed minInt == Just s = minInt
| otherwise = interceptByTime t p (seconds (timeToInterceptSpeed t p s))
where
minInt = intercept t p
interceptByTime :: (Spherical a) => Track a -> Position a -> Duration -> Maybe (Intercept a)
interceptByTime t p d
| toMilliseconds d <= 0 = Nothing
| llEq (trackPosition t) p = Nothing
| isNothing ib = Nothing
| otherwise =
let is = averageSpeed idist d
in Just (Intercept d idist ipos (fromJust ib) is)
where
ipos = trackPositionAfter t d
idist = surfaceDistance p ipos
ib = initialBearing p ipos <|> initialBearing p (trackPosition t)
position' :: (Spherical a) => Position a -> Course -> Speed -> Double -> Position a
position' p0 (Course c) s sec = nvh v1 h0 (model p0)
where
nv0 = nvec p0
h0 = height p0
v1 = position'' nv0 c s sec (radiusM p0)
position'' :: Vector3d -> Vector3d -> Speed -> Double -> Double -> Vector3d
position'' v0 c s sec rm = v1
where
a = toMetresPerSecond s / rm * sec
v1 = vadd (vscale v0 (cos a)) (vscale c (sin a))
timeToCpa ::
(Spherical a) => Position a -> Course -> Speed -> Position a -> Course -> Speed -> Double
timeToCpa p1 (Course c10) s1 p2 (Course c20) s2 = cpaNrRec v10 c10 w1 v20 c20 w2 0 0
where
v10 = nvec p1
rm = radiusM p1
w1 = toMetresPerSecond s1 / rm
v20 = nvec p2
w2 = toMetresPerSecond s2 / rm
timeToIntercept :: (Spherical a) => Track a -> Position a -> Double
timeToIntercept (Track p2 b2 s2) p1 = intMinNrRec v10v20 v10c2 w2 (sep v10 v20 c2 s2 rm) t0 0
where
v10 = nvec p1
v20 = nvec p2
(Course c2) = course p2 b2
v10v20 = vdot v10 v20
v10c2 = vdot v10 c2
s2mps = toMetresPerSecond s2
rm = radiusM p1
w2 = s2mps / rm
s0 = angleRadians v10 v20
t0 = rm * s0 / s2mps
timeToInterceptSpeed :: (Spherical a) => Track a -> Position a -> Speed -> Double
timeToInterceptSpeed (Track p2 b2 s2) p1 s1 =
intSpdNrRec v10v20 v10c2 w1 w2 (sep v10 v20 c2 s2 rm) t0 0
where
v10 = nvec p1
v20 = nvec p2
(Course c2) = course p2 b2
v10v20 = vdot v10 v20
v10c2 = vdot v10 c2
rm = radiusM p1
w1 = toMetresPerSecond s1 / rm
w2 = toMetresPerSecond s2 / rm
t0 = 0.1
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-11 = 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 :: Double -> Double -> Double -> (Double -> Double) -> Double -> Int -> Double
intMinNrRec v10v20 v10c2 w2 st ti i
| i == 50 = -1.0
| abs fi < 1e-11 = ti1
| otherwise = intMinNrRec v10v20 v10c2 w2 st ti1 (i + 1)
where
cosw2t = cos (w2 * ti)
sinw2t = sin (w2 * ti)
v10dv2dt = (-w2) * (v10v20 * sinw2t - v10c2 * cosw2t)
v10d2v2dt2 = (-1.0 * w2 * w2) * (v10v20 * cosw2t + v10c2 * sinw2t)
si = st ti
sinS = sin si
a = (-1.0) / sinS
b = cos si / (sinS * sinS)
f = ti * a * v10dv2dt - si
d2sdt2 = a * (b * v10dv2dt * v10dv2dt + v10d2v2dt2)
df = ti * d2sdt2
fi = f / df
ti1 = ti - fi
intSpdNrRec :: Double -> Double -> Double -> Double -> (Double -> Double) -> Double -> Int -> Double
intSpdNrRec v10v20 v10c2 w1 w2 st ti i
| i == 50 = -1.0
| abs fi < 1e-11 = ti1
| otherwise = intSpdNrRec v10v20 v10c2 w1 w2 st ti1 (i + 1)
where
cosw2t = cos (w2 * ti)
sinw2t = sin (w2 * ti)
si = st ti
f = si / ti - w1
dsdt = (w2 * (v10v20 * sinw2t - v10c2 * cosw2t)) / sin si
df = (dsdt - (si / ti)) / ti
fi = f / df
ti1 = ti - fi
sep :: Vector3d -> Vector3d -> Vector3d -> Speed -> Double -> Double -> Double
sep v10 v20 c2 s2 r ti = angleRadians v10 (position'' v20 c2 s2 ti r)
radius :: (Spherical a) => Position a -> Length
radius = equatorialRadius . surface . model
radiusM :: (Spherical a) => Position a -> Double
radiusM = toMetres . radius