gore-and-ash-actor-1.1.1.0: Gore&Ash engine extension that implements actor style of programming

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

Game.GoreAndAsh.Actor

Contents

Description

The core module contains API for actor based aproach of game development. The module doesn't depends on others core modules and could be place in any place in game monad stack.

The module is pure within first phase (see ModuleStack docs) but requires MonadThrow instance of end monad, therefore currently only IO end monad can handler the module.

Example of embedding:

-- | Application monad is monad stack build from given list of modules over base monad (IO)
type AppStack = ModuleStack [ActorT, ... other modules ... ] IO
newtype AppState = AppState (ModuleState AppStack)
  deriving (Generic)

instance NFData AppState 

-- | Wrapper around type family
newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, ActorMonad, ... other modules monads ... )
  
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

Actor (GameActor) is wire with its unique id. For instance you want actor for your player:

data Player = Player {
  playerId :: !PlayerId
, playerPos :: !(Double, Double)
} deriving (Generic)

instance NFData Player 

newtype PlayerId = PlayerId { unPlayerId :: Int } deriving (Eq, Show, Generic) 
instance NFData PlayerId 
instance Hashable PlayerId 
instance Serialize PlayerId

data PlayerMessage =
    -- | The player was shot by specified player
    PlayerShotMessage !PlayerId 
  deriving (Typeable, Generic)

instance NFData PlayerMessage 

instance ActorMessage PlayerId where
  type ActorMessageType PlayerId = PlayerMessage
  toCounter = unPlayerId
  fromCounter = PlayerId

Now you can create statefull actor:

playerActor :: ActorMonad m => (PlayerId -> Player) -> AppActor m PlayerId Game Player 
playerActor initialPlayer = makeActor $ i -> stateWire (initialPlayer i) $ mainController i
  where
  mainController i = proc (g, p) -> do
    emsg <- actorMessages i isPlayerShotMessage -< ()
    -- do with emsg something
    returnA -< p

And you can have dynamic collection of actors:

processPlayers :: ActorMonad m => AppWire m Game [Player]
processPlayer = proc g -> do 
  addEvent <- periodic 4 -< newPlayer
  remEvent <- never -< ()
  dynCollection [] -< (g, addEvent, remEvent)

Synopsis

Low level

data ActorState s Source

Inner state of actor module.

s
- State of next module, the states are chained via nesting.

Instances

Generic (ActorState s) Source 
NFData s => NFData (ActorState s) Source 
Monad m => MonadState (ActorState s) (ActorT s m) 
type Rep (ActorState s) Source 

data ActorT s m a Source

Monad transformer of actor core module.

s
- State of next core module in modules chain;
m
- Next monad in modules monad stack;
a
- Type of result value;

How to embed module:

type AppStack = ModuleStack [ActorT, ... other modules ... ] IO

newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, ActorMonad)

The module is pure within first phase (see ModuleStack docs) but requires MonadThrow instance of end monad, therefore currently only IO end monad can handler the module.

Instances

MonadTrans (ActorT s) Source 
Monad m => MonadState (ActorState s) (ActorT s m) Source 
Monad m => Monad (ActorT s m) Source 
Functor m => Functor (ActorT s m) Source 
MonadFix m => MonadFix (ActorT s m) Source 
Monad m => Applicative (ActorT s m) Source 
MonadIO m => MonadIO (ActorT s m) Source 
MonadThrow m => MonadThrow (ActorT s m) Source 
MonadMask m => MonadMask (ActorT s m) Source 
MonadCatch m => MonadCatch (ActorT s m) Source 
MonadThrow m => ActorMonad (ActorT s m) Source 
type ModuleState (ActorT s m) = ActorState s Source 

class MonadThrow m => ActorMonad m where Source

Low level monadic API for module.

Methods

actorRegisterM :: ActorMessage i => m i Source

Registers new actor in message system

actorRegisterFixedM :: ActorMessage i => i -> m () Source

Registers specific id, throws ActorException if there is id clash

actorDeleteM :: ActorMessage i => i -> m () Source

