{-| Module : Unit.Smart.ATank Description : Advanced tank Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Unit.Smart.ATank ( ATank(..) , new ) where import Prelude ((.), Maybe(..), max, (-), pi, Bool(..), (/), Double) import Data.WrapAround ( WP, WM ) import Sound.ALUT ( Source ) import Animation import Math import ResourceTracker import Updating import qualified Moving as M ( Moving(..), Locatable(..), Colliding(..), newVelocity, newLocation ) import Combat import qualified Projectile.BulletMI as P.BulletMI ( prj ) import AfterEffect ( AfterEffect(AfterEffect) ) import qualified AfterEffect.SimpleExplosion as SimpleExplosion ( new ) import Universe ( Arena ) import qualified Universe as U () import Common import UnitUtil import Unit radialVelocity = pi/4 maxVelocityMag = 60 kamikazeDamage = 14 maxIntegrity = 4 accelerationRate = 40 collisionR = 20 data ATank = ATank { angle :: Angle -- radians , velocity :: Velocity , center :: WP , wmap :: WM , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , vision :: Maybe Arena , rt :: ResourceTracker , queueShotSnd :: Bool , shotSndSrc :: Maybe Source } instance Audible ATank where processAudio s a = handSndSrc s queueShotSnd shotSndSrc (\a -> a { queueShotSnd = False }) rt "energy-shot-02.wav" (\a b -> a { shotSndSrc = Just b }) a (wmap s) (M.center) terminateAudio s = termSndSrc s shotSndSrc new :: ResourceTracker -> WM -> WP -> Angle -> ATank new a b c d = ATank { center = c , angle = d , velocity = (0.0, 0.0) , wmap = b , launchTube = [] , sinceLastShot = 0.0 , integrity = maxIntegrity , vision = Nothing , rt = a , queueShotSnd = False , shotSndSrc = Nothing } instance Observant ATank where updateVision s a = s { vision = Just a } updateAngle t s = adjAngle s t vision (\x y -> x { angle = y }) angle (pi / 6) radialVelocity updateVelocity t s = s { velocity = M.newVelocity (velocity s) accelerationRate (angle s) maxVelocityMag t } instance Animation ATank where image s _ = reorient (angle s) (protectedGetImage (rt s) "atank.bmp") instance M.Locatable ATank where center = center instance M.Moving ATank where velocity = velocity instance M.Colliding ATank where collisionRadius _ = collisionR instance InternallyUpdating ATank where preUpdate s t = (updateFiringInformation t . updateVelocity t . updateAngle t) s postUpdate s t = s { center = M.newLocation (wmap s) (center s) (velocity s) t } updateFiringInformation t s = firing s sinceLastShot 1.5 (\x y -> x { sinceLastShot = y }) (\x y -> x { launchTube = y }) (\x y -> x { queueShotSnd = y }) [p] t launchTube where p = P.BulletMI.prj s wmap (firingAngle s vision angle) instance Launcher ATank where deployProjectiles s = (launchTube s, s { launchTube = [] }) instance Transient ATank where expired' s = if moreThanZero (integrity s) then Nothing else Just [a] where a = AfterEffect (SimpleExplosion.new (rt s)(wmap s) (center s) (velocity s)) instance Damageable ATank where inflictDamage s d = s { integrity = max 0 (integrity s - d) } instance Damaging ATank where damageEnergy s = kamikazeDamage