gore-and-ash-network-1.4.0.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

Generic (NetworkState s) Source # 

Associated Types

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

Methods

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

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

NFData s => NFData (NetworkState s) Source # 

Methods

rnf :: NetworkState s -> () #

Monad m => MonadState (NetworkState s) (NetworkT s m) 

Methods

get :: NetworkT s m (NetworkState s)

put :: NetworkState s -> NetworkT s m ()

state :: (NetworkState s -> (a, NetworkState s)) -> NetworkT s m a

type Rep (NetworkState s) Source # 
type Rep (NetworkState s) = D1 (MetaData "NetworkState" "Game.GoreAndAsh.Network.State" "gore-and-ash-network-1.4.0.0-D5xAn58Rw8JIdW4B4WCLcw" False) (C1 (MetaCons "NetworkState" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "networkHost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Host))) (S1 (MetaSel (Just Symbol "networkPeers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq Peer)))) ((:*:) (S1 (MetaSel (Just Symbol "networkConnectedPeers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq Peer))) (S1 (MetaSel (Just Symbol "networkDisconnectedPeers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq Peer))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "networkMessages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap (Peer, ChannelID) (Seq ByteString)))) (S1 (MetaSel (Just Symbol "networkDetailedLogging") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "networkMaximumChannels") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word)) (S1 (MetaSel (Just Symbol "networkNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s))))))

type Host = Ptr Host Source #

Local endpoint

type Peer = Ptr Peer Source #

Remote endpoint

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

MonadBase IO m => MonadBase IO (NetworkT s m) Source # 

Methods

liftBase :: IO α -> NetworkT s m α

MonadError e m => MonadError e (NetworkT s m) Source # 

Methods

throwError :: e -> NetworkT s m a

catchError :: NetworkT s m a -> (e -> NetworkT s m a) -> NetworkT s m a

MonadTrans (NetworkT s) Source # 

Methods

lift :: Monad m => m a -> NetworkT s m a #

Monad m => MonadState (NetworkState s) (NetworkT s m) Source # 

Methods

get :: NetworkT s m (NetworkState s)

put :: NetworkState s -> NetworkT s m ()

state :: (NetworkState s -> (a, NetworkState s)) -> NetworkT s m a

Monad m => Monad (NetworkT s m) Source # 

Methods

(>>=) :: NetworkT s m a -> (a -> NetworkT s m b) -> NetworkT s m b #

(>>) :: NetworkT s m a -> NetworkT s m b -> NetworkT s m b #

return :: a -> NetworkT s m a #

fail :: String -> NetworkT s m a #

Functor m => Functor (NetworkT s m) Source # 

Methods

fmap :: (a -> b) -> NetworkT s m a -> NetworkT s m b #

(<$) :: a -> NetworkT s m b -> NetworkT s m a #

MonadFix m => MonadFix (NetworkT s m) Source # 

Methods

mfix :: (a -> NetworkT s m a) -> NetworkT s m a #

Monad m => Applicative (NetworkT s m) Source # 

Methods

pure :: a -> NetworkT s m a #

(<*>) :: NetworkT s m (a -> b) -> NetworkT s m a -> NetworkT s m b #

(*>) :: NetworkT s m a -> NetworkT s m b -> NetworkT s m b #

(<*) :: NetworkT s m a -> NetworkT s m b -> NetworkT s m a #

MonadIO m => MonadIO (NetworkT s m) Source # 

Methods

liftIO :: IO a -> NetworkT s m a #

MonadThrow m => MonadThrow (NetworkT s m) Source # 

Methods

throwM :: Exception e => e -> NetworkT s m a

MonadMask m => MonadMask (NetworkT s m) Source # 

Methods

mask :: ((forall a. NetworkT s m a -> NetworkT s m a) -> NetworkT s m b) -> NetworkT s m b

uninterruptibleMask :: ((forall a. NetworkT s m a -> NetworkT s m a) -> NetworkT s m b) -> NetworkT s m b

MonadCatch m => MonadCatch (NetworkT s m) Source # 

Methods

catch :: Exception e => NetworkT s m a -> (e -> NetworkT s m a) -> NetworkT s m a

MonadResource m => MonadResource (NetworkT s m) Source # 

Methods

liftResourceT :: ResourceT IO a -> NetworkT s m a

(MonadIO m, MonadCatch m) => NetworkMonad (NetworkT s m) Source # 
type ModuleState (NetworkT s m) Source # 
type ModuleState (NetworkT s m) = NetworkState s

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

Low-level monadic API of the core module

Methods

networkBind :: LoggingMonad m => Maybe SockAddr -> Word -> Word -> Word32 -> Word32 -> m () Source #

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 :: LoggingMonad m => SockAddr -> Word -> Word32 -> m (Maybe ()) Source #

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

data Message Source #

Message that has individual options about reliability

Instances

Show Message Source # 
Generic Message Source # 

Associated Types

type Rep Message :: * -> * #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

NFData Message Source # 

Methods

rnf :: Message -> () #

type Rep Message Source # 
type Rep Message = D1 (MetaData "Message" "Game.GoreAndAsh.Network.Message" "gore-and-ash-network-1.4.0.0-D5xAn58Rw8JIdW4B4WCLcw" False) (C1 (MetaCons "Message" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "messageType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MessageType)) (S1 (MetaSel (Just Symbol "messagePayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))))

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

Instances

Bounded MessageType Source # 
Enum MessageType Source # 
Eq MessageType Source # 
Ord MessageType Source # 
Show MessageType Source # 
Generic MessageType Source # 

Associated Types

type Rep MessageType :: * -> * #

NFData MessageType Source # 

Methods

rnf :: MessageType -> () #

type Rep MessageType Source # 
type Rep MessageType = D1 (MetaData "MessageType" "Game.GoreAndAsh.Network.Message" "gore-and-ash-network-1.4.0.0-D5xAn58Rw8JIdW4B4WCLcw" False) ((:+:) ((:+:) (C1 (MetaCons "ReliableMessage" PrefixI False) U1) (C1 (MetaCons "UnreliableMessage" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UnsequencedMessage" PrefixI False) U1) ((:+:) (C1 (MetaCons "UnreliableFragmentedMessage" PrefixI False) U1) (C1 (MetaCons "UnsequencedFragmentedMessage" PrefixI False) U1))))

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