{-| Module : Interceptor Description : Interceptor projectile Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Projectile.Interceptor ( Interceptor(..) , new -- , prj , speed ) where import Prelude ((-), (||), (.), Maybe(..), Bool(..), (*), ($), cos, sin, (>), (+), max, Double) import Graphics.Gloss.Data.Picture ( Picture(Circle, Color) ) 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 = 900 rangeC = 1200 damE = 4 radiusC = 12.0 speed = velocityC data Interceptor = Interceptor { velocity :: Velocity , center :: WP , rangeLeft :: Double , wrapMap :: WM , impacted :: Bool , clock :: Time , rt :: RT , angle :: Angle } new a r b c (d, e) = Interceptor { velocity = (x + d, y + e) , center = c , rangeLeft = rangeC , wrapMap = a , impacted = False , clock = 0.0 , rt = r , angle = b } where (x, y) = appPair ((* velocityC) . ($ b)) (cos, sin) instance Animation Interceptor where image s t = reorient (angle s) c where f x = fromMaybe (Color white (Circle r)) (getImage (rt s) x) p1 = f "interceptor-1.bmp" p2 = f "interceptor-2.bmp" p3 = f "interceptor-3.bmp" g = ((clock s `remF` 0.3) >) c = if g 0.2 then p3 else if g 0.1 then p2 else p1 r = double2Float radiusC instance M.Colliding Interceptor where collisionRadius _ = radiusC instance M.Moving Interceptor where velocity = velocity instance M.Locatable Interceptor where center = center instance SimpleTransient Interceptor where expired s = impacted s || (zeroOrLess . rangeLeft) s instance InternallyUpdating Interceptor 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 Interceptor where damageEnergy _ = damE instance Transient Interceptor where expired' s = if impacted s || (zeroOrLess . rangeLeft) s then Just [] else Nothing instance Damageable Interceptor where inflictDamage s d = if moreThanZero d then s { impacted = True } else s -- -- | Func abstracting construction of 'Interceptor' 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))