module Unit.Simple.Turret ( Turret(..) , new ) where import Data.WrapAround (WP, WM) import Animation (Audible(..), Animation(..), handSndSrc, termSndSrc, reorient) import Math (appPair) import ResourceTracker (RT, protectedGetImage) import Updating (InternallyUpdating(..), Transient(..)) import qualified Moving as M (Locatable(..) , Moving(..) , Colliding(..) , newLocation') import Combat (Launcher(..), Damageable(..), Damaging(..), Projectile(..)) import qualified Projectile.BulletSI as P.BulletSI (prj) import AfterEffect (AfterEffect(..)) import qualified AfterEffect.SimpleExplosion as SimpleExplosion (new) import Sound.ALUT (Source(..)) import Common (Angle, Velocity, Time) import Unit (firing) radVelocity = pi/6 -- radians per second velMagnitude = 40 kamikazeDmg = 6.0 maxInteg = 2.0 cRadius = 16 data Turret = Turret { tAngle :: Angle , velocity :: Velocity , center :: WP , wmap :: WM , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , rt :: RT , queueShotSnd :: Bool , shotSndSrc :: Maybe Source } instance Audible Turret 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 a b c d e = Turret { center = c , tAngle = d , velocity = appPair (* velMagnitude) (sin e, cos e) , wmap = b , launchTube = [] , sinceLastShot = 0 , integrity = maxInteg , rt = a , queueShotSnd = False , shotSndSrc = Nothing } updateAngle t s = s { tAngle = tAngle s - radVelocity * t} instance Animation Turret where image s _ = reorient (tAngle s) (protectedGetImage (rt s) "turret.bmp") instance M.Locatable Turret where center = center instance M.Moving Turret where velocity = velocity instance M.Colliding Turret where collisionRadius _ = cRadius instance InternallyUpdating Turret where preUpdate s t = (updateFiringInformation t . updateAngle t) s postUpdate s t = s { center = M.newLocation' s (wmap 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 = map f [ 0.0, pi / 2, pi, 3 * pi / 2 ] f x = P.BulletSI.prj s wmap (tAngle s + x) instance Launcher Turret where deployProjectiles s = (launchTube s, s { launchTube = [] }) instance Transient Turret where expired' s = if integrity s > 0 then Nothing else Just [a] where a = AfterEffect (SimpleExplosion.new (rt s) (wmap s) (center s) (velocity s)) instance Damageable Turret where inflictDamage s d = s { integrity = max 0 (integrity s - d) } instance Damaging Turret where damageEnergy s = kamikazeDmg