module Unit.Smart.DeathII ( DeathII(..) , new ) where import Data.WrapAround ( WP, WM, vectorRelation ) import Animation ( Audible(..), Animation(..), termSndSrc, handSndSrc ) import Graphics.Gloss.Data.Picture () import Graphics.Gloss.Data.Color () import GHC.Float () import Math ( vectorDirection, targetingA, subV, moreThanZero, isNan ) import ResourceTracker ( RT, protectedGetImage ) import Updating ( Transient(..), Observant(..), InternallyUpdating(..) ) import qualified Moving as M ( Moving(..), Locatable(..), Colliding(..), newVelocity, newLocation ) import Combat ( Projectile(..), Launcher(..), Damaging(..), Damageable(..) ) import qualified Projectile.Interceptor as P.Interceptor ( speed, new ) import qualified Projectile.BulletMII as P.BulletMII ( new ) import AfterEffect ( AfterEffect(AfterEffect) ) import qualified AfterEffect.SimpleExplosion as SimpleExplosion ( new ) import Data.Maybe () import Universe ( Arena(lance) ) import qualified Universe as U ( Arena(wrapMap) ) import Sound.ALUT ( Source ) import Common ( Velocity, Time, Angle ) radialVelocity = pi maxVelocityMag = 400 kamikazeDamage = 150 maxIntegrity = 16 accelerationRate = 400 adjAngleC = pi / 8 shotDelay_sniper = 3.5 shotDelay_spread = 2.5 collisionR = 75 data DeathII = DeathII { angle :: Angle , velocity :: Velocity , center :: WP , wmap :: WM , launchTube :: [Projectile] , sinceLastShot_sniper :: Time , sinceLastShot_spread :: Time , integrity :: Double , vision :: Maybe Arena , rt :: RT , queueShotSnd :: Bool , shotSndSrc :: Maybe Source } instance Audible DeathII 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 = DeathII { center = c , angle = d , velocity = (0, 0) , wmap = b , launchTube = [] , sinceLastShot_sniper = 0 , sinceLastShot_spread = 0 , integrity = maxIntegrity , vision = Nothing , rt = a , queueShotSnd = False , shotSndSrc = Nothing } instance Observant DeathII where updateVision s a = s { vision = Just a } updateAngle t s = case vision s of Nothing -> s Just a -> case lance a of Nothing -> s Just l -> let b = angle s in let e = if isNan b then 0.1 else b in let m = vectorDirection (vectorRelation (wmap s) (center s) (M.center l)) in let adj | m - e > adjAngleC = radialVelocity * t | m - e < (-1) * adjAngleC = (-radialVelocity) * t | otherwise = 0 in s { angle = angle s + adj } updateVelocity t s = s { velocity = b } where c = M.newVelocity (velocity s) accelerationRate (angle s) maxVelocityMag t b = case vision s of Nothing -> velocity s Just a -> case lance a of Nothing -> velocity s Just l -> let d = angle s in let e = if isNan d then 0.1 else d in let m = vectorDirection (vectorRelation (wmap s) (center s) (M.center l)) in if abs (m - e) <= adjAngleC then c else velocity s instance Animation DeathII where image s _ = protectedGetImage (rt s) "deathii.bmp" instance M.Locatable DeathII where center = center instance M.Moving DeathII where velocity = velocity instance M.Colliding DeathII where collisionRadius _ = collisionR instance InternallyUpdating DeathII 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 = fst ((handleSpreadFiring . handleSniperFiring) (s, t)) handleSniperFiring (self, t) = let sinceLastShot_sniper' = sinceLastShot_sniper self + t in if sinceLastShot_sniper' >= shotDelay_sniper then (self { sinceLastShot_sniper = 0.0 , launchTube = projectile : launchTube self , queueShotSnd = True }, t) else (self { sinceLastShot_sniper = sinceLastShot_sniper' }, t) where projectile = Projectile (P.Interceptor.new (wmap self) (rt self) pAngle (center self) (velocity self)) pSpeed = P.Interceptor.speed pAngle = case vision self of Nothing -> angle self Just arena -> case lance arena of Nothing -> angle self Just l -> targetingA pSpeed (vectorRelation (U.wrapMap arena) (center self) (M.center l)) (subV (M.velocity l) (M.velocity self)) handleSpreadFiring (self, t) = let sinceLastShot_spread' = sinceLastShot_spread self + t in if sinceLastShot_spread' >= shotDelay_spread then (self { sinceLastShot_spread = 0.0 , launchTube = projectiles ++ launchTube self , queueShotSnd = True }, t) else (self { sinceLastShot_spread = sinceLastShot_spread' }, t) where projectiles = map projectile [ x * pi / 8.0 - pi / 4.0 | x <- [0..7] ] projectile x = Projectile (P.BulletMII.new (wmap self) (pAngle + x) (center self) (velocity self)) pAngle = case vision self of Nothing -> angle self Just arena -> case lance arena of Nothing -> angle self Just l -> vectorDirection (vectorRelation (U.wrapMap arena) (center self) (M.center l)) instance Launcher DeathII where deployProjectiles s = (launchTube s, s { launchTube = [] }) instance Transient DeathII 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 DeathII where inflictDamage s d = s { integrity = max 0 (integrity s - d) } instance Damaging DeathII where damageEnergy _ = kamikazeDamage