engine-io-1.2.22: A Haskell implementation of Engine.IO

Safe HaskellNone
LanguageHaskell2010

Network.EngineIO

Contents

Synopsis

Documentation

Network.EngineIO is a Haskell of implementation of Engine.IO, a real-time framework for the web. Engine.IO provides you with an abstraction for doing real-time communication between a server and a client. Engine.IO abstracts the framing and transport away, so that you can have real-time communication over long-polling HTTP requests, which are later upgraded to web sockets, if available.

Network.EngineIO needs to be provided with a ServerAPI in order to be run. ServerAPI informs us how to fetch request headers, write HTTP responses to the client, and run web socket applications. Hackage contains implementations of ServerAPI as:

If you write your own implementation of ServerAPI, please share it on Hackage and I will link to it from here.

Example Usage

A simple echo server is easy to write with Engine.IO. The following imports will be required:

import Control.Concurrent.STM
import Control.Monad (forever)
import Network.EngineIO
import Network.EngineIO.Snap
import Snap.Http.Server

Next, we write the implementation of our per-socket processing logic. For this application we simply receive from the socket, and then send the result back to the socket. We wrap this all in forever as this connection should never terminate.

handleSocket :: MonadIO m => Socket -> m SocketApp
handleSocket s = return $ SocketApp app onDisconnect
  where
   app = forever $ STM.atomically $ receive s >>= EIO.send s
   onDisconnect = STM.atomically $ send s $ TextPacket "Bye!"

Finally, we add a main function to our application to launch it. I'll use engine-io-snap as my server implementation:

main :: IO ()
main = do
  eio <- initialize
  quickHttpServe $ handler eio handleSocket snapAPI

This means that any URL works as the Engine.IO server, which is sufficient for our example. In a real production application, you will probably want to nest the handler under /engine.io.

Running Engine.IO applications

initialize :: IO EngineIO Source #

initialize initializes a new Engine.IO server. You can later serve this session by using handler.

handler :: MonadIO m => EngineIO -> (Socket -> m SocketApp) -> ServerAPI m -> m () Source #

Build the necessary handler for Engine.IO. The result of this function is a computation that you should serve under the engine.io path.

handler takes a function as an argument that is called every time a new session is created. This function runs in the m monad, so you have access to initial web request, which may be useful for performing authentication or collecting cookies. This function then returns a SocketApp, describing the main loop and an action to perform on socket disconnection.

data EngineIO Source #

An opaque data type representing an open Engine.IO server.

data ServerAPI m Source #

A dictionary of functions that Engine.IO needs in order to provide communication channels.

Constructors

ServerAPI 

Fields

data SocketApp Source #

The application to run for the duration of a connected socket.

Constructors

SocketApp 

Fields

  • saApp :: IO ()

    An IO action to run for the duration of the socket's lifetime. If this action terminates, the connection will be closed. You will likely want to loop forever and block as appropriate with receive.

  • saOnDisconnect :: IO ()

    An action to execute when the connection is closed, either by saApp terminating, or the client disconnecting.

Interacting with Sockets

send :: Socket -> PacketContent -> STM () Source #

Send a packet to the client. This is a non-blocking write.

receive :: Socket -> STM PacketContent Source #

Receive data from the client, blocking if the input queue is empty.

data Socket Source #

A connected Engine.IO session.

Instances
Eq Socket Source # 
Instance details

Defined in Network.EngineIO

Methods

(==) :: Socket -> Socket -> Bool #

(/=) :: Socket -> Socket -> Bool #

Ord Socket Source # 
Instance details

Defined in Network.EngineIO

type SocketId = ByteString Source #

The type of unique Engine.IO sessions. This is currently a base64-encoded random identifier.

getOpenSockets :: EngineIO -> STM (HashMap SocketId Socket) Source #

Retrieve a list of all currently open Engine.IO sessions.

dupRawReader :: Socket -> IO (STM Packet) Source #

Create a new IO action to read the socket's raw incoming communications. The result of this call is iteslf an STM action, which when called will return the next unread incoming packet (or block). This provides you with a separate channel to monitor incoming communications. It may be useful to monitor this to determine if the socket has activity.

This is a fairly low level operation, so you will receive *all* packets - including pings and other control codes.

The Engine.IO Protocol

Packets

data Packet Source #

A single Engine.IO packet.

Instances
Eq Packet Source # 
Instance details

Defined in Network.EngineIO

Methods

(==) :: Packet -> Packet -> Bool #

(/=) :: Packet -> Packet -> Bool #

Show Packet Source # 
Instance details

Defined in Network.EngineIO

parsePacket :: Parser Packet Source #

Parse bytes as an Packet assuming the packet contents extends to the end-of-input.

encodePacket Source #

Arguments

:: Bool

If true, all bytes can be used. Otherwise, the packet will be base 64 encoded.

-> Packet 
-> Builder 

Encode a Packet to a Builder. The first argument determines whether or not binary is supported - if not, binary data will be base 64 encoded.

Packet Contents

data PacketContent Source #

The contents attached to a packet. Engine.IO makes a clear distinction between binary data and text data. Clients will receive binary data as a Javascript ArrayBuffer, where as TextPackets will be received as UTF-8 strings.

Payloads

newtype Payload Source #

A Payload is a stream of 0-or-more Packets.

Constructors

Payload (Vector Packet) 
Instances
Eq Payload Source # 
Instance details

Defined in Network.EngineIO

Methods

(==) :: Payload -> Payload -> Bool #

(/=) :: Payload -> Payload -> Bool #

Show Payload Source # 
Instance details

Defined in Network.EngineIO

parsePayload :: Parser Payload Source #

Parse a stream of bytes into a Payload.

encodePayload Source #

Arguments

:: Bool

If true, all bytes can be used. Otherwise, the packet will be base 64 encoded.

-> Payload 
-> Builder 

Encode a Payload to a Builder. As with encodePacket, the first argument determines whether or not binary transmission is supported.

Transport types

data TransportType Source #

The possible types of transports Engine.IO supports.

Constructors

Polling

XHR long polling.

Websocket

HTML 5 websockets.

parseTransportType :: Text -> Maybe TransportType Source #

Attempt to parse a TransportType from its textual representation.