module Network.TLS.Types.Secret where
import Network.TLS.Imports
data EarlySecret
data HandshakeSecret
data ApplicationSecret
data ResumptionSecret
newtype BaseSecret a = BaseSecret ByteString
instance Show (BaseSecret a) where
show :: BaseSecret a -> String
show (BaseSecret ByteString
bs) = ByteString -> String
showBytesHex ByteString
bs
newtype AnyTrafficSecret a = AnyTrafficSecret ByteString
instance Show (AnyTrafficSecret a) where
show :: AnyTrafficSecret a -> String
show (AnyTrafficSecret ByteString
bs) = ByteString -> String
showBytesHex ByteString
bs
newtype ClientTrafficSecret a = ClientTrafficSecret ByteString
instance Show (ClientTrafficSecret a) where
show :: ClientTrafficSecret a -> String
show (ClientTrafficSecret ByteString
bs) = ByteString -> String
showBytesHex ByteString
bs
newtype ServerTrafficSecret a = ServerTrafficSecret ByteString
instance Show (ServerTrafficSecret a) where
show :: ServerTrafficSecret a -> String
show (ServerTrafficSecret ByteString
bs) = ByteString -> String
showBytesHex ByteString
bs
data SecretTriple a = SecretTriple
{ forall a. SecretTriple a -> BaseSecret a
triBase :: BaseSecret a
, forall a. SecretTriple a -> ClientTrafficSecret a
triClient :: ClientTrafficSecret a
, forall a. SecretTriple a -> ServerTrafficSecret a
triServer :: ServerTrafficSecret a
}
deriving (Int -> SecretTriple a -> ShowS
[SecretTriple a] -> ShowS
SecretTriple a -> String
(Int -> SecretTriple a -> ShowS)
-> (SecretTriple a -> String)
-> ([SecretTriple a] -> ShowS)
-> Show (SecretTriple a)
forall a. Int -> SecretTriple a -> ShowS
forall a. [SecretTriple a] -> ShowS
forall a. SecretTriple a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Int -> SecretTriple a -> ShowS
showsPrec :: Int -> SecretTriple a -> ShowS
$cshow :: forall a. SecretTriple a -> String
show :: SecretTriple a -> String
$cshowList :: forall a. [SecretTriple a] -> ShowS
showList :: [SecretTriple a] -> ShowS
Show)
data SecretPair a = SecretPair
{ forall a. SecretPair a -> BaseSecret a
pairBase :: BaseSecret a
, forall a. SecretPair a -> ClientTrafficSecret a
pairClient :: ClientTrafficSecret a
}
deriving (Int -> SecretPair a -> ShowS
[SecretPair a] -> ShowS
SecretPair a -> String
(Int -> SecretPair a -> ShowS)
-> (SecretPair a -> String)
-> ([SecretPair a] -> ShowS)
-> Show (SecretPair a)
forall a. Int -> SecretPair a -> ShowS
forall a. [SecretPair a] -> ShowS
forall a. SecretPair a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Int -> SecretPair a -> ShowS
showsPrec :: Int -> SecretPair a -> ShowS
$cshow :: forall a. SecretPair a -> String
show :: SecretPair a -> String
$cshowList :: forall a. [SecretPair a] -> ShowS
showList :: [SecretPair a] -> ShowS
Show)
type TrafficSecrets a = (ClientTrafficSecret a, ServerTrafficSecret a)
newtype MainSecret = MainSecret ByteString
instance Show MainSecret where
show :: MainSecret -> String
show (MainSecret ByteString
bs) = ByteString -> String
showBytesHex ByteString
bs