gore-and-ash-sync-1.2.0.1: Gore&Ash module for high level network synchronization

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

Game.GoreAndAsh.Sync.State

Description

 

Synopsis

Documentation

data SyncState s Source #

Inner state of sync module

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

Constructors

SyncState 

Fields

Instances

Generic (SyncState s) Source # 

Associated Types

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

Methods

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

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

NFData s => NFData (SyncState s) Source # 

Methods

rnf :: SyncState s -> () #

Monad m => MonadState (SyncState s) (SyncT s m) 

Methods

get :: SyncT s m (SyncState s)

put :: SyncState s -> SyncT s m ()

state :: (SyncState s -> (a, SyncState s)) -> SyncT s m a

type Rep (SyncState s) Source # 
type Rep (SyncState s) = D1 (MetaData "SyncState" "Game.GoreAndAsh.Sync.State" "gore-and-ash-sync-1.2.0.1-C0M5s2yQvsxJQyH5pbk8Jg" False) (C1 (MetaCons "SyncState" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "syncNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s)) ((:*:) (S1 (MetaSel (Just Symbol "syncIdMap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap HashableTypeRep Word64))) (S1 (MetaSel (Just Symbol "syncIdMapRev") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Word64 HashableTypeRep))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "syncNextId") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "syncScheduledMessages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Peer (Seq (String, ChannelID, Word64 -> Message)))))) ((:*:) (S1 (MetaSel (Just Symbol "syncLogging") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "syncRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SyncRole))))))

data SyncRole Source #

Defines behavior in synchronization for actor ids

Constructors

SyncMaster

Registers types of actors

SyncSlave

Always ask for ids from other nodes

Instances

Enum SyncRole Source # 
Eq SyncRole Source # 
Show SyncRole Source # 
Generic SyncRole Source # 

Associated Types

type Rep SyncRole :: * -> * #

Methods

from :: SyncRole -> Rep SyncRole x #

to :: Rep SyncRole x -> SyncRole #

NFData SyncRole Source # 

Methods

rnf :: SyncRole -> () #

type Rep SyncRole Source # 
type Rep SyncRole = D1 (MetaData "SyncRole" "Game.GoreAndAsh.Sync.State" "gore-and-ash-sync-1.2.0.1-C0M5s2yQvsxJQyH5pbk8Jg" False) ((:+:) (C1 (MetaCons "SyncMaster" PrefixI False) U1) (C1 (MetaCons "SyncSlave" PrefixI False) U1))

class ActorMessage i => NetworkMessage i Source #

Extension for actor message, messages that are sent to remote host

Associated Types

type NetworkMessageType i :: * Source #

Corresponding message payload for i identifier, usually ADT

data SyncServiceMsg Source #

Internal service message for synchronizing ids of actors

Constructors

SyncServiceRequestId !String

Request id of actor with specified name

SyncServiceResponseId !String !Word64

Response with actor id and name

SyncServiceResponseNotRegistered !String

Response that given actor is not found

Instances

Generic SyncServiceMsg Source # 

Associated Types

type Rep SyncServiceMsg :: * -> * #

Serialize SyncServiceMsg Source # 

Methods

put :: Putter SyncServiceMsg

get :: Get SyncServiceMsg

type Rep SyncServiceMsg Source # 
type Rep SyncServiceMsg = D1 (MetaData "SyncServiceMsg" "Game.GoreAndAsh.Sync.State" "gore-and-ash-sync-1.2.0.1-C0M5s2yQvsxJQyH5pbk8Jg" False) ((:+:) (C1 (MetaCons "SyncServiceRequestId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String))) ((:+:) (C1 (MetaCons "SyncServiceResponseId" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word64)))) (C1 (MetaCons "SyncServiceResponseNotRegistered" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))))

emptySyncState :: s -> SyncState s Source #

Make empty sync state