\section{Node Info (packed node format)}

The Node Info data structure contains a Transport Protocol, a Socket Address,
and a Public Key.  This is sufficient information to start communicating with
that node.  The binary representation of a Node Info is called the "packed node
format".

\begin{tabular}{l|l|l}
  Length             & Type               & Contents \\
  \hline
  \texttt{1} bit     & Transport Protocol & UDP = 0, TCP = 1 \\
  \texttt{7} bit     & Address Family     & 2 = IPv4, 10 = IPv6 \\
  \texttt{4 $|$ 16}  & IP address         & 4 bytes for IPv4, 16 bytes for IPv6 \\
  \texttt{2}         & Port Number        & Port number \\
  \texttt{32}        & Public Key         & Node ID \\
\end{tabular}

The packed node format is a way to store the node info in a small yet easy to
parse format.  To store more than one node, simply append another one to the
previous one: \texttt{[packed node 1][packed node 2][...]}.

In the packed node format, the first byte (high bit protocol, lower 7 bits
address family) are called the IP Type.  The following table is informative and
can be used to simplify the implementation.

\begin{tabular}{l|l|l}
  IP Type               & Transport Protocol & Address Family \\
  \hline
  \texttt{2   (0x02)}   & UDP                & IPv4 \\
  \texttt{10  (0x0a)}   & UDP                & IPv6 \\
  \texttt{130 (0x82)}   & TCP                & IPv4 \\
  \texttt{138 (0x8a)}   & TCP                & IPv6 \\
\end{tabular}

The number \texttt{130} is used for an IPv4 TCP relay and \texttt{138} is used
to indicate an IPv6 TCP relay.

The reason for these numbers is that the numbers on Linux for IPv4 and IPv6
(the \texttt{AF\_INET} and \texttt{AF\_INET6} defines) are \texttt{2} and
\texttt{10}.  The TCP numbers are just the UDP numbers \texttt{+ 128}.

\begin{code}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE Safe               #-}
{-# LANGUAGE StrictData         #-}
module Network.Tox.NodeInfo.NodeInfo where

import           Control.Applicative                    ((<$>), (<*>))
import           Data.Binary                            (Binary)
import qualified Data.Binary                            as Binary (get, put)
import           Data.MessagePack                       (MessagePack)
import           Data.Typeable                          (Typeable)
import           GHC.Generics                           (Generic)
import           Test.QuickCheck.Arbitrary              (Arbitrary, arbitrary)

import           Network.Tox.Crypto.Key                 (PublicKey)
import           Network.Tox.NodeInfo.SocketAddress     (SocketAddress)
import qualified Network.Tox.NodeInfo.SocketAddress     as SocketAddress
import           Network.Tox.NodeInfo.TransportProtocol (TransportProtocol)


{-------------------------------------------------------------------------------
 -
 - :: Implementation.
 -
 ------------------------------------------------------------------------------}


data NodeInfo = NodeInfo
  { NodeInfo -> TransportProtocol
protocol  :: TransportProtocol
  , NodeInfo -> SocketAddress
address   :: SocketAddress
  , NodeInfo -> PublicKey
publicKey :: PublicKey
  }
  deriving (NodeInfo -> NodeInfo -> Bool
(NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> Bool) -> Eq NodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeInfo -> NodeInfo -> Bool
$c/= :: NodeInfo -> NodeInfo -> Bool
== :: NodeInfo -> NodeInfo -> Bool
$c== :: NodeInfo -> NodeInfo -> Bool
Eq, Eq NodeInfo
Eq NodeInfo
-> (NodeInfo -> NodeInfo -> Ordering)
-> (NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> Bool)
-> (NodeInfo -> NodeInfo -> NodeInfo)
-> (NodeInfo -> NodeInfo -> NodeInfo)
-> Ord NodeInfo
NodeInfo -> NodeInfo -> Bool
NodeInfo -> NodeInfo -> Ordering
NodeInfo -> NodeInfo -> NodeInfo
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 :: NodeInfo -> NodeInfo -> NodeInfo
$cmin :: NodeInfo -> NodeInfo -> NodeInfo
max :: NodeInfo -> NodeInfo -> NodeInfo
$cmax :: NodeInfo -> NodeInfo -> NodeInfo
>= :: NodeInfo -> NodeInfo -> Bool
$c>= :: NodeInfo -> NodeInfo -> Bool
> :: NodeInfo -> NodeInfo -> Bool
$c> :: NodeInfo -> NodeInfo -> Bool
<= :: NodeInfo -> NodeInfo -> Bool
$c<= :: NodeInfo -> NodeInfo -> Bool
< :: NodeInfo -> NodeInfo -> Bool
$c< :: NodeInfo -> NodeInfo -> Bool
compare :: NodeInfo -> NodeInfo -> Ordering
$ccompare :: NodeInfo -> NodeInfo -> Ordering
$cp1Ord :: Eq NodeInfo
Ord, Int -> NodeInfo -> ShowS
[NodeInfo] -> ShowS
NodeInfo -> String
(Int -> NodeInfo -> ShowS)
-> (NodeInfo -> String) -> ([NodeInfo] -> ShowS) -> Show NodeInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeInfo] -> ShowS
$cshowList :: [NodeInfo] -> ShowS
show :: NodeInfo -> String
$cshow :: NodeInfo -> String
showsPrec :: Int -> NodeInfo -> ShowS
$cshowsPrec :: Int -> NodeInfo -> ShowS
Show, ReadPrec [NodeInfo]
ReadPrec NodeInfo
Int -> ReadS NodeInfo
ReadS [NodeInfo]
(Int -> ReadS NodeInfo)
-> ReadS [NodeInfo]
-> ReadPrec NodeInfo
-> ReadPrec [NodeInfo]
-> Read NodeInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NodeInfo]
$creadListPrec :: ReadPrec [NodeInfo]
readPrec :: ReadPrec NodeInfo
$creadPrec :: ReadPrec NodeInfo
readList :: ReadS [NodeInfo]
$creadList :: ReadS [NodeInfo]
readsPrec :: Int -> ReadS NodeInfo
$creadsPrec :: Int -> ReadS NodeInfo
Read, (forall x. NodeInfo -> Rep NodeInfo x)
-> (forall x. Rep NodeInfo x -> NodeInfo) -> Generic NodeInfo
forall x. Rep NodeInfo x -> NodeInfo
forall x. NodeInfo -> Rep NodeInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NodeInfo x -> NodeInfo
$cfrom :: forall x. NodeInfo -> Rep NodeInfo x
Generic, Typeable)

