module AfterEffect.MineExplosion 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 MineExplosion = MineExplosion { center :: WP , timeRemaining :: Time , sndSrc :: Maybe Source , wmap :: WM , rt :: RT , animClock :: Time } new a b c = MineExplosion { center = c , timeRemaining = 3 , sndSrc = Nothing , wmap = b , rt = a , animClock = 0 } instance Animation MineExplosion where image s t = if animClock s < 0.1 then fromMaybe (Color white (Scale 0.10 0.10 (Text "boom!"))) (getImage (rt s) "mine-explosion.bmp") else Blank instance M.Locatable MineExplosion where center = center instance Transient MineExplosion where expired' s = if timeRemaining s <= 0 then Just [] else Nothing instance InternallyUpdating MineExplosion where preUpdate s t = s { timeRemaining = timeRemaining s - t } postUpdate s t = s { animClock = animClock s + t } instance Audible MineExplosion 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