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 module defines GameMonadT
monad transformer as base monad for all arrows of ther engine.
Also there is GameModule
class that must be implemented by all core modules. Finally ModuleStack
type family is for user usage to compose all modules in single monad stack.
- data GameMonadT m a
- data GameContext = GameContext {
- newGameContext :: GameContext
- evalGameMonad :: GameMonadT m a -> GameContext -> m (a, GameContext)
- 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 ()
- data IOState
- data IdentityState
- type family ModuleStack ms endm :: * -> *
Documentation
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 |
data GameContext Source
State of core.
At the moment it is empty, but left for future extensions. For example, some introspection API of enabled modules would be added.
newGameContext :: GameContext Source
Create empty context
evalGameMonad :: GameMonadT m a -> GameContext -> m (a, GameContext) Source
Runs game monad with given context
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 |
Endpoint of state chain for IO monad.
Could be used in ModuleStack
as end monad:
type AppStack = ModuleStack [LoggingT, ActorT, NetworkT] IO
data IdentityState Source
Endpoint of state chain for Identity monad
Could be used in ModuleStack
as end monad:
type AppStack = ModuleStack [LoggingT, ActorT] Identity
Generic IdentityState Source | |
NFData IdentityState Source | |
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 Rep IdentityState Source |
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) |