module Network.TLS.Handshake.Control (
    ClientState (..),
    ServerState (..),
    EarlySecretInfo (..),
    HandshakeSecretInfo (..),
    ApplicationSecretInfo (..),
    NegotiatedProtocol,
) where

import Network.TLS.Cipher
import Network.TLS.Imports
import Network.TLS.Struct
import Network.TLS.Types

----------------------------------------------------------------

-- | ID of the application-level protocol negotiated between client and server.
-- See values listed in the <https://www.iana.org/assignments/tls-extensiontype-values/tls-extensiontype-values.xhtml#alpn-protocol-ids IANA registry>.
type NegotiatedProtocol = ByteString

-- | Handshake information generated for traffic at 0-RTT level.
data EarlySecretInfo = EarlySecretInfo Cipher (ClientTrafficSecret EarlySecret)
    deriving (Int -> EarlySecretInfo -> ShowS
[EarlySecretInfo] -> ShowS
EarlySecretInfo -> String
(Int -> EarlySecretInfo -> ShowS)
-> (EarlySecretInfo -> String)
-> ([EarlySecretInfo] -> ShowS)
-> Show EarlySecretInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EarlySecretInfo -> ShowS
showsPrec :: Int -> EarlySecretInfo -> ShowS
$cshow :: EarlySecretInfo -> String
show :: EarlySecretInfo -> String
$cshowList :: [EarlySecretInfo] -> ShowS
showList :: [EarlySecretInfo] -> ShowS
Show)

-- | Handshake information generated for traffic at handshake level.
data HandshakeSecretInfo
    = HandshakeSecretInfo Cipher (TrafficSecrets HandshakeSecret)
    deriving (Int -> HandshakeSecretInfo -> ShowS
[HandshakeSecretInfo] -> ShowS
HandshakeSecretInfo -> String
(Int -> HandshakeSecretInfo -> ShowS)
-> (HandshakeSecretInfo -> String)
-> ([HandshakeSecretInfo] -> ShowS)
-> Show HandshakeSecretInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HandshakeSecretInfo -> ShowS
showsPrec :: Int -> HandshakeSecretInfo -> ShowS
$cshow :: HandshakeSecretInfo -> String
show :: HandshakeSecretInfo -> String
$cshowList :: [HandshakeSecretInfo] -> ShowS
showList :: [HandshakeSecretInfo] -> ShowS
Show)

-- | Handshake information generated for traffic at application level.
newtype ApplicationSecretInfo = ApplicationSecretInfo (TrafficSecrets ApplicationSecret)
    deriving (Int -> ApplicationSecretInfo -> ShowS
[ApplicationSecretInfo] -> ShowS
ApplicationSecretInfo -> String
(Int -> ApplicationSecretInfo -> ShowS)
-> (ApplicationSecretInfo -> String)
-> ([ApplicationSecretInfo] -> ShowS)
-> Show ApplicationSecretInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationSecretInfo -> ShowS
showsPrec :: Int -> ApplicationSecretInfo -> ShowS
$cshow :: ApplicationSecretInfo -> String
show :: ApplicationSecretInfo -> String
$cshowList :: [ApplicationSecretInfo] -> ShowS
showList :: [ApplicationSecretInfo] -> ShowS
Show)

----------------------------------------------------------------

data ClientState
    = SendClientHello (Maybe EarlySecretInfo)
    | RecvServerHello HandshakeSecretInfo
    | SendClientFinished [ExtensionRaw] ApplicationSecretInfo

data ServerState
    = SendServerHello [ExtensionRaw] (Maybe EarlySecretInfo) HandshakeSecretInfo
    | SendServerFinished ApplicationSecretInfo