haskelloids/src/Main.hs

88 lines
2.2 KiB
Haskell
Raw Normal View History

2017-01-03 18:36:01 +00:00
{-# LANGUAGE OverloadedStrings #-}
2016-12-26 21:26:25 +00:00
module Main where
2017-12-19 05:49:41 +00:00
import Affection as A
2016-12-27 22:25:58 +00:00
import qualified SDL
2017-12-16 10:55:30 +00:00
import Linear as L
2016-12-27 22:25:58 +00:00
2017-12-19 21:36:42 +00:00
import NanoVG hiding (V2(..), V4(..))
2017-12-19 05:49:41 +00:00
2017-12-20 23:56:16 +00:00
import Control.Monad (when)
2017-12-19 05:49:41 +00:00
import Control.Monad.IO.Class (liftIO)
2016-12-31 16:01:24 +00:00
-- internal imports
import Types
2017-12-16 10:55:30 +00:00
import StateMachine ()
import Init
2016-12-31 16:01:24 +00:00
2016-12-26 21:26:25 +00:00
main :: IO ()
2017-12-16 10:55:30 +00:00
main = do
2017-12-19 05:49:41 +00:00
logIO A.Debug "Starting"
2017-12-16 10:55:30 +00:00
withAffection AffectionConfig
{ initComponents = All
, windowTitle = "Haskelloids"
2017-12-16 18:06:36 +00:00
, windowConfig = SDL.defaultWindow
2017-12-16 10:55:30 +00:00
{ SDL.windowOpenGL = Just SDL.defaultOpenGL
2017-12-20 23:56:16 +00:00
{ SDL.glProfile = SDL.Core SDL.Normal 3 2
2017-12-21 04:21:20 +00:00
, SDL.glColorPrecision = V4 8 8 8 1
2017-12-16 10:55:30 +00:00
}
2017-12-29 16:21:47 +00:00
, SDL.windowResizable = True
2017-12-16 10:55:30 +00:00
}
, initScreenMode = SDL.Windowed
, canvasSize = Nothing
, loadState = load
2017-12-19 20:53:07 +00:00
, preLoop = pre >> smLoad Menu
2017-12-16 10:55:30 +00:00
, eventLoop = handle
, updateLoop = update
, drawLoop = draw
2017-12-21 13:43:13 +00:00
, cleanUp = \_ -> return ()
2017-12-16 10:55:30 +00:00
}
2016-12-27 22:25:58 +00:00
2017-12-19 20:53:07 +00:00
pre :: Affection UserData ()
pre = do
subs <- subsystems <$> getAffection
liftIO $ logIO A.Debug "Setting global resize event listener"
2018-01-11 07:31:14 +00:00
_ <- partSubscribe (subWindow subs) (fitViewport (800/600))
2017-12-20 23:56:16 +00:00
_ <- partSubscribe (subKeyboard subs) $ \kbdev ->
when (msgKbdKeyMotion kbdev == SDL.Pressed) $
case SDL.keysymKeycode (msgKbdKeysym kbdev) of
SDL.KeycodeF -> do
dt <- getDelta
liftIO $ logIO A.Debug $ "FPS: " ++ show (1/dt)
2017-12-21 04:21:20 +00:00
SDL.KeycodeO -> toggleScreen
2017-12-20 23:56:16 +00:00
_ -> return ()
2017-12-19 20:53:07 +00:00
return ()
2016-12-27 22:25:58 +00:00
update :: Double -> Affection UserData ()
update sec = do
2017-11-04 17:13:28 +00:00
ud <- getAffection
smUpdate (state ud) sec
2016-12-27 22:25:58 +00:00
2017-12-16 18:06:36 +00:00
handle :: [SDL.EventPayload] -> Affection UserData ()
2017-12-16 10:55:30 +00:00
handle e = do
2017-12-19 16:30:44 +00:00
(Subsystems w k) <- subsystems <$> getAffection
_ <- consumeSDLEvents w =<< consumeSDLEvents k e
return ()
2016-12-28 11:19:45 +00:00
2016-12-27 22:25:58 +00:00
draw :: Affection UserData ()
draw = do
2017-12-19 05:49:41 +00:00
ud <- getAffection
2017-12-20 23:56:16 +00:00
liftIO $ beginFrame (nano ud) 800 600 1
2017-12-19 05:49:41 +00:00
smDraw (state ud)
2017-12-21 12:09:15 +00:00
drawVignette
2017-12-19 05:49:41 +00:00
liftIO $ endFrame (nano ud)
2017-12-21 12:09:15 +00:00
drawVignette :: Affection UserData ()
drawVignette = do
ctx <- nano <$> getAffection
liftIO $ do
save ctx
beginPath ctx
grad <- boxGradient ctx 200 150 400 300 0 500 (rgba 0 0 0 0) (rgba 0 0 0 255)
rect ctx 0 0 800 600
fillPaint ctx grad
fill ctx
restore ctx