module Data.Geo.Jord.Kinematics
(
Track(..)
, Course
, Cpa
, timeToCpa
, distanceAtCpa
, cpaOwnshipPosition
, cpaIntruderPosition
, Intercept
, timeToIntercept
, distanceToIntercept
, interceptPosition
, interceptorBearing
, interceptorSpeed
, course
, positionAfter
, 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.Angle (Angle)
import qualified Data.Geo.Jord.Angle as Angle
import Data.Geo.Jord.Duration (Duration)
import qualified Data.Geo.Jord.Duration as Duration (seconds, toMilliseconds, toSeconds, zero)
import Data.Geo.Jord.Ellipsoid (equatorialRadius)
import Data.Geo.Jord.Geodetic (HorizontalPosition)
import qualified Data.Geo.Jord.Geodetic as Geodetic
import qualified Data.Geo.Jord.GreatCircle as GreatCircle (distance, initialBearing)
import Data.Geo.Jord.Length (Length)
import qualified Data.Geo.Jord.Length as Length (toMetres, zero)
import qualified Data.Geo.Jord.Math3d as Math3d
import Data.Geo.Jord.Model (Spherical, surface)
import Data.Geo.Jord.Speed (Speed)
import qualified Data.Geo.Jord.Speed as Speed (average, toMetresPerSecond)
data Track a =
Track
{ trackPosition :: HorizontalPosition a
, trackBearing :: Angle
, trackSpeed :: Speed
}
deriving (Eq, Show)
newtype Course =
Course Math3d.V3
deriving (Eq, Show)
data Cpa a =
Cpa
{ timeToCpa :: Duration
, distanceAtCpa :: Length
, cpaOwnshipPosition :: HorizontalPosition a
, cpaIntruderPosition :: HorizontalPosition a
}
deriving (Eq, Show)
data Intercept a =
Intercept
{ timeToIntercept :: Duration
, distanceToIntercept :: Length
, interceptPosition :: HorizontalPosition a
, interceptorBearing :: Angle
, interceptorSpeed :: Speed
}
deriving (Eq, Show)
course :: (Spherical a) => HorizontalPosition a -> Angle -> Course
course p b = Course (Math3d.vec3 (Math3d.v3z (head r)) (Math3d.v3z (r !! 1)) (Math3d.v3z (r !! 2)))
where
lat = Geodetic.latitude p
lon = Geodetic.longitude p
r = Math3d.dotM (Math3d.dotM (rz (Angle.negate lon)) (ry lat)) (rx b)
positionAfter ::
(Spherical a) => HorizontalPosition a -> Angle -> Speed -> Duration -> HorizontalPosition a
positionAfter p b s d = position' p (course p b) s (Duration.toSeconds d)
positionAfter' ::
(Spherical a) => HorizontalPosition a -> Course -> Speed -> Duration -> HorizontalPosition a
positionAfter' p c s d = position' p c s (Duration.toSeconds d)
trackPositionAfter :: (Spherical a) => Track a -> Duration -> HorizontalPosition 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)
| p1 == p2 = Just (Cpa Duration.zero Length.zero p1 p2)
| t < 0 = Nothing
| otherwise = Just (Cpa (Duration.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 = GreatCircle.distance cp1 cp2
intercept :: (Spherical a) => Track a -> HorizontalPosition a -> Maybe (Intercept a)
intercept t p = interceptByTime t p (Duration.seconds (timeToIntercept' t p))
interceptBySpeed :: (Spherical a) => Track a -> HorizontalPosition a -> Speed -> Maybe (Intercept a)
interceptBySpeed t p s
| isNothing minInt = Nothing
| fmap interceptorSpeed minInt == Just s = minInt
| otherwise = interceptByTime t p (Duration.seconds (timeToInterceptSpeed t p s))
where
minInt = intercept t p
interceptByTime ::
(Spherical a) => Track a -> HorizontalPosition a -> Duration -> Maybe (Intercept a)
interceptByTime t p d
| Duration.toMilliseconds d <= 0 = Nothing
| trackPosition t == p = Nothing
| isNothing ib = Nothing
| otherwise =
let is = Speed.average idist d
in Just (Intercept d idist ipos (fromJust ib) is)
where
ipos = trackPositionAfter t d
idist = GreatCircle.distance p ipos
ib = GreatCircle.initialBearing p ipos <|> GreatCircle.initialBearing p (trackPosition t)
position' ::
(Spherical a) => HorizontalPosition a -> Course -> Speed -> Double -> HorizontalPosition a
position' p0 (Course c) s sec = Geodetic.nvectorPos' v1 (Geodetic.model p0)
where
nv0 = Geodetic.nvector p0
v1 = position'' nv0 c s sec (radiusM p0)
position'' :: Math3d.V3 -> Math3d.V3 -> Speed -> Double -> Double -> Math3d.V3
position'' v0 c s sec rm = v1
where
a = Speed.toMetresPerSecond s / rm * sec
v1 = Math3d.add (Math3d.scale v0 (cos a)) (Math3d.scale c (sin a))
timeToCpa' ::
(Spherical a)
=> HorizontalPosition a
-> Course
-> Speed
-> HorizontalPosition a
-> Course
-> Speed
-> Double
timeToCpa' p1 (Course c10) s1 p2 (Course c20) s2 = cpaNrRec v10 c10 w1 v20 c20 w2 0 0
where
v10 = Geodetic.nvector p1
rm = radiusM p1
w1 = Speed.toMetresPerSecond s1 / rm
v20 = Geodetic.nvector p2
w2 = Speed.toMetresPerSecond s2 / rm
timeToIntercept' :: (Spherical a) => Track a -> HorizontalPosition a -> Double
timeToIntercept' (Track p2 b2 s2) p1 = intMinNrRec v10v20 v10c2 w2 (sep v10 v20 c2 s2 rm) t0 0
where
v10 = Geodetic.nvector p1
v20 = Geodetic.nvector p2
(Course c2) = course p2 b2
v10v20 = Math3d.dot v10 v20
v10c2 = Math3d.dot v10 c2
s2mps = Speed.toMetresPerSecond s2
rm = radiusM p1
w2 = s2mps / rm
s0 = angleBetweenRadians v10 v20
t0 = rm * s0 / s2mps
timeToInterceptSpeed :: (Spherical a) => Track a -> HorizontalPosition 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 = Geodetic.nvector p1
v20 = Geodetic.nvector p2
(Course c2) = course p2 b2
v10v20 = Math3d.dot v10 v20
v10c2 = Math3d.dot v10 c2
rm = radiusM p1
w1 = Speed.toMetresPerSecond s1 / rm
w2 = Speed.toMetresPerSecond s2 / rm
t0 = 0.1
rx :: Angle -> [Math3d.V3]
rx a = [Math3d.vec3 1 0 0, Math3d.vec3 0 c s, Math3d.vec3 0 (-s) c]
where
c = Angle.cos a
s = Angle.sin a
ry :: Angle -> [Math3d.V3]
ry a = [Math3d.vec3 c 0 (-s), Math3d.vec3 0 1 0, Math3d.vec3 s 0 c]
where
c = Angle.cos a
s = Angle.sin a
rz :: Angle -> [Math3d.V3]
rz a = [Math3d.vec3 c s 0, Math3d.vec3 (-s) c 0, Math3d.vec3 0 0 1]
where
c = Angle.cos a
s = Angle.sin a
cpaA :: Math3d.V3 -> Math3d.V3 -> Double -> Math3d.V3 -> Math3d.V3 -> Double -> Double
cpaA v10 c10 w1 v20 c20 w2 =
negate (Math3d.dot (Math3d.scale v10 w1) c20 + Math3d.dot (Math3d.scale v20 w2) c10)
cpaB :: Math3d.V3 -> Math3d.V3 -> Double -> Math3d.V3 -> Math3d.V3 -> Double -> Double
cpaB v10 c10 w1 v20 c20 w2 =
Math3d.dot (Math3d.scale c10 w1) v20 + Math3d.dot (Math3d.scale c20 w2) v10
cpaC :: Math3d.V3 -> Math3d.V3 -> Double -> Math3d.V3 -> Math3d.V3 -> Double -> Double
cpaC v10 c10 w1 v20 c20 w2 =
negate (Math3d.dot (Math3d.scale v10 w1) v20 - Math3d.dot (Math3d.scale c20 w2) c10)
cpaD :: Math3d.V3 -> Math3d.V3 -> Double -> Math3d.V3 -> Math3d.V3 -> Double -> Double
cpaD v10 c10 w1 v20 c20 w2 =
Math3d.dot (Math3d.scale c10 w1) c20 - Math3d.dot (Math3d.scale 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 :: Math3d.V3 -> Math3d.V3 -> Double -> Math3d.V3 -> Math3d.V3 -> 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 ::
Math3d.V3
-> Math3d.V3
-> Double
-> Math3d.V3
-> Math3d.V3
-> 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 :: Math3d.V3 -> Math3d.V3 -> Math3d.V3 -> Speed -> Double -> Double -> Double
sep v10 v20 c2 s2 r ti = angleBetweenRadians v10 (position'' v20 c2 s2 ti r)
radius :: (Spherical a) => HorizontalPosition a -> Length
radius = equatorialRadius . surface . Geodetic.model
radiusM :: (Spherical a) => HorizontalPosition a -> Double
radiusM = Length.toMetres . radius
angleBetweenRadians :: Math3d.V3 -> Math3d.V3 -> Double
angleBetweenRadians v1 v2 = atan2 sinO cosO
where
sinO = Math3d.norm (Math3d.cross v1 v2)
cosO = Math3d.dot v1 v2