gore-and-ash-network-1.2.2.0: Core module for Gore&Ash engine with low level network API

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

Game.GoreAndAsh.Network

Contents

Description

The core module contains API for basic networking for Gore&Ash. The network module is built over Enet library, UDP transport with custom implementation of reliability. The API provides connection handling and basic message handling (bytestring sending and receiving).

The module depends on following core modules:

So NetworkT should be placed after LoggingT in monad stack.

The module is NOT pure within first phase (see ModuleStack docs), 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 [LoggingT, NetworkT, ... 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, MonadThrow, MonadCatch, LoggingMonad, NetworkMonad, ... 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

Synopsis

Low-level API

data NetworkState s Source

Inner state of network layer

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

Instances

type Host = Ptr Host Source

Local endpoint

type Peer = Ptr Peer Source

Remote endpoint

newtype ChannelID Source

Wrapper for channel index

Constructors

ChannelID Word8 

data NetworkT s m a Source

Monad transformer of network 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 [LoggingT, NetworkT, ... other modules ... ] IO

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

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Instances

MonadTrans (NetworkT s) Source 
Monad m => MonadState (NetworkState s) (NetworkT s m) Source 
Monad m => Monad (NetworkT s m) Source 
Functor m => Functor (NetworkT s m) Source 
MonadFix m => MonadFix (NetworkT s m) Source 
Monad m => Applicative (NetworkT s m) Source 
MonadIO m => MonadIO (NetworkT s m) Source 
MonadThrow m => MonadThrow (NetworkT s m) Source 
MonadMask m => MonadMask (NetworkT s m) Source 
MonadCatch m => MonadCatch (NetworkT s m) Source 
(MonadIO m, MonadCatch m) => NetworkMonad (NetworkT s m) Source 
type ModuleState (NetworkT s m) = NetworkState s Source 

class (MonadIO m, MonadCatch m) => NetworkMonad m where Source

Low-level monadic API of the core module

Methods

networkBind Source

Arguments

:: LoggingMonad m 
=> Maybe SockAddr

Address to listen, Nothing is client

-> Word

Maximum count of connections

-> Word

Number of channels to open

-> Word32

Incoming max bandwidth

-> Word32

Outcoming max bandwidth

-> m () 

Start listening for messages, should be called once

peersConnectedM :: m (Seq Peer) Source

Returns peers that were connected during last frame

peersDisconnectedM :: m (Seq Peer) Source

Returns peers that were disconnected during last frame

networkConnect Source

Arguments

:: LoggingMonad m 
=> SockAddr

Address of host

-> Word

Count of channels to open

-> Word32

Additional data (0 default)

-> m (Maybe ()) 

Initiate connection to the remote host

peerMessagesM :: Peer -> ChannelID -> m (Seq ByteString) Source

Returns received packets for given peer and channel

peerSendM :: LoggingMonad m => Peer -> ChannelID -> Message -> m () Source

Sends a packet to given peer on given channel

networkPeersM :: m (Seq Peer) Source

Returns list of currently connected peers (servers on client side, clients on server side)

networkSetDetailedLoggingM :: Bool -> m () Source

Sets flag for detailed logging (for debug)

networkChannels :: m Word Source

Return count of allocated network channels

Instances

(MonadIO (mt m), MonadCatch (mt m), LoggingMonad m, NetworkMonad m, MonadTrans mt) => NetworkMonad (mt m) Source 
(MonadIO m, MonadCatch m) => NetworkMonad (NetworkT s m) Source 

data Message Source

Message that has individual options about reliability

data MessageType Source

Strategy how given message is delivered to remote host

Constructors

ReliableMessage

TCP like, ordered reliable delivery

UnreliableMessage

Unrelieable, sequenced but fragments are sent with reliability

UnsequencedMessage

Unreliable and unsequenced (not sort while receiving)

UnreliableFragmentedMessage

Unreliable, sequenced sent with fragments sent within unreliable method

UnsequencedFragmentedMessage

Unreliable, unsequenced with fragments sent within unreliable method

Arrow API

Peer handling

peersConnected :: (LoggingMonad m, NetworkMonad m) => GameWire m a (Event (Seq Peer)) Source

Fires when one or several clients were connected

peersDisconnected :: (LoggingMonad m, NetworkMonad m) => GameWire m a (Event (Seq Peer)) Source

Fires when one of connected peers is disconnected for some reason

peerDisconnected :: (LoggingMonad m, NetworkMonad m) => Peer -> GameWire m a (Event ()) Source

Fires when statically known peer is disconnected

currentPeers :: (LoggingMonad m, NetworkMonad m) => GameWire m a (Seq Peer) Source

Returns list of current peers (clients on server, servers on client)

onPeers Source

Arguments

:: (MonadFix m, LoggingMonad m, NetworkMonad m) 
=> (Seq Peer -> GameWire m a b)

Wire that uses current peer collection

-> GameWire m a b 

Sometimes you want to listen all peers and use statefull computations at the same time.

The helper maintance internal collection of current peers and switches over it each time it changes.

Messaging support

peerMessages :: (LoggingMonad m, NetworkMonad m) => Peer -> ChannelID -> GameWire m a (Event (Seq ByteString)) Source

Returns sequence of packets that were recieved during last frame from given peer and channel id

peerSend :: (LoggingMonad m, NetworkMonad m) => Peer -> ChannelID -> GameWire m (Event Message) (Event ()) Source

Send message to given peer with given channel id

peerSendMany :: (LoggingMonad m, NetworkMonad m, Foldable t) => Peer -> ChannelID -> GameWire m (Event (t Message)) (Event ()) Source

Send several messages to given peer with given channel id