Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- makeSenderHandshake :: Key -> ByteString
- makeReceiverHandshake :: Key -> ByteString
- makeRecordKeys :: Key -> Either CryptoError (Key, Key)
- makeRelayHandshake :: Key -> Side -> ByteString
- senderTransitExchange :: EncryptedConnection -> [ConnectionHint] -> IO (Either CommunicationError TransitMsg)
- senderOfferExchange :: EncryptedConnection -> FilePath -> IO (Either Text FilePath)
- sendOffer :: EncryptedConnection -> Offer -> IO ()
- receiveOffer :: EncryptedConnection -> IO (Either ByteString Offer)
- sendMessageAck :: EncryptedConnection -> Text -> IO ()
- receiveMessageAck :: EncryptedConnection -> IO (Either CommunicationError ())
- senderHandshakeExchange :: TCPEndpoint -> Key -> Side -> IO (Either InvalidHandshake ())
- receiverHandshakeExchange :: TCPEndpoint -> Key -> Side -> IO (Either InvalidHandshake ())
- sendTransitMsg :: EncryptedConnection -> [Ability] -> [ConnectionHint] -> IO ()
- decodeTransitMsg :: ByteString -> Either CommunicationError TransitMsg
- makeAckMessage :: Key -> ByteString -> Either CryptoError CipherText
- receiveWormholeMessage :: EncryptedConnection -> IO ByteString
- sendWormholeMessage :: EncryptedConnection -> ByteString -> IO ()
- generateTransitSide :: MonadRandom m => m Side
- data InvalidHandshake
- sendRecord :: TCPEndpoint -> ByteString -> IO (Either CommunicationError Int)
- receiveRecord :: TCPEndpoint -> Key -> IO (Either CryptoError ByteString)
- unzipInto :: FilePath -> FilePath -> IO ()
Documentation
makeSenderHandshake :: Key -> ByteString Source #
Make a bytestring for the handshake message sent by the sender which is of the form "transit sender XXXXXXX..XX readynn" where XXXXXX..XX is the hex ascii representation of the sender handshake key.
makeReceiverHandshake :: Key -> ByteString Source #
Make a bytestring for the handshake message sent by the receiver which is of the form "transit receiver XXXX...XX readynn" where XXXX...XX is the receiver handshake key.
makeRecordKeys :: Key -> Either CryptoError (Key, Key) Source #
Make sender and receiver symmetric keys for the records transmission. Records are chunks of data corresponding to the blocks of the file. Sender record key is used for decrypting incoming records and receiver record key is for sending file_ack back to the sender.
makeRelayHandshake :: Key -> Side -> ByteString Source #
create relay handshake bytestring "please relay HEXHEX for side XXXXXn"
senderTransitExchange :: EncryptedConnection -> [ConnectionHint] -> IO (Either CommunicationError TransitMsg) Source #
senderTransitExchange
exchanges transit message with the peer.
Sender sends a transit message with its abilities and hints.
Receiver sends either another Transit message or an Error message.
senderOfferExchange :: EncryptedConnection -> FilePath -> IO (Either Text FilePath) Source #
Exchange offer message with the peer over the wormhole connection
sendOffer :: EncryptedConnection -> Offer -> IO () Source #
Send an offer message to the connected peer over the wormhole
receiveOffer :: EncryptedConnection -> IO (Either ByteString Offer) Source #
receive a message over wormhole and try to decode it as an offer message. If it is not an offer message, pass the raw bytestring as a Left value.
sendMessageAck :: EncryptedConnection -> Text -> IO () Source #
Send an Ack message as a regular text message encapsulated in
an Answer
message over the wormhole connection
receiveMessageAck :: EncryptedConnection -> IO (Either CommunicationError ()) Source #
Receive an Ack message over the wormhole connection
senderHandshakeExchange :: TCPEndpoint -> Key -> Side -> IO (Either InvalidHandshake ()) Source #
Sender side exchange of the handshake messages. Sender sends send-side handshake
message created by makeSenderHandshake
and concurrently receives the handshake
message from the receive side and compares it with the bytestring created by
makeReceiverHandshake
. If it matches, then it sends "gon" to the receiver, else
it sends "nevermindn" to the receiver and returns an InvalidHandshake
.
receiverHandshakeExchange :: TCPEndpoint -> Key -> Side -> IO (Either InvalidHandshake ()) Source #
Receiver side exchange of handshake messages. Receiver sends the receive-side
handshake message appended with "gon" and receives the handshake message from
the sender. It then compares the message received from the sender with the locally
computed sender handshake bytestring appended with "gon". If they don't match, it
returns an InvalidHandshake
.
sendTransitMsg :: EncryptedConnection -> [Ability] -> [ConnectionHint] -> IO () Source #
create and send a Transit message to the peer.
decodeTransitMsg :: ByteString -> Either CommunicationError TransitMsg Source #
Parse the given bytestring into a Transit Message
makeAckMessage :: Key -> ByteString -> Either CryptoError CipherText Source #
Create an encrypted Transit Ack message
receiveWormholeMessage :: EncryptedConnection -> IO ByteString Source #
Receive a bytestring via the established wormhole connection
sendWormholeMessage :: EncryptedConnection -> ByteString -> IO () Source #
Send a bytestring over the established wormhole connection
generateTransitSide :: MonadRandom m => m Side Source #
There is a separate 8-bytes of random side
for Transit protocol, which
is different from the side
used in the wormhole encrypted channel establishment
data InvalidHandshake Source #
Error type for the Peer module
InvalidHandshake | Handshake with the peer didn't succeed |
InvalidRelayHandshake | Handshake with the relay server didn't succeed |
Instances
Eq InvalidHandshake Source # | |
Defined in Transit.Internal.Peer (==) :: InvalidHandshake -> InvalidHandshake -> Bool (/=) :: InvalidHandshake -> InvalidHandshake -> Bool | |
Show InvalidHandshake Source # | |
Defined in Transit.Internal.Peer showsPrec :: Int -> InvalidHandshake -> ShowS show :: InvalidHandshake -> String showList :: [InvalidHandshake] -> ShowS | |
Exception InvalidHandshake Source # | |
Defined in Transit.Internal.Peer toException :: InvalidHandshake -> SomeException fromException :: SomeException -> Maybe InvalidHandshake displayException :: InvalidHandshake -> String |
sendRecord :: TCPEndpoint -> ByteString -> IO (Either CommunicationError Int) Source #
A Record is an encrypted chunk of byte string. On the wire, a header of 4 bytes which denotes the length of the payload is sent before sending the actual payload.
receiveRecord :: TCPEndpoint -> Key -> IO (Either CryptoError ByteString) Source #
Receive a packet corresponding to a record (4-byte header representing the length n, of the record, followed by n bytes of encrypted payload) and then decrypts and returns the payload.