{-| Module : Projectile.BulletMI Description : Bullet projectile Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Projectile.BulletMI ( BulletMI(..) , new , prj ) where import Prelude ((+), max, (-), (||), Maybe(..), Bool(..), ($), cos, sin, (.), (<), otherwise, (*), Double) import Graphics.Gloss.Data.Picture ( Picture(Circle, Color) ) import Graphics.Gloss.Data.Color ( yellow, red, green ) import Data.WrapAround ( WP, WM, distance ) import GHC.Float (double2Float) import Combat import Animation import Updating import qualified Moving as M ( Moving(..), Locatable(..), Colliding(..), newLocation ) import Common import Math velocityC = 400.0 rangeC = 500.0 damE = 2 collisionR = 4 data BulletMI = BulletMI { velocity :: Velocity , center :: WP , rangeLeft :: Double , wrapMap :: WM , idealNewCenter :: Maybe WP , impacted :: Bool , clock :: Time } new a b c (d, e) = BulletMI { velocity = (x + d, y + e) , center = c , rangeLeft = rangeC , wrapMap = a , idealNewCenter = Nothing , impacted = False , clock = 0.0 } where (x, y) = appPair ((* velocityC) . ($ b)) (cos, sin) instance Animation BulletMI where image s t = (Color (c r) . Circle) (double2Float collisionR) where c x | x < 0.10 = red | otherwise = yellow r = remF (clock s) 0.2 instance M.Colliding BulletMI where collisionRadius _ = collisionR instance M.Moving BulletMI where velocity = velocity instance M.Locatable BulletMI where center = center instance SimpleTransient BulletMI where expired = zeroOrLess . rangeLeft instance InternallyUpdating BulletMI 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 - Data.WrapAround.distance (wrapMap s) (center s) a) instance Damaging BulletMI where damageEnergy _ = damE instance Transient BulletMI where expired' s = if impacted s || zeroOrLess (rangeLeft s) then Just [] else Nothing instance Damageable BulletMI where inflictDamage s d = if moreThanZero d then s { impacted = True } else s -- | Func abstracting construction of 'BulletMI' 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))