module UnitUtil where import Lance (Lance) import Math import Data.WrapAround import Moving import Data.Maybe import Common import Universe adjAngle :: (Moving a) => a -- ^ the object whose angle is adjusted -> Time -- ^ elapsed time -> (a -> Maybe Arena) -- ^ func that gets arena vision from object -> (a -> Angle -> a) -- ^ func that sets angle of object -> (a -> Angle) -- ^ func that gets angle of object -> Angle -- ^ adjustment angle -> Double -- ^ radial velocity -> a -- |Abstraction for adjusting angle in response to location of Lance adjAngle s t f g h m n = case f s of Nothing -> s Just a -> if isNothing (lance a) then s else let c = vectorDirection (velocity s) in let d = vectorDirection (vectorRelation (wrapMap a) (center s) (center (fromJust (lance a)))) in let b | d - c > m = n * t | d - c < (-m) = (-n) * t | otherwise = 0 in g s (h s + b) -- |Abstraction for semi-smart firing angle. firingAngle :: (Locatable a) => a -- ^ object looking to lance -> (a -> Maybe Arena) -- ^ func that retrieves arena vision -> (a -> Angle) -- ^ fun that retrieves angle direction of object -> Angle firingAngle s f g = case f s of Nothing -> g s Just a -> case lance a of Nothing -> g s Just l -> vectorDirection (vectorRelation (wrapMap a) (center s) (center l))