Deletes actor with given id

actorRegisteredM :: ActorMessage i => i -> m Bool Source

Checks if given id is already taken

actorSendM :: (ActorMessage i, Typeable (ActorMessageType i)) => i -> ActorMessageType i -> m () Source

Sends typed message to actor with given id

actorGetMessagesM :: (ActorMessage i, Typeable (ActorMessageType i)) => i -> m (Seq (ActorMessageType i)) Source

Get all messages that were collected for given actor's id

Note: Doesn't clears the queue

findActorTypeRepM :: String -> m (Maybe HashableTypeRep) Source

Find type representation of actor by it type name

registerActorTypeRepM :: forall proxy i. ActorMessage i => proxy i -> m () Source

Register type representation for actor (sometimes this should be done before any actor is registered)

Instances

(MonadThrow (mt m), ActorMonad m, MonadTrans mt) => ActorMonad (mt m) Source 
MonadThrow m => ActorMonad (ActorT s m) Source 

data ActorException Source

Exceptions thrown by ActorMonad

Constructors

ActorIdConflict TypeRep Int

Tried to register already presented actor

Actor API

data GameWireIndexed m i a b Source

Game wire that has its own id

Constructors

GameWireIndexed 

Fields

indexedId :: i
 
indexedWire :: GameWire m a b
 

Instances

Eq i => Eq (GameWireIndexed m i a b) Source

Equality by equality of ids

type GameActor m i a b = GameMonadT m (GameWireIndexed m i a b) Source

Common pattern in game for creating incapsulated objects

Usually wires that are actors need context to register themselfes in core. Major part of wire functions operates with such wrapped indexed arrows thats why the convinient type synonym is exists.

class Typeable objectId => ActorMessage objectId where Source

The typeclass separates message API's of different type of actors

In general you don't want to have one global type to handle all possible types of messages, it will break modularity. Thats why you creates (with newtype) separate types of ids for each actor and statically binds message type (usually algebraic type) to the id.

The class implies that your id is some integer type, but it could be not. Just provide way to stable convertion of you id to integer and vice-versa.

Associated Types

type ActorMessageType objectId :: * Source

Binded message type, mailbox with id type of objectId would accept only this message type

Methods

fromCounter :: Int -> objectId Source

Convertion from global counter. Don't use it in client code as it could break type safety.

toCounter :: objectId -> Int Source

Convertion to global counter. Don't use it in client code as it could break type safety.

postActorAction :: Monad m => GameActor m i a b -> (i -> GameWire m b c) -> GameActor m i a c Source

Compose actor and wire, the wire is added at the end of actor controller

preActorAction :: Monad m => (i -> GameWire m c a) -> GameActor m i a b -> GameActor m i c b Source

Compose actor and wire, the wire is added at the beginning of actor controller

makeActor Source

Arguments

:: (ActorMonad m, ActorMessage i) 
=> (i -> GameWire m a b)

Body wire

-> GameActor m i a b

Operation that makes actual actor

Registers new index for wire and makes an actor wire

makeFixedActor Source

Arguments

:: (ActorMonad m, ActorMessage i) 
=> i

Manual id of actor

-> GameWire m a b

Body wire

-> GameActor m i a b

Operation that makes actual actor

Registers new actor with fixed id, can fail with ActorException if there is already registered actor for that id

runActor Source

Arguments

:: ActorMonad m 
=> GameActor m i a b

Actor creator

-> GameWire m a (b, i)

Usual wire that also returns id of inner indexed wire

If need no dynamic switching, you can use the function to embed index wire just at time

runActor' Source

Arguments

:: ActorMonad m 
=> GameActor m i a b

Actor creator

-> GameWire m a b

Usual wire

Same as runActor, but doesn't return id of actor

Helpers for libraries

getActorFingerprint :: forall i. ActorMessage i => i -> HashableTypeRep Source

Helper to get actor fingerprint from id value

actorFingerprint :: forall proxy a. ActorMessage a => proxy a -> HashableTypeRep Source

Returns hashable fingerprint of actor that is stable across applications (unique by type name)

