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

Alpaca.NetCode

Contents

Description

This module should be all you need to get started writing multiplayer games. See Alpaca.NetCode.Advanced for more advanced usage.

Synopsis

Documentation

runServer Source #

Arguments

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

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

-> 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 the tick rate.

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

runClient 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".

-> 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 the tick rate.

-> input

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

Note that the client and server do input "prediction" by assuming inputs do not change. It is important to design your input type accordingly. For example, Do NOT store a Bool indicating that a button has been clicked. Instead, store a Bool indicating if that button is currently held down. Then, store enough information in the world state to identify a click.

-> 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). In practice you can choose to use whatever monad stack within as long as you (un)wrap into a pure function e.g. you can use ST as long as you wrap it in runST. Must be the same across all clients and the server. Takes:

  • a map from PlayerId to current input. You can use the key set as the set of all connected players.
  • current game tick.
  • previous tick's world state.

It is important that this is deterministic else clients' states will diverge. Beware of floating point non-determinism!

-> IO (Client world input) 

Start a client. This blocks until the initial handshake with the server is finished. You must call clientSetInput on the returned client to submit new inputs.

Think of world as shared state between all clients. Alpaca NetCode takes care of synchronizing and predicting the world state across all clients. Additionally, clock synchronization is done with the server and the "current" tick is decided for you when sampling with clientSample.

Typical usage looks like this:

   main :: IO ()
   main = do
     myClient <- runClient "localhost" "8111" 30 myInput0 myWorld0 worldStep
     let myPlayerId = clientPlayerId myClient

     mainGameLoop $ do
       myInput <- pollInput          -- Poll inputs from some other library
       clientSetInput myClient       -- Push inputs to Alpaca NetCode
       world <- clientSample         -- Sample the current (predicted) world
       renderWorld myPlayerId world  -- Render the world

       -- You're free to do IO and maintain state local to the client.

       return (gameIsOver world)     -- Return True to keep looping

   clientStop myClient

   -- Given
   data World = World { .. }
   data Input = Input { .. } deriving (Generic, Eq, Flat)
   myWorld0 :: World
   gameIsOver :: World -> Bool
   myInput0 :: Input
   worldStep :: Map PlayerId Input -> Tick -> World -> World
   renderWorld :: PlayerId -> World -> IO ()
   pollInput :: IO Input
   mainGameLoop :: IO Bool -> IO ()

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.

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

Set the client's current input.

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

Stop the client.

Types

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

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.