module Trigonometry where import Data.Maybe radToDeg :: Floating a => a -> a radToDeg x = x * 180 / pi mulSV :: Double -> (Double, Double) -> (Double, Double) mulSV s (x, y) = (s * x, s * y) distance :: (Double, Double) -> (Double, Double) -> Double distance (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) normAngle :: Double -> Double -- radians normAngle x = if x >= 0 then asin (sin x) else 2 * pi + asin (sin x) vectorDirection :: (Double, Double) -- vector -> Double -- angle in radians vectorDirection (0, 0) = 0.0 / 0.0 -- NaN vectorDirection (x, y) | x >= 0 && y >= 0 = a | x < 0 && y >= 0 = pi - a | x < 0 && y < 0 = pi + a | otherwise = 2 * pi - a where a = atan (abs y / abs x) -- let x = 2 * pi + pi / 2 in asin (sin x) -- let x = (- (2*pi)) + (- (pi / 2)) in 2*pi + asin (sin x) {- Assumes source (origin of projectile) is at origin of grid (0, 0) and so target center is relative to this. Assumes source is stationary and so velocity of target is relative to source. -} targetingA :: Double -> (Double, Double) -> (Double, Double) -> Double targetingA pSpeed tCenter tVelocity = targetingA' pSpeed tCenter tVelocity Nothing 3 where targetingA' pSpeed oCenter tVelocity nCenter iter = let eCenter = fromMaybe oCenter nCenter in let d = distance (0, 0) eCenter in let t = d / pSpeed in let aCenter = addV oCenter (mulSV t tVelocity) in if iter > 0 then targetingA' pSpeed oCenter tVelocity (Just aCenter) (iter - 1) else vectorDirection aCenter addV :: (Double, Double) -> (Double, Double) -> (Double, Double) addV (x1, y1) (x2, y2) = (x1 + x2, y1 + y2) subV :: (Double, Double) -> (Double, Double) -> (Double, Double) subV (x1, y1) (x2, y2) = (x1 - x2, y1 - y2) doubleRem :: Double -> Double -> Double doubleRem x y = let a = x / y in (a - (fromIntegral (truncate a))) * y