alpaca-netcode-0.1.0.0: Rollback/replay NetCode for realtime, deterministic, multiplayer games.
Safe HaskellNone
LanguageHaskell2010

Alpaca.NetCode.Advanced

Description

Rollback and replay based game networking

Synopsis

Server

runServerWith Source #

Arguments

:: forall input. (Eq input, Flat input) 
=> ServiceName

The server's port number e.g. "8111".

-> Maybe SimNetConditions

Optional simulation of network conditions. In production this should be Nothing.

-> ServerConfig

The defaultServerConfig works well for most cases.

-> input

Initial input for new players. Must be the same across all clients and the server.

-> IO () 

Run a server for a single game. This will block until the game ends, specifically when all players have disconnected.

runServerWith' Source #

Arguments

:: forall input clientAddress. (Eq input, Flat input, Show clientAddress, Ord clientAddress) 
=> (NetMsg input -> clientAddress -> IO ())

Function to send messages to clients. The underlying communication protocol need only guarantee data integrity but is otherwise free to drop and reorder packets. Typically this is backed by a UDP socket.

-> IO (NetMsg input, clientAddress)

Blocking function to receive messages from the clients. Has the same reliability requirements as the send function.

-> Maybe SimNetConditions

Optional simulation of network conditions. In production this should be Nothing. May differ between clients.

-> ServerConfig

The defaultServerConfig works well for most cases.

-> input

Initial input for new players. Must be the same across all clients and the server. See runClient.

-> IO () 

Run a server for a single game. This will block until the game ends, specifically when all players have disconnected.

data ServerConfig Source #

Configuration options specific to the server.

Constructors

ServerConfig 

Fields

  • scTickRate :: Int

    Tick rate (ticks per second). Typically 30 or 60. Must be the same across all clients and the server. Packet rate and hence network bandwidth will scale linearly with this the tick rate.

  • scClientTimeout :: Float

    Seconds of not receiving packets from a client before disconnecting that client.

defaultServerConfig Source #

Arguments

:: Int

Tick rate (ticks per second). Typically 30 or 60. Must be the same across all clients and the server. Packet rate and hence network bandwidth will scale linearly with this the tick rate.

-> ServerConfig 

Sensible defaults for ServerConfig based on the tick rate.

Client

runClientWith Source #

Arguments

:: forall world input. Flat input 
=> HostName

The server's host name or IP address e.g. "localhost".

-> ServiceName

The server's port number e.g. "8111".

-> Maybe SimNetConditions

Optional simulation of network conditions. In production this should be Nothing. May differ between clients.

-> ClientConfig

The defaultClientConfig works well for most cases.

-> input

Initial input for new players. Must be the same across all clients and the server. See runClient.

-> world

Initial world state. Must be the same across all clients.

-> (Map PlayerId input -> Tick -> world -> world)

A deterministic stepping function (for a single tick). Must be the same across all clients and the server. See runClient.

-> IO (Client world input) 

Start a client. This blocks until the initial handshake with the server is finished.

runClientWith' Source #

Arguments

:: forall world input. Flat input 
=> (NetMsg input -> IO ())

Function to send messages to the server. The underlying communication protocol need only guarantee data integrity but is otherwise free to drop and reorder packets. Typically this is backed by a UDP socket.

-> IO (NetMsg input)

Blocking function to receive messages from the server. Has the same reliability requirements as the send function.

-> Maybe SimNetConditions

Optional simulation of network conditions. In production this should be Nothing. May differ between clients.

-> ClientConfig

The defaultClientConfig works well for most cases.

-> input

Initial input for new players. Must be the same across all clients and the server. See runClient.

-> world

Initial world state. Must be the same across all clients.

-> (Map PlayerId input -> Tick -> world -> world)

A deterministic stepping function (for a single tick). Must be the same across all clients and the server. See runClient.

-> IO (Client world input) 

Start a client. This blocks until the initial handshake with the server is finished.

data ClientConfig Source #

Configuration options specific to clients.

Constructors

ClientConfig 

Fields

  • ccTickRate :: Int

    Tick rate (ticks per second). Typically 30 or 60. Must be the same across all clients and the server. Packet rate and hence network bandwidth will scale linearly with this the tick rate.

  • ccFixedInputLatency :: Float

    Add this constant amount of latency (in seconds) to this client's inputs. A good value is 0.03 or something between 0 and 0.1. May differ between clients.

    Too high of a value and the player will get annoyed at the extra input latency. On the other hand, a higher value means less miss-predictions of other clients. In the extreme case, set to something higher than ping, there will be no miss predictions: all clients will receive inputs before rendering the corresponding tick.

  • ccMaxPredictionTicks :: Int

    Maximum number of ticks to predict when sampling. defaultClientConfig uses ccTickRate / 2. If the client is this many ticks behind the current tick, it will simply stop at an earlier tick. You may want to scale this value along with the tick rate. May differ between clients.

  • ccResyncThresholdTicks :: Int

    If the client's latest known authoritative world is this many ticks behind the current tick, no prediction will be done at all when sampling. defaultClientConfig uses ccTickRate * 3. Useful because want to save CPU cycles for catching up with the server. You may want to scale this value along with the tick rate. May differ between clients.

  • ccSubmitInputDuplication :: Int

    When submitting inputs to the server, we also send a copy of ccSubmitInputDuplication many recently submitted inputs in order to mittigate the effect for dropped packets. defaultClientConfig uses 15.

