gore-and-ash-actor-1.2.2.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.State

Contents

Description

Internal state of actor core module.

Synopsis

Documentation

data ActorState s Source #

Inner state of actor module.

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

Constructors

ActorState 

Fields

  • actorBoxes :: !(HashMap (HashableTypeRep, Int) (Seq Dynamic, Seq Dynamic))

    Stores messages for actor with specified id

    Message has type of Dynamic as message manager doesn't know anything about message types. We don't need to serialization protocol due passing via memory. Type safety is forced with Messagable type class with type family (see Actor.Message module). Id space is separate for each actor type

    There are two sequences of messages, one for recieved messages from previous frame, and the second one for messages recieved at current frame. At the end of each frame first sequence is purged and filled with contents of first and the second one is replaced with empty sequence.

  • actorNextId :: !(HashMap HashableTypeRep Int)

    Next empty id of actor, id space is separate for each actor type

  • actorNameMap :: !(HashMap String HashableTypeRep)

    Search table for actor names

  • actorNextState :: !s

    Next state in state chain of modules

Instances

Generic (ActorState s) Source # 

Associated Types

type Rep (ActorState s) :: * -> * #

Methods

from :: ActorState s -> Rep (ActorState s) x #

to :: Rep (ActorState s) x -> ActorState s #

NFData s => NFData (ActorState s) Source # 

Methods

rnf :: ActorState s -> () #

Monad m => MonadState (ActorState s) (ActorT s m) 

Methods

get :: ActorT s m (ActorState s)

put :: ActorState s -> ActorT s m ()

state :: (ActorState s -> (a, ActorState s)) -> ActorT s m a

type Rep (ActorState s) Source # 
type Rep (ActorState s) = D1 (MetaData "ActorState" "Game.GoreAndAsh.Actor.State" "gore-and-ash-actor-1.2.2.0-D8NGmXg07PZChKwPBSaxqg" False) (C1 (MetaCons "ActorState" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "actorBoxes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap (HashableTypeRep, Int) (Seq Dynamic, Seq Dynamic)))) (S1 (MetaSel (Just Symbol "actorNextId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap HashableTypeRep Int)))) ((:*:) (S1 (MetaSel (Just Symbol "actorNameMap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap String HashableTypeRep))) (S1 (MetaSel (Just Symbol "actorNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s)))))

emptyActorState :: s -> ActorState s Source #

Create empty actor state

moveSendedMessages :: ActorState s -> ActorState s Source #

Perform rotation between sended messages and recieved ones

Orphan instances

NFData Dynamic Source # 

Methods

rnf :: Dynamic -> () #