{-| Module : Projectile.Blade Description : Spinning blade projectile Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Projectile.Blade ( Blade(..) , new , speed ) where import Prelude ((.), (+), max, (-), Maybe(..), pi, (*), Double, ($), cos, sin) import Graphics.Gloss.Data.Picture ( Picture(Color, Line, Rotate) ) import Graphics.Gloss.Data.Color ( white ) import Data.WrapAround ( WP, WM, distance ) import GHC.Float ( double2Float ) import Data.Maybe ( fromMaybe ) import Combat import Animation import Updating import qualified Moving as M ( Colliding(..), Moving(..), Locatable(..), newLocation ) import Common import Math import ResourceTracker velocityC = 250 rangeC = 1500 damE = 4 speed = velocityC collisionR = 20 data Blade = Blade { velocity :: Velocity , center :: WP , rangeLeft :: Double , wmap :: WM , idealNewCenter :: Maybe WP , clock :: Time , rt :: RT } new a b c d (e, f) = Blade { velocity = (x + e, y + e) , center = d , rangeLeft = rangeC , wmap = a , idealNewCenter = Nothing , clock = 0.0 , rt = b } where (x, y) = appPair ((* velocityC) . ($ c)) (cos, sin) instance Animation Blade where image s t = Rotate (double2Float deg) p where deg = radToDeg ((clock s * 4 * pi) `remF` (2 * pi)) p = fromMaybe (Color white (Line [(-40, 0), (40, 0)])) (getImage (rt s) "blade.bmp") instance M.Colliding Blade where collisionRadius _ = collisionR instance M.Moving Blade where velocity = velocity instance M.Locatable Blade where center = center instance SimpleTransient Blade where expired = zeroOrLess . rangeLeft instance InternallyUpdating Blade where preUpdate s t = s { clock = clock s + t } postUpdate s t = s { center = a, rangeLeft = r } where a = M.newLocation (wmap s) (center s) (velocity s) t r = max 0 (rangeLeft s - Data.WrapAround.distance (wmap s) (center s) a) instance Damaging Blade where damageEnergy _ = damE instance Transient Blade where expired' s = if (zeroOrLess . rangeLeft) s then Just [] else Nothing instance Damageable Blade where inflictDamage s _ = s -- -- | Func abstracting construction of 'Blade' 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))