| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
MagicWormhole.Internal.Rendezvous
Description
Interactions with a Magic Wormhole Rendezvous server.
Intended to be imported qualified, e.g. ``` import qualified MagicWormhole.Internal.Rendezvous as Rendezvous ```
Synopsis
- ping :: HasCallStack => Session -> Int -> IO Int
- list :: HasCallStack => Session -> IO [Nameplate]
- allocate :: HasCallStack => Session -> IO Nameplate
- claim :: HasCallStack => Session -> Nameplate -> IO Mailbox
- release :: HasCallStack => Session -> Maybe Nameplate -> IO ()
- open :: HasCallStack => Session -> Mailbox -> IO Connection
- close :: HasCallStack => Session -> Maybe Mailbox -> Maybe Mood -> IO ()
- runClient :: HasCallStack => WebSocketEndpoint -> AppID -> Side -> Maybe Socket -> (Session -> IO a) -> IO a
- data Session
- data ServerError- = ResponseWithoutRequest ServerMessage
- | UnexpectedMessage ServerMessage
- | ErrorForNonRequest Text ClientMessage
- | Unwelcome Text
- | ParseError String
 
- data ClientError
Specific RPCs
ping :: HasCallStack => Session -> Int -> IO Int Source #
Ping the server.
This is an in-band ping, used mostly for testing. It is not necessary to keep the connection alive.
Throws a ClientError if the server rejects the message for any reason.
list :: HasCallStack => Session -> IO [Nameplate] Source #
List the nameplates on the server.
Throws a ClientError if the server rejects the message for any reason.
allocate :: HasCallStack => Session -> IO Nameplate Source #
Allocate a nameplate 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.
release :: HasCallStack => Session -> Maybe Nameplate -> IO () Source #
Release a nameplate on the server.
TODO: Document semantics around "optional" nameplate.
TODO: Make this impossible to call unless we have already claimed a namespace.
Throws a ClientError if the server rejects the message for any reason.
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.
Running a Rendezvous client
Arguments
| :: 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.
Errors
data ServerError Source #
Error due to weirdness from the server.
Constructors
| 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 | |
| Show ServerError Source # | |
| Defined in MagicWormhole.Internal.Rendezvous Methods showsPrec :: Int -> ServerError -> ShowS show :: ServerError -> String showList :: [ServerError] -> ShowS | |
| Exception ServerError Source # | |
| Defined in MagicWormhole.Internal.Rendezvous Methods toException :: ServerError -> SomeException fromException :: SomeException -> Maybe ServerError displayException :: ServerError -> String | |
data ClientError Source #
Error caused by misusing the client.
Constructors
| 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 | |
| Show ClientError Source # | |
| Defined in MagicWormhole.Internal.Rendezvous Methods showsPrec :: Int -> ClientError -> ShowS show :: ClientError -> String showList :: [ClientError] -> ShowS | |
| Exception ClientError Source # | |
| Defined in MagicWormhole.Internal.Rendezvous Methods toException :: ClientError -> SomeException fromException :: SomeException -> Maybe ClientError displayException :: ClientError -> String | |