\section{Packet Kind}
The following is an exhaustive list of top level packet kind names and their
number. Their payload is specified in dedicated sections. Each section is
named after the Packet Kind it describes followed by the byte value in
parentheses, e.g. \href{#ping-request-0x00}{Ping Request (0x00)}.
\begin{tabular}{l|l}
Byte value & Packet Kind \\
\hline
\texttt{0x00} & Ping Request \\
\texttt{0x01} & Ping Response \\
\texttt{0x02} & Nodes Request \\
\texttt{0x04} & Nodes Response \\
\texttt{0x18} & Cookie Request \\
\texttt{0x19} & Cookie Response \\
\texttt{0x1a} & Crypto Handshake \\
\texttt{0x1b} & Crypto Data \\
\texttt{0x20} & DHT Request \\
\texttt{0x21} & LAN Discovery \\
\texttt{0x80} & Onion Request 0 \\
\texttt{0x81} & Onion Request 1 \\
\texttt{0x82} & Onion Request 2 \\
\texttt{0x83} & Announce Request \\
\texttt{0x84} & Announce Response \\
\texttt{0x85} & Onion Data Request \\
\texttt{0x86} & Onion Data Response \\
\texttt{0x8c} & Onion Response 3 \\
\texttt{0x8d} & Onion Response 2 \\
\texttt{0x8e} & Onion Response 1 \\
\texttt{0xf0} & Bootstrap Info \\
\end{tabular}
\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StrictData #-}
module Network.Tox.Protocol.PacketKind where
import Control.Arrow ((&&&))
import Data.Binary (Binary, get, put)
import Data.MessagePack (MessagePack)
import Data.Typeable (Typeable)
import Data.Word (Word8)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary,
arbitraryBoundedEnum)
data PacketKind
= PingRequest
| PingResponse
| NodesRequest
| NodesResponse
| CookieRequest
| CookieResponse
| CryptoHandshake
| CryptoData
| Crypto
| LanDiscovery
| OnionRequest0
| OnionRequest1
| OnionRequest2
| AnnounceRequest
| AnnounceResponse
| OnionDataRequest
| OnionDataResponse
| OnionResponse3
| OnionResponse2
| OnionResponse1
| BootstrapInfo
deriving (PacketKind -> PacketKind -> Bool
(PacketKind -> PacketKind -> Bool)
-> (PacketKind -> PacketKind -> Bool) -> Eq PacketKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PacketKind -> PacketKind -> Bool
$c/= :: PacketKind -> PacketKind -> Bool
== :: PacketKind -> PacketKind -> Bool
$c== :: PacketKind -> PacketKind -> Bool
Eq, ReadPrec [PacketKind]
ReadPrec PacketKind
Int -> ReadS PacketKind
ReadS [PacketKind]
(Int -> ReadS PacketKind)
-> ReadS [PacketKind]
-> ReadPrec PacketKind
-> ReadPrec [PacketKind]
-> Read PacketKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PacketKind]
$creadListPrec :: ReadPrec [PacketKind]
readPrec :: ReadPrec PacketKind
$creadPrec :: ReadPrec PacketKind
readList :: ReadS [PacketKind]
$creadList :: ReadS [PacketKind]
readsPrec :: Int -> ReadS PacketKind
$creadsPrec :: Int -> ReadS PacketKind
Read, Int -> PacketKind -> ShowS
[PacketKind] -> ShowS
PacketKind -> String
(Int -> PacketKind -> ShowS)
-> (PacketKind -> String)
-> ([PacketKind] -> ShowS)
-> Show PacketKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PacketKind] -> ShowS
$cshowList :: [PacketKind] -> ShowS
show :: PacketKind -> String
$cshow :: PacketKind -> String
showsPrec :: Int -> PacketKind -> ShowS
$cshowsPrec :: Int -> PacketKind -> ShowS
Show, PacketKind
PacketKind -> PacketKind -> Bounded PacketKind
forall a. a -> a -> Bounded a
maxBound :: PacketKind
$cmaxBound :: PacketKind
minBound :: PacketKind
$cminBound :: PacketKind
Bounded, Int -> PacketKind
PacketKind -> Int
PacketKind -> [PacketKind]
PacketKind -> PacketKind
PacketKind -> PacketKind -> [PacketKind]
PacketKind -> PacketKind -> PacketKind -> [PacketKind]
(PacketKind -> PacketKind)
-> (PacketKind -> PacketKind)
-> (Int -> PacketKind)
-> (PacketKind -> Int)
-> (PacketKind -> [PacketKind])
-> (PacketKind -> PacketKind -> [PacketKind])
-> (PacketKind -> PacketKind -> [PacketKind])
-> (PacketKind -> PacketKind -> PacketKind -> [PacketKind])
-> Enum PacketKind
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: PacketKind -> PacketKind -> PacketKind -> [PacketKind]
$cenumFromThenTo :: PacketKind -> PacketKind -> PacketKind -> [PacketKind]
enumFromTo :: PacketKind -> PacketKind -> [PacketKind]
$cenumFromTo :: PacketKind -> PacketKind -> [PacketKind]
enumFromThen :: PacketKind -> PacketKind -> [PacketKind]
$cenumFromThen :: PacketKind -> PacketKind -> [PacketKind]
enumFrom :: PacketKind -> [PacketKind]
$cenumFrom :: PacketKind -> [PacketKind]
fromEnum :: PacketKind -> Int
$cfromEnum :: PacketKind -> Int
toEnum :: Int -> PacketKind
$ctoEnum :: Int -> PacketKind
pred :: PacketKind -> PacketKind
$cpred :: PacketKind -> PacketKind
succ :: PacketKind -> PacketKind
$csucc :: PacketKind -> PacketKind
Enum, (forall x. PacketKind -> Rep PacketKind x)
-> (forall x. Rep PacketKind x -> PacketKind) -> Generic PacketKind
forall x. Rep PacketKind x -> PacketKind
forall x. PacketKind -> Rep PacketKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PacketKind x -> PacketKind
$cfrom :: forall x. PacketKind -> Rep PacketKind x
Generic, Typeable)
instance MessagePack PacketKind
kindDescription :: PacketKind -> String
kindDescription :: PacketKind -> String
kindDescription = \case
PacketKind
PingRequest -> String
"Ping request"
PacketKind
PingResponse -> String
"Ping response"
PacketKind
NodesRequest -> String
"Nodes request"
PacketKind
NodesResponse -> String
"Nodes response"
PacketKind
CookieRequest -> String
"Cookie request"
PacketKind
CookieResponse -> String
"Cookie response"
PacketKind
CryptoHandshake -> String
"Crypto handshake"
PacketKind
CryptoData -> String
"Crypto data"
PacketKind
Crypto -> String
"Encrypted data"
PacketKind
LanDiscovery -> String
"LAN discovery"
PacketKind
OnionRequest0 -> String
"Initial onion request"
PacketKind
OnionRequest1 -> String
"First level wrapped onion request"
PacketKind
OnionRequest2 -> String
"Second level wrapped onion request"
PacketKind
AnnounceRequest -> String
"Announce request"
PacketKind
AnnounceResponse -> String
"Announce response"
PacketKind
OnionDataRequest -> String
"Onion data request"
PacketKind
OnionDataResponse -> String
"Onion data response"
PacketKind
OnionResponse3 -> String
"Third level wrapped onion response"
PacketKind
OnionResponse2 -> String
"Second level wrapped onion response"
PacketKind
OnionResponse1 -> String
"First level wrapped onion response"
PacketKind
BootstrapInfo -> String
"Bootstrap node info request and response"
kindToByte :: PacketKind -> Word8
kindToByte :: PacketKind -> Word8
kindToByte = \case
PacketKind
PingRequest -> Word8
0x00
PacketKind
PingResponse -> Word8
0x01
PacketKind
NodesRequest -> Word8
0x02
PacketKind
NodesResponse -> Word8
0x04
PacketKind
CookieRequest -> Word8
0x18
PacketKind
CookieResponse -> Word8
0x19
PacketKind
CryptoHandshake -> Word8
0x1a
PacketKind
CryptoData -> Word8
0x1b
PacketKind
Crypto -> Word8
0x20
PacketKind
LanDiscovery -> Word8
0x21
PacketKind
OnionRequest0 -> Word8
0x80
PacketKind
OnionRequest1 -> Word8
0x81
PacketKind
OnionRequest2 -> Word8
0x82
PacketKind
AnnounceRequest -> Word8
0x83
PacketKind
AnnounceResponse -> Word8
0x84
PacketKind
OnionDataRequest -> Word8
0x85
PacketKind
OnionDataResponse -> Word8
0x86
PacketKind
OnionResponse3 -> Word8
0x8c
PacketKind
OnionResponse2 -> Word8
0x8d
PacketKind
OnionResponse1 -> Word8
0x8e
PacketKind
BootstrapInfo -> Word8
0xf0
byteToKind :: Word8 -> Maybe PacketKind
byteToKind :: Word8 -> Maybe PacketKind
byteToKind =
(Word8 -> [(Word8, PacketKind)] -> Maybe PacketKind)
-> [(Word8, PacketKind)] -> Word8 -> Maybe PacketKind
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> [(Word8, PacketKind)] -> Maybe PacketKind
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [(Word8, PacketKind)]
mapping
where
mapping :: [(Word8, PacketKind)]
mapping = (PacketKind -> (Word8, PacketKind))
-> [PacketKind] -> [(Word8, PacketKind)]
forall a b. (a -> b) -> [a] -> [b]
map (PacketKind -> Word8
kindToByte (PacketKind -> Word8)
-> (PacketKind -> PacketKind) -> PacketKind -> (Word8, PacketKind)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& PacketKind -> PacketKind
forall a. a -> a
id) [PacketKind
forall a. Bounded a => a
minBound..PacketKind
forall a. Bounded a => a
maxBound]
instance Binary PacketKind where
put :: PacketKind -> Put
put = Word8 -> Put
forall t. Binary t => t -> Put
put (Word8 -> Put) -> (PacketKind -> Word8) -> PacketKind -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PacketKind -> Word8
kindToByte
get :: Get PacketKind
get = do
Word8
byte <- Get Word8
forall t. Binary t => Get t
get
case Word8 -> Maybe PacketKind
byteToKind Word8
byte of
Maybe PacketKind
Nothing -> String -> Get PacketKind
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get PacketKind) -> String -> Get PacketKind
forall a b. (a -> b) -> a -> b
$ String
"no binary mapping for packet kind " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
byte
Just PacketKind
kind -> PacketKind -> Get PacketKind
forall (m :: * -> *) a. Monad m => a -> m a
return PacketKind
kind
instance Arbitrary PacketKind where
arbitrary :: Gen PacketKind
arbitrary = Gen PacketKind
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
\end{code}