hwormhole-0.2.0.1: magic-wormhole client

Safe HaskellNone
LanguageHaskell2010

Transit.Internal.Peer

Contents

Description

 
Synopsis

Documentation

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.

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

handshakeExchange :: Mode -> TCPEndpoint -> Key -> Side -> IO (Either InvalidHandshake ()) Source #

Exchange transit handshake message

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

Constructors

InvalidHandshake

Handshake with the peer didn't succeed

InvalidRelayHandshake

Handshake with the relay server didn't succeed

Instances
Eq InvalidHandshake Source # 
Instance details

Defined in Transit.Internal.Peer

Show InvalidHandshake Source # 
Instance details

Defined in Transit.Internal.Peer

Methods

showsPrec :: Int -> InvalidHandshake -> ShowS

show :: InvalidHandshake -> String

showList :: [InvalidHandshake] -> ShowS

Exception InvalidHandshake Source # 
Instance details

Defined in Transit.Internal.Peer

Methods

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.

unzipInto :: FilePath -> FilePath -> IO () Source #

unzip the given zip file into the especified directory under current working directory

data Mode Source #

Client mode

Constructors

Send 
Receive 
Instances
Eq Mode Source # 
Instance details

Defined in Transit.Internal.Peer

Methods

(==) :: Mode -> Mode -> Bool

(/=) :: Mode -> Mode -> Bool

Show Mode Source # 
Instance details

Defined in Transit.Internal.Peer

Methods

showsPrec :: Int -> Mode -> ShowS

show :: Mode -> String

showList :: [Mode] -> ShowS

for tests

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.

makeRelayHandshake :: Key -> Side -> ByteString Source #

create relay handshake bytestring "please relay HEXHEX for side XXXXXn"