reliable-io-0.0.2: Bindings to the low-level reliable.io library.
Copyright(c) Pavel Krajcevski 2020
LicenseBSD-3
Maintainerkrajcevski@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Reliable.IO

Description

This module contains the high-level bindings on top of the module Bindings.Netcode.IO. These provide a cleaner interface to the reliable.io C library and are the recommended interface for application developers.

These bindings have some limitations. Namely, they are not as performant as the "close to the metal" bindings provided in Bindings.Reliable.IO. In the event that you need more performance, that module is available for use.

This library is intended to be used with a way to send and receive fixed size packets over an unreliable channel. If such an interface exists, then, assuming that the two parties are in constant communication, this library will do the following for you:

  1. Break a packet down into a sequence of fixed size fragments to match your data channel size.
  2. Determine whether or not a sent packet has been acked by the receiver.
  3. Reassemble a packet once all fragments have been received.

With this in mind, the singular datatype provided by this library is an Endpoint. Each endpoint requires the following:

Once you have an Endpoint, the two main operations that you would do with it are to send a (possibly very large) packet (sendPacket), and provide it with (possibly just one) packet fragments (receivePacket). On top of this library, if a user would like to create a fully-reliable data channel (a la TCP), it is that user's responsibility to identify when a packet has been dropped or has arrived out of order to resend the appropriate packet.

Synopsis

Initialization

initialize :: IO () Source #

Initializes the reliable.io library runtime. This should be called before any additional functions in this library. Throws an IOException on failure.

terminate :: IO () Source #

Terminates the reliable.io library runtime. This should be called only after all other library functions terminate.

Utilities

data LogLevel Source #

Specifies the logging behavior of reliable.io. Note, this logging behavior is called from C calls to printf and therefore might interfere with the Haskell runtime (such as putStrLn).

Instances

Instances details
Bounded LogLevel Source # 
Instance details

Defined in Reliable.IO

Enum LogLevel Source # 
Instance details

Defined in Reliable.IO

Eq LogLevel Source # 
Instance details

Defined in Reliable.IO

Data LogLevel Source # 
Instance details

Defined in Reliable.IO

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LogLevel -> c LogLevel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LogLevel #

toConstr :: LogLevel -> Constr #

dataTypeOf :: LogLevel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LogLevel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LogLevel) #

gmapT :: (forall b. Data b => b -> b) -> LogLevel -> LogLevel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LogLevel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LogLevel -> r #

gmapQ :: (forall d. Data d => d -> u) -> LogLevel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LogLevel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LogLevel -> m LogLevel #

Ord LogLevel Source # 
Instance details

Defined in Reliable.IO

Read LogLevel Source # 
Instance details

Defined in Reliable.IO

Show LogLevel Source # 
Instance details

Defined in Reliable.IO

Generic LogLevel Source # 
Instance details

Defined in Reliable.IO

Associated Types

type Rep LogLevel :: Type -> Type #

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

type Rep LogLevel Source # 
Instance details

Defined in Reliable.IO

