| Maintainer | John Galt <centromere@users.noreply.github.com> | 
|---|---|
| Stability | experimental | 
| Portability | POSIX | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Crypto.Noise.Internal.HandshakeState
Description
- class Monad m => MonadHandshake m where
- tokenPreLS :: m ()
 - tokenPreRS :: m ()
 - tokenPreLE :: m ()
 - tokenPreRE :: m ()
 - tokenRE :: ByteString -> m ByteString
 - tokenRS :: ByteString -> m ByteString
 - tokenWE :: MonadIO m => m ByteString
 - tokenWS :: m ByteString
 - tokenDHEE :: m ()
 - tokenDHES :: m ()
 - tokenDHSE :: m ()
 - tokenDHSS :: m ()
 
 - data HandshakeState c d h
 - type Descriptor c d h a = DescriptorT c d h Identity a
 - type DescriptorIO c d h a = DescriptorT c d h IO a
 - runDescriptorT :: Monad m => DescriptorT c d h m a -> HandshakeState c d h -> m (a, HandshakeState c d h)
 - getRemoteStaticKey :: Curve d => HandshakeState c d h -> PublicKey d
 - handshakeState :: (Cipher c, Curve d, Hash h) => ScrubbedBytes -> Maybe (KeyPair d) -> Maybe (KeyPair d) -> Maybe (PublicKey d) -> Maybe (PublicKey d) -> Maybe (Descriptor c d h ()) -> HandshakeState c d h
 - writeHandshakeMsg :: (Cipher c, Curve d, Hash h) => HandshakeState c d h -> DescriptorIO c d h ByteString -> Plaintext -> IO (ByteString, HandshakeState c d h)
 - readHandshakeMsg :: (Cipher c, Curve d, Hash h) => HandshakeState c d h -> ByteString -> (ByteString -> Descriptor c d h ByteString) -> (Plaintext, HandshakeState c d h)
 - writeHandshakeMsgFinal :: (Cipher c, Curve d, Hash h) => HandshakeState c d h -> DescriptorIO c d h ByteString -> Plaintext -> IO (ByteString, CipherState c, CipherState c)
 - readHandshakeMsgFinal :: (Cipher c, Curve d, Hash h) => HandshakeState c d h -> ByteString -> (ByteString -> Descriptor c d h ByteString) -> (Plaintext, CipherState c, CipherState c)
 - encryptPayload :: Cipher c => Plaintext -> CipherState c -> (ByteString, CipherState c)
 - decryptPayload :: Cipher c => ByteString -> CipherState c -> (Plaintext, CipherState c)
 
Classes
class Monad m => MonadHandshake m where Source
Methods
tokenPreLS :: m () Source
tokenPreRS :: m () Source
tokenPreLE :: m () Source
tokenPreRE :: m () Source
tokenRE :: ByteString -> m ByteString Source
tokenRS :: ByteString -> m ByteString Source
tokenWE :: MonadIO m => m ByteString Source
tokenWS :: m ByteString Source
Types
data HandshakeState c d h Source
Contains the state of a handshake.
type Descriptor c d h a = DescriptorT c d h Identity a Source
Represents a series of operations that can be performed on a Noise message.
type DescriptorIO c d h a = DescriptorT c d h IO a Source
Represents a series of operations that will result in a Noise message. This must be done in IO to facilitate the generation of ephemeral keys.
Functions
runDescriptorT :: Monad m => DescriptorT c d h m a -> HandshakeState c d h -> m (a, HandshakeState c d h) Source
getRemoteStaticKey :: Curve d => HandshakeState c d h -> PublicKey d Source
Returns the remote party's public static key. This is useful when the static key has been transmitted to you and you want to save it for future use.
Arguments
| :: (Cipher c, Curve d, Hash h) | |
| => ScrubbedBytes | Handshake name  | 
| -> Maybe (KeyPair d) | Local static key  | 
| -> Maybe (KeyPair d) | Local ephemeral key  | 
| -> Maybe (PublicKey d) | Remote public static key  | 
| -> Maybe (PublicKey d) | Remote public ephemeral key  | 
| -> Maybe (Descriptor c d h ()) | Pre-message processing descriptor  | 
| -> HandshakeState c d h | 
Constructs a HandshakeState. The keys you need to provide are dependent on the type of handshake you are using. If you fail to provide a key that your handshake type depends on, you will receive an error such as "local static key not set".
Arguments
| :: (Cipher c, Curve d, Hash h) | |
| => HandshakeState c d h | The handshake state  | 
| -> DescriptorIO c d h ByteString | A descriptor for this particular message  | 
| -> Plaintext | Optional message to transmit  | 
| -> IO (ByteString, HandshakeState c d h) | 
Creates a handshake message. The plaintext can be left empty if no plaintext is to be transmitted. All subsequent handshake processing must use the returned state.
Arguments
| :: (Cipher c, Curve d, Hash h) | |
| => HandshakeState c d h | The handshake state  | 
| -> ByteString | The handshake message received  | 
| -> (ByteString -> Descriptor c d h ByteString) | A descriptor for this particular message  | 
| -> (Plaintext, HandshakeState c d h) | 
Reads a handshake message. All subsequent handshake processing must use the returned state.
Arguments
| :: (Cipher c, Curve d, Hash h) | |
| => HandshakeState c d h | The handshake state  | 
| -> DescriptorIO c d h ByteString | A descriptor for this particular message  | 
| -> Plaintext | Optional message to transmit  | 
| -> IO (ByteString, CipherState c, CipherState c) | 
The final call of a handshake negotiation. Used to generate a pair of CipherStates, one for each transmission direction.
Arguments
| :: (Cipher c, Curve d, Hash h) | |
| => HandshakeState c d h | The handshake state  | 
| -> ByteString | The handshake message received  | 
| -> (ByteString -> Descriptor c d h ByteString) | A descriptor for this particular message  | 
| -> (Plaintext, CipherState c, CipherState c) | 
The final call of a handshake negotiation. Used to generate a pair of CipherStates, one for each transmission direction.
Arguments
| :: Cipher c | |
| => Plaintext | The data to encrypt  | 
| -> CipherState c | The CipherState to use for encryption  | 
| -> (ByteString, CipherState c) | 
Encrypts a payload. The returned CipherState must be used for all
   subsequent calls.
Arguments
| :: Cipher c | |
| => ByteString | The data to decrypt  | 
| -> CipherState c | The CipherState to use for decryption  | 
| -> (Plaintext, CipherState c) | 
Decrypts a payload. The returned CipherState must be used for all
   subsequent calls.