instance MessagePack NodeInfo


instance Binary NodeInfo where
  get :: Get NodeInfo
get =
    (TransportProtocol -> SocketAddress -> PublicKey -> NodeInfo)
-> (TransportProtocol, SocketAddress) -> PublicKey -> NodeInfo
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry TransportProtocol -> SocketAddress -> PublicKey -> NodeInfo
NodeInfo ((TransportProtocol, SocketAddress) -> PublicKey -> NodeInfo)
-> Get (TransportProtocol, SocketAddress)
-> Get (PublicKey -> NodeInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (TransportProtocol, SocketAddress)
SocketAddress.getSocketAddress Get (PublicKey -> NodeInfo) -> Get PublicKey -> Get NodeInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get PublicKey
forall t. Binary t => Get t
Binary.get

  put :: NodeInfo -> Put
put NodeInfo
ni = do
    TransportProtocol -> SocketAddress -> Put
SocketAddress.putSocketAddress (NodeInfo -> TransportProtocol
protocol NodeInfo
ni) (NodeInfo -> SocketAddress
address NodeInfo
ni)
    PublicKey -> Put
forall t. Binary t => t -> Put
Binary.put (PublicKey -> Put) -> PublicKey -> Put
forall a b. (a -> b) -> a -> b
$ NodeInfo -> PublicKey
publicKey NodeInfo
ni


{-------------------------------------------------------------------------------
 -
 - :: Tests.
 -
 ------------------------------------------------------------------------------}


instance Arbitrary NodeInfo where
  arbitrary :: Gen NodeInfo
arbitrary =
    TransportProtocol -> SocketAddress -> PublicKey -> NodeInfo
NodeInfo (TransportProtocol -> SocketAddress -> PublicKey -> NodeInfo)
-> Gen TransportProtocol
-> Gen (SocketAddress -> PublicKey -> NodeInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TransportProtocol
forall a. Arbitrary a => Gen a
arbitrary Gen (SocketAddress -> PublicKey -> NodeInfo)
-> Gen SocketAddress -> Gen (PublicKey -> NodeInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen SocketAddress
forall a. Arbitrary a => Gen a
arbitrary Gen (PublicKey -> NodeInfo) -> Gen PublicKey -> Gen NodeInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen PublicKey
forall a. Arbitrary a => Gen a
arbitrary
\end{code}