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.Remote.Actor

Description

 

Synopsis

Documentation

class NetworkMessage i => RemoteActor i a | i -> a, a -> i Source #

API to support automatic synchronization of actors between client and server

Associated Types

type RemoteActorState i :: * Source #

State of remote actor (should be equal a)

type RemoteActorId a :: * Source #

Id of remote actor (should be equal i)

newtype RemActorId i Source #

Id of synchronization actor build over another actor

Constructors

RemActorId 

Fields

Instances

Eq i => Eq (RemActorId i) Source # 

Methods

(==) :: RemActorId i -> RemActorId i -> Bool #

(/=) :: RemActorId i -> RemActorId i -> Bool #

Ord i => Ord (RemActorId i) Source # 
Show i => Show (RemActorId i) Source # 
Generic (RemActorId i) Source # 

Associated Types

type Rep (RemActorId i) :: * -> * #

Methods

from :: RemActorId i -> Rep (RemActorId i) x #

to :: Rep (RemActorId i) x -> RemActorId i #

RemoteActor i a => ActorMessage (RemActorId i) Source # 

Associated Types

type ActorMessageType (RemActorId i) :: *

RemoteActor i a => NetworkMessage (RemActorId i) Source # 

Associated Types

type NetworkMessageType (RemActorId i) :: * Source #

type Rep (RemActorId i) Source # 
type Rep (RemActorId i) = D1 (MetaData "RemActorId" "Game.GoreAndAsh.Sync.Remote.Actor" "gore-and-ash-sync-1.2.0.1-C0M5s2yQvsxJQyH5pbk8Jg" True) (C1 (MetaCons "RemActorId" PrefixI True) (S1 (MetaSel (Just Symbol "unRemActorId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 i)))
type ActorMessageType (RemActorId i) Source # 
type ActorMessageType (RemActorId i)
type NetworkMessageType (RemActorId i) Source # 

data RemActorNetMessage i Source #

Network protocol of synchronization actor

Constructors

RemActorSyncRequest

Request full synchronization

RemActorSyncValue !Word64 !ByteString

Carries value of indexed value

Instances

Show (RemActorNetMessage i) Source # 
Generic (RemActorNetMessage i) Source # 

Associated Types

type Rep (RemActorNetMessage i) :: * -> * #

Serialize (RemActorNetMessage i) Source # 

Methods

put :: Putter (RemActorNetMessage i)

get :: Get (RemActorNetMessage i)

type Rep (RemActorNetMessage i) Source # 
type Rep (RemActorNetMessage i) = D1 (MetaData "RemActorNetMessage" "Game.GoreAndAsh.Sync.Remote.Actor" "gore-and-ash-sync-1.2.0.1-C0M5s2yQvsxJQyH5pbk8Jg" False) ((:+:) (C1 (MetaCons "RemActorSyncRequest" PrefixI False) U1) (C1 (MetaCons "RemActorSyncValue" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word64)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)))))

clientSync Source #

Arguments

:: (ActorMonad m, SyncMonad m, NetworkMonad m, LoggingMonad m, RemoteActor i a) 
=> Sync m i s a

Sync strategy

-> Peer

Server connection

-> i

Actor id

-> GameWire m s a

Synchronizing of client state

Perform client side synchronization

serverSync Source #

Arguments

:: (MonadFix m, ActorMonad m, SyncMonad m, NetworkMonad m, LoggingMonad m, RemoteActor i a) 
=> Sync m i s a

Sync strategy

-> i

Actor id

-> GameWire m s a

Synchronizing of server state

Perform server side synchronization

registerRemoteActor Source #

Arguments

:: (ActorMonad m, ActorMessage i, RemoteActor i a) 
=> proxy i

Proxy of type of base actor id

-> GameMonadT m ()

Register basic id

Need to be called once for each remote actor (remote collections actually do this)