netcode-io-0.0.3: Bindings to the low-level netcode.io library.
Copyright(c) Pavel Krajcevski 2020
LicenseBSD-3
Maintainerkrajcevski@gmail.com
Stabilityexperimental
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Netcode.IO

Description

This module contains the high-level bindings on top of the module Bindings.Netcode.IO. These provide a cleaner interface to the netcode.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.Netcode.IO. In the event that you need more performance, that module is available for use.

The general architecture of a netcode.io application is outlined in the C library documentation. The jist is that we need three main entities:

  • A server to connect to
  • An authentication server to dispatch connection tokens
  • A client that wants to connect to a server

In this case, the client will request a connection token from the authentication server. The authentication server will know a-priori what the available servers are for the client to connect to. These servers (and other information) are stored in an encrypted ConnectToken, based on the 64-bit unique client ID. The authentication server will send a ConnectToken to a client when that client looks for servers to connect to.

Once a connection between server and client is established, they may exchange packets of information. These packets are sent over UDP and therefore are not guaranteed to arrive in order or even arrive at all. In order to create a reliable information channel between client and server, it is recommended to use this library in conjunction with the reliable.io library.

Synopsis

Initialization

initialize :: IO () Source #

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

terminate :: IO () Source #

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

Addresses

data Address Source #

An opaque type that encapsulates an address that can be used with netcode.io. The address may be stored in memory in different ways (for example with encryption), and therefore needs the IO monad to interact with it.

TODO: Use a high-level representation here to enable a more pure interface.

Instances

Instances details
Show Address Source # 
Instance details

Defined in Netcode.IO.Address

data AddressMode Source #

The address mode based on how the address is represented. Usually a consequence of how it was parsed.

Constructors

AddressMode'Unknown

Usually when address is stored encrypted.

AddressMode'IPv4 
AddressMode'IPv6 

Instances

Instances details
Bounded AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Enum AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Eq AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Data AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Methods

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

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

toConstr :: AddressMode -> Constr #

dataTypeOf :: AddressMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Read AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Show AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Generic AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

Associated Types

type Rep AddressMode :: Type -> Type #

type Rep AddressMode Source # 
Instance details

Defined in Netcode.IO.Address

