{-| Module : Unit.Smart.Saucer Description : Flying saucer Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com -} module Unit.Smart.Saucer ( Saucer(..) , new ) where import Prelude (Maybe(..), (>), max, (-), Bool(..), length, (+), (!!), (>=), (&&), (.), (<=), (/), abs, otherwise, (==), return, (*), (<), pi, Double, Int, not, ($)) import Data.WrapAround ( WP, WM, vectorRelation, distance ) import Graphics.Gloss.Data.Picture ( Picture(Color, 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(..), newVelocity, newLocation ) import Combat import qualified Projectile.Pellet as P.Pellet ( range, new ) import AfterEffect ( AfterEffect(AfterEffect) ) import qualified AfterEffect.SimpleExplosion as SimpleExplosion ( new ) import Universe ( Arena(lance) ) import qualified Universe as U () import Common radialVelocity = pi -- radians per second maxVelocityMag = 300 kamikazeDamage = 6.0 maxIntegrity = 1 accelerationRate = 300 adjAngle = pi / 8 shotDelay = 0.10 data Saucer = Saucer { angle :: Angle -- radians , velocity :: Velocity , center :: WP , idealTargetLocation :: Maybe WP , wrapMap :: WM , launchTube :: [Projectile] , sinceLastShot :: Time , integrity :: Double , vision :: Maybe Arena , resourceTracker :: ResourceTracker , firingAnglesIndex :: Int -- Sound , queueShotSound :: Bool , shotSoundSource :: Maybe Source } instance Audible Saucer 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 -> Saucer new rt wmap center' angle' = Saucer { center = center' , angle = angle' , idealTargetLocation = Nothing , velocity = (0.0, 0.0) , wrapMap = wmap , launchTube = [] , sinceLastShot = 0.0 , integrity = maxIntegrity , vision = Nothing , resourceTracker = rt , firingAnglesIndex = 0 , queueShotSound = False , shotSoundSource = Nothing } instance Observant Saucer where updateVision self arena = self { vision = Just arena } updateAngle t self = case vision self of Nothing -> self Just a -> case lance a of Nothing -> self Just l -> let sDir = angle self in let sDir' = if sDir == 0.0 / 0.0 then 0.1 else sDir in let tDir = vectorDirection (vectorRelation (wrapMap self) (center self) (M.center l)) 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 -> Saucer -> Saucer updateVelocity t self = let thrustingVelocity = M.newVelocity (velocity self) accelerationRate (angle self) maxVelocityMag t in let velocity' = case vision self of Nothing -> velocity self Just a -> case lance a of Nothing -> velocity self Just l -> let sDir = angle self in let sDir' = if sDir == 0.0 / 0.0 then 0.1 else sDir in let tDir = vectorDirection (vectorRelation (wrapMap self) (center self) (M.center l)) in if abs (tDir - sDir') <= adjAngle then thrustingVelocity else velocity self in self { velocity = velocity' } instance Animation Saucer where image self _ = fromMaybe (Scale 0.20 0.20 (Color white (Text "Error! Missing image!"))) (getImage rt "saucer.bmp") where rt = resourceTracker self instance M.Locatable Saucer where center = center instance M.Moving Saucer where velocity = velocity instance M.Colliding Saucer where collisionRadius _ = 20.0 instance InternallyUpdating Saucer 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 inRange = case vision self of Nothing -> False Just a -> case lance a of Nothing -> False Just l -> Data.WrapAround.distance (wrapMap self) (center self) (M.center l) <= P.Pellet.range in let sinceLastShot' = sinceLastShot self + t in if sinceLastShot' >= shotDelay && inRange then self { sinceLastShot = 0.0 , launchTube = projectile : launchTube self , queueShotSound = True , firingAnglesIndex = if firingAnglesIndex self >= length firingAngles - 1 then 0 else firingAnglesIndex self + 1 } else self { sinceLastShot = sinceLastShot' } where projectile = Projectile (P.Pellet.new (wrapMap self) pAngle (center self) (velocity self)) pAngle = firingAngles !! firingAnglesIndex self firingAngles = [ 0.0 , 3.142 , 0.785 , 3.927 , 1.571 , 4.712 , 2.356 , 5.498 ] updateIdealTargetLocation :: Time -> Saucer -> Saucer updateIdealTargetLocation t self = self { idealTargetLocation = Just (M.newLocation (wrapMap self) (center self) (velocity self) t) } instance Launcher Saucer where deployProjectiles self = (launchTube self, self { launchTube = [] }) instance Transient Saucer 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 Saucer where inflictDamage self d = self { integrity = max 0.0 (integrity self - d) } instance Damaging Saucer where damageEnergy self = kamikazeDamage