{-| Module : Math Description : Mathematical functions Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Math where divBySum a b c = a / (b + c) divideProduct a b c = a * b / c ratioRadDeg = 180 / pi radToDeg = (ratioRadDeg *) mulSV s (x, y) = (s * x, s * y) join f a = f a a sqr = join (*) distrib f g a b = g (f a) (f b) sumSquares = distrib sqr (+) pairLen f = distrib f (flip (-)) pairLenFst = pairLen fst pairLenSnd = pairLen snd -- vectMag a = sqrt (sum hypotenuse a b = sqrt (sumSquares a b) distance a b = hypotenuse (pairLenFst a b) (pairLenSnd a b) vectMag (a, b) = hypotenuse a b circleRads = 2 * pi nan = 0 / 0 isNan = (== nan) isPos :: (Num a, Ord a) => a -> Bool isPos = (>= 0) isNeg :: (Num a, Ord a) => a -> Bool isNeg = not . isPos bothPos = distrib isPos (&&) bothNeg = distrib isNeg (&&) -- return unit radians vectorDirection (0, 0) = nan vectorDirection (x, y) | bothPos x y = a | isNeg x && isPos y = pi - a | bothNeg x y = pi + a | otherwise = circleRads - a where a = atan (distrib abs (/) y 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 s c v = f c 3 where f n i = if moreThanZero i then f (g n) (decrem i) else vectorDirection (g n) g n = addV c (mulSV (distOrigin n / s) v) inc, increm :: Num a => a -> a increm = flip (+) 1 inc = increm dec, decrem :: Num a => a -> a decrem = flip (-) 1 dec = decrem origin = (0, 0) distOrigin = distance origin addV (x1, y1) (x2, y2) = (x1 + x2, y1 + y2) subV (x1, y1) (x2, y2) = (x1 - x2, y1 - y2) remF x y = (a - coerciveTrunc a) * y where a = x / y coerciveTrunc = fromIntegral . truncate isZero :: (Num a, Eq a) => a -> Bool isZero = (== 0) notZero :: (Num a, Eq a) => a -> Bool notZero = (/= 0) zeroProtect a b = if isZero b then a else b appPair f (a, b) = (f a, f b) neither a b = not (a || b) zeroOrLess :: (Num a, Ord a) => a -> Bool zeroOrLess = (<= 0) moreThanZero :: (Num a, Ord a) => a -> Bool moreThanZero = (> 0) -- |Transforms vector to coordinate form. vecCoord :: Floating t => t -- ^ angle -> t -- ^ magnitude -> (t, t) vecCoord a b = appPair ((* b) . ($ a)) (cos, sin) qArc = pi / 2