haskelloids/src/Menu.hs

95 lines
2.5 KiB
Haskell
Raw Normal View History

2017-02-20 19:51:33 +00:00
module Menu where
2017-12-16 18:06:36 +00:00
import Affection as A
2017-02-20 19:51:33 +00:00
import qualified SDL
import Debug.Trace
2017-12-16 18:06:36 +00:00
import Data.Maybe
2017-12-19 16:30:44 +00:00
import qualified Data.Set as S
2017-12-16 18:06:36 +00:00
import Control.Monad (when)
import Control.Monad.IO.Class (liftIO)
import qualified Data.Map as M
2017-12-19 16:30:44 +00:00
import NanoVG hiding (V2(..), V4(..))
2017-12-19 05:49:41 +00:00
import Linear
import Foreign.C.Types
2017-12-16 18:06:36 +00:00
-- internal imports
2017-02-20 19:51:33 +00:00
import Types
2017-12-16 18:06:36 +00:00
import Commons
2017-02-20 19:51:33 +00:00
2017-12-16 18:06:36 +00:00
handleMenuEvent :: (Affection UserData ()) -> [SDL.EventPayload] -> Affection UserData ()
2017-12-19 05:49:41 +00:00
handleMenuEvent _ es = do
(Subsystems w k) <- subsystems <$> getAffection
_ <- consumeSDLEvents w =<< consumeSDLEvents k es
return ()
2017-12-16 10:55:30 +00:00
loadMenu :: Affection UserData ()
loadMenu = do
2017-12-16 18:06:36 +00:00
liftIO $ logIO A.Debug "Loading Menu"
2017-12-16 10:55:30 +00:00
ud <- getAffection
2017-12-19 20:53:07 +00:00
hs <- newHaskelloids (haskImage ud)
2017-12-19 05:49:41 +00:00
_ <- partSubscribe (subKeyboard $ subsystems ud)
(\kbdev -> case SDL.keysymKeycode (msgKbdKeysym kbdev) of
SDL.KeycodeEscape -> do
liftIO $ logIO A.Debug "seeya"
quit
SDL.KeycodeF -> do
when (msgKbdKeyMotion kbdev == SDL.Pressed) $ do
liftIO $ logIO A.Debug "screen toggling"
toggleScreen
_ -> return ()
)
2017-12-16 10:55:30 +00:00
putAffection ud
{ haskelloids = hs
, fade = FadeIn 1
, state = Menu
2017-12-16 18:06:36 +00:00
-- , shots = (shots ud)
-- { partSysParts = ParticleStorage Nothing [] }
2017-12-16 10:55:30 +00:00
}
updateMenu :: Double -> Affection UserData ()
updateMenu sec = do
ud <- getAffection
2017-12-16 18:06:36 +00:00
let nhs = map (updateHaskelloid sec) (haskelloids ud)
2017-12-16 10:55:30 +00:00
case fade ud of
FadeIn ttl -> do
putAffection ud
{ fade = if (ttl - sec) > 0 then FadeIn (ttl - sec) else FadeOut 1
, haskelloids = nhs
}
FadeOut ttl -> do
putAffection ud
{ fade = if (ttl - sec) > 0 then FadeOut (ttl - sec) else FadeIn 1
, haskelloids = nhs
}
2017-12-19 05:49:41 +00:00
drawMenu :: Affection UserData ()
drawMenu = do
ud <- getAffection
2017-12-19 07:18:57 +00:00
mapM_ drawHaskelloid (haskelloids ud)
2017-12-19 16:30:44 +00:00
liftIO $ do
let ctx = nano ud
alpha fio = case fio of
FadeIn d -> (floor (255 * (1 - d)))
FadeOut d -> (floor (255 * d))
save ctx
fontSize ctx 120
fontFace ctx "modulo"
textAlign ctx (S.fromList [AlignCenter,AlignTop])
-- (Bounds (V4 b0 b1 b2 b3)) <- textBoxBounds ctx x y' 150 "HASKELLOIDS"
fillColor ctx (rgba 255 255 255 255)
textBox ctx 0 200 800 "HASKELLOIDS"
fillColor ctx (rgba 255 128 0 (alpha $ fade ud))
fontSize ctx 40
2017-12-19 16:35:06 +00:00
textBox ctx 0 350 800 "Press [Space] to Play\nPress [Esc] to exit"
2017-12-19 16:30:44 +00:00
restore ctx
2017-12-19 07:18:57 +00:00
-- t <- getElapsedTime
-- liftIO $ drawSpinner (nano ud) 100 100 100 t