defaultClientConfig Source #

Arguments

:: Int

Tick rate (ticks per second). Must be the same across all clients and the server. Packet rate and hence network bandwidth will scale linearly with this the tick rate.

-> ClientConfig 

Sensible defaults for ClientConfig based on the tick rate.

data Client world input Source #

A Client. You'll generally obtain this via runClient.

clientPlayerId :: Client world input -> PlayerId Source #

The client's PlayerId

clientSample :: Client world input -> IO world Source #

Sample the current world state.

. First, This will estimate the current tick based on ping and clock synchronization with the server. Then, this extrapolates past the latest know authoritative world state by assuming no user inputs have changed (unless otherwise known e.g. our own player's inputs are known). If the client has been stopped, this will return the last predicted world.

clientSample' :: Client world input -> IO ([world], world) Source #

Sample the world state. First, This will estimate the current tick based on ping and clock synchronization with the server. Then, the world state will be rollback and inputs replayed as necessary. This returns:

  • New authoritative world states in chronological order since the last sample time. These world states are the True world states at each tick. This list will be empty if no new authoritative world states have been derived since that last call to this sample function. Though it's often simpler to just use the predicted world state, you can use these authoritative world states to render output when you're not willing to miss-predict but are willing to have greater latency. If the client has been stopped, this will be an empty list.
  • The predicted current world state. This extrapolates past the latest know authoritative world state by assuming no user inputs have changed (unless otherwise known e.g. our own player's inputs are known). If the client has been stopped, this will return the last predicted world.

clientSetInput :: Client world input -> input -> IO () Source #

Set the client's current input.

clientStop :: Client world input -> IO () Source #

Stop the client.

Common Types

data SimNetConditions Source #

Settings for simulating network conditions. Packets in both the send and receive directions are randomly dropped or delayed by `simPing/2` plus some random duration between `-simJitter` and simJitter.

Constructors

SimNetConditions 

Fields

newtype Tick Source #

The game is broken into discrete ticks starting from 0.

Constructors

Tick Int64 

Instances

Instances details
Enum Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

succ :: Tick -> Tick #

pred :: Tick -> Tick #

toEnum :: Int -> Tick #

fromEnum :: Tick -> Int #

enumFrom :: Tick -> [Tick] #

enumFromThen :: Tick -> Tick -> [Tick] #

enumFromTo :: Tick -> Tick -> [Tick] #

enumFromThenTo :: Tick -> Tick -> Tick -> [Tick] #

Eq Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

(==) :: Tick -> Tick -> Bool #

(/=) :: Tick -> Tick -> Bool #

Integral Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

quot :: Tick -> Tick -> Tick #

rem :: Tick -> Tick -> Tick #

div :: Tick -> Tick -> Tick #

mod :: Tick -> Tick -> Tick #

quotRem :: Tick -> Tick -> (Tick, Tick) #

divMod :: Tick -> Tick -> (Tick, Tick) #

toInteger :: Tick -> Integer #

Num Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

(+) :: Tick -> Tick -> Tick #

(-) :: Tick -> Tick -> Tick #

(*) :: Tick -> Tick -> Tick #

negate :: Tick -> Tick #

abs :: Tick -> Tick #

signum :: Tick -> Tick #

fromInteger :: Integer -> Tick #

Ord Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

compare :: Tick -> Tick -> Ordering #

(<) :: Tick -> Tick -> Bool #

(<=) :: Tick -> Tick -> Bool #

(>) :: Tick -> Tick -> Bool #

(>=) :: Tick -> Tick -> Bool #

max :: Tick -> Tick -> Tick #

min :: Tick -> Tick -> Tick #

Real Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

toRational :: Tick -> Rational #

Show Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Flat Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Hashable Tick Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

hashWithSalt :: Int -> Tick -> Int #

hash :: Tick -> Int #

newtype PlayerId Source #

Constructors

PlayerId 

Fields

data NetMsg input Source #

Instances

Instances details
Show input => Show (NetMsg input) Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

showsPrec :: Int -> NetMsg input -> ShowS #

show :: NetMsg input -> String #

showList :: [NetMsg input] -> ShowS #

Generic (NetMsg input) Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Associated Types

type Rep (NetMsg input) :: Type -> Type #

Methods

from :: NetMsg input -> Rep (NetMsg input) x #

to :: Rep (NetMsg input) x -> NetMsg input #

Flat input => Flat (NetMsg input) Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

Methods

encode :: NetMsg input -> Encoding #

decode :: Get (NetMsg input) #

size :: NetMsg input -> NumBits -> NumBits #

type Rep (NetMsg input) Source # 
Instance details

Defined in Alpaca.NetCode.Internal.Common

type Rep (NetMsg input)

type HostName = String #

Either a host name e.g., "haskell.org" or a numeric host address string consisting of a dotted decimal IPv4 address or an IPv6 address e.g., "192.168.0.1".

type ServiceName = String #

Either a service name e.g., "http" or a numeric port number.