Safe Haskell | None |
---|---|
Language | Haskell2010 |
Magic Wormhole is a technology for getting things from one computer to another, safely.
To use it, you must
- Start a
Session
with the Rendezvous server, to allow peers to find each other (runClient
) - Negotiate a shared
Nameplate
so peers can find each other on the server (allocate
,list
) - Use the shared
Nameplate
toopen
a sharedMailbox
- Use a secret password shared between peers to establish an encrypted connection (
withEncryptedConnection
)
Once you've done this, you can communicate with your peer via sendMessage
and receiveMessage
.
The password is never sent over the wire. Rather, it is used to negotiate a session key using SPAKE2, and that key itself is used to derive many per-message keys, so that each message is encrypted using NaCl SecretBox.
This library is a client library for the Rendezvous server and a library for communicating with Magic Wormhole peers.
Synopsis
- data Session
- runClient :: HasCallStack => WebSocketEndpoint -> AppID -> Side -> Maybe Socket -> (Session -> IO a) -> IO a
- newtype AppID = AppID Text
- newtype Side = Side Text
- generateSide :: MonadRandom randomly => randomly Side
- data WebSocketEndpoint = WebSocketEndpoint Hostname Port Path
- parseWebSocketEndpoint :: String -> Maybe WebSocketEndpoint
- allocate :: HasCallStack => Session -> IO Nameplate
- newtype Nameplate = Nameplate Text
- list :: HasCallStack => Session -> IO [Nameplate]
- claim :: HasCallStack => Session -> Nameplate -> IO Mailbox
- newtype Mailbox = Mailbox Text
- open :: HasCallStack => Session -> Mailbox -> IO Connection
- close :: HasCallStack => Session -> Maybe Mailbox -> Maybe Mood -> IO ()
- data ServerError
- = ResponseWithoutRequest ServerMessage
- | UnexpectedMessage ServerMessage
- | ErrorForNonRequest Text ClientMessage
- | Unwelcome Text
- | ParseError String
- data ClientError
- withEncryptedConnection :: Connection -> Password -> (EncryptedConnection -> IO a) -> IO a
- data Connection
- data EncryptedConnection
- deriveKey :: EncryptedConnection -> Purpose -> Key
- data PeerError
- data VersionsError
- data PakeError
- sendMessage :: EncryptedConnection -> PlainText -> IO ()
- receiveMessage :: EncryptedConnection -> STM PlainText
- newtype PlainText = PlainText {
- plainTextToByteString :: ByteString
- data Offer
- = Message Text
- | File FilePath FileOffset
- | Directory {
- directoryMode :: DirectoryMode
- dirName :: Text
- zipSize :: Natural
- numBytes :: Natural
- numFiles :: Natural
- data DirectoryMode = ZipFileDeflated
Client/server
Before you can communicate with a Magic Wormhole peer, you must first find them.
The way to do this is to establish a Session
with a Magic Wormhole Rendezvous server.
Establishing a session
:: HasCallStack | |
=> WebSocketEndpoint | The websocket to connect to |
-> AppID | ID for your application (e.g. example.com/your-application) |
-> Side | Identifier for your side |
-> Maybe Socket | Just an existing socket to use or Nothing to create and use a new one |
-> (Session -> IO a) | Action to perform inside the Magic Wormhole session |
-> IO a | The result of the action |
Run a Magic Wormhole Rendezvous client. Use this to interact with a Magic Wormhole server.
Will throw a ServerError
if the server declares we are unwelcome.
Short string to identify the application. Clients must use the same application ID if they wish to communicate with each other.
Recommendation is to use "$DNSNAME/$APPNAME", e.g.
the Python wormhole
command-line tool uses
lothar.com/wormhole/text-or-file-xfer
.
AppID Text |
Instances
Eq AppID Source # | |
Show AppID Source # | |
FromJSON AppID Source # | |
Defined in MagicWormhole.Internal.Messages parseJSON :: Value -> Parser AppID parseJSONList :: Value -> Parser [AppID] | |
ToJSON AppID Source # | |
Defined in MagicWormhole.Internal.Messages |
Short string used to differentiate between echoes of our own messages and real messages from other clients.
TODO: This needs to be cleanly encoded to ASCII, so update the type or provide a smart constructor.
Side Text |
Instances
Eq Side Source # | |
Show Side Source # | |
FromJSON Side Source # | |
Defined in MagicWormhole.Internal.Messages parseJSON :: Value -> Parser Side parseJSONList :: Value -> Parser [Side] | |
ToJSON Side Source # | |
Defined in MagicWormhole.Internal.Messages |
generateSide :: MonadRandom randomly => randomly Side Source #
Generate a random Side
Locating the server
Rendezvous servers are implemented as web sockets.
data WebSocketEndpoint Source #
Endpoint for a websocket connection.
Construct directly or with parseWebSocketEndpoint
.
Instances
Eq WebSocketEndpoint Source # | |
Defined in MagicWormhole.Internal.WebSockets (==) :: WebSocketEndpoint -> WebSocketEndpoint -> Bool (/=) :: WebSocketEndpoint -> WebSocketEndpoint -> Bool | |
Show WebSocketEndpoint Source # | |
Defined in MagicWormhole.Internal.WebSockets showsPrec :: Int -> WebSocketEndpoint -> ShowS show :: WebSocketEndpoint -> String showList :: [WebSocketEndpoint] -> ShowS |
parseWebSocketEndpoint :: String -> Maybe WebSocketEndpoint Source #
Parse a WebSocketEndpoint
.
Operations on the server
allocate :: HasCallStack => Session -> IO Nameplate Source #
Allocate a nameplate on the server.
Throws a ClientError
if the server rejects the message for any reason.
Identifier for a "nameplate".
A nameplate is a very short string that identifies one peer to another. Its
purpose is to allow peers to find each other without having to communicate
the Mailbox
identifier, which is generally too lengthy and cumbersome to
be easily shared between humans.
Typically, one peer will allocate a nameplate and then communicate it out-of-band to the other peer.
Nameplate Text |
Instances
Eq Nameplate Source # | |
Show Nameplate Source # | |
FromJSON Nameplate Source # | |
Defined in MagicWormhole.Internal.Messages parseJSON :: Value -> Parser Nameplate parseJSONList :: Value -> Parser [Nameplate] | |
ToJSON Nameplate Source # | |
Defined in MagicWormhole.Internal.Messages toEncoding :: Nameplate -> Encoding toJSONList :: [Nameplate] -> Value toEncodingList :: [Nameplate] -> Encoding |
list :: HasCallStack => Session -> IO [Nameplate] Source #
List the nameplates on the server.
Throws a ClientError
if the server rejects the message for any reason.
claim :: HasCallStack => Session -> Nameplate -> IO Mailbox Source #
Claim a nameplate on the server.
Throws a ClientError
if the server rejects the message for any reason.
Identifier for a mailbox.
A mailbox is a shared access point between Magic Wormhole peers within the
same application (specified by AppID
). To get a mailbox, you must first
acquire a Nameplate
and then claim that nameplate for your side with
claim
.
A mailbox ID is defined in the spec as a "large random string", but in practice is a 13 character, lower-case, alpha-numeric string.
Mailbox Text |
Instances
Eq Mailbox Source # | |
Show Mailbox Source # | |
FromJSON Mailbox Source # | |
Defined in MagicWormhole.Internal.Messages parseJSON :: Value -> Parser Mailbox parseJSONList :: Value -> Parser [Mailbox] | |
ToJSON Mailbox Source # | |
Defined in MagicWormhole.Internal.Messages toEncoding :: Mailbox -> Encoding toJSONList :: [Mailbox] -> Value toEncodingList :: [Mailbox] -> Encoding |
open :: HasCallStack => Session -> Mailbox -> IO Connection Source #
Open a mailbox on the server.
If there's already a mailbox open, the server will send an error message. In the current implementation, that error will arise in a strange and unexpected place.
See https://github.com/warner/magic-wormhole/issues/261#issuecomment-343192449
close :: HasCallStack => Session -> Maybe Mailbox -> Maybe Mood -> IO () Source #
Close a mailbox on the server.
Throws a ClientError
if the server rejects the message for any reason.
Errors
data ServerError Source #
Error due to weirdness from the server.
ResponseWithoutRequest ServerMessage | Server sent us a response for something that we hadn't requested. |
UnexpectedMessage ServerMessage | We were sent a message other than Welcome on connect, or a Welcome message at any other time. |
ErrorForNonRequest Text ClientMessage | We received an |
Unwelcome Text | Clients are not welcome on the server right now. |
ParseError String | We couldn't understand the message from the server. |
Instances
Eq ServerError Source # | |
Defined in MagicWormhole.Internal.Rendezvous (==) :: ServerError -> ServerError -> Bool (/=) :: ServerError -> ServerError -> Bool | |
Show ServerError Source # | |
Defined in MagicWormhole.Internal.Rendezvous showsPrec :: Int -> ServerError -> ShowS show :: ServerError -> String showList :: [ServerError] -> ShowS | |
Exception ServerError Source # | |
Defined in MagicWormhole.Internal.Rendezvous toException :: ServerError -> SomeException fromException :: SomeException -> Maybe ServerError displayException :: ServerError -> String |
data ClientError Source #
Error caused by misusing the client.
AlreadySent ClientMessage | We tried to do an RPC while another RPC with the same response type was in flight. See warner/magic-wormhole#260 for details. |
NotAnRPC ClientMessage | Tried to send a non-RPC as if it were an RPC (i.e. expecting a response). |
BadRequest Text ClientMessage | We sent a message that the server could not understand. |
Instances
Eq ClientError Source # | |
Defined in MagicWormhole.Internal.Rendezvous (==) :: ClientError -> ClientError -> Bool (/=) :: ClientError -> ClientError -> Bool | |
Show ClientError Source # | |
Defined in MagicWormhole.Internal.Rendezvous showsPrec :: Int -> ClientError -> ShowS show :: ClientError -> String showList :: [ClientError] -> ShowS | |
Exception ClientError Source # | |
Defined in MagicWormhole.Internal.Rendezvous toException :: ClientError -> SomeException fromException :: SomeException -> Maybe ClientError displayException :: ClientError -> String |
Peer-to-peer
Opening a Mailbox
shared with a peer gets you a Connection
,
but this is not enough to securely communicate with a peer.
The next step is to establish an EncryptedConnection
(via -- withEncryptedConnection
),
and then communicate with sendMessage
and receiveMessage
.
Establishing a secure connection
withEncryptedConnection Source #
:: Connection | Underlying to a peer. Get this with |
-> Password | The shared password that is the basis of the encryption. Construct with |
-> (EncryptedConnection -> IO a) | Action to perform with the encrypted connection. |
-> IO a | The result of the action |
Run an action that communicates with a Magic Wormhole peer through an encrypted connection.
Does the "pake" and "version" exchanges necessary to negotiate an encrypted
connection and then runs the user-provided action. This action can then use
sendMessage
and receiveMessage
to send & receive messages from its peer.
Can throw:
PeerError
, when we receive nonsensical data from the other peerPakeError
, when SPAKE2 cryptography failsVersionsError
, when we cannot agree on shared capabilities (this can sometimes imply SPAKE2 cryptography failure)
data Connection Source #
A connection to a peer via the Rendezvous server.
Normally construct this with open
.
data EncryptedConnection Source #
A Magic Wormhole peer-to-peer application session.
Construct one of these using withEncryptedConnection
.
You get one of these after you have found a peer, successfully negotatiated a shared key, and verified that negotiation by exchanging versions. (Note that this does not include the "verifying" step mentioned in magic-wormhole's documentation, which is about a human being verifying the correctness of the code).
All messages in this session, sent & received, are encrypted using keys derived from this shared key.
deriveKey :: EncryptedConnection -> Purpose -> Key Source #
Derive a new key for the given purpose
Construct a new key from the encrypted connection's session key for the given purpose
Errors
Something that went wrong with the client protocol.
Instances
Eq PeerError Source # | |
Show PeerError Source # | |
Exception PeerError Source # | |
Defined in MagicWormhole.Internal.ClientProtocol toException :: PeerError -> SomeException fromException :: SomeException -> Maybe PeerError displayException :: PeerError -> String |
data VersionsError Source #
An error occurred during versionExchange
.
Instances
Eq VersionsError Source # | |
Defined in MagicWormhole.Internal.Versions (==) :: VersionsError -> VersionsError -> Bool (/=) :: VersionsError -> VersionsError -> Bool | |
Show VersionsError Source # | |
Defined in MagicWormhole.Internal.Versions showsPrec :: Int -> VersionsError -> ShowS show :: VersionsError -> String showList :: [VersionsError] -> ShowS | |
Exception VersionsError Source # | |
Defined in MagicWormhole.Internal.Versions toException :: VersionsError -> SomeException fromException :: SomeException -> Maybe VersionsError displayException :: VersionsError -> String |
An error that occured during pakeExchange
.
Instances
Eq PakeError Source # | |
Show PakeError Source # | |
Exception PakeError Source # | |
Defined in MagicWormhole.Internal.Pake toException :: PakeError -> SomeException fromException :: SomeException -> Maybe PakeError displayException :: PakeError -> String |
Communicating with a peer
sendMessage :: EncryptedConnection -> PlainText -> IO () Source #
Send an encrypted message to the peer.
Obtain an EncryptedConnection
with withEncryptedConnection
.
The message will be encrypted using a one-off key deriving from the shared key.
receiveMessage :: EncryptedConnection -> STM PlainText Source #
Receive a decrypted message from the peer.
Obtain an EncryptedConnection
with withEncryptedConnection
.
Unencrypted text.
PlainText | |
|
Magic Wormhole applications
Once you've established an EncryptedConnection
to your peer, the world is your oyster.
You can send whatever data you'd like.
However, Magic Wormhole comes with at least one built-in "application": message and file transfer. This Haskell implementation only supports sending and receiving a simple message.
An offer made by a sender as part of the Magic Wormhole file transfer protocol.
Currently only supports sending simple text messages. A full version would also support sending files and directories.
Message Text | A simple text message. |
File FilePath FileOffset | Offer a File with filename and size. |
Directory | Offer a Directory |
|
Instances
Eq Offer Source # | |
Show Offer Source # | |
FromJSON Offer Source # | |
Defined in MagicWormhole.Internal.FileTransfer parseJSON :: Value -> Parser Offer parseJSONList :: Value -> Parser [Offer] | |
ToJSON Offer Source # | |
Defined in MagicWormhole.Internal.FileTransfer |
data DirectoryMode Source #
Textual representation of the format in which the directory tree is encoded
Instances
Eq DirectoryMode Source # | |
Defined in MagicWormhole.Internal.FileTransfer (==) :: DirectoryMode -> DirectoryMode -> Bool (/=) :: DirectoryMode -> DirectoryMode -> Bool | |
Show DirectoryMode Source # | |
Defined in MagicWormhole.Internal.FileTransfer showsPrec :: Int -> DirectoryMode -> ShowS show :: DirectoryMode -> String showList :: [DirectoryMode] -> ShowS | |
FromJSON DirectoryMode Source # | |
Defined in MagicWormhole.Internal.FileTransfer parseJSON :: Value -> Parser DirectoryMode parseJSONList :: Value -> Parser [DirectoryMode] | |
ToJSON DirectoryMode Source # | |
Defined in MagicWormhole.Internal.FileTransfer toJSON :: DirectoryMode -> Value toEncoding :: DirectoryMode -> Encoding toJSONList :: [DirectoryMode] -> Value toEncodingList :: [DirectoryMode] -> Encoding |