{-# LANGUAGE Trustworthy #-} module GJK ( Convex (..) , convexIntersect ) where import Linear (Epsilon (nearZero), Metric (dot), V2, crossZ, unangle) -- | Convex is represented by its supprot function newtype Convex = Convex { support :: Double -> V2 Double } -- | Minkowski Difference between 2 Convexes minkowskiDifference :: Convex -> Convex -> Convex minkowskiDifference a b = Convex $ (-) <$> support a <*> (support b . (+ pi)) -- | Core Logic: Detect if origin point is contained inside a Convex originInside :: Convex -> Bool originInside s = if dot a b > 0 then False else doSimplex (support s) a b where a = support s 0 b = support s $ unangle (-a) -- | Simplex addition till nearZero doSimplex :: (Double -> V2 Double) -> V2 Double -> V2 Double -> Bool doSimplex s a b = nearZero (b - a) || (if (axb > 0) /= (bxc > 0) then doSimplex s b c else (if (axc > 0) /= (cxb > 0) then doSimplex s a c else True)) where c = s $ unangle (b - a) + (if axb > 0 then pi / 2 else -pi / 2) axb = crossZ a b axc = crossZ a c bxc = crossZ b c cxb = -bxc -- | If two Convex colliside convexIntersect :: Convex -> Convex -> Bool convexIntersect a b = originInside $ minkowskiDifference a b