module Unit.Smart.Sniper ( Sniper(..) , new ) where import Data.WrapAround ( WP, WM, vectorRelation ) import Animation ( Audible(..), Animation(..), audioReferenceDistance, audioRolloffFactor ) import Graphics.Gloss.Data.Picture ( Picture(Color, Rotate, Scale, Text) ) import Graphics.Gloss.Data.Color ( white ) import GHC.Float ( double2Float ) import Math ( radToDeg, vectorDirection, targetingA, subV ) import ResourceTracker ( ResourceTracker, getImage, getSound ) import Updating ( Observant(..), Transient(..), InternallyUpdating(..) ) import qualified Moving as M ( Colliding(..), Moving(..), Locatable(..), newVelocity, newLocation ) import Combat ( Launcher(..), Damageable(..), Damaging(..), Projectile(..) ) import qualified Projectile.BulletSII as P.BulletSII ( speed, new ) import AfterEffect ( AfterEffect(AfterEffect) ) import qualified AfterEffect.SimpleExplosion as SimpleExplosion ( new ) import Data.Maybe ( isNothing, fromMaybe, fromJust ) import Universe ( Arena(lance) ) import qualified Universe as U ( Arena(wrapMap) ) import Sound.ALUT ( Vertex3(Vertex3), HasSetter(($=)), SourceRelative(Listener), Source, ObjectName(genObjectNames), stop, sourceRelative, sourcePosition, rolloffFactor, referenceDistance, play, buffer ) import Common ( Velocity, Angle, Time ) radialVelocity = pi/6 -- radians per second maxVelocityMag = 20 kamikazeDamage = 2.0 maxIntegrity = 1 accelerationRate = 30 adjAngle = pi / 8 shotDelay = 4.0 data Sniper = Sniper { angle :: Angle -- radians , velocity :: Velocity , center :: WP , idealTargetLocation :: Maybe WP , wrapMap :: WM , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , vision :: Maybe Arena , resourceTracker :: ResourceTracker -- Sound , queueShotSound :: Bool , shotSoundSource :: Maybe Source } instance Audible Sniper where processAudio self lcenter = do self' <- if isNothing (shotSoundSource self) then initializeShotSoundSource self else return self if not (queueShotSound self) then return self' else do let (x, y) = vectorRelation (wrapMap self) (lcenter) (center self) let s = fromJust $ shotSoundSource self sourcePosition s $= (Vertex3 (double2Float x) (double2Float (-y)) 0) play [s] return self' { queueShotSound = False } terminateAudio self = if isNothing (shotSoundSource self) then return self else do stop [fromJust (shotSoundSource self)] return self initializeShotSoundSource self = do [source] <- genObjectNames 1 buffer source $= getSound (resourceTracker self) "energy-shot-02.wav" -- ... sourceRelative source $= Listener referenceDistance source $= audioReferenceDistance -- maxDistance source $= audioMaxDistance rolloffFactor source $= audioRolloffFactor return self { shotSoundSource = Just source } new :: ResourceTracker -> WM -> WP -> Angle -> Sniper new rt wmap center' angle' = Sniper { center = center' , angle = angle' , idealTargetLocation = Nothing , velocity = (0.0, 0.0) , wrapMap = wmap , launchTube = [] , sinceLastShot = 0.0 , integrity = maxIntegrity , vision = Nothing , resourceTracker = rt , queueShotSound = False , shotSoundSource = Nothing } instance Observant Sniper where updateVision self arena = self { vision = Just arena } updateAngle t self = case vision self of Nothing -> self Just arena -> if isNothing (lance arena) then self else let sDir = vectorDirection (velocity self) in let tDir = vectorDirection (vectorRelation (U.wrapMap arena) (center self) (M.center (fromJust (lance arena)))) in let adj | tDir - sDir > adjAngle = radialVelocity * t | tDir -sDir < (-1) * adjAngle = (-radialVelocity) * t | otherwise = 0.0 in self { angle = angle self + adj } updateVelocity :: Time -> Sniper -> Sniper updateVelocity t self = self { velocity = M.newVelocity (velocity self) accelerationRate (angle self) maxVelocityMag t } instance Animation Sniper where image self _ = Rotate (double2Float (radToDeg (angle self)) * (-1) - 90) pic where pic = fromMaybe (Scale 0.20 0.20 (Color white (Text "Error! Missing image!"))) (getImage rt "sniper.bmp") rt = resourceTracker self instance M.Locatable Sniper where center = center instance M.Moving Sniper where velocity = velocity instance M.Colliding Sniper where collisionRadius _ = 20.0 instance InternallyUpdating Sniper where preUpdate self t = (updateFiringInformation t . updateIdealTargetLocation t . updateVelocity t . updateAngle t) self postUpdate self t = let center' = fromMaybe (center self) (idealTargetLocation self) in self { center = center' , idealTargetLocation = Nothing } updateFiringInformation t self = let sinceLastShot' = sinceLastShot self + t in if sinceLastShot' >= shotDelay then self { sinceLastShot = 0.0 , launchTube = projectile : launchTube self , queueShotSound = True } else self { sinceLastShot = sinceLastShot' } where projectile = Projectile (P.BulletSII.new (wrapMap self) pAngle (center self) (velocity self)) pSpeed = P.BulletSII.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)) updateIdealTargetLocation :: Time -> Sniper -> Sniper updateIdealTargetLocation t self = self { idealTargetLocation = Just (M.newLocation (wrapMap self) (center self) (velocity self) t) } instance Launcher Sniper where deployProjectiles self = (launchTube self, self { launchTube = [] }) instance Transient Sniper where expired' self = if integrity self > 0.0 then Nothing else Just [aeffect] where aeffect = AfterEffect (SimpleExplosion.new (resourceTracker self) (wrapMap self) (center self) (velocity self)) instance Damageable Sniper where inflictDamage self d = self { integrity = max 0.0 (integrity self - d) } instance Damaging Sniper where damageEnergy self = kamikazeDamage