type Rep LogLevel = D1 ('MetaData "LogLevel" "Reliable.IO" "reliable-io-0.0.2-KiwQ8d3FPmHKA4uF66nAUZ" 'False) ((C1 ('MetaCons "LogLevel'None" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogLevel'Info" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LogLevel'Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogLevel'Debug" 'PrefixI 'False) (U1 :: Type -> Type)))

logLevel :: LogLevel -> IO () Source #

Set the reliable.io LogLevel. The default is LogLevel'None.

Endpoint Configuration

data EndpointConfig Source #

An EndpointConfig is a write-only opaque datatype that is used to define the settings for creating an Endpoint.

defaultConfig :: EndpointConfig Source #

The default EndpointConfig. This uses sensible defaults for the library (as opposed to being zero-initialized, for example).

setName :: String -> EndpointConfig -> EndpointConfig Source #

Sets the name of the endpoint. This is usually not relevant, except when setting the log level to be more than LogLevel'None.

setMaxPacketSize :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the maximum packet size for the endpoint. This will allow the API to know when to throw an error when the packet being sent is too big. The packet size is purely application specific, but may be useful for making sure that your data sizes don't grow too large during development. The default value for this is 16KB.

setPacketFragmentationLimit :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the fragmentation limit for this endpoint. The fragmentation limit is the size in bytes for a packet where it will be split into multiple fragments. This need not be maxPacketSize / maxNumFragments, but that is usually a sensible choice. The default value is 1KB.

setPacketFragmentSize :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the fragment size for this endpoint. The fragment size determines the size in bytes of each fragment. This need not be the same as the fragmentation limit, although that is certainly a sensible choice. The default for this value is 1KB.

setMaxNumFragments :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the number of fragments per packet in this endpoint. This is only to make sure that the endpoint has enough buffer space provisioned for incoming packets. Default for this value is 16, and the maximum value is 256.

setAckBufferSize :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the number of packets for which to store received sequence numbers. The default value is 256.

setSentPacketsBufferSize :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the maximum number of packets for which to store sent packet info. This number reflects the largest number of packets we expect to be in flight at any given time, in order to properly ack them upon receipt of some other endpoint's packets. Also useful for properly computing bandwidth of the endpoint. Default value is 256.

setReceivedPacketsBufferSize :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the maximum number of packets for which to store received packet info. Useful for properly acking packets and for accurately computing bandwidth of the endpoint. Default value is 256.

setFragmentReassemblyBufferSize :: Int -> EndpointConfig -> EndpointConfig Source #

Sets the maximum number of in flight packet fragments that we can store in order to properly recreate the packets upon receipt. This buffer is used to process out of order and dropped packets, as fragments from a packet may not arrive contiguously. Default value is 64.

setRTTSmoothingFactor :: Float -> EndpointConfig -> EndpointConfig Source #

Sets the round trip time smoothing factor. This is purely for diagnostic purposes when determining what the round trip time is for this endpoint. Smaller numbers will vary the RTT measurement more slowly. Default value is 0.0025f.

setPacketLossSmoothingFactor :: Float -> EndpointConfig -> EndpointConfig Source #

Sets the packet loss smoothing factor. This is purely for diagnostic purposes when determining what the packet loss rate is for this endpoint. Smaller numbers will vary the packet loss measurement more slowly. Default value is 0.1f.

setBandwidthSmoothingFactor :: Float -> EndpointConfig -> EndpointConfig Source #

Sets the bandwidth smoothing factor. This is purely for diagnostic purposes when determining what the bandwidth is from this endpoint. Smaller numbers will vary the bandwidth measurement more slowly. Default value is 0.1f.

data PacketType Source #

Endpoints support two packet types, either IPV4 or IPV6.

Instances

Instances details
Bounded PacketType Source # 
Instance details

Defined in Reliable.IO

Enum PacketType Source # 
Instance details

Defined in Reliable.IO

Eq PacketType Source # 
Instance details

Defined in Reliable.IO

Data PacketType Source # 
Instance details

Defined in Reliable.IO

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PacketType -> c PacketType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PacketType #

toConstr :: PacketType -> Constr #

dataTypeOf :: PacketType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PacketType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PacketType) #

gmapT :: (forall b. Data b => b -> b) -> PacketType -> PacketType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PacketType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PacketType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PacketType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PacketType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PacketType -> m PacketType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PacketType -> m PacketType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PacketType -> m PacketType #

Ord PacketType Source # 
Instance details

Defined in Reliable.IO

Read PacketType Source # 
Instance details

Defined in Reliable.IO

Show PacketType Source # 
Instance details

Defined in Reliable.IO

Generic PacketType Source # 
Instance details

Defined in Reliable.IO

Associated Types

type Rep PacketType :: Type -> Type #

type Rep PacketType Source # 
Instance details

Defined in Reliable.IO

type Rep PacketType = D1 ('MetaData "PacketType" "Reliable.IO" "reliable-io-0.0.2-KiwQ8d3FPmHKA4uF66nAUZ" 'False) (C1 ('MetaCons "PacketType'IPV4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PacketType'IPV6" 'PrefixI 'False) (U1 :: Type -> Type))

setPacketType :: PacketType -> EndpointConfig -> EndpointConfig Source #

Sets the packet type for this endpoint, which determines the header size that the library needs to allocate in order to properly keep track of the packets.

Callbacks

type TransmitPacketFunction Source #

Arguments

 = Word16

Sequence number of the packet being sent

-> Ptr Word8

Pointer to memory containing the packet data

-> Int

Size of the data in bytes

-> IO () 

Function used by an Endpoint to send packet fragments over the unreliable data channel. One use case would be to have the given data sent to a UDP socket.

type ProcessPacketFunction Source #

Arguments

 = Word16

Sequence number of the packet received.

-> Ptr Word8

Pointer to the memory containing the packet data

-> Int

Size of the data in bytes.

-> IO Bool

Returns true if the packet was successfully processed

A user function supplied to an Endpoint that handles reassembled packets once they've been received.

Endpoints

data Endpoint Source #

An Endpoint is the main datatype of the reliable.io library. Two endpoints (usually, but not exclusively) on separate hosts represent a connection over an unreliable network, such as the UDP protocol over the internet. The function of an endpoint is to provide a way to administer traffic to the corresponding receiver. It is not responsible for performing the actual sending and receiving of data.

Endpoints provide two main services:

  1. Breaking down a large packet into fragments, each of which is a predetermined size.
  2. Assembling a sequence of fragments from a corresponding endpoint.
  3. Notifying the user when a packet has been received (ack'd) by the corresponding endpoint.

Packets to be disassembled into fragments and transmitted are passed to the endpoint via the sendPacket function. Fragments that are received from the corresponding endpoint and should be reassmbled are passed to the endpoint via the receivePacket function. These functions only queue the data for processing, but the actual processing of packets only takes place during a call to update.

Additionally, each Endpoint keeps track of the metrics associated with it, providing the user with ways to measure the round trip time for each packet, the bandwidth of the connection, and a measurement of the packet loss.

createEndpoint :: EndpointConfig -> Double -> TransmitPacketFunction -> ProcessPacketFunction -> IO Endpoint Source #

Creates an Endpoint. The two main callbacks required for each endpoint:

  1. A TransmitPacketFunction that is able to send packet fragments to a corresponding Endpoint
  2. A ProcessPacketFunction that administers the reassmbled packet from a collection of fragments.

The Double parameter corresponds to the time (in seconds) at which the endpoint is created. This time value is needed to be in the same domain to subsequent calls to update in order to properly calculate metrics.

destroyEndpoint :: Endpoint -> IO () Source #

Destroys an Endpoint and any associated callbacks.

withEndpoint :: EndpointConfig -> Double -> TransmitPacketFunction -> ProcessPacketFunction -> (Endpoint -> IO a) -> IO a Source #

Convenience function that follows the Bracket pattern for encapsulating the resource management associated with interfacing with an Endpoint.

nextPacketSequence :: Endpoint -> IO Word16 Source #

Returns the sequence number of the next packet that will be sent from this Endpoint.

sendPacket :: Endpoint -> Ptr Word8 -> Int -> IO () Source #

sendPacket e p sz will send a packet from Endpoint e with sz bytes whose data resides in the memory pointed to by p. If sz is larger than the fragment limit, the packet will be split into multiple fragments. Each fragment will then be sent via the TransmitPacketFunction passed to createEndpoint. Note, this function does not actually send the packet, and rather queues it for sending during the next call to update.

receivePacket :: Endpoint -> Ptr Word8 -> Int -> IO () Source #

receivePacket e p sz will add a packet fragment to Endpoint e with sz bytes whose data resides in the memory pointed to by p. Once all of the fragments of a given packet have been received via this function, the Endpoint will pass the reassembled packet to the ProcessPacketFunction passed to createEndpoint. Note, this function does not actually reassemble the packet, and rather queues it for processing during the next call to update.

getAcks :: Endpoint -> IO [Word16] Source #

Returns the list of sequence numbers for the most recently ack'd packets that have been sent from this Endpoint.

clearAcks :: Endpoint -> IO () Source #

Clears the list of sequence numbers for the most recently ack'd packets.

reset :: Endpoint -> IO () Source #

Resets the endpoint, including all metrics about network traffic and any information about ack'd packets.

update :: Endpoint -> Double -> IO () Source #

Performs the work of updating the endpoint. This sends packets, reassembles packets, and identifies any acks received from the corresponding Endpoint. The time passed to this function must be measured in seconds and correspond to the same time domain as createEndpoint.

Analytics

roundTripTime :: Endpoint -> IO Float Source #

Returns the measured round trip time for packets sent from this Endpoint.

packetLoss :: Endpoint -> IO Float Source #

Returns the measured packet loss for packets sent from this Endpoint.

data BandwidthMeasurements Source #

Bandwidth measurements taken for each Endpoint.

Instances

Instances details
Read BandwidthMeasurements Source # 
Instance details

Defined in Reliable.IO

Show BandwidthMeasurements Source # 
Instance details

Defined in Reliable.IO

Generic BandwidthMeasurements Source # 
Instance details

Defined in Reliable.IO

Associated Types

type Rep BandwidthMeasurements :: Type -> Type #

type Rep BandwidthMeasurements Source # 
Instance details

Defined in Reliable.IO

type Rep BandwidthMeasurements = D1 ('MetaData "BandwidthMeasurements" "Reliable.IO" "reliable-io-0.0.2-KiwQ8d3FPmHKA4uF66nAUZ" 'False) (C1 ('MetaCons "BandwidthMeasurements" 'PrefixI 'True) (S1 ('MetaSel ('Just "bandwidthSentKbps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: (S1 ('MetaSel ('Just "bandwidthReceivedKbps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Just "bandwidthAckedKbps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))

bandwidth :: Endpoint -> IO BandwidthMeasurements Source #

Returns the measured bandwidth for data on this Endpoint.

data Counter Source #

Counters for metrics that are collected for each Endpoint. These are reset upon calling reset for the given Endpoint.

Instances

Instances details
Bounded Counter Source # 
Instance details

Defined in Reliable.IO

Enum Counter Source # 
Instance details

Defined in Reliable.IO

Eq Counter Source # 
Instance details

Defined in Reliable.IO

Methods

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

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

Data Counter Source # 
Instance details

Defined in Reliable.IO

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Counter -> c Counter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Counter #

toConstr :: Counter -> Constr #

dataTypeOf :: Counter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Counter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Counter) #

gmapT :: (forall b. Data b => b -> b) -> Counter -> Counter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Counter -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Counter -> r #

gmapQ :: (forall d. Data d => d -> u) -> Counter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Counter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Counter -> m Counter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Counter -> m Counter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Counter -> m Counter #

Ord Counter Source # 
Instance details

Defined in Reliable.IO

Read Counter Source # 
Instance details

Defined in Reliable.IO

Show Counter Source # 
Instance details

Defined in Reliable.IO

Generic Counter Source # 
Instance details

Defined in Reliable.IO

Associated Types

type Rep Counter :: Type -> Type #

Methods

from :: Counter -> Rep Counter x #

to :: Rep Counter x -> Counter #

type Rep Counter Source # 
Instance details

Defined in Reliable.IO

type Rep Counter = D1 ('MetaData "Counter" "Reliable.IO" "reliable-io-0.0.2-KiwQ8d3FPmHKA4uF66nAUZ" 'False) (((C1 ('MetaCons "Counter'NumPacketsSent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Counter'NumPacketsReceived" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Counter'NumPacketsAcked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Counter'NumPacketsStale" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Counter'NumPacketsInvalid" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Counter'NumPacketsTooLargeToSend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Counter'NumPacketsTooLargeToReceive" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Counter'NumFragmentsSent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Counter'NumFragmentsReceived" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Counter'NumFragmentsInvalid" 'PrefixI 'False) (U1 :: Type -> Type)))))

getCounter :: Endpoint -> Counter -> IO Word64 Source #

Returns the counter value associated with the Counter for the given Endpoint.