{-| Module : Projectile.SWForward Description : Growing super weapon projectile Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Projectile.SWForward ( SWForward(..) , new , prj ) where import Prelude (min, (+), (*), Maybe(..), (-), ($), cos, (||), (.), Double, Bool(..), sin, max) import Graphics.Gloss.Data.Picture ( Picture(Circle, Color) ) import Graphics.Gloss.Data.Color ( violet ) import Data.WrapAround ( WP, WM, distance ) import GHC.Float ( double2Float ) import Combat import Animation import Updating import qualified Moving as M ( Colliding(..), Moving(..), Locatable(..), newLocation ) import Common import Math velocityC = 700 rangeC = 1000 integrityMax = 60 damE = 6 radiusGrowth = 30 data SWForward = SWForward { velocity :: Velocity , center :: WP , rangeLeft :: Double , wrapMap :: WM , impacted :: Bool , clock :: Time , integrity :: Double , radius :: Double } new a b c (d, e) = SWForward { velocity = (x + d, y + e) , center = c , rangeLeft = rangeC , wrapMap = a , impacted = False , clock = 0.0 , integrity = integrityMax , radius = 2.0 } where (x, y) = appPair ((* velocityC) . ($ b)) (cos, sin) instance Animation SWForward where image s t = Color violet (Circle (double2Float (radius s))) instance M.Colliding SWForward where collisionRadius = radius instance M.Moving SWForward where velocity = velocity instance M.Locatable SWForward where center = center expirationFormula s = f rangeLeft || f integrity where f g = (zeroOrLess . g) s instance SimpleTransient SWForward where expired = expirationFormula instance InternallyUpdating SWForward where preUpdate s t = s { clock = clock s + t } postUpdate s t = s { center = a, rangeLeft = r, radius = q } where a = M.newLocation (wrapMap s) (center s) (velocity s) t r = max 0 (rangeLeft s - Data.WrapAround.distance (wrapMap s) (center s) a) q = min 128.0 ((radius s) + radiusGrowth * t) instance Damaging SWForward where damageEnergy _ = damE instance Transient SWForward where expired' s = if expirationFormula s then Just [] else Nothing instance Damageable SWForward where inflictDamage s d = s { integrity = integrity s - d } -- | Func abstracting construction of 'SWForward' 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))