module Projectile.Cannon ( Cannon(..) , new , prj ) where import Combat ( Damageable(..), Damaging(..), Projectile(..) ) import Animation ( Animation(..) ) import Updating ( SimpleTransient(..), Transient(..), InternallyUpdating(..) ) import Graphics.Gloss.Data.Picture ( Picture(Circle, Color) ) import Graphics.Gloss.Data.Color ( cyan, blue ) import Data.WrapAround ( WP, WM, distance ) import qualified Moving as M ( Colliding(..), Moving(..), Locatable(..), newLocation ) import Common ( Velocity, Angle, Time ) import Math ( remF, appPair, zeroOrLess ) import GHC.Float ( double2Float ) velocityC = 500.0 rangeC = 800.0 integrityMax = 60.0 damE = 4 radiusC = 12.0 data Cannon = Cannon { velocity :: Velocity , center :: WP , rangeLeft :: Double , wrapMap :: WM , impacted :: Bool , clock :: Time , integrity :: Double } new a b c (d, e) = Cannon { velocity = (x + d, y + e) , center = c , rangeLeft = rangeC , wrapMap = a , impacted = False , clock = 0.0 , integrity = integrityMax } where (x, y) = appPair ((* velocityC) . ($ b)) (cos, sin) instance Animation Cannon where image s t = (Color (c r) . Circle) (double2Float radiusC) where c x | x < 0.10 = blue | otherwise = cyan r = remF (clock s) 0.2 instance M.Colliding Cannon where collisionRadius _ = radiusC instance M.Moving Cannon where velocity = velocity instance M.Locatable Cannon where center = center expirationFormula s = f rangeLeft || f integrity where f g = (zeroOrLess . g) s instance SimpleTransient Cannon where expired = expirationFormula instance InternallyUpdating Cannon where preUpdate s t = s { clock = clock s + t } postUpdate s t = s { center = a, rangeLeft = r } where a = M.newLocation (wrapMap s) (center s) (velocity s) t r = max 0 (rangeLeft s - distance (wrapMap s) (center s) a) instance Damaging Cannon where damageEnergy _ = damE instance Transient Cannon where expired' s = if expirationFormula s then Just [] else Nothing instance Damageable Cannon where inflictDamage s d = s { integrity = integrity s - d } -- | Func abstracting construction of 'Cannon' projectile prj :: (M.Moving a) => a -- ^ object receiving projectile -> (a -> WM) -- ^ func which retrieves WM from object -> Angle -- ^ firing angle -> Projectile prj a f b = Projectile (new (f a) b (M.center a) (M.velocity a))