| Safe Haskell | None |
|---|
Web.SocketIO
Contents
Description
Socket.IO for Haskell folks.
- server :: Port -> HandlerM () -> IO ()
- serverConfig :: Port -> Configuration -> HandlerM () -> IO ()
- defaultConfig :: Configuration
- data Configuration = Configuration {
- transports :: [Transport]
- logLevel :: Int
- logTo :: Handle
- heartbeats :: Bool
- header :: ResponseHeaders
- closeTimeout :: Int
- heartbeatTimeout :: Int
- heartbeatInterval :: Int
- pollingDuration :: Int
- type Port = Int
- data Transport = XHRPolling
- class Subscriber m where
- class Publisher m where
- reply :: CallbackM [Value]
- msg :: CallbackM [Value]
- msg' :: CallbackM [ByteString]
- getEventName :: CallbackM EventName
- class HasSessionID m where
- getSessionID :: m SessionID
- type EventName = Text
- type SessionID = ByteString
- data HandlerM a
- data CallbackM a
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
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
| |
Instances
Now only xhr-polling is supported. socket.io-spec#transport-id
Constructors
| XHRPolling |
Sending and receiving events
Sends events
reply :: CallbackM [Value]Source
Deprecated: use msg instead
This function is deprecated; use msg instead
msg' :: CallbackM [ByteString]Source
Lazy ByteString version of msg, convenient for Aeson decoding.
getEventName :: CallbackM EventNameSource
Name of the event
type SessionID = ByteStringSource
Session ID
Special events
On disconnection
on "disconnect" $ do
liftIO $ print "client disconnected"
Types
Capable of both sending and receiving events.
Use liftIO if you wanna do some IO here.