toxcore-0.2.11: A Tox protocol implementation in Haskell

Safe HaskellSafe
LanguageHaskell2010

Network.Tox.SaveData

Documentation

newtype SaveData Source #

Constructors

SaveData [Section] 
Instances
Eq SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

Read SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

Show SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

Generic SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

Associated Types

type Rep SaveData :: Type -> Type #

Methods

from :: SaveData -> Rep SaveData x #

to :: Rep SaveData x -> SaveData #

Arbitrary SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

Binary SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

put :: SaveData -> Put #

get :: Get SaveData #

putList :: [SaveData] -> Put #

type Rep SaveData Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep SaveData = D1 (MetaData "SaveData" "Network.Tox.SaveData" "toxcore-0.2.11-AzzkmiDUfjL8GGvWK827C9" True) (C1 (MetaCons "SaveData" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Section])))

data Section Source #

Instances
Eq Section Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

(==) :: Section -> Section -> Bool #

(/=) :: Section -> Section -> Bool #

Read Section Source # 
Instance details

Defined in Network.Tox.SaveData

Show Section Source # 
Instance details

Defined in Network.Tox.SaveData

Generic Section Source # 
Instance details

Defined in Network.Tox.SaveData

Associated Types

type Rep Section :: Type -> Type #

Methods

from :: Section -> Rep Section x #

to :: Rep Section x -> Section #

Arbitrary Section Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep Section Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep Section = D1 (MetaData "Section" "Network.Tox.SaveData" "toxcore-0.2.11-AzzkmiDUfjL8GGvWK827C9" False) (((C1 (MetaCons "SectionNospamKeys" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NospamKeys)) :+: C1 (MetaCons "SectionDHT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DHT))) :+: (C1 (MetaCons "SectionFriends" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Friends)) :+: (C1 (MetaCons "SectionName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes)) :+: C1 (MetaCons "SectionStatusMessage" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes))))) :+: ((C1 (MetaCons "SectionStatus" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)) :+: C1 (MetaCons "SectionTcpRelays" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Nodes))) :+: (C1 (MetaCons "SectionPathNodes" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Nodes)) :+: (C1 (MetaCons "SectionConferences" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Conferences)) :+: C1 (MetaCons "SectionEOF" PrefixI False) (U1 :: Type -> Type)))))

data NospamKeys Source #

Instances
Eq NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

Read NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

Show NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

Generic NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

Associated Types

type Rep NospamKeys :: Type -> Type #

Arbitrary NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

Binary NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep NospamKeys Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep NospamKeys = D1 (MetaData "NospamKeys" "Network.Tox.SaveData" "toxcore-0.2.11-AzzkmiDUfjL8GGvWK827C9" False) (C1 (MetaCons "NospamKeys" PrefixI True) (S1 (MetaSel (Just "nospam") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32) :*: (S1 (MetaSel (Just "publicKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PublicKey) :*: S1 (MetaSel (Just "secretKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SecretKey))))

newtype Friends Source #

Constructors

Friends [Friend] 
Instances
Eq Friends Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

(==) :: Friends -> Friends -> Bool #

(/=) :: Friends -> Friends -> Bool #

Read Friends Source # 
Instance details

Defined in Network.Tox.SaveData

Show Friends Source # 
Instance details

Defined in Network.Tox.SaveData

Generic Friends Source # 
Instance details

Defined in Network.Tox.SaveData

Associated Types

type Rep Friends :: Type -> Type #

Methods

from :: Friends -> Rep Friends x #

to :: Rep Friends x -> Friends #

Arbitrary Friends Source # 
Instance details

Defined in Network.Tox.SaveData

Binary Friends Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

put :: Friends -> Put #

get :: Get Friends #

putList :: [Friends] -> Put #

type Rep Friends Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep Friends = D1 (MetaData "Friends" "Network.Tox.SaveData" "toxcore-0.2.11-AzzkmiDUfjL8GGvWK827C9" True) (C1 (MetaCons "Friends" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Friend])))

newtype Bytes Source #

Constructors

Bytes ByteString 
Instances
Eq Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

(==) :: Bytes -> Bytes -> Bool #

(/=) :: Bytes -> Bytes -> Bool #

Read Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

Show Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Generic Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Arbitrary Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

arbitrary :: Gen Bytes #

shrink :: Bytes -> [Bytes] #

Binary Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

Methods

put :: Bytes -> Put #

get :: Get Bytes #

putList :: [Bytes] -> Put #

type Rep Bytes Source # 
Instance details

Defined in Network.Tox.SaveData

type Rep Bytes = D1 (MetaData "Bytes" "Network.Tox.SaveData" "toxcore-0.2.11-AzzkmiDUfjL8GGvWK827C9" True) (C1 (MetaCons "Bytes" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))