{-| Module : Unit.Smart.Zeus Description : Stationary heavy cannon with targeting Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Unit.Smart.Zeus ( Zeus(..) , new ) where import Prelude (Bool(..), (>), max, (-), (+), (++), (.), (>=), Maybe(..), ($), return, (*), pi, not, Double) import Data.WrapAround ( WP, WM, vectorRelation ) import Graphics.Gloss.Data.Picture ( Picture(Color, Pictures, Rotate, Scale, Text) ) import Graphics.Gloss.Data.Color ( white ) import GHC.Float ( double2Float ) import Data.Maybe ( isNothing, fromMaybe, fromJust ) import Sound.ALUT ( Vertex3(Vertex3), HasSetter(($=)), SourceRelative(Listener), Source, ObjectName(genObjectNames), stop, sourceRelative, sourcePosition, rolloffFactor, referenceDistance, play, buffer ) import Animation import Math import ResourceTracker import Updating import qualified Moving as M ( Colliding(..), Moving(..), Locatable(..) ) import Combat import qualified Projectile.Interceptor as P.Interceptor ( speed, new ) import AfterEffect ( AfterEffect(AfterEffect) ) import qualified AfterEffect.SimpleExplosion as SimpleExplosion ( new ) import Universe ( Arena(lance) ) import qualified Universe as U ( Arena(wrapMap) ) import Common radialVelocity = pi -- radians per second kamikazeDamage = 8.0 maxIntegrity = 2 shotDelay = 6.0 collisionRadiusC = 23.0 data Zeus = Zeus { angle :: Angle -- radians , center :: WP , wrapMap :: WM , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , vision :: Maybe Arena , resourceTracker :: ResourceTracker , shotDelayShift :: Time -- Sound , queueShotSound :: Bool , shotSoundSource :: Maybe Source } instance Audible Zeus 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 rolloffFactor source $= audioRolloffFactor return self { shotSoundSource = Just source } new :: ResourceTracker -> WM -> WP -> Angle -> Time -> Zeus new rt wmap center' angle' shotDelayShift' = Zeus { center = center' , angle = angle' , wrapMap = wmap , launchTube = [] , sinceLastShot = 0.0 , integrity = maxIntegrity , vision = Nothing , resourceTracker = rt , shotDelayShift = shotDelayShift' , queueShotSound = False , shotSoundSource = Nothing } instance Observant Zeus where updateVision self arena = self { vision = Just arena } updateAngle t self = self { angle = 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)) } where pSpeed = P.Interceptor.speed instance Animation Zeus where image self _ = Pictures [ bpic, tpic' ] where bpic = fromMaybe (Scale 0.20 0.20 (Color white (Text "Error! Missing image!"))) (getImage rt "zeus-base.bmp") tpic = fromMaybe (Scale 0.20 0.20 (Color white (Text "Error! Missing image!"))) (getImage rt "zeus-cannon.bmp") tpic' = Rotate (double2Float (radToDeg (angle self)) * (-1) - 90) tpic rt = resourceTracker self instance M.Locatable Zeus where center = center instance M.Moving Zeus where velocity self = (0, 0) instance M.Colliding Zeus where collisionRadius _ = collisionRadiusC instance InternallyUpdating Zeus where preUpdate self t = (updateFiringInformation t . updateAngle t) self postUpdate self t = self updateFiringInformation t self = let sinceLastShot' = sinceLastShot self + t in if sinceLastShot' >= shotDelay + shotDelayShift self then self { sinceLastShot = 0.0 , launchTube = launchTube self ++ [projectile] , queueShotSound = True } else self { sinceLastShot = sinceLastShot' } where projectile = Projectile ( P.Interceptor.new (wrapMap self) (resourceTracker self) (angle self) (center self) (M.velocity self) ) instance Launcher Zeus where deployProjectiles self = (launchTube self, self { launchTube = [] }) instance Transient Zeus where expired' self = if integrity self > 0.0 then Nothing else Just [aeffect] where aeffect = AfterEffect (SimpleExplosion.new (resourceTracker self) (wrapMap self) (center self) (M.velocity self)) instance Damageable Zeus where inflictDamage self d = self { integrity = max 0.0 (integrity self - d) } instance Damaging Zeus where damageEnergy self = kamikazeDamage