| Maintainer | John Galt <jgalt@centromere.net> |
|---|---|
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Crypto.Noise.Internal.Handshake.State
Contents
Description
Synopsis
- data HandshakeRole
- data HandshakeOpts d = HandshakeOpts {
- _hoRole :: HandshakeRole
- _hoPrologue :: Plaintext
- _hoLocalEphemeral :: Maybe (KeyPair d)
- _hoLocalStatic :: Maybe (KeyPair d)
- _hoRemoteEphemeral :: Maybe (PublicKey d)
- _hoRemoteStatic :: Maybe (PublicKey d)
- hoRole :: forall d. Lens' (HandshakeOpts d) HandshakeRole
- hoRemoteStatic :: forall d. Lens' (HandshakeOpts d) (Maybe (PublicKey d))
- hoRemoteEphemeral :: forall d. Lens' (HandshakeOpts d) (Maybe (PublicKey d))
- hoPrologue :: forall d. Lens' (HandshakeOpts d) Plaintext
- hoLocalStatic :: forall d. Lens' (HandshakeOpts d) (Maybe (KeyPair d))
- hoLocalEphemeral :: forall d. Lens' (HandshakeOpts d) (Maybe (KeyPair d))
- data HandshakeState c d h = HandshakeState {}
- hsSymmetricState :: forall c d h c h. Lens (HandshakeState c d h) (HandshakeState c d h) (SymmetricState c h) (SymmetricState c h)
- hsPSKMode :: forall c d h. Lens' (HandshakeState c d h) Bool
- hsOpts :: forall c d h d. Lens (HandshakeState c d h) (HandshakeState c d h) (HandshakeOpts d) (HandshakeOpts d)
- hsMsgBuffer :: forall c d h. Lens' (HandshakeState c d h) ScrubbedBytes
- data HandshakeResult
- newtype Handshake c d h r = Handshake {
- runHandshake :: Coroutine (Request HandshakeResult ScrubbedBytes) (StateT (HandshakeState c d h) Catch) r
- defaultHandshakeOpts :: HandshakeRole -> Plaintext -> HandshakeOpts d
- setLocalEphemeral :: Maybe (KeyPair d) -> HandshakeOpts d -> HandshakeOpts d
- setLocalStatic :: Maybe (KeyPair d) -> HandshakeOpts d -> HandshakeOpts d
- setRemoteEphemeral :: Maybe (PublicKey d) -> HandshakeOpts d -> HandshakeOpts d
- setRemoteStatic :: Maybe (PublicKey d) -> HandshakeOpts d -> HandshakeOpts d
- mkHandshakeName :: forall c d h proxy. (Cipher c, DH d, Hash h) => ByteString -> proxy (c, d, h) -> ScrubbedBytes
- handshakeState :: forall c d h. (Cipher c, DH d, Hash h) => HandshakeOpts d -> HandshakePattern -> HandshakeState c d h
Documentation
data HandshakeRole Source #
Represents the side of the conversation upon which a party resides.
Constructors
| InitiatorRole | |
| ResponderRole |
Instances
| Show HandshakeRole Source # | |
Defined in Crypto.Noise.Internal.Handshake.State Methods showsPrec :: Int -> HandshakeRole -> ShowS # show :: HandshakeRole -> String # showList :: [HandshakeRole] -> ShowS # | |
| Eq HandshakeRole Source # | |
Defined in Crypto.Noise.Internal.Handshake.State Methods (==) :: HandshakeRole -> HandshakeRole -> Bool # (/=) :: HandshakeRole -> HandshakeRole -> Bool # | |
data HandshakeOpts d Source #
Represents the various options and keys for a handshake parameterized by
the DH method.
Constructors
| HandshakeOpts | |
Fields
| |
hoRole :: forall d. Lens' (HandshakeOpts d) HandshakeRole Source #
hoRemoteStatic :: forall d. Lens' (HandshakeOpts d) (Maybe (PublicKey d)) Source #
hoRemoteEphemeral :: forall d. Lens' (HandshakeOpts d) (Maybe (PublicKey d)) Source #
hoPrologue :: forall d. Lens' (HandshakeOpts d) Plaintext Source #
hoLocalStatic :: forall d. Lens' (HandshakeOpts d) (Maybe (KeyPair d)) Source #
hoLocalEphemeral :: forall d. Lens' (HandshakeOpts d) (Maybe (KeyPair d)) Source #
data HandshakeState c d h Source #
Holds all state associated with the interpreter.
Constructors
| HandshakeState | |
Fields
| |
Instances
| MonadState (HandshakeState c d h) (Handshake c d h) Source # | |
Defined in Crypto.Noise.Internal.Handshake.State Methods get :: Handshake c d h (HandshakeState c d h) # put :: HandshakeState c d h -> Handshake c d h () # state :: (HandshakeState c d h -> (a, HandshakeState c d h)) -> Handshake c d h a # | |
hsSymmetricState :: forall c d h c h. Lens (HandshakeState c d h) (HandshakeState c d h) (SymmetricState c h) (SymmetricState c h) Source #
hsOpts :: forall c d h d. Lens (HandshakeState c d h) (HandshakeState c d h) (HandshakeOpts d) (HandshakeOpts d) Source #
hsMsgBuffer :: forall c d h. Lens' (HandshakeState c d h) ScrubbedBytes Source #
data HandshakeResult Source #
This data structure is yielded by the coroutine when more data is needed.
newtype Handshake c d h r Source #
All HandshakePattern interpreters run within this Monad.
Constructors
| Handshake | |
Fields
| |
Instances
| Applicative (Handshake c d h) Source # | |
Defined in Crypto.Noise.Internal.Handshake.State Methods pure :: a -> Handshake c d h a # (<*>) :: Handshake c d h (a -> b) -> Handshake c d h a -> Handshake c d h b # liftA2 :: (a -> b -> c0) -> Handshake c d h a -> Handshake c d h b -> Handshake c d h c0 # (*>) :: Handshake c d h a -> Handshake c d h b -> Handshake c d h b # (<*) :: Handshake c d h a -> Handshake c d h b -> Handshake c d h a # | |
| Functor (Handshake c d h) Source # | |
| Monad (Handshake c d h) Source # | |
| MonadThrow (Handshake c d h) Source # | |
Defined in Crypto.Noise.Internal.Handshake.State Methods throwM :: (HasCallStack, Exception e) => e -> Handshake c d h a # | |
| MonadState (HandshakeState c d h) (Handshake c d h) Source # | |
Defined in Crypto.Noise.Internal.Handshake.State Methods get :: Handshake c d h (HandshakeState c d h) # put :: HandshakeState c d h -> Handshake c d h () # state :: (HandshakeState c d h -> (a, HandshakeState c d h)) -> Handshake c d h a # | |
defaultHandshakeOpts :: HandshakeRole -> Plaintext -> HandshakeOpts d Source #
defaultHandshakeOpts role prologue returns a default set of handshake
options. All keys are set to Nothing.
setLocalEphemeral :: Maybe (KeyPair d) -> HandshakeOpts d -> HandshakeOpts d Source #
Sets the local ephemeral key.
setLocalStatic :: Maybe (KeyPair d) -> HandshakeOpts d -> HandshakeOpts d Source #
Sets the local static key.
setRemoteEphemeral :: Maybe (PublicKey d) -> HandshakeOpts d -> HandshakeOpts d Source #
Sets the remote ephemeral key (rarely needed).
setRemoteStatic :: Maybe (PublicKey d) -> HandshakeOpts d -> HandshakeOpts d Source #
Sets the remote static key.
mkHandshakeName :: forall c d h proxy. (Cipher c, DH d, Hash h) => ByteString -> proxy (c, d, h) -> ScrubbedBytes Source #
Given a protocol name, returns the full handshake name according to the rules in section 8.
handshakeState :: forall c d h. (Cipher c, DH d, Hash h) => HandshakeOpts d -> HandshakePattern -> HandshakeState c d h Source #
Orphan instances
| (Functor f, MonadState s m) => MonadState s (Coroutine f m) Source # | |
| (Functor f, MonadThrow m) => MonadThrow (Coroutine f m) Source # | |
Methods throwM :: (HasCallStack, Exception e) => e -> Coroutine f m a # | |