{-| Module : Asteroid Description : Defines the asteroid game object Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Asteroid where import Prelude (const) import Graphics.Gloss.Data.Picture () import Graphics.Gloss.Data.Color () import Data.WrapAround (WP, WM) import Animation import Updating import Moving ( Locatable, Colliding(collisionRadius), Moving, newLocation' ) import qualified Moving as M ( Moving(..), Locatable(..) ) import ResourceTracker import Combat import SpaceJunk import Common radius = 15.0 damage = 100.0 data Asteroid = Asteroid { center :: WP , velocity :: Velocity , wmap :: WM , rt :: RT } new :: ResourceTracker -> WM -> WP -> Velocity -> Asteroid new a b c d = Asteroid { center = c , velocity = d , wmap = b , rt = a } instance Animation Asteroid where image self _ = protectedGetImage (rt self) "asteroid.bmp" instance Locatable Asteroid where center = Asteroid.center instance Moving Asteroid where velocity = Asteroid.velocity instance Colliding Asteroid where collisionRadius _ = radius instance InternallyUpdating Asteroid where preUpdate s _ = s postUpdate s t = s { center = newLocation' s (wmap s) t } instance Damageable Asteroid where inflictDamage = const instance Damaging Asteroid where damageEnergy _ = damage