\section{Transport Protocol}
A Transport Protocol is a transport layer protocol directly below the Tox
protocol itself. Tox supports two transport protocols: UDP and TCP. The
binary representation of the Transport Protocol is a single bit: 0 for UDP, 1
for TCP. If encoded as standalone value, the bit is stored in the least
significant bit of a byte. If followed by other bit-packed data, it consumes
exactly one bit.
The human-readable representation for UDP is \texttt{UDP} and for TCP is
\texttt{TCP}.
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StrictData #-}
module Network.Tox.NodeInfo.TransportProtocol where
import Data.Binary (Binary)
import qualified Data.Binary.Bits.Get as Bits (getBool)
import qualified Data.Binary.Bits.Put as Bits (putBool)
import Data.MessagePack (MessagePack)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Network.Tox.Encoding (BitEncoding, bitGet, bitPut)
import Test.QuickCheck.Arbitrary (Arbitrary (..))
import qualified Test.QuickCheck.Gen as Gen
data TransportProtocol
= UDP
| TCP
deriving (TransportProtocol -> TransportProtocol -> Bool
(TransportProtocol -> TransportProtocol -> Bool)
-> (TransportProtocol -> TransportProtocol -> Bool)
-> Eq TransportProtocol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransportProtocol -> TransportProtocol -> Bool
$c/= :: TransportProtocol -> TransportProtocol -> Bool
== :: TransportProtocol -> TransportProtocol -> Bool
$c== :: TransportProtocol -> TransportProtocol -> Bool
Eq, Eq TransportProtocol
Eq TransportProtocol
-> (TransportProtocol -> TransportProtocol -> Ordering)
-> (TransportProtocol -> TransportProtocol -> Bool)
-> (TransportProtocol -> TransportProtocol -> Bool)
-> (TransportProtocol -> TransportProtocol -> Bool)
-> (TransportProtocol -> TransportProtocol -> Bool)
-> (TransportProtocol -> TransportProtocol -> TransportProtocol)
-> (TransportProtocol -> TransportProtocol -> TransportProtocol)
-> Ord TransportProtocol
TransportProtocol -> TransportProtocol -> Bool
TransportProtocol -> TransportProtocol -> Ordering
TransportProtocol -> TransportProtocol -> TransportProtocol
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TransportProtocol -> TransportProtocol -> TransportProtocol
$cmin :: TransportProtocol -> TransportProtocol -> TransportProtocol
max :: TransportProtocol -> TransportProtocol -> TransportProtocol
$cmax :: TransportProtocol -> TransportProtocol -> TransportProtocol
>= :: TransportProtocol -> TransportProtocol -> Bool
$c>= :: TransportProtocol -> TransportProtocol -> Bool
> :: TransportProtocol -> TransportProtocol -> Bool
$c> :: TransportProtocol -> TransportProtocol -> Bool
<= :: TransportProtocol -> TransportProtocol -> Bool
$c<= :: TransportProtocol -> TransportProtocol -> Bool
< :: TransportProtocol -> TransportProtocol -> Bool
$c< :: TransportProtocol -> TransportProtocol -> Bool
compare :: TransportProtocol -> TransportProtocol -> Ordering
$ccompare :: TransportProtocol -> TransportProtocol -> Ordering
$cp1Ord :: Eq TransportProtocol
Ord, Int -> TransportProtocol -> ShowS
[TransportProtocol] -> ShowS
TransportProtocol -> String
(Int -> TransportProtocol -> ShowS)
-> (TransportProtocol -> String)
-> ([TransportProtocol] -> ShowS)
-> Show TransportProtocol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransportProtocol] -> ShowS
$cshowList :: [TransportProtocol] -> ShowS
show :: TransportProtocol -> String
$cshow :: TransportProtocol -> String
showsPrec :: Int -> TransportProtocol -> ShowS
$cshowsPrec :: Int -> TransportProtocol -> ShowS
Show, ReadPrec [TransportProtocol]
ReadPrec TransportProtocol
Int -> ReadS TransportProtocol
ReadS [TransportProtocol]
(Int -> ReadS TransportProtocol)
-> ReadS [TransportProtocol]
-> ReadPrec TransportProtocol
-> ReadPrec [TransportProtocol]
-> Read TransportProtocol
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TransportProtocol]
$creadListPrec :: ReadPrec [TransportProtocol]
readPrec :: ReadPrec TransportProtocol
$creadPrec :: ReadPrec TransportProtocol
readList :: ReadS [TransportProtocol]
$creadList :: ReadS [TransportProtocol]
readsPrec :: Int -> ReadS TransportProtocol
$creadsPrec :: Int -> ReadS TransportProtocol
Read, (forall x. TransportProtocol -> Rep TransportProtocol x)
-> (forall x. Rep TransportProtocol x -> TransportProtocol)
-> Generic TransportProtocol
forall x. Rep TransportProtocol x -> TransportProtocol
forall x. TransportProtocol -> Rep TransportProtocol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransportProtocol x -> TransportProtocol
$cfrom :: forall x. TransportProtocol -> Rep TransportProtocol x
Generic, Typeable)
instance Binary TransportProtocol
instance MessagePack TransportProtocol
instance BitEncoding TransportProtocol where
bitGet :: BitGet TransportProtocol
bitGet = (Bool -> TransportProtocol)
-> BitGet Bool -> BitGet TransportProtocol
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\case
Bool
False -> TransportProtocol
UDP
Bool
True -> TransportProtocol
TCP
) BitGet Bool
Bits.getBool
bitPut :: TransportProtocol -> BitPut ()
bitPut TransportProtocol
UDP = Bool -> BitPut ()
Bits.putBool Bool
False
bitPut TransportProtocol
TCP = Bool -> BitPut ()
Bits.putBool Bool
True
instance Arbitrary TransportProtocol where
arbitrary :: Gen TransportProtocol
arbitrary = [TransportProtocol] -> Gen TransportProtocol
forall a. HasCallStack => [a] -> Gen a
Gen.elements [TransportProtocol
UDP, TransportProtocol
TCP]
\end{code}