socketio-0.1.2: Socket.IO server

Safe HaskellNone

Web.SocketIO

Contents

Description

Socket.IO for Haskell folks.

Synopsis

How to use this module

Note that most of the string literals below are of type Lazy Text.

{-# LANGUAGE OverloadedStrings #-}

import Web.SocketIO

-- listens to port 4000
main = server 4000 $ do

    -- send something to the client
    emit "some event" ["hey"]

    -- ping-pong
    on "ping" $ do
        emit "pong" []

    -- do some IO
    on "Kim Jong-Un" $ liftIO launchMissile
        
    -- broadcast
    broadcast "UN" "North Korea is best Korea"

Running a standalone server

server :: Port -> HandlerM () -> IO ()Source

Run a socket.io application, build on top of Warp.

serverConfig :: Port -> Configuration -> HandlerM () -> IO ()Source

Run a socket.io application with configurations applied.

defaultConfig :: ConfigurationSource

Default configuration.

 defaultConfig = Configuration
    {   transports = [XHRPolling]
    ,   logLevel = 2               
    ,   logTo = stderr        
    ,   header = [("Access-Control-Allow-Credentials", "true")]      
    ,   heartbeats = True
    ,   closeTimeout = 60
    ,   heartbeatTimeout = 60
    ,   heartbeatInterval = 25
    ,   pollingDuration = 20
    }

You can override it like so:

 myConfig = defaultConfig { logLevel = 0 }

Unless specified, the header will be modified to enable cross-origin resource sharing (CORS) like this.

 header = 
    [   ("Access-Control-Allow-Origin", <origin-of-the-reqeust>)]      
    ,   ("Access-Control-Allow-Credentials", "true")
    ]      

data Configuration Source

Defines behaviors of a Socket.IO server

Constructors

Configuration 

Fields

transports :: [Transport]
 
logLevel :: Int

there are 4 levels, from 0 to 3: Error, Warn, Info, Debug

logTo :: Handle
 
heartbeats :: Bool
 
header :: ResponseHeaders
 
closeTimeout :: Int
 
heartbeatTimeout :: Int
 
heartbeatInterval :: Int
 
pollingDuration :: Int
 

Instances

type Port = IntSource

Port number for a standalone Socket.IO server.

data Transport Source

Now only xhr-polling is supported. socket.io-spec#transport-id

Constructors

XHRPolling 

Sending and receiving events

class Subscriber m whereSource

Receives events.

Methods

onSource

Arguments

:: EventName

name of event to listen to

-> CallbackM ()

callback

-> m () 

Instances

class Publisher m whereSource

Sends events

Methods

emitSource

Arguments

:: EventName

name of event to trigger

-> [Text]

payload to carry with

-> m () 

Sends a message to the socket that starts it.

 emit "launch" ["missile", "nuke"] 

broadcastSource

Arguments

:: EventName

name of event to trigger

-> [Text]

payload to carry with

-> m () 

Sends a message to everybody except for the socket that starts it.

 broadcast "hide" ["nukes coming!"] 

reply :: CallbackM [Text]Source

Deprecated: use msg instead

This function is deprecated; use msg instead

msg :: CallbackM [Text]Source

Extracts payload carried by the event

 on "echo" $ do
     payload <- msg
     liftIO $ print payload
     emit echo payload 

msg' :: CallbackM [ByteString]Source

Lazy ByteString version of msg, convenient for Aeson decoding.

type EventName = TextSource

Name of an Event

type SessionID = ByteStringSource

Session ID

Special events

On disconnection

 on "disconnect" $ do
     liftIO $ print "client disconnected"

Types

data HandlerM a Source

Capable of both sending and receiving events.

Use liftIO if you wanna do some IO here.

data CallbackM a Source

Capable of only sending events.

Use liftIO if you wanna do some IO here.