2016-10-31 22:47:16 +00:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2017-02-23 23:18:29 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
2016-03-25 08:41:22 +00:00
|
|
|
module Affection
|
2016-10-31 22:47:16 +00:00
|
|
|
( withAffection
|
2016-12-12 01:10:30 +00:00
|
|
|
, getAffection
|
|
|
|
, putAffection
|
2016-11-13 12:39:25 +00:00
|
|
|
-- , withWindow
|
|
|
|
-- , withDefaultWindow
|
2016-03-25 10:43:31 +00:00
|
|
|
, delaySec
|
2016-11-04 15:06:16 +00:00
|
|
|
, get
|
|
|
|
, put
|
2017-03-20 04:24:30 +00:00
|
|
|
, getElapsedTime
|
2017-03-16 19:12:41 +00:00
|
|
|
, getDelta
|
|
|
|
, quit
|
2016-12-08 17:22:29 +00:00
|
|
|
, module A
|
2016-03-25 08:41:22 +00:00
|
|
|
) where
|
|
|
|
|
2016-10-31 22:47:16 +00:00
|
|
|
import qualified SDL
|
2016-12-08 17:22:29 +00:00
|
|
|
import qualified SDL.Internal.Numbered as SDL (toNumber)
|
2016-11-08 03:31:51 +00:00
|
|
|
import qualified SDL.Raw as Raw
|
2016-10-31 22:47:16 +00:00
|
|
|
import qualified GEGL as G
|
|
|
|
|
|
|
|
import Data.Maybe
|
2017-02-19 21:28:10 +00:00
|
|
|
import Data.IORef
|
2016-10-31 22:47:16 +00:00
|
|
|
|
2016-11-02 00:14:53 +00:00
|
|
|
import System.Clock
|
2016-10-31 22:47:16 +00:00
|
|
|
|
|
|
|
import Control.Monad.Loops
|
2017-03-20 04:24:02 +00:00
|
|
|
import qualified Control.Monad.Parallel as MP
|
2016-10-31 22:47:16 +00:00
|
|
|
import Control.Monad.State
|
2016-03-25 10:43:31 +00:00
|
|
|
|
2016-12-11 16:38:03 +00:00
|
|
|
import Foreign.C.Types (CInt(..))
|
|
|
|
import Foreign.Storable (peek)
|
|
|
|
|
2017-02-17 16:15:06 +00:00
|
|
|
import Debug.Trace
|
|
|
|
|
2016-12-08 17:22:29 +00:00
|
|
|
import Affection.Types as A
|
|
|
|
import Affection.Draw as A
|
2016-12-13 10:08:49 +00:00
|
|
|
import Affection.Particle as A
|
2017-03-05 15:39:37 +00:00
|
|
|
import Affection.StateMachine as A
|
|
|
|
import Affection.MouseInteractable as A
|
2017-03-18 16:38:26 +00:00
|
|
|
import Affection.Property as A
|
|
|
|
import Affection.Actor as A
|
2016-03-25 15:58:46 +00:00
|
|
|
|
2016-12-11 16:38:03 +00:00
|
|
|
import qualified BABL as B
|
|
|
|
|
2016-11-06 04:02:06 +00:00
|
|
|
-- | Main function which bootstraps everything else.
|
|
|
|
withAffection
|
|
|
|
:: AffectionConfig us -- ^ Configuration of the Game and its engine.
|
|
|
|
-> IO ()
|
2016-11-08 04:15:44 +00:00
|
|
|
withAffection AffectionConfig{..} = do
|
2017-02-23 21:54:26 +00:00
|
|
|
-- intialiaze SDL
|
2016-10-31 22:47:16 +00:00
|
|
|
case initComponents of
|
|
|
|
All ->
|
|
|
|
SDL.initializeAll
|
|
|
|
Only is ->
|
|
|
|
SDL.initialize is
|
2016-11-04 15:06:16 +00:00
|
|
|
G.gegl_init
|
2017-02-23 21:54:26 +00:00
|
|
|
-- give SDL render quality
|
|
|
|
SDL.HintRenderScaleQuality SDL.$= SDL.ScaleLinear
|
|
|
|
-- just checking…
|
|
|
|
do
|
|
|
|
renderQuality <- SDL.get SDL.HintRenderScaleQuality
|
|
|
|
when (renderQuality /= SDL.ScaleLinear) $
|
|
|
|
putStrLn "Warning: Linear texture filtering not enabled!"
|
|
|
|
-- get current time
|
2017-02-19 21:28:10 +00:00
|
|
|
execTime <- newIORef =<< getTime Monotonic
|
2017-02-23 21:54:26 +00:00
|
|
|
-- construct window
|
2016-10-31 22:47:16 +00:00
|
|
|
window <- SDL.createWindow windowTitle windowConfig
|
2017-02-23 21:54:26 +00:00
|
|
|
SDL.showWindow window
|
|
|
|
-- create renderer
|
|
|
|
renderer <- SDL.createRenderer
|
|
|
|
window
|
|
|
|
(-1)
|
|
|
|
SDL.defaultRenderer
|
2017-03-22 15:59:24 +00:00
|
|
|
-- make draw texture
|
|
|
|
texture <- SDL.createTexture
|
|
|
|
renderer
|
|
|
|
SDL.ABGR8888
|
|
|
|
SDL.TextureAccessStreaming
|
2017-03-23 03:32:43 +00:00
|
|
|
(case canvasSize of
|
|
|
|
Just (cw, ch) -> (SDL.V2
|
|
|
|
(CInt $ fromIntegral cw)
|
|
|
|
(CInt $ fromIntegral ch)
|
|
|
|
)
|
|
|
|
Nothing ->
|
|
|
|
SDL.windowInitialSize windowConfig
|
|
|
|
)
|
2017-02-23 21:54:26 +00:00
|
|
|
-- make draw surface
|
2017-03-23 03:32:43 +00:00
|
|
|
-- pixelFormat <- liftIO $ peek . Raw.surfaceFormat =<< peek ptr
|
|
|
|
let SDL.V2 (CInt rw) (CInt rh) = windowInitialSize windowConfig
|
|
|
|
(w, h) = case canvasSize of
|
|
|
|
Just (cw, ch) -> (cw, ch)
|
|
|
|
Nothing -> (fromIntegral rw, fromIntegral rh)
|
|
|
|
-- stride = fromIntegral (Raw.pixelFormatBytesPerPixel pixelFormat) * w
|
|
|
|
bablFormat = B.PixelFormat B.RGBA B.CFu8
|
2017-02-19 21:28:10 +00:00
|
|
|
cpp = B.babl_components_per_pixel bablFormat
|
2017-03-23 03:32:43 +00:00
|
|
|
!stride = cpp * w
|
2016-12-11 16:38:03 +00:00
|
|
|
format <- B.babl_format bablFormat
|
2016-12-20 23:16:21 +00:00
|
|
|
initContainer <- (\x -> AffectionData
|
2016-11-04 15:06:16 +00:00
|
|
|
{ quitEvent = False
|
|
|
|
, userState = x
|
2016-11-02 00:14:53 +00:00
|
|
|
, drawWindow = window
|
2017-02-23 21:54:26 +00:00
|
|
|
, windowRenderer = renderer
|
2017-03-22 15:59:24 +00:00
|
|
|
-- , drawSurface = surface
|
|
|
|
, drawTexture = texture
|
2016-12-21 03:28:57 +00:00
|
|
|
, drawFormat = format
|
2017-03-23 03:32:43 +00:00
|
|
|
-- , drawPixels = pixels
|
|
|
|
, drawDimensions = case canvasSize of
|
|
|
|
Just (cw, ch) -> (cw, ch)
|
|
|
|
Nothing -> (w, h)
|
2017-02-19 21:28:10 +00:00
|
|
|
, drawStride = stride
|
|
|
|
, drawCPP = cpp
|
2016-12-11 16:38:03 +00:00
|
|
|
, drawStack = []
|
2016-12-25 07:14:51 +00:00
|
|
|
, elapsedTime = 0
|
2017-03-16 19:12:41 +00:00
|
|
|
, dt = 0
|
2017-03-23 03:34:04 +00:00
|
|
|
}) <$> loadState
|
2016-12-11 16:38:03 +00:00
|
|
|
(_, nState) <- runStateT ( A.runState $ do
|
2016-12-11 19:24:16 +00:00
|
|
|
preLoop
|
2016-10-31 22:47:16 +00:00
|
|
|
whileM_ (do
|
|
|
|
current <- get
|
2016-12-08 17:22:29 +00:00
|
|
|
return $ not $ A.quitEvent current
|
2016-10-31 22:47:16 +00:00
|
|
|
)
|
2016-11-04 15:06:16 +00:00
|
|
|
(do
|
2016-12-20 03:14:57 +00:00
|
|
|
-- Measure time difference form last run
|
2016-11-02 00:14:53 +00:00
|
|
|
now <- liftIO $ getTime Monotonic
|
2017-02-19 21:28:10 +00:00
|
|
|
lastTime <- liftIO $ readIORef execTime
|
2016-12-20 03:14:57 +00:00
|
|
|
-- get state
|
2016-12-11 16:38:03 +00:00
|
|
|
ad <- get
|
2016-12-20 03:14:57 +00:00
|
|
|
-- clean draw requests from last run
|
2017-03-28 22:46:03 +00:00
|
|
|
MP.mapM_ (invalidateDrawRequest (drawStride ad) (drawCPP ad)) (drawStack ad)
|
2017-02-23 21:54:26 +00:00
|
|
|
-- clean the renderer form last time
|
2017-03-20 04:24:30 +00:00
|
|
|
-- SDL.clear renderer
|
2016-12-25 07:14:51 +00:00
|
|
|
-- compute dt and update elapsedTime
|
2017-03-20 04:24:30 +00:00
|
|
|
let !dt = fromIntegral (toNanoSecs $ diffTimeSpec lastTime now) / (10 ^ 9)
|
2017-02-23 23:18:29 +00:00
|
|
|
!ne = elapsedTime ad + dt
|
2016-12-11 16:38:03 +00:00
|
|
|
put $ ad
|
2016-12-25 07:14:51 +00:00
|
|
|
{ drawStack = []
|
2017-02-23 23:18:29 +00:00
|
|
|
, elapsedTime = ne
|
2017-03-16 19:12:41 +00:00
|
|
|
, dt = dt
|
2016-12-25 07:14:51 +00:00
|
|
|
}
|
2017-02-17 16:15:06 +00:00
|
|
|
-- poll events
|
|
|
|
evs <- preHandleEvents =<< liftIO SDL.pollEvents
|
2017-03-28 22:46:03 +00:00
|
|
|
mapM_ eventLoop evs
|
2016-12-20 03:14:57 +00:00
|
|
|
-- execute user defined update loop
|
2017-03-23 03:34:04 +00:00
|
|
|
updateLoop dt
|
2016-12-23 13:18:39 +00:00
|
|
|
-- execute user defined draw loop
|
|
|
|
drawLoop
|
2016-12-20 03:14:57 +00:00
|
|
|
-- handle all new draw requests
|
2016-12-20 04:27:35 +00:00
|
|
|
ad2 <- get
|
2017-02-19 21:28:10 +00:00
|
|
|
clear <- catMaybes <$>
|
2017-03-28 22:46:03 +00:00
|
|
|
MP.mapM (handleDrawRequest (drawStride ad) (drawCPP ad)) (drawStack ad2)
|
2016-12-20 03:14:57 +00:00
|
|
|
-- save all draw requests to clear in next run
|
2016-12-20 04:27:35 +00:00
|
|
|
put $ ad2
|
2016-12-11 19:24:16 +00:00
|
|
|
{ drawStack = clear }
|
2017-02-23 21:54:26 +00:00
|
|
|
-- actual drawing
|
|
|
|
SDL.present (windowRenderer ad2)
|
2016-12-20 03:14:57 +00:00
|
|
|
-- save new time
|
2017-03-20 04:24:30 +00:00
|
|
|
liftIO $ writeIORef execTime now
|
2016-11-04 15:06:16 +00:00
|
|
|
)
|
2016-10-31 22:47:16 +00:00
|
|
|
) initContainer
|
2016-11-04 15:06:16 +00:00
|
|
|
G.gegl_exit
|
2016-11-13 12:39:25 +00:00
|
|
|
cleanUp $ userState nState
|
2017-02-23 21:54:26 +00:00
|
|
|
SDL.destroyWindow window
|
2016-10-31 22:47:16 +00:00
|
|
|
SDL.quit
|
2016-03-25 10:43:31 +00:00
|
|
|
|
2017-02-17 16:15:06 +00:00
|
|
|
getSurfaces :: SDL.Window -> IO (SDL.Surface, SDL.Surface)
|
|
|
|
getSurfaces window = do
|
|
|
|
oldSurf@(SDL.Surface ptr _) <- SDL.getWindowSurface window
|
|
|
|
rawSurfacePtr <- Raw.convertSurfaceFormat ptr (SDL.toNumber SDL.ABGR8888) 0
|
2017-03-20 04:24:30 +00:00
|
|
|
let surface = SDL.Surface rawSurfacePtr Nothing
|
2017-02-17 16:15:06 +00:00
|
|
|
return (oldSurf, surface)
|
|
|
|
|
2017-02-22 17:02:34 +00:00
|
|
|
-- Prehandle SDL events in case any window events occur
|
2017-03-16 19:12:41 +00:00
|
|
|
preHandleEvents :: [SDL.Event] -> Affection us [SDL.EventPayload]
|
2017-02-17 16:15:06 +00:00
|
|
|
preHandleEvents evs =
|
2017-02-25 16:24:21 +00:00
|
|
|
-- mapM handle evs
|
|
|
|
-- where
|
|
|
|
-- handle e =
|
|
|
|
-- case SDL.eventPayload e of
|
|
|
|
-- SDL.WindowMovedEvent _ -> do
|
|
|
|
-- liftIO $ traceIO "I was moved"
|
|
|
|
-- return e
|
|
|
|
-- _ ->
|
|
|
|
-- return e
|
2017-03-16 19:12:41 +00:00
|
|
|
return $ map SDL.eventPayload evs
|
2017-02-17 16:15:06 +00:00
|
|
|
|
2016-12-12 01:10:30 +00:00
|
|
|
-- | Return the userstate to the user
|
|
|
|
getAffection :: Affection us us
|
|
|
|
getAffection = do
|
|
|
|
ad <- get
|
|
|
|
return $ userState ad
|
|
|
|
|
|
|
|
-- | Put altered user state back
|
|
|
|
putAffection
|
|
|
|
:: us -- User state
|
|
|
|
-> Affection us ()
|
|
|
|
putAffection us = do
|
|
|
|
ad <- get
|
|
|
|
put $ ad
|
|
|
|
{ userState = us }
|
2016-03-25 10:43:31 +00:00
|
|
|
|
2016-11-06 04:02:06 +00:00
|
|
|
-- | block a thread for a specified amount of time
|
|
|
|
delaySec
|
|
|
|
:: Int -- ^ Number of seconds
|
|
|
|
-> IO ()
|
2016-10-31 22:47:16 +00:00
|
|
|
delaySec dur = SDL.delay (fromIntegral $ dur * 1000)
|
2017-03-16 19:12:41 +00:00
|
|
|
|
|
|
|
-- | Get time since start but always the same in the current tick.
|
2017-03-20 04:24:30 +00:00
|
|
|
getElapsedTime :: Affection us Double
|
|
|
|
getElapsedTime =
|
2017-03-16 19:12:41 +00:00
|
|
|
elapsedTime <$> get
|
|
|
|
|
|
|
|
getDelta :: Affection us Double
|
|
|
|
getDelta =
|
|
|
|
dt <$> get
|
|
|
|
|
|
|
|
quit :: Affection us ()
|
|
|
|
quit = do
|
|
|
|
ad <- get
|
|
|
|
put $ ad { quitEvent = True }
|