{-| Module : Item Description : Defines objects that can be picked up by the space ship Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Item where import Prelude (($), return, Int, IO, Show, Eq) import Data.WrapAround (WP) import Data.Maybe (fromMaybe) import Graphics.Gloss.Data.Picture ( Picture ( Scale, Color, Text)) import Graphics.Gloss.Data.Color (white) import System.Random (randomRIO) import Moving import Animation import ResourceTracker data ItemType = Health | FourWay | Cannon | Spread | RapidFire | Nuke deriving (Show, Eq) data Item = Item ItemType RT WP deriving (Show) instance Colliding Item where collisionRadius _ = 11.0 instance Locatable Item where center (Item _ _ a) = a instance Moving Item where velocity _ = (0, 0) instance Animation Item where image (Item a b _) _ = protectedGetImage b $ case a of Health -> "item-health.bmp" FourWay -> "item-fourway.bmp" Cannon -> "item-cannon.bmp" Spread -> "item-spread.bmp" RapidFire -> "item-rapidfire.bmp" Nuke -> "item-nuke.bmp" randomItemType = do r <- randomRIO (0, 5) :: IO Int return $ case r of 0 -> Health 1 -> FourWay 2 -> Cannon 3 -> Spread 4 -> RapidFire otherwise -> Nuke