module Projectile.Pellet ( Pellet(..) , new , range ) where import Combat ( Damaging(..), Damageable(..) ) import Animation ( Animation(..) ) import Updating ( Transient(..), SimpleTransient(..), InternallyUpdating(..) ) import Graphics.Gloss.Data.Picture ( Picture(Circle, Color) ) import Graphics.Gloss.Data.Color ( makeColor8 ) import Data.WrapAround ( WP, WM, distance ) import qualified Moving as M ( Moving(..), Locatable(..), Colliding(..), newLocation ) import Common ( Velocity, Angle ) import Math ( vecCoord, addV, zeroOrLess, moreThanZero ) velocityC = 600 rangeC = 300 punch = 0.3 range = rangeC data Pellet = Pellet { velocity :: Velocity , center :: WP , rangeLeft :: Double , wmap :: WM , impacted :: Bool } -- angle is radians new :: WM -> Angle -> WP -> Velocity -> Pellet new a b c d = Pellet { velocity = addV (vecCoord b velocityC) d , center = c , rangeLeft = rangeC , wmap = a , impacted = False } instance Animation Pellet where image _ _ = Color (makeColor8 172 172 172 255) (Circle 1) instance M.Colliding Pellet where collisionRadius _ = 1 instance M.Moving Pellet where velocity = velocity instance M.Locatable Pellet where center = center expFormula s = impacted s || (zeroOrLess . rangeLeft) s instance SimpleTransient Pellet where expired = expFormula instance InternallyUpdating Pellet where preUpdate s t = s postUpdate s t = s { center = a , rangeLeft = max 0 (rangeLeft s - distance (wmap s) (center s) a) } where a = M.newLocation (wmap s) (center s) (velocity s) t instance Damaging Pellet where damageEnergy b = punch instance Transient Pellet where expired' s = if expFormula s then Just [] else Nothing instance Damageable Pellet where inflictDamage s d = if moreThanZero d then s { impacted = True } else s