cacophony-0.10.1: A library implementing the Noise protocol.

MaintainerJohn Galt <jgalt@centromere.net>
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Crypto.Noise.Internal.Handshake.State

Contents

Description

 
Synopsis

Documentation

data HandshakeRole Source #

Represents the side of the conversation upon which a party resides.

data HandshakeOpts d Source #

Represents the various options and keys for a handshake parameterized by the DH method.

data HandshakeState c d h Source #

Holds all state associated with the interpreter.

Instances
MonadState (HandshakeState c d h) (Handshake c d h) Source # 
Instance details

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 #

hsPSKMode :: forall c d h. Lens' (HandshakeState c d h) Bool Source #

hsOpts :: forall c d h d. Lens (HandshakeState c d h) (HandshakeState c d h) (HandshakeOpts d) (HandshakeOpts d) 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.

Instances
Monad (Handshake c d h) Source # 
Instance details

Defined in Crypto.Noise.Internal.Handshake.State

Methods

(>>=) :: Handshake c d h a -> (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 b #

return :: a -> Handshake c d h a #

fail :: String -> Handshake c d h a #

Functor (Handshake c d h) Source # 
Instance details

Defined in Crypto.Noise.Internal.Handshake.State

Methods

fmap :: (a -> b) -> Handshake c d h a -> Handshake c d h b #

(<$) :: a -> Handshake c d h b -> Handshake c d h a #

Applicative (Handshake c d h) Source # 
Instance details

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 #

MonadThrow (Handshake c d h) Source # 
Instance details

Defined in Crypto.Noise.Internal.Handshake.State

Methods

throwM :: Exception e => e -> Handshake c d h a #

MonadState (HandshakeState c d h) (Handshake c d h) Source # 
Instance details

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 #

Constructs a HandshakeState from a given set of options and a protocol name (such as NN or IK).

Orphan instances

(Functor f, MonadState s m) => MonadState s (Coroutine f m) Source # 
Instance details

Methods

get :: Coroutine f m s #

put :: s -> Coroutine f m () #

state :: (s -> (a, s)) -> Coroutine f m a #

(Functor f, MonadThrow m) => MonadThrow (Coroutine f m) Source # 
Instance details

Methods

throwM :: Exception e => e -> Coroutine f m a #