module AfterEffect.SimpleExplosion where import Data.WrapAround import Animation import Updating import qualified Moving as M import Graphics.Gloss.Data.Picture import Graphics.Gloss.Data.Color import Sound.ALUT import Data.Maybe import ResourceTracker import GHC.Float import Common data SimpleExplosion = SimpleExplosion { center :: WP , timeRemaining :: Time , sndSrc :: Maybe Source , wmap :: WM , rt :: RT , animClock :: Time , velocity :: Velocity } new a b c d = SimpleExplosion { center = c , timeRemaining = 3.0 , sndSrc = Nothing , wmap = b , rt = a , animClock = 0.0 , velocity = d } instance Animation SimpleExplosion where image s t = if g 1 then f "explosion-00.bmp" else if g 2 then f "explosion-01.bmp" else if g 3 then f "explosion-02.bmp" else if g 4 then f "explosion-03.bmp" else if g 5 then f "explosion-04.bmp" else if g 6 then f "explosion-05.bmp" else if g 7 then f "explosion-06.bmp" else Blank where f b = fromMaybe (Color white (Scale 0.10 0.10 (Text "boom!"))) (getImage (rt s) b) g x = (animClock s < 0.07 * x) instance M.Locatable SimpleExplosion where center = center instance Transient SimpleExplosion where expired' s = if timeRemaining s <= 0 then Just [] else Nothing instance InternallyUpdating SimpleExplosion where preUpdate s t = s { timeRemaining = timeRemaining s - t , center = M.newLocation (wmap s) (center s) (velocity s) t } postUpdate s t = s { animClock = animClock s + t } instance Audible SimpleExplosion where processAudio s a = procOneTimeSnd s sndSrc a rt "explosion.wav" 0.5 wmap (\x y -> x { sndSrc = y }) terminateAudio s = if isNothing (sndSrc s) then return s else do stop [fromJust (sndSrc s)] return s