Copyright | (c) Anton Gushcha, 2015-2016 Oganyan Levon, 2016 |
---|---|
License | BSD3 |
Maintainer | ncrashed@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
The core of all engine. It contains generic arrow operations and helpers, definition of core module system, game session declaration and utilities to control main loop of application.
- type GameTime = Timed NominalDiffTime ()
- type GameSession = Session IO GameTime
- data NominalDiffTime :: *
- data GameState m s a
- stepGame :: (GameModule m s, NFData s, MonadIO m') => GameState m s a -> GameMonadT m b -> m' (Maybe a, GameState m s a)
- newGameState :: (GameModule m s, MonadIO m') => GameWire m () a -> m' (GameState m s a)
- newGameStateM :: (GameModule m s, MonadIO m') => GameMonadT m (GameWire m () a) -> m' (GameState m s a)
- cleanupGameState :: (GameModule m s, MonadIO m') => GameState m s a -> m' ()
- data GameMonadT m a
- class Monad m => GameModule m s | m -> s, s -> m where
- type ModuleState m :: *
- runModule :: MonadIO m' => m a -> s -> m' (a, s)
- newModuleState :: MonadIO m' => m' s
- withModule :: Proxy m -> IO a -> IO a
- cleanupModule :: s -> IO ()
- type family ModuleStack ms endm :: * -> *
- type GameWire m a b = Wire GameTime () (GameMonadT m) a b
- liftGameMonad :: Monad m => GameMonadT m b -> GameWire m a b
- liftGameMonad1 :: Monad m => (a -> GameMonadT m b) -> GameWire m a b
- liftGameMonad2 :: Monad m => (a -> b -> GameMonadT m c) -> GameWire m (a, b) c
- liftGameMonad3 :: Monad m => (a -> b -> c -> GameMonadT m d) -> GameWire m (a, b, c) d
- liftGameMonad4 :: Monad m => (a -> b -> c -> d -> GameMonadT m e) -> GameWire m (a, b, c, d) e
- liftGameMonadOnce :: Monad m => GameMonadT m b -> GameWire m a b
- liftGameMonad1Once :: Monad m => (a -> GameMonadT m b) -> GameWire m a b
- liftGameMonad2Once :: Monad m => (a -> b -> GameMonadT m c) -> GameWire m (a, b) c
- liftGameMonad3Once :: Monad m => (a -> b -> c -> GameMonadT m d) -> GameWire m (a, b, c) d
- liftGameMonad4Once :: Monad m => (a -> b -> c -> d -> GameMonadT m e) -> GameWire m (a, b, c, d) e
- once' :: Monad m => GameWire m a (Event b) -> GameWire m a (Event b)
- mapE :: Monad m => (a -> b) -> GameWire m (Event a) (Event b)
- filterE :: (a -> Bool) -> Wire s e m (Event a) (Event a)
- filterEG :: (Foldable f, Filterable f, FilterConstraint f a, Monad m) => (a -> Bool) -> GameWire m (Event (f a)) (Event (f a))
- filterEGM :: (Foldable f, Filterable f, FilterConstraint f a, Monad m) => (a -> GameMonadT m Bool) -> GameWire m (Event (f a)) (Event (f a))
- filterJustE :: Monad m => GameWire m (Event (Maybe a)) (Event a)
- filterJustLE :: (Monad m, Filterable f, FilterConstraint f (Maybe a), Functor f) => GameWire m (Event (f (Maybe a))) (Event (f a))
- liftGameMonadEvent1 :: Monad m => (a -> GameMonadT m b) -> GameWire m (Event a) (Event b)
- changes :: (Monad m, Eq a) => GameWire m a (Event a)
- stateWire :: MonadFix m => b -> GameWire m (a, b) b -> GameWire m a b
- chainWires :: Monad m => [GameWire m a a] -> GameWire m a a
- dispense :: Monad m => [a] -> GameWire m (Event b) a
- dDispense :: Monad m => [a] -> GameWire m (Event b) a
- deltaTime :: (Fractional b, Monad m) => GameWire m a b
Reexports of used time types
type GameTime = Timed NominalDiffTime () Source
Current value of simulation time.
type GameSession = Session IO GameTime Source
Session that stores time in diff format The only purpose is to store time while stepping simulation.
data NominalDiffTime :: *
This is a length of time, as measured by UTC. Conversion functions will treat it as seconds. It has a precision of 10^-12 s. It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.
Game loop control
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 gsRefonCtrlC
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 ponCtrlC
q = catchJust isUserInterrupt p (const $ q >> ponCtrlC
q) where isUserInterrupt :: AsyncException -> Maybe () isUserInterrupt UserInterrupt = Just () isUserInterrupt _ = Nothing
:: (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 |
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
.
:: (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.
:: (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
.
:: (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.
Core module definition
data GameMonadT m a Source
Basic game monad transformer which wraps core modules.
Here goes all core API that accessable from each
game object. All specific (mods etc) API should
be included in inner m
monad.
m
- Core modules monads stacked up here.
a
- Value caried by the monad.
The monad is used to create new arrows, there a 90% chances
that you will create your own arrows. You could use Control.Wire.Core
module and especially mkGen
, mkGen_
and mkSFN
functions to create
new arrows.
MonadTrans GameMonadT Source | |
Monad m => Monad (GameMonadT m) Source | |
Functor m => Functor (GameMonadT m) Source | |
MonadFix m => MonadFix (GameMonadT m) Source | |
Monad m => Applicative (GameMonadT m) Source | Monad is needed as StateT Applicative instance requires it |
MonadThrow m => MonadThrow (GameMonadT m) Source | |
MonadCatch m => MonadCatch (GameMonadT m) Source | |
MonadMask m => MonadMask (GameMonadT m) Source | |
MonadIO m => MonadIO (GameMonadT m) Source |
class Monad m => GameModule m s | m -> s, s -> m where Source
Describes how to run core modules. Each core module must define an instance of the class.
The class describes how the module is executed each game frame and how to pass its own state to the next state.
The state s
must be unique for each game module.
GameMonadT
has m
parameter that should implement the class.
Typical backbone of new core module:
-- | State of your module data MyModuleState s = MyModuleState { -- | Next state in state chain of modules , myModuleNextState :: !s } deriving (Generic) -- | Needed to step game state instance NFData s => NFData (MyModuleState s) -- | Creation of initial state emptyMyModuleState :: s -> MyModuleState s emptyMyModuleState s = MyModuleState { myModuleNextState = s } -- Your monad transformer that implements module API newtype MyModuleT s m a = MyModuleT { runMyModuleT :: StateT (MyModuleState s) m a } deriving (Functor, Applicative, Monad, MonadState (MyModuleState s), MonadFix, MonadTrans, MonadIO, MonadThrow, MonadCatch, MonadMask) instance GameModule m s => GameModule (MyModuleT s m) (MyModuleState s) where type ModuleState (MyModuleT s m) = MyModuleState s runModule (MyModuleT m) s = do -- First phase: execute all dependent modules actions and transform own state ((a, s'), nextState) <- runModule (runStateT m s) (myModuleNextState s) -- Second phase: here you could execute your IO actions return (a, s' { myModuleNextState = nextState }) newModuleState = emptyMyModuleState $ newModuleState withModule _ = id cleanupModule _ = return () -- | Define your module API class OtherModuleMonad m => MyModuleMonad m where -- | The function would be seen in any arrow myAwesomeFunction :: AnotherModule m => a -> b -> m (a, b) -- | Implementation of API instance {-# OVERLAPPING #-} OtherModuleMonad m => MyModuleMonad (MyModuleT s m) where myAwesomeFunction = ... -- | Passing calls through other modules instance {-# OVERLAPPABLE #-} (MyModuleMonad m, MonadTrans mt) => MyModuleMonad (mt m) where myAwesomeFunction a b = lift $ myAwesomeFunction a b
After the backbone definition you could include your monad to application stack with ModuleStack
and use it within any arrow in your application.
type ModuleState m :: * Source
Defines what state has given module.
The correct implentation of the association: >>> type ModuleState (MyModuleT s m) = MyModuleState s
runModule :: MonadIO m' => m a -> s -> m' (a, s) Source
Executes module action with given state. Produces new state that should be passed to next step
Each core module has responsibility of executing underlying modules with nested call to runModule
.
Typically there are two phases of execution:
- Calculation of own state and running underlying modules
- Execution of IO actions that are queued in module state
Some of modules requires IO
monad at the end of monad stack to call IO
actions in place within
first phase of module execution (example: network module). You should avoid the pattern and prefer
to execute IO
actions at the second phase as bad designed use of first phase could lead to strange
behavior at arrow level.
newModuleState :: MonadIO m' => m' s Source
Creates new state of module.
Typically there are nested calls to newModuleState
for nested modules.
newModuleState = emptyMyModuleState $ newModuleState
withModule :: Proxy m -> IO a -> IO a Source
Wrap action with module initialization and cleanup.
Could be withSocketsDo
or another external library initalization.
cleanupModule :: s -> IO () Source
Cleanup resources of the module, should be called on exit (actually cleanupGameState
do this for your)
GameModule IO IOState Source | Module stack that does IO action. Could be used in type AppStack = ModuleStack [LoggingT, ActorT, NetworkT] IO |
GameModule Identity IdentityState Source | Module stack that does only pure actions in its first phase. Could be used in type AppStack = ModuleStack [LoggingT, ActorT] Identity |
type family ModuleStack ms endm :: * -> * Source
Type level function that constucts complex module stack from given list of modules.
The type family helps to simplify chaining of core modules at user application:
-- | Application monad is monad stack build from given list of modules over base monad (IO) type AppStack = ModuleStack [LoggingT, ActorT, NetworkT] IO newtype AppState = AppState (ModuleState AppStack) deriving (Generic) instance NFData AppState -- | Wrapper around type family to enable automatic deriving -- -- Note: There could be need of manual declaration of module API stub instances, as GHC can fail to derive instance automatically. newtype AppMonad a = AppMonad (AppStack a) deriving (Functor, Applicative, Monad, MonadFix, MonadIO, LoggingMonad, NetworkMonad, ActorMonad, MonadThrow, MonadCatch) -- | Top level wrapper for module stack instance GameModule AppMonad AppState where type ModuleState AppMonad = AppState runModule (AppMonad m) (AppState s) = do (a, s') <- runModule m s return (a, AppState s') newModuleState = AppState $ newModuleState withModule _ = withModule (Proxy :: Proxy AppStack) cleanupModule (AppState s) = cleanupModule s -- | Arrow that is build over the monad stack type AppWire a b = GameWire AppMonad a b -- | Action that makes indexed app wire type AppActor i a b = GameActor AppMonad i a b
There are two endpoint monads that are currently built in the core:
ModuleStack `[]` curm = curm | |
ModuleStack (m : ms) curm = ModuleStack ms (m (ModuleState curm) curm) |
Arrow combinators and helpers
type GameWire m a b = Wire GameTime () (GameMonadT m) a b Source
Game wire with given API m
and input value a
and output value b
.
Typically end point application defines a type synonyms:
-- | Arrow that is build over the monad stack type AppWire a b = GameWire AppMonad a b
Lifting monad to arrow
liftGameMonad :: Monad m => GameMonadT m b -> GameWire m a b Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calclulated each frame.
liftGameMonad1 :: Monad m => (a -> GameMonadT m b) -> GameWire m a b Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calclulated each frame.
liftGameMonad2 :: Monad m => (a -> b -> GameMonadT m c) -> GameWire m (a, b) c Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calclulated each frame.
liftGameMonad3 :: Monad m => (a -> b -> c -> GameMonadT m d) -> GameWire m (a, b, c) d Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calclulated each frame.
liftGameMonad4 :: Monad m => (a -> b -> c -> d -> GameMonadT m e) -> GameWire m (a, b, c, d) e Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calclulated each frame.
liftGameMonadOnce :: Monad m => GameMonadT m b -> GameWire m a b Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calculated ONCE and next execution returns cached value
liftGameMonad1Once :: Monad m => (a -> GameMonadT m b) -> GameWire m a b Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calculated ONCE and next execution returns cached value
liftGameMonad2Once :: Monad m => (a -> b -> GameMonadT m c) -> GameWire m (a, b) c Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calculated ONCE and next execution returns cached value
liftGameMonad3Once :: Monad m => (a -> b -> c -> GameMonadT m d) -> GameWire m (a, b, c) d Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calculated ONCE and next execution returns cached value
liftGameMonad4Once :: Monad m => (a -> b -> c -> d -> GameMonadT m e) -> GameWire m (a, b, c, d) e Source
Takes game monad and wraps it into game wire.
Note: Result of wire is calculated ONCE and next execution returns cached value
Event functions
once' :: Monad m => GameWire m a (Event b) -> GameWire m a (Event b) Source
Pass through first occurence and then forget about event producer.
Note: netwire once combinator still holds it event producer when event is produced.
mapE :: Monad m => (a -> b) -> GameWire m (Event a) (Event b) Source
Mapping events as a wire.
It is semantically equal to:
>>>
arr (fmap f)
filterE :: (a -> Bool) -> Wire s e m (Event a) (Event a) Source
Forget all occurrences for which the given predicate is false.
- Depends: now.
:: (Foldable f, Filterable f, FilterConstraint f a, Monad m) | |
=> (a -> Bool) | Predicate to test elements that are left in collection |
-> GameWire m (Event (f a)) (Event (f a)) | Wire that leaves only non empty collections |
Same as filterE
but for generic Foldable
and Filterable
.
:: (Foldable f, Filterable f, FilterConstraint f a, Monad m) | |
=> (a -> GameMonadT m Bool) | Predicate to test elements that are left in collection |
-> GameWire m (Event (f a)) (Event (f a)) | Wire that leaves only non empty collections |
Same as filterEG
but with monadic action.
filterJustE :: Monad m => GameWire m (Event (Maybe a)) (Event a) Source
Filters only Just events
Shortcut for:
>>>
mapE fromJust . filterE isJust
filterJustLE :: (Monad m, Filterable f, FilterConstraint f (Maybe a), Functor f) => GameWire m (Event (f (Maybe a))) (Event (f a)) Source
Filters only Just events in foldable struct
liftGameMonadEvent1 :: Monad m => (a -> GameMonadT m b) -> GameWire m (Event a) (Event b) Source
Lifting game monad action to event processing arrow
Synonym for onEventM
from Control.Wire.Core.Unsafe.Event.
Helpers
stateWire :: MonadFix m => b -> GameWire m (a, b) b -> GameWire m a b Source
Loops output of wire to it input, first parameter is start value of state
Common combinator for build game actors.
chainWires :: Monad m => [GameWire m a a] -> GameWire m a a Source
Sequence compose list of wires (right to left order)
dispense :: Monad m => [a] -> GameWire m (Event b) a Source
Infinitely dispense given elements and switches to next item on event.
Note: is not defined on empty list.
Note: not delayed version, new item is returned on same frame when input event occurs.
dDispense :: Monad m => [a] -> GameWire m (Event b) a Source
Infinitely dispense given elements and switches to next item on event.
Note: is not defined on empty list.
Note: delayed version, new item is returned on frame after input event occurs.
Time utilities
deltaTime :: (Fractional b, Monad m) => GameWire m a b Source
Returns delta time scince last frame.