gore-and-ash-1.2.2.0: Core of FRP game engine called Gore&Ash

Copyright(c) Anton Gushcha, 2015-2016 Oganyan Levon, 2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.Core.State

Description

Handling of game main loop, creation of initial state, stepping and cleaning up.

Synopsis

Documentation

data GameState m s a Source

Holds all data that is needed to produce next step of game simulation.

You need to call stepGame to get next game state repeatedly and finally cleanupGameState at the end of program.

m
is game monad is used including all enabled API of core modules;
s
is game state that includes chained state of core modules;
a
is return value of main arrow;

Typical game main loop:

main :: IO ()
main = withModule (Proxy :: Proxy AppMonad) $ do
  gs <- newGameState $ runActor' mainWire
  gsRef <- newIORef gs
  firstStep gs gsRef onCtrlC exitHandler gsRef
  where
    -- | What to do on emergency exit
    exitHandler gsRef = do 
      gs <- readIORef gsRef 
      cleanupGameState gs
      exitSuccess

    -- | Initialization step
    firstStep gs gsRef = do 
      (_, gs') <- stepGame gs $ do 
        -- ... some initialization steps
      writeIORef gsRef gs'
      gameLoop gs' gsRef

    -- | Normal game loop
    gameLoop gs gsRef = do 
      (_, gs') <- stepGame gs (return ())
      writeIORef gsRef gs'
      gameLoop gs' gsRef

-- | Executes given handler on Ctrl-C pressing
onCtrlC :: IO a -> IO () -> IO a
p onCtrlC q = catchJust isUserInterrupt p (const $ q >> p onCtrlC q)
  where
    isUserInterrupt :: AsyncException -> Maybe ()
    isUserInterrupt UserInterrupt = Just ()
    isUserInterrupt _             = Nothing

Constructors

GameState 

Instances

NFData s => NFData (GameState m s a) Source 

stepGame Source

Arguments

:: (GameModule m s, NFData s, MonadIO m') 
=> GameState m s a

Current game state

-> GameMonadT m b

Some action to perform before each frame

-> m' (Maybe a, GameState m s a)

Main wire can inhibit therefore result is Maybe

Main loop of the game where each frame is calculated.

Call it frequently enough for smooth simulation. At the end of application there should be call to cleanupGameState.

newGameState Source

Arguments

:: (GameModule m s, MonadIO m') 
=> GameWire m () a

Wire that we calculate

-> m' (GameState m s a) 

Creates new game state from given main wire.

Use stepGame to update the state and free it with cleanupGameState at the end of your application.

If you need some initialization steps, you can use newGameStateM version.

newGameStateM Source

Arguments

:: (GameModule m s, MonadIO m') 
=> GameMonadT m (GameWire m () a)

Action that makes wire to execute

-> m' (GameState m s a) 

Creates new game state, monadic version that allows some initialization steps in game monad.

The function is helpful if you want to make an global actor from your main wire.

Use stepGame to update the state and free it with cleanupGameState at the end of your application.

See also newGameState.

cleanupGameState Source

Arguments

:: (GameModule m s, MonadIO m') 
=> GameState m s a

Game state with resources

-> m' () 

Cleanups resources that is holded in game state.

The function should be called before the exit of application to free all resources catched by core modules.