module Unit.Simple.Turret ( Turret(..) , 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 Sound.ALUT import Common radialVelocity = pi/6 -- radians per second velocityMagnitude = 40 kamikazeDamage = 6.0 maxIntegrity = 2.0 data Turret = Turret { turretAngle :: Angle -- radians , velocity :: Velocity , center :: WrapPoint , idealTargetLocation :: Maybe WrapPoint , wrapMap :: WrapMap , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , animDefault0 :: Picture , resourceTracker :: ResourceTracker -- Sound , queueShotSound :: Bool , shotSoundSource :: Maybe Source } instance Audible Turret 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 -> Angle -> Turret new rt wmap center' tAngle mAngle = let pic = fromMaybe (Scale 0.20 0.20 (Color white (Text "Error! Missing image!"))) (getImage rt "turret.bmp") in Turret { center = center' , turretAngle = tAngle , idealTargetLocation = Nothing , velocity = velocity' , wrapMap = wmap , launchTube = [] , sinceLastShot = 0.0 , integrity = maxIntegrity , animDefault0 = pic , resourceTracker = rt , queueShotSound = False , shotSoundSource = Nothing } where velocity' =( sin mAngle * velocityMagnitude , cos mAngle * velocityMagnitude ) updateAngle t self = self { turretAngle = turretAngle self - radialVelocity * t} instance Animation Turret where image self _ = Rotate (radToDeg (double2Float (turretAngle self)) * (-1) - 90) (animDefault0 self) instance M.Locatable Turret where center = center instance M.Moving Turret where velocity = velocity instance M.Colliding Turret where collisionRadius _ = 16.0 instance InternallyUpdating Turret where preUpdate self t = (updateFiringInformation t . updateIdealTargetLocation 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' >= 1.5 then self { sinceLastShot = 0.0 , launchTube = launchTube self ++ projectiles , queueShotSound = True } else self { sinceLastShot = sinceLastShot' } where projectiles = map projectile [ 0.0, pi / 2, pi, 3 * pi / 2 ] projectile x = Projectile ( P.BulletSI.new (wrapMap self) (turretAngle self + x) (center self) (velocity self) ) updateIdealTargetLocation :: Time -> Turret -> Turret updateIdealTargetLocation t self = self { idealTargetLocation = Just (M.idealNewLocation (wrapMap self) (center self) (velocity self) t) } instance Launcher Turret where deployProjectiles self = (launchTube self, self { launchTube = [] }) instance Transient Turret 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 Turret where inflictDamage self d = self { integrity = max 0.0 (integrity self - d) } instance Damaging Turret where damageEnergy self = kamikazeDamage