\subsection{Ping Service}

The Ping Service is used to check if a node is responsive.

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

import           Data.Binary               (Binary)
import           Data.MessagePack          (MessagePack)
import           Data.Typeable             (Typeable)
import           GHC.Generics              (Generic)
import           Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Test.QuickCheck.Gen       as Gen


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


\end{code}

A Ping Packet payload consists of just a boolean value saying whether it is a
request or a response.

The one byte boolean inside the encrypted payload is added to prevent peers
from creating a valid Ping Response from a Ping Request without decrypting the
packet and encrypting a new one.  Since symmetric encryption is used, the
encrypted Ping Response would be byte-wise equal to the Ping Request without
the discriminator byte.

\begin{tabular}{l|l|l}
  Length             & Type        & \href{#rpc-services}{Contents} \\
  \hline
  \texttt{1}         & Bool        & Response flag: 0x00 for Request, 0x01 for Response \\
\end{tabular}

\subsubsection{Ping Request (0x00)}

A Ping Request is a Ping Packet with the response flag set to False.  When a
Ping Request is received and successfully decrypted, a Ping Response packet is
created and sent back to the requestor.

\subsubsection{Ping Response (0x01)}

A Ping Response is a Ping Packet with the response flag set to True.

\begin{code}


data PingPacket
  = PingRequest
  | PingResponse
  deriving (PingPacket -> PingPacket -> Bool
(PingPacket -> PingPacket -> Bool)
-> (PingPacket -> PingPacket -> Bool) -> Eq PingPacket
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PingPacket -> PingPacket -> Bool
$c/= :: PingPacket -> PingPacket -> Bool
== :: PingPacket -> PingPacket -> Bool
$c== :: PingPacket -> PingPacket -> Bool
Eq, ReadPrec [PingPacket]
ReadPrec PingPacket
Int -> ReadS PingPacket
ReadS [PingPacket]
(Int -> ReadS PingPacket)
-> ReadS [PingPacket]
-> ReadPrec PingPacket
-> ReadPrec [PingPacket]
-> Read PingPacket
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PingPacket]
$creadListPrec :: ReadPrec [PingPacket]
readPrec :: ReadPrec PingPacket
$creadPrec :: ReadPrec PingPacket
readList :: ReadS [PingPacket]
$creadList :: ReadS [PingPacket]
readsPrec :: Int -> ReadS PingPacket
$creadsPrec :: Int -> ReadS PingPacket
Read, Int -> PingPacket -> ShowS
[PingPacket] -> ShowS
PingPacket -> String
(Int -> PingPacket -> ShowS)
-> (PingPacket -> String)
-> ([PingPacket] -> ShowS)
-> Show PingPacket
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PingPacket] -> ShowS
$cshowList :: [PingPacket] -> ShowS
show :: PingPacket -> String
$cshow :: PingPacket -> String
showsPrec :: Int -> PingPacket -> ShowS
$cshowsPrec :: Int -> PingPacket -> ShowS
Show, (forall x. PingPacket -> Rep PingPacket x)
-> (forall x. Rep PingPacket x -> PingPacket) -> Generic PingPacket
forall x. Rep PingPacket x -> PingPacket
forall x. PingPacket -> Rep PingPacket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PingPacket x -> PingPacket
$cfrom :: forall x. PingPacket -> Rep PingPacket x
Generic, Typeable)

instance Binary PingPacket
instance MessagePack PingPacket


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


instance Arbitrary PingPacket where
  arbitrary :: Gen PingPacket
arbitrary =
    [PingPacket] -> Gen PingPacket
forall a. [a] -> Gen a
Gen.elements
      [ PingPacket
PingRequest
      , PingPacket
PingResponse
      ]
\end{code}