Message API

actorSend :: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i)) => i -> GameWire m (Event (ActorMessageType i)) (Event ()) Source

Sends message to statically known actor

actorSendMany :: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i), Foldable t) => i -> GameWire m (Event (t (ActorMessageType i))) (Event ()) Source

Sends many messages to statically known actor

actorSendDyn :: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i)) => GameWire m (Event (i, ActorMessageType i)) (Event ()) Source

Sends message to actor with incoming id

actorSendManyDyn :: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i), Foldable t) => GameWire m (Event (t (i, ActorMessageType i))) (Event ()) Source

Sends many messages, dynamic version of actorSendMany which takes actor id as arrow input

actorProcessMessages Source

Arguments

:: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i)) 
=> i

Actor id known statically

-> (a -> ActorMessageType i -> a)

Action that modifies accumulator

-> GameWire m a a

Wire that updates input value using supplied function

Helper to process all messages from message queue and update a state

actorProcessMessagesM Source

Arguments

:: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i)) 
=> i

Actor id known statically

-> (a -> ActorMessageType i -> GameMonadT m a)

Monadic action that modifies accumulator

-> GameWire m a a

Wire that updates input value using supplied function

Helper to process all messages from message queue and update a state (monadic version)

actorMessages Source

Arguments

:: (ActorMonad m, ActorMessage i, Typeable (ActorMessageType i)) 
=> i

Actor id which messages we look for

-> (ActorMessageType i -> Bool)

Filter function, leaves only with True return value

-> GameWire m a (Event (Seq (ActorMessageType i))) 

Non-centric style of subscribing to messages

Dynamic collections

class (Filterable c, Foldable c, Functor c, Traversable c) => DynCollection c where Source

Dynamic collection for control wire that automates handling collections of FRP actors. The class defines minimum set of actions that collection should support to be used as base for collection of actors.

Associated Types

type DynConsConstr c o :: Constraint Source

Instance specific constraint for appending function

Methods

concatDynColl :: c a -> c a -> c a Source

Concat of two collections

unzipDynColl :: c (a, b) -> (c a, c b) Source

Unzipping of collection

zipDynColl :: c a -> c b -> c (a, b) Source

Ziping collection

emptyDynColl :: c a Source

Getting empty collection

consDynColl :: DynConsConstr c a => a -> c a -> c a Source

Adding element to the begining of collection

Instances

DynCollection [] Source 
DynCollection Seq Source 
(Eq k, Hashable k) => DynCollection (HashMap k) Source

Order of elements is not preserved

class (Hashable i, Eq i) => ElementWithId a i where Source

Elements that contains id

Methods

elementId :: a -> i Source

dynCollection Source

Arguments

:: (ActorMonad m, Eq i, DynCollection c, FilterConstraint c (GameWireIndexed m i a b), FilterConstraint c (Either () b), Foldable c2) 
=> c (GameActor m i a b)

Inital set of wires

-> GameWire m (a, Event (c (GameActor m i a b)), Event (c2 i)) (c b) 

Makes dynamic collection of wires.

  • First input of wire is input for each inner wire.
  • Second input is event for adding several wires to collection.
  • Third input is event for removing several wires from collection.
  • Wire returns list of outputs of inner wires.

Note: if ihibits one of the wires, it is removed from output result during its inhibition

dDynCollection Source

Arguments

:: (ActorMonad m, Eq i, DynCollection c, FilterConstraint c (GameWireIndexed m i a b), FilterConstraint c (Either () b), Foldable c2) 
=> c (GameActor m i a b)

Inital set of wires

-> GameWire m (a, Event (c (GameActor m i a b)), Event (c2 i)) (c b) 

Makes dynamic collection of wires.

  • First input of wire is input for each inner wire.
  • Second input is event for adding several wires to collection.
  • Third input is event for removing several wires from collection.
  • Wire returns list of outputs of inner wires.

Note: it is delayed version of dynCollection, removing and adding of agents performs on next step after current.

Note: if ihibits one of the wires, it is removed from output result while it inhibits.