type Rep AddressMode = D1 ('MetaData "AddressMode" "Netcode.IO.Address" "netcode-io-0.0.3-9xepEf1EZTT2RFu8Aba0L2" 'False) (C1 ('MetaCons "AddressMode'Unknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AddressMode'IPv4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AddressMode'IPv6" 'PrefixI 'False) (U1 :: Type -> Type)))

addressMode :: Address -> IO AddressMode Source #

Returns the address mode for the given address. Note, this address may be stored in memory in different ways, so we must inspect the memory contents in order to retreive the addressing mode.

addressPort :: Address -> IO Word16 Source #

Returns the port associated with this address.

addressValues :: Address -> IO [Word16] Source #

Returns the address as a sequence of values in its human readable format. For example:

>>> parseAddress "123.231.132.213" >>= addressValues
[123, 231, 132, 213]

The length of the list is either 4 or 8 depending on the address mode. If the address mode is unknown, addressValues returns the empty list.

constructAddress Source #

Arguments

:: AddressMode 
-> Word16

Port

-> [Word16] 
-> IO Address 

Returns an address with the given values interpreted using the given mode. For IPv4 addresses, only the bottom 8 bits of each 16-bit word will be used. The list will be zero padded to contain enough values to fill the address as needed.

parseAddress :: String -> IO Address Source #

Takes a String and parses it to create an Address. The string should be formatted as either a valid IPv4 or IPv6 address. It does not, however, support dual address modes.

addressToString :: Address -> IO String Source #

Returns a string that represents the given Address.

addressEqual :: Address -> Address -> IO Bool Source #

Returns True if two addresses are equal by examining their memory contents.

Common callbacks

type SendPacketOverride Source #

Arguments

 = Address

Address to send the packet to

-> Ptr Word8

A pointer to the memory that holds the packet data

-> CInt

The size of the packet

-> IO () 

Override that sends a packet to the given address. This can be used by both clients and servers. This is invoked after netcode.io processes and encrypts the packet.

type ReceivePacketOverride Source #

Arguments

 = Address

Address from which to receive a packet

-> Ptr Word8

Pointer to the buffer where to write packet data

-> CInt

Maximum size of destination buffer in bytes

-> IO CInt

Return value: should be size of packet data

Override that receives a packet from the given address. This can be used by both clients and servers. This is invoked before netcode.io processes and decrypts the packet data.

Implementations of this callback are meant to fill the memory at the given pointer with the data from a packet received from the Address. The maximum size of the buffer pointed to is also passed and the implementation is expected to return the actual size of the packet. In the event that there is no packet (or equivalently, no packet data), then the implementation should return zero.

Packets

data Packet Source #

A packet is a basic unit of data that is transferred between client and server. Sequence numbers indicate the order in which the packets were sent, and this library contains no guarantee that they will be received in a monotonically increasing order.

Constructors

Packet 

Fields

Instances

Instances details
Show Packet Source # 
Instance details

Defined in Netcode.IO.Packet

Generic Packet Source # 
Instance details

Defined in Netcode.IO.Packet

Associated Types

type Rep Packet :: Type -> Type #

Methods

from :: Packet -> Rep Packet x #

to :: Rep Packet x -> Packet #

type Rep Packet Source # 
Instance details

Defined in Netcode.IO.Packet

type Rep Packet = D1 ('MetaData "Packet" "Netcode.IO.Packet" "netcode-io-0.0.3-9xepEf1EZTT2RFu8Aba0L2" 'False) (C1 ('MetaCons "Packet" 'PrefixI 'True) (S1 ('MetaSel ('Just "packetSequenceNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "packetSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "packetDataPtr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForeignPtr Word8)))))

maximumPacketSize :: Num a => a Source #

The maximum size, in bytes, of a packet. In other words, this is the maximum value that packetSize can take.

Clients

Client-specific callbacks

type ClientStateChangeCallback Source #

Arguments

 = ClientState

Old state

-> ClientState

New state

-> IO () 

A client-specific callback that gets invoked each time the underlying state of the client changes.

Client configs

data ClientConfig Source #

A ClientConfig is a type that specifies the behavior of a Client. Client configs are pretty spartan: the only options available at this time are setting callbacks.

defaultClientConfig :: ClientConfig Source #

A ClientConfig with no callback overrides.

setClientStateChangeCallback :: ClientStateChangeCallback -> ClientConfig -> ClientConfig Source #

Creates a config that removes the existing ClientStateChangeCallback and instead uses the given callback.

setClientSendReceiveOverrides :: SendPacketOverride -> ReceivePacketOverride -> ClientConfig -> ClientConfig Source #

Removes the existing send and receive overrides for the given config, if set, and instead uses the ones given.

clearClientSendReceiveOverrides :: ClientConfig -> ClientConfig Source #

Changes the config to use the default send and receive packet functions.

Client objects

data Client Source #

A client object. This is an opaque type meant to be used in conjunction with this library.

A Client is generally meant to connect to one of potentially many servers through a ConnectToken. The main loop of the application that manages the lifetime of the client is expected to maintain a running timer with a resolution of at least seconds. This main loop is also expected to call updateClient on a regular basis to allow the library to process incoming packets and send outgoing packets.

Instances

Instances details
Show Client Source # 
Instance details

Defined in Netcode.IO.Client

createClient :: String -> ClientConfig -> Double -> IO Client Source #

Creates a client at the given address using the provided config. Throws an IOException on failure.

Note, the address used here can be either formatted as an IPv4 address or an IPv6 address, similar to the arguments passed to parseAddress. In the common case, you will likely want to use INADDR_ANY to bind to the underlying socket, which is represented by the address "0.0.0.0"

The time passed to this create function should be a measurement in seconds, such that when connecting in the future using updateClient, the same resolution timer is being passed. That allows the library to properly timeout in cases where connections are taking too long to establish.

destroyClient :: Client -> IO () Source #

Destroys the client and frees all of the Haskell-side function pointers that were registered as callbacks.

generateClientID :: IO Word64 Source #

Generates a random 64-bit client ID to be used with generateConnectToken

connectClient :: Client -> ConnectToken -> IO () Source #

Begin the process to connect the client to a server stored in the given ConnectToken. This does not connect the client immediately, but rather resets the client object and sets the state to ClientState'SendingConnectionRequest. The client will attempt to connect on the next call to updateClient.

disconnectClient :: Client -> IO () Source #

Disconnects the client from anything it might be connected to.

updateClient :: Client -> Double -> IO () Source #

Main processing call for clients with the current time in seconds (in the same domain as the time passed to createClient). This flushes packet queues at the appropriate rate and updates connection statuses among other things. It is expected to be called in the main loop of the application.

sendPacketFromClient :: Client -> Int -> Ptr Word8 -> IO () Source #

Enqueues a packet to be sent during the next call to updateClient.

receivePacketFromServer :: Client -> IO (Maybe Packet) Source #

Dequeues a received packet from the Server. This function returns a Just until the queue is empty, upon which it will return Nothing.

nextClientPacketSequence :: Client -> IO Word64 Source #

Returns the sequence number of the next packet that the Client will send.

getClientPort :: Client -> IO Word16 Source #

Returns the port assigned to this Client.

withClientServerAddress :: Client -> (Address -> IO a) -> IO a Source #

Performs an action with the address of the server to which the given Client is connected to. This is meant to minimize the chances that the Address value will be used in a manner that outlives the given Client. Callers should avoid storing the Address value or returning it as a result of this function.

In the event that the client is not connected to a server, the address passed to the action will be 0.0.0.0.

Client state

data ClientState Source #

The possible connection states of a Client. The default state is ClientState'Disconnected.

Instances

Instances details
Bounded ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Enum ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Eq ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Data ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Methods

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

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

toConstr :: ClientState -> Constr #

dataTypeOf :: ClientState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Show ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Generic ClientState Source # 
Instance details

Defined in Netcode.IO.Client

Associated Types

type Rep ClientState :: Type -> Type #

type Rep ClientState Source # 
Instance details

Defined in Netcode.IO.Client

type Rep ClientState = D1 ('MetaData "ClientState" "Netcode.IO.Client" "netcode-io-0.0.3-9xepEf1EZTT2RFu8Aba0L2" 'False) (((C1 ('MetaCons "ClientState'ConnectTokenExpired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClientState'InvalidConnectToken" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ClientState'ConnectionTimedOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ClientState'ConnectionResponseTimedOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClientState'ConnectionRequestTimedOut" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ClientState'ConnectionDenied" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClientState'Disconnected" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ClientState'SendingConnectionRequest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ClientState'SendingConnectionResponse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClientState'Connected" 'PrefixI 'False) (U1 :: Type -> Type)))))

getClientState :: Client -> IO ClientState Source #

Returns the current state of the Client.

isClientDisconnected :: Client -> IO Bool Source #

Returns true if the Client is in a state considered to be disconnected, as opposed to connected or connecting.

Connect Tokens

data ConnectToken Source #

A ConnectToken represents an encrypted set of data fields that describe both the client requesting to make a connection and the available servers to which that connection can be made. It is generated solely via the

maximumServersPerConnect :: Num a => a Source #

Returns the maximum number of servers that can be stored in a ConnectToken.

maximumUserDataSize :: Num a => a Source #

Gives the maximum size, in bytes, of user data stored in a ConnectToken.

privateKeySize :: Num a => a Source #

Returns the number of bytes expected in the private key used to generate a ConnectToken

generateConnectToken Source #

Arguments

:: [(String, String)]

Public and internal servers

-> Int

Token expiration in seconds

-> Int

Token timeout in seconds

-> Word64

Unique Client ID

-> Word64

Protocol ID

-> [Word8]

Private key

-> [Word8]

User data

-> IO ConnectToken 

Creates a connect token for the given client (by clientID) with the list of associated addresses. User data may be at most maximumUserDataSize values, otherwise is truncated or zero-padded to fill. The list of public and internal servers must not be empty and may contain at most maximumServersPerConnect values, otherwise is truncated. Throws an IOException on failure.

Servers

Server-specific callbacks

type ServerConnectDisconnectCallback Source #

Arguments

 = Int

Client index connected

-> Bool

True if the client connected

-> IO () 

A server-specific callback that gets invoked each time a client either connects to, or disconnects from, the server.

Server configs

data ServerConfig Source #

A ServerConfig is a type that specifies the behavior of a Server and contains associated metadata.

At a minimum, the connection protocol ID and the private key for the application should be set for each server (via setProtocolID and setPrivateKey, respectively).

defaultServerConfig :: ServerConfig Source #

The default ServerConfig contains no callbacks or overrides, and contains empty values for the required fields needed to properly have a server respond to a connecting Client.

setProtocolID :: Word64 -> ServerConfig -> ServerConfig Source #

Sets the connection protocol ID used by this Server. This is a unique ID that must match the protocol ID used in generateConnectToken

setPrivateKey :: [Word8] -> ServerConfig -> ServerConfig Source #

Sets the private key used by this Server. This key must match the private key used in generateConnectToken

setServerConnectDisconnectCallback :: ServerConnectDisconnectCallback -> ServerConfig -> ServerConfig Source #

Replaces the existing ServerConnectDisconnectCallback with the given one and frees any associated memory that may be allocated for the the existing callback.

clearServerConnectDisconnectCallback :: ServerConfig -> ServerConfig Source #

Removes the existing ServerConnectDisconnectCallback and frees any associated memory that may be allocated for the the existing callback.

setServerSendReceiveOverrides :: SendPacketOverride -> ReceivePacketOverride -> ServerConfig -> ServerConfig Source #

Removes the existing send and receive overrides for the given config, if set, and instead uses the ones given.

clearServerSendReceiveOverrides :: ServerConfig -> ServerConfig Source #

Changes the config to use the default send and receive packet functions.

Server objects

data Server Source #

A server object. This is an opaque type meant to be used in conjunction with this library.

A server is generally meant to represent and endpoint for one or more Clients to connect to. The server application is similar to that of the client in that it is expected to have a running timer with a resolution of at least seconds. The main loop of the server application is meant to call updateServer to allow the library to process incoming packets and send outgoing packets to the clients.

Instances

Instances details
Show Server Source # 
Instance details

Defined in Netcode.IO.Server

createServer :: String -> ServerConfig -> Double -> IO Server Source #

Creates a server at the given address using the provided config. Throws an IOException on failure.

Note, the address used here can be either formatted as an IPv4 address or an IPv6 address, similar to the arguments passed to parseAddress. In the common case, you will likely want to use INADDR_ANY to bind to the underlying socket, which is represented by the address "0.0.0.0"

The time passed to this create function should be a measurement in seconds, such that when connecting in the future using updateServer, the same resolution timer is being passed. That allows the library to properly timeout in cases where connections are taking too long to establish.

destroyServer :: Server -> IO () Source #

Destroys the server object and frees the associated Haskell-side callbacks and overrides

startServer :: Server -> Int -> IO () Source #

Starts the server and specifies the maximum number of clients that can connect. Emits a warning when the maximum number of clients is more than maxNumClients.

maxNumClients :: Num a => a Source #

Returns the maximum number of clients that a server can support.

stopServer :: Server -> IO () Source #

Stops the server.

updateServer :: Server -> Double -> IO () Source #

Main processing call for a Server with the current time in seconds (in the same domain as the time passed to createServer). This flushes packet queues at the appropriate rate and updates connection statuses among other things. It is expected to be called in the main loop of the application.

clientConnectedAtIndex :: Server -> Int -> IO Bool Source #

Returns True if the client at the given client index is connected to the server. Returns False if not connected, if the server is not running, or if the client index is out of bounds.

clientIdAtIndex :: Server -> Int -> IO Word64 Source #

Returns the client ID of the client at the given client index. Returns 0 if not connected, the server is not running, or if the client index is out of bounds.

withClientAddressAtIndex :: Server -> Int -> (Address -> IO a) -> IO a Source #

Performs an action with the address of the client to which the given Server is connected to. This is meant to minimize the chances that the Address value will be used in a manner that outlives the given Server or the connection lifetime of the client. Callers should avoid storing the Address value or returning it as a result of this function.

In the event that the client index is out of bounds, or the client is not connected at that slot, the address passed to the action will be 0.0.0.0.

withClientUserDataAtIndex :: Server -> Int -> (Ptr () -> IO a) -> IO a Source #

Performs an action with the user data of the client to which the given Server is connected to. This is meant to minimize the chances that the memory buffer will be used in a manner that outlives the given Server or the connection lifetime of the client. Callers should avoid storing the Ptr value or returning it as a result of this function.

In the event that the client index is out of bounds, or the client is not connected at that slot, the given action will receive nullPtr.

clientUserDataAtIndex :: Server -> Int -> IO [Word8] Source #

Returns the user data for the client connected at the given client index.

In the event that the client index is out of bounds, or the client is not connected at that slot, the result will be the empty list.

maxClientsForServer :: Server -> IO Int Source #

Returns the maximum number of clients that can connect to this server, or zero if the server has not been started yet (via a call to startServer).

numConnectedClients :: Server -> IO Int Source #

Returns the number of currently connected clients.

isServerRunning :: Server -> IO Bool Source #

Returns True if the server has been started, and is ready to accept incoming connections from clients.

isServerFull :: Server -> IO Bool Source #

Returns true if the number of connected clients matches the maximum number of possibly connected clients.

getServerPort :: Server -> IO Word16 Source #

Returns the port assigned to the server's IP address.

sendPacketFromServer Source #

Arguments

:: Server 
-> Int

Client index

-> Int

Size in bytes of packet data

-> Ptr Word8

Packet data buffer

-> IO () 

Enqueues a packet to be sent to the client at the given index during the next call to updateServer.

broadcastPacketFromServer :: Server -> Int -> Ptr Word8 -> IO () Source #

Enqueues a packet with the given size and data to all connected clients.

disconnectClientFromServer :: Server -> Int -> IO () Source #

Disconnects the client at the given index from the server.

disconnectAllClientsFromServer :: Server -> IO () Source #

Disconnects all clients from the server.

receivePacketFromClient :: Server -> Int -> IO (Maybe Packet) Source #

Dequeues a received packet from the Client at the given client index. This function returns a Just until the queue is empty, upon which it will return a Nothing.

nextServerPacketSequence :: Server -> Int -> IO Word64 Source #

Returns the next sequence number of a packet destined for the client at the given client index.

Utilities

sleep :: Double -> IO () Source #

Sleep the current thread. This is usually only used in example programs. It's probably safer to use the built-in threadDelay.

data LogLevel Source #

Specifies the logging behavior of netcode.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 Netcode.IO

Enum LogLevel Source # 
Instance details

Defined in Netcode.IO

Eq LogLevel Source # 
Instance details

Defined in Netcode.IO

Data LogLevel Source # 
Instance details

Defined in Netcode.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 Netcode.IO

Read LogLevel Source # 
Instance details

Defined in Netcode.IO

Show LogLevel Source # 
Instance details

Defined in Netcode.IO

Generic LogLevel Source # 
Instance details

Defined in Netcode.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 Netcode.IO

type Rep LogLevel = D1 ('MetaData "LogLevel" "Netcode.IO" "netcode-io-0.0.3-9xepEf1EZTT2RFu8Aba0L2" '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 netcode.io LogLevel. The default is LogLevel'None.