module Unit.Smart.Tank ( Tank(..) , new ) where import Data.WrapAround import Animation import Graphics.Gloss.Data.Picture import Graphics.Gloss.Data.Color import GHC.Float import Trigonometry import ResourceTracker import Updating import qualified Moving as M import Combat import qualified Projectile.BulletSI as P.BulletSI import AfterEffect import qualified AfterEffect.SimpleExplosion as SimpleExplosion import Data.Maybe import Universe hiding (wrapMap, resourceTracker) import qualified Universe as U import Sound.ALUT import Common radialVelocity = pi/6 -- radians per second maxVelocityMag = 40 kamikazeDamage = 10.0 maxIntegrity = 3 accelerationRate = 30 data Tank = Tank { angle :: Angle -- radians , velocity :: Velocity , center :: WrapPoint , idealTargetLocation :: Maybe WrapPoint , wrapMap :: WrapMap , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , vision :: Maybe Arena , resourceTracker :: ResourceTracker -- Sound , queueShotSound :: Bool , shotSoundSource :: Maybe Source } instance Audible Tank 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 -> WrapMap -> WrapPoint -> Angle -> Tank new rt wmap center' angle' = Tank { 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 Tank 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 > pi / 6 = radialVelocity * t | tDir -sDir < (-pi) / 6 = (-radialVelocity) * t | otherwise = 0.0 in self { angle = angle self + adj } updateVelocity :: Time -> Tank -> Tank updateVelocity t self = self { velocity = M.calcNewVelocity (velocity self) accelerationRate (angle self) maxVelocityMag t } instance Animation Tank where image self _ = Rotate (radToDeg (double2Float (angle self)) * (-1) - 90) pic where pic = fromMaybe (Scale 0.20 0.20 (Color white (Text "Error! Missing image!"))) (getImage rt "tank.bmp") rt = resourceTracker self instance M.Locatable Tank where center = center instance M.Moving Tank where velocity = velocity instance M.Colliding Tank where collisionRadius _ = 20.0 instance InternallyUpdating Tank 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' >= 3 then self { sinceLastShot = 0.0 , launchTube = projectile : launchTube self , queueShotSound = True } else self { sinceLastShot = sinceLastShot' } where projectile = Projectile (P.BulletSI.new (wrapMap self) pAngle (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)) updateIdealTargetLocation :: Time -> Tank -> Tank updateIdealTargetLocation t self = self { idealTargetLocation = Just (M.idealNewLocation (wrapMap self) (center self) (velocity self) t) } instance Launcher Tank where deployProjectiles self = (launchTube self, self { launchTube = [] }) instance Transient Tank 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 Tank where inflictDamage self d = self { integrity = max 0.0 (integrity self - d) } instance Damaging Tank where damageEnergy self = kamikazeDamage