\chapter{State Format} \begin{code} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE StrictData #-} module Network.Tox.SaveData ( SaveData (..) , Section (..) , NospamKeys (..) , Friends (..) , Bytes (..) ) where \end{code} The reference Tox implementation uses a custom binary format to save the state of a Tox client between restarts. This format is far from perfect and will be replaced eventually. For the sake of maintaining compatibility down the road, it is documented here. The binary encoding of all integer types in the state format is a fixed-width byte sequence with the integer encoded in Little Endian unless stated otherwise. \begin{code} import Control.Arrow (second) import Control.Monad (when) import Data.Binary (Binary (..)) import Data.Binary.Get (Get) import qualified Data.Binary.Get as Get import Data.Binary.Put (Put) import qualified Data.Binary.Put as Put import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS import Data.Word (Word16, Word32, Word8) import GHC.Generics (Generic) import Network.Tox.Crypto.Key (PublicKey, SecretKey) import Network.Tox.SaveData.Conferences (Conferences) import Network.Tox.SaveData.DHT (DHT) import Network.Tox.SaveData.Friend (Friend) import Network.Tox.SaveData.Nodes (Nodes) import qualified Network.Tox.SaveData.Util as Util import Test.QuickCheck.Arbitrary (Arbitrary (..), genericShrink) import qualified Test.QuickCheck.Gen as Gen \end{code} \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{4} & Zeroes \\ \texttt{4} & \texttt{uint32\_t} (0x15ED1B1F) \\ \texttt{?} & List of sections \\ \end{tabular} \begin{code} saveDataMagic :: Word32 saveDataMagic :: Word32 saveDataMagic = Word32 0x15ED1B1F newtype SaveData = SaveData [Section] deriving (SaveData -> SaveData -> Bool (SaveData -> SaveData -> Bool) -> (SaveData -> SaveData -> Bool) -> Eq SaveData forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: SaveData -> SaveData -> Bool $c/= :: SaveData -> SaveData -> Bool == :: SaveData -> SaveData -> Bool $c== :: SaveData -> SaveData -> Bool Eq, Int -> SaveData -> ShowS [SaveData] -> ShowS SaveData -> String (Int -> SaveData -> ShowS) -> (SaveData -> String) -> ([SaveData] -> ShowS) -> Show SaveData forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [SaveData] -> ShowS $cshowList :: [SaveData] -> ShowS show :: SaveData -> String $cshow :: SaveData -> String showsPrec :: Int -> SaveData -> ShowS $cshowsPrec :: Int -> SaveData -> ShowS Show, ReadPrec [SaveData] ReadPrec SaveData Int -> ReadS SaveData ReadS [SaveData] (Int -> ReadS SaveData) -> ReadS [SaveData] -> ReadPrec SaveData -> ReadPrec [SaveData] -> Read SaveData forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [SaveData] $creadListPrec :: ReadPrec [SaveData] readPrec :: ReadPrec SaveData $creadPrec :: ReadPrec SaveData readList :: ReadS [SaveData] $creadList :: ReadS [SaveData] readsPrec :: Int -> ReadS SaveData $creadsPrec :: Int -> ReadS SaveData Read, (forall x. SaveData -> Rep SaveData x) -> (forall x. Rep SaveData x -> SaveData) -> Generic SaveData forall x. Rep SaveData x -> SaveData forall x. SaveData -> Rep SaveData x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep SaveData x -> SaveData $cfrom :: forall x. SaveData -> Rep SaveData x Generic) instance Binary SaveData where get :: Get SaveData get = do Word32 zeroes <- Get Word32 Get.getWord32le Bool -> Get () -> Get () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (Word32 zeroes Word32 -> Word32 -> Bool forall a. Eq a => a -> a -> Bool /= Word32 0) (Get () -> Get ()) -> Get () -> Get () forall a b. (a -> b) -> a -> b $ String -> Get () forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Get ()) -> String -> Get () forall a b. (a -> b) -> a -> b $ String "savedata should start with 32 zero-bits, but got " String -> ShowS forall a. [a] -> [a] -> [a] ++ Word32 -> String forall a. Show a => a -> String show Word32 zeroes Word32 magic <- Get Word32 Get.getWord32le Bool -> Get () -> Get () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (Word32 magic Word32 -> Word32 -> Bool forall a. Eq a => a -> a -> Bool /= Word32 saveDataMagic) (Get () -> Get ()) -> Get () -> Get () forall a b. (a -> b) -> a -> b $ String -> Get () forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Get ()) -> String -> Get () forall a b. (a -> b) -> a -> b $ String "wrong magic number for savedata: " String -> ShowS forall a. [a] -> [a] -> [a] ++ Word32 -> String forall a. Show a => a -> String show Word32 magic String -> ShowS forall a. [a] -> [a] -> [a] ++ String " != " String -> ShowS forall a. [a] -> [a] -> [a] ++ Word32 -> String forall a. Show a => a -> String show Word32 saveDataMagic [Section] -> SaveData SaveData ([Section] -> SaveData) -> Get [Section] -> Get SaveData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get [Section] getSections put :: SaveData -> Put put (SaveData [Section] sections) = do Word32 -> Put Put.putWord32le Word32 0 Word32 -> Put Put.putWord32le Word32 saveDataMagic [Section] -> Put putSections [Section] sections instance Arbitrary SaveData where arbitrary :: Gen SaveData arbitrary = [Section] -> SaveData SaveData ([Section] -> SaveData) -> ([Section] -> [Section]) -> [Section] -> SaveData forall b c a. (b -> c) -> (a -> b) -> a -> c . ([Section] -> [Section] -> [Section] forall a. [a] -> [a] -> [a] ++ [Section SectionEOF]) ([Section] -> SaveData) -> Gen [Section] -> Gen SaveData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen [Section] forall a. Arbitrary a => Gen a arbitrary shrink :: SaveData -> [SaveData] shrink = (SaveData -> Bool) -> [SaveData] -> [SaveData] forall a. (a -> Bool) -> [a] -> [a] filter (\(SaveData [Section] ss) -> Section SectionEOF Section -> [Section] -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `elem` [Section] ss) ([SaveData] -> [SaveData]) -> (SaveData -> [SaveData]) -> SaveData -> [SaveData] forall b c a. (b -> c) -> (a -> b) -> a -> c . SaveData -> [SaveData] forall a. (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] genericShrink \end{code} \section{Sections} The core of the state format consists of a list of sections. Every section has its type and length specified at the beginning. In some cases, a section only contains one item and thus takes up the entire length of the section. This is denoted with '?'. \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{4} & \texttt{uint32\_t} Length of this section \\ \texttt{2} & \texttt{uint16\_t} Section type \\ \texttt{2} & \texttt{uint16\_t} (0x01CE) \\ \texttt{?} & Section \\ \end{tabular} \begin{code} sectionMagic :: Word16 sectionMagic :: Word16 sectionMagic = Word16 0x01CE \end{code} Section types: \begin{tabular}{l|l} Name & Value \\ \hline NospamKeys & 0x01 \\ DHT & 0x02 \\ Friends & 0x03 \\ Name & 0x04 \\ StatusMessage & 0x05 \\ Status & 0x06 \\ TcpRelays & 0x0A \\ PathNodes & 0x0B \\ Conferences & 0x14 \\ EOF & 0xFF \\ \end{tabular} \begin{code} getSections :: Get [Section] getSections :: Get [Section] getSections = Get [Section] go where go :: Get [Section] go = do (Int len, Word16 ty) <- Word16 -> Get (Int, Word16) Util.getSectionHeader Word16 sectionMagic let load :: (a -> Section) -> Get [Section] load a -> Section f = (:) (Section -> [Section] -> [Section]) -> Get Section -> Get ([Section] -> [Section]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (a -> Section f (a -> Section) -> Get a -> Get Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Int -> Get a -> Get a forall a. Int -> Get a -> Get a Get.isolate (Int -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral Int len) Get a forall t. Binary t => Get t get) Get ([Section] -> [Section]) -> Get [Section] -> Get [Section] forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Get [Section] go case Word16 ty of Word16 0x01 -> (NospamKeys -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load NospamKeys -> Section SectionNospamKeys Word16 0x02 -> (DHT -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load DHT -> Section SectionDHT Word16 0x03 -> (Friends -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Friends -> Section SectionFriends Word16 0x04 -> (Bytes -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Bytes -> Section SectionName Word16 0x05 -> (Bytes -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Bytes -> Section SectionStatusMessage Word16 0x06 -> (Word8 -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Word8 -> Section SectionStatus Word16 0x0A -> (Nodes -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Nodes -> Section SectionTcpRelays Word16 0x0B -> (Nodes -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Nodes -> Section SectionPathNodes Word16 0x14 -> (Conferences -> Section) -> Get [Section] forall a. Binary a => (a -> Section) -> Get [Section] load Conferences -> Section SectionConferences Word16 0xFF -> [Section] -> Get [Section] forall (m :: * -> *) a. Monad m => a -> m a return [Section SectionEOF] Word16 _ -> String -> Get [Section] forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Get [Section]) -> String -> Get [Section] forall a b. (a -> b) -> a -> b $ Word16 -> String forall a. Show a => a -> String show Word16 ty putSections :: [Section] -> Put putSections :: [Section] -> Put putSections = (Section -> Put) -> [Section] -> Put forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ Section -> Put go where go :: Section -> Put go Section section = do let (Word16 ty, ByteString bytes) = (Put -> ByteString) -> (Word16, Put) -> (Word16, ByteString) forall (a :: * -> * -> *) b c d. Arrow a => a b c -> a (d, b) (d, c) second Put -> ByteString Put.runPut ((Word16, Put) -> (Word16, ByteString)) -> (Word16, Put) -> (Word16, ByteString) forall a b. (a -> b) -> a -> b $ Section -> (Word16, Put) putSection Section section Word16 -> Word32 -> Word16 -> Put Util.putSectionHeader Word16 sectionMagic (Int64 -> Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (Int64 -> Word32) -> Int64 -> Word32 forall a b. (a -> b) -> a -> b $ ByteString -> Int64 LBS.length ByteString bytes) Word16 ty ByteString -> Put Put.putLazyByteString ByteString bytes putSection :: Section -> (Word16, Put) putSection = \case SectionNospamKeys NospamKeys x -> (Word16 0x01, NospamKeys -> Put forall t. Binary t => t -> Put put NospamKeys x) SectionDHT DHT x -> (Word16 0x02, DHT -> Put forall t. Binary t => t -> Put put DHT x) SectionFriends Friends x -> (Word16 0x03, Friends -> Put forall t. Binary t => t -> Put put Friends x) SectionName Bytes x -> (Word16 0x04, Bytes -> Put forall t. Binary t => t -> Put put Bytes x) SectionStatusMessage Bytes x -> (Word16 0x05, Bytes -> Put forall t. Binary t => t -> Put put Bytes x) SectionStatus Word8 x -> (Word16 0x06, Word8 -> Put forall t. Binary t => t -> Put put Word8 x) SectionTcpRelays Nodes x -> (Word16 0x0A, Nodes -> Put forall t. Binary t => t -> Put put Nodes x) SectionPathNodes Nodes x -> (Word16 0x0B, Nodes -> Put forall t. Binary t => t -> Put put Nodes x) SectionConferences Conferences x -> (Word16 0x14, Conferences -> Put forall t. Binary t => t -> Put put Conferences x) Section SectionEOF -> (Word16 0xFF, () -> Put forall (m :: * -> *) a. Monad m => a -> m a return ()) \end{code} Not every section listed above is required to be present in order to restore from a state file. Only NospamKeys is required. \subsection{Nospam and Keys (0x01)} \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{4} & \texttt{uint32\_t} Nospam \\ \texttt{32} & Long term public key \\ \texttt{32} & Long term secret key \\ \end{tabular} \input{src/Network/Tox/SaveData/DHT.lhs} \subsection{Friends (0x03)} This section contains a list of friends. A friend can either be a peer we've sent a friend request to or a peer we've accepted a friend request from. \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{?} & List of friends \\ \end{tabular} \input{src/Network/Tox/SaveData/Friend.lhs} \subsection{Name (0x04)} \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{?} & Name as a UTF-8 encoded string \\ \end{tabular} \subsection{Status Message (0x05)} \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{?} & Status message as a UTF-8 encoded string \\ \end{tabular} \subsection{Status (0x06)} \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{1} & \texttt{uint8\_t} User status (see also: \texttt{USERSTATUS}) \\ \end{tabular} \subsection{Tcp Relays (0x0A)} This section contains a list of TCP relays. \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{?} & List of TCP relays \\ \end{tabular} The structure of a TCP relay is the same as \texttt{Node Info}. Note: this means that the integers stored in these nodes are stored in Big Endian as well. \subsection{Path Nodes (0x0B)} This section contains a list of path nodes used for onion routing. \begin{tabular}{l|l} Length & Contents \\ \hline \texttt{?} & List of path nodes \\ \end{tabular} The structure of a path node is the same as \texttt{Node Info}. Note: this means that the integers stored in these nodes are stored in Big Endian as well. \input{src/Network/Tox/SaveData/Conferences.lhs} \subsection{EOF (0xFF)} This section indicates the end of the state file. This section doesn't have any content and thus its length is 0. \begin{code} data Section = SectionNospamKeys NospamKeys | SectionDHT DHT | SectionFriends Friends | SectionName Bytes | SectionStatusMessage Bytes | SectionStatus Word8 | SectionTcpRelays Nodes | SectionPathNodes Nodes | SectionConferences Conferences | SectionEOF deriving (Section -> Section -> Bool (Section -> Section -> Bool) -> (Section -> Section -> Bool) -> Eq Section forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Section -> Section -> Bool $c/= :: Section -> Section -> Bool == :: Section -> Section -> Bool $c== :: Section -> Section -> Bool Eq, Int -> Section -> ShowS [Section] -> ShowS Section -> String (Int -> Section -> ShowS) -> (Section -> String) -> ([Section] -> ShowS) -> Show Section forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Section] -> ShowS $cshowList :: [Section] -> ShowS show :: Section -> String $cshow :: Section -> String showsPrec :: Int -> Section -> ShowS $cshowsPrec :: Int -> Section -> ShowS Show, ReadPrec [Section] ReadPrec Section Int -> ReadS Section ReadS [Section] (Int -> ReadS Section) -> ReadS [Section] -> ReadPrec Section -> ReadPrec [Section] -> Read Section forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Section] $creadListPrec :: ReadPrec [Section] readPrec :: ReadPrec Section $creadPrec :: ReadPrec Section readList :: ReadS [Section] $creadList :: ReadS [Section] readsPrec :: Int -> ReadS Section $creadsPrec :: Int -> ReadS Section Read, (forall x. Section -> Rep Section x) -> (forall x. Rep Section x -> Section) -> Generic Section forall x. Rep Section x -> Section forall x. Section -> Rep Section x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Section x -> Section $cfrom :: forall x. Section -> Rep Section x Generic) instance Arbitrary Section where arbitrary :: Gen Section arbitrary = [Gen Section] -> Gen Section forall a. [Gen a] -> Gen a Gen.oneof [ NospamKeys -> Section SectionNospamKeys (NospamKeys -> Section) -> Gen NospamKeys -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen NospamKeys forall a. Arbitrary a => Gen a arbitrary , DHT -> Section SectionDHT (DHT -> Section) -> Gen DHT -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen DHT forall a. Arbitrary a => Gen a arbitrary , Friends -> Section SectionFriends (Friends -> Section) -> Gen Friends -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Friends forall a. Arbitrary a => Gen a arbitrary , Bytes -> Section SectionName (Bytes -> Section) -> Gen Bytes -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Bytes forall a. Arbitrary a => Gen a arbitrary , Bytes -> Section SectionStatusMessage (Bytes -> Section) -> Gen Bytes -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Bytes forall a. Arbitrary a => Gen a arbitrary , Word8 -> Section SectionStatus (Word8 -> Section) -> Gen Word8 -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Word8 forall a. Arbitrary a => Gen a arbitrary , Nodes -> Section SectionTcpRelays (Nodes -> Section) -> Gen Nodes -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Nodes forall a. Arbitrary a => Gen a arbitrary , Nodes -> Section SectionPathNodes (Nodes -> Section) -> Gen Nodes -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Nodes forall a. Arbitrary a => Gen a arbitrary , Conferences -> Section SectionConferences (Conferences -> Section) -> Gen Conferences -> Gen Section forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Conferences forall a. Arbitrary a => Gen a arbitrary ] shrink :: Section -> [Section] shrink = Section -> [Section] forall a. (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] genericShrink data NospamKeys = NospamKeys { NospamKeys -> Word32 nospam :: Word32 , NospamKeys -> PublicKey publicKey :: PublicKey , NospamKeys -> SecretKey secretKey :: SecretKey } deriving (NospamKeys -> NospamKeys -> Bool (NospamKeys -> NospamKeys -> Bool) -> (NospamKeys -> NospamKeys -> Bool) -> Eq NospamKeys forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: NospamKeys -> NospamKeys -> Bool $c/= :: NospamKeys -> NospamKeys -> Bool == :: NospamKeys -> NospamKeys -> Bool $c== :: NospamKeys -> NospamKeys -> Bool Eq, Int -> NospamKeys -> ShowS [NospamKeys] -> ShowS NospamKeys -> String (Int -> NospamKeys -> ShowS) -> (NospamKeys -> String) -> ([NospamKeys] -> ShowS) -> Show NospamKeys forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [NospamKeys] -> ShowS $cshowList :: [NospamKeys] -> ShowS show :: NospamKeys -> String $cshow :: NospamKeys -> String showsPrec :: Int -> NospamKeys -> ShowS $cshowsPrec :: Int -> NospamKeys -> ShowS Show, ReadPrec [NospamKeys] ReadPrec NospamKeys Int -> ReadS NospamKeys ReadS [NospamKeys] (Int -> ReadS NospamKeys) -> ReadS [NospamKeys] -> ReadPrec NospamKeys -> ReadPrec [NospamKeys] -> Read NospamKeys forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [NospamKeys] $creadListPrec :: ReadPrec [NospamKeys] readPrec :: ReadPrec NospamKeys $creadPrec :: ReadPrec NospamKeys readList :: ReadS [NospamKeys] $creadList :: ReadS [NospamKeys] readsPrec :: Int -> ReadS NospamKeys $creadsPrec :: Int -> ReadS NospamKeys Read, (forall x. NospamKeys -> Rep NospamKeys x) -> (forall x. Rep NospamKeys x -> NospamKeys) -> Generic NospamKeys forall x. Rep NospamKeys x -> NospamKeys forall x. NospamKeys -> Rep NospamKeys x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep NospamKeys x -> NospamKeys $cfrom :: forall x. NospamKeys -> Rep NospamKeys x Generic) instance Binary NospamKeys where get :: Get NospamKeys get = Word32 -> PublicKey -> SecretKey -> NospamKeys NospamKeys (Word32 -> PublicKey -> SecretKey -> NospamKeys) -> Get Word32 -> Get (PublicKey -> SecretKey -> NospamKeys) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Word32 Get.getWord32le Get (PublicKey -> SecretKey -> NospamKeys) -> Get PublicKey -> Get (SecretKey -> NospamKeys) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Get PublicKey forall t. Binary t => Get t get Get (SecretKey -> NospamKeys) -> Get SecretKey -> Get NospamKeys forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Get SecretKey forall t. Binary t => Get t get put :: NospamKeys -> Put put NospamKeys{Word32 SecretKey PublicKey secretKey :: SecretKey publicKey :: PublicKey nospam :: Word32 secretKey :: NospamKeys -> SecretKey publicKey :: NospamKeys -> PublicKey nospam :: NospamKeys -> Word32 ..} = do Word32 -> Put Put.putWord32le Word32 nospam PublicKey -> Put forall t. Binary t => t -> Put put PublicKey publicKey SecretKey -> Put forall t. Binary t => t -> Put put SecretKey secretKey instance Arbitrary NospamKeys where arbitrary :: Gen NospamKeys arbitrary = Word32 -> PublicKey -> SecretKey -> NospamKeys NospamKeys (Word32 -> PublicKey -> SecretKey -> NospamKeys) -> Gen Word32 -> Gen (PublicKey -> SecretKey -> NospamKeys) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen Word32 forall a. Arbitrary a => Gen a arbitrary Gen (PublicKey -> SecretKey -> NospamKeys) -> Gen PublicKey -> Gen (SecretKey -> NospamKeys) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen PublicKey forall a. Arbitrary a => Gen a arbitrary Gen (SecretKey -> NospamKeys) -> Gen SecretKey -> Gen NospamKeys forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen SecretKey forall a. Arbitrary a => Gen a arbitrary shrink :: NospamKeys -> [NospamKeys] shrink = NospamKeys -> [NospamKeys] forall a. (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] genericShrink newtype Friends = Friends [Friend] deriving (Friends -> Friends -> Bool (Friends -> Friends -> Bool) -> (Friends -> Friends -> Bool) -> Eq Friends forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Friends -> Friends -> Bool $c/= :: Friends -> Friends -> Bool == :: Friends -> Friends -> Bool $c== :: Friends -> Friends -> Bool Eq, Int -> Friends -> ShowS [Friends] -> ShowS Friends -> String (Int -> Friends -> ShowS) -> (Friends -> String) -> ([Friends] -> ShowS) -> Show Friends forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Friends] -> ShowS $cshowList :: [Friends] -> ShowS show :: Friends -> String $cshow :: Friends -> String showsPrec :: Int -> Friends -> ShowS $cshowsPrec :: Int -> Friends -> ShowS Show, ReadPrec [Friends] ReadPrec Friends Int -> ReadS Friends ReadS [Friends] (Int -> ReadS Friends) -> ReadS [Friends] -> ReadPrec Friends -> ReadPrec [Friends] -> Read Friends forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Friends] $creadListPrec :: ReadPrec [Friends] readPrec :: ReadPrec Friends $creadPrec :: ReadPrec Friends readList :: ReadS [Friends] $creadList :: ReadS [Friends] readsPrec :: Int -> ReadS Friends $creadsPrec :: Int -> ReadS Friends Read, (forall x. Friends -> Rep Friends x) -> (forall x. Rep Friends x -> Friends) -> Generic Friends forall x. Rep Friends x -> Friends forall x. Friends -> Rep Friends x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Friends x -> Friends $cfrom :: forall x. Friends -> Rep Friends x Generic) instance Binary Friends where get :: Get Friends get = [Friend] -> Friends Friends ([Friend] -> Friends) -> Get [Friend] -> Get Friends forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get [Friend] forall a. (Binary a, Show a) => Get [a] Util.getList put :: Friends -> Put put (Friends [Friend] xs) = (Friend -> Put) -> [Friend] -> Put forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ Friend -> Put forall t. Binary t => t -> Put put [Friend] xs instance Arbitrary Friends where arbitrary :: Gen Friends arbitrary = [Friend] -> Friends Friends ([Friend] -> Friends) -> Gen [Friend] -> Gen Friends forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen [Friend] forall a. Arbitrary a => Gen a arbitrary shrink :: Friends -> [Friends] shrink = Friends -> [Friends] forall a. (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] genericShrink newtype Bytes = Bytes LBS.ByteString deriving (Bytes -> Bytes -> Bool (Bytes -> Bytes -> Bool) -> (Bytes -> Bytes -> Bool) -> Eq Bytes forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Bytes -> Bytes -> Bool $c/= :: Bytes -> Bytes -> Bool == :: Bytes -> Bytes -> Bool $c== :: Bytes -> Bytes -> Bool Eq, Int -> Bytes -> ShowS [Bytes] -> ShowS Bytes -> String (Int -> Bytes -> ShowS) -> (Bytes -> String) -> ([Bytes] -> ShowS) -> Show Bytes forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Bytes] -> ShowS $cshowList :: [Bytes] -> ShowS show :: Bytes -> String $cshow :: Bytes -> String showsPrec :: Int -> Bytes -> ShowS $cshowsPrec :: Int -> Bytes -> ShowS Show, ReadPrec [Bytes] ReadPrec Bytes Int -> ReadS Bytes ReadS [Bytes] (Int -> ReadS Bytes) -> ReadS [Bytes] -> ReadPrec Bytes -> ReadPrec [Bytes] -> Read Bytes forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [Bytes] $creadListPrec :: ReadPrec [Bytes] readPrec :: ReadPrec Bytes $creadPrec :: ReadPrec Bytes readList :: ReadS [Bytes] $creadList :: ReadS [Bytes] readsPrec :: Int -> ReadS Bytes $creadsPrec :: Int -> ReadS Bytes Read, (forall x. Bytes -> Rep Bytes x) -> (forall x. Rep Bytes x -> Bytes) -> Generic Bytes forall x. Rep Bytes x -> Bytes forall x. Bytes -> Rep Bytes x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Bytes x -> Bytes $cfrom :: forall x. Bytes -> Rep Bytes x Generic) instance Binary Bytes where get :: Get Bytes get = ByteString -> Bytes Bytes (ByteString -> Bytes) -> Get ByteString -> Get Bytes forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get ByteString Get.getRemainingLazyByteString put :: Bytes -> Put put (Bytes ByteString bs) = ByteString -> Put Put.putLazyByteString ByteString bs instance Arbitrary Bytes where arbitrary :: Gen Bytes arbitrary = ByteString -> Bytes Bytes (ByteString -> Bytes) -> ([Word8] -> ByteString) -> [Word8] -> Bytes forall b c a. (b -> c) -> (a -> b) -> a -> c . [Word8] -> ByteString LBS.pack ([Word8] -> Bytes) -> Gen [Word8] -> Gen Bytes forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen [Word8] forall a. Arbitrary a => Gen a arbitrary \end{code}