{-| Module : Projectile.Nuke Description : Tactical nuclear projectile Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Projectile.Nuke ( Nuke(..) , new ) where import Prelude ((+), (>=), (<), Maybe(..), Bool(..), (*), (.), ($), cos, sin) import Graphics.Gloss.Data.Picture ( Picture(Blank, Circle, Color, Scale) ) import Graphics.Gloss.Data.Color ( white, green ) import Data.WrapAround ( WP, WM ) import Data.Maybe ( fromMaybe ) import Combat import Animation import Updating import qualified Moving as M ( Moving(..), Locatable(..), Colliding(..), newLocation ) import ResourceTracker import Common import Math velocityC = 200.0 punch = 8.0 residualPunch = 0.1 detTime = 1.5 data Nuke = Nuke { velocity :: Velocity , center :: WP , wmap :: WM , clock :: Time , initialBlastCompleted :: Bool , rt :: RT } new :: WM -> ResourceTracker -> Angle -> WP -> Velocity -> Nuke new a b c d (e, f) = Nuke { velocity = (x + e, y + f) , center = d , wmap = a , clock = 0.0 , initialBlastCompleted = False , rt = b } where (x, y) = appPair ((* velocityC) . ($ c)) (cos, sin) instance Animation Nuke where image s t = if c < detTime then Color green (Circle 2.0) else if c < detTime + 0.05 then f "nuke-0.bmp" else if c < detTime + 0.1 then f "nuke-1.bmp" else if c < detTime + 0.15 then f "nuke-2.bmp" else if c < detTime + 0.2 then f "nuke-3.bmp" else Blank where f = \x -> Scale 2 2 (fromMaybe (Color white (Circle 125)) (getImage (rt s) x)) c = clock s instance M.Colliding Nuke where collisionRadius s = if clock s < detTime then 2 else 200 instance M.Moving Nuke where velocity b = velocity b instance M.Locatable Nuke where center b = center b expFormula a = clock a >= detTime + 0.5 instance SimpleTransient Nuke where expired = expFormula instance InternallyUpdating Nuke where preUpdate s t = s { clock = clock s + t , velocity = if clock s >= detTime then (0, 0) else velocity s } postUpdate s t = s { center = M.newLocation (wmap s) (center s) (velocity s) t , initialBlastCompleted = clock s >= detTime } instance Damaging Nuke where damageEnergy s = if clock s < detTime then 0 else if initialBlastCompleted s then residualPunch else punch instance Transient Nuke where expired' s = if expFormula s then Just [] else Nothing instance Damageable Nuke where inflictDamage s _ = s