box-socket-0.3.0: Box websockets
Safe HaskellNone
LanguageHaskell2010

Box.Socket

Description

Websocket components built with Boxes.

Synopsis

Documentation

data SocketConfig Source #

Socket configuration

>>> defaultSocketConfig
SocketConfig {host = "127.0.0.1", port = 9160, path = "/"}

Constructors

SocketConfig 

Fields

Instances

Instances details
Eq SocketConfig Source # 
Instance details

Defined in Box.Socket

Show SocketConfig Source # 
Instance details

Defined in Box.Socket

Generic SocketConfig Source # 
Instance details

Defined in Box.Socket

Associated Types

type Rep SocketConfig :: Type -> Type #

type Rep SocketConfig Source # 
Instance details

Defined in Box.Socket

type Rep SocketConfig = D1 ('MetaData "SocketConfig" "Box.Socket" "box-socket-0.3.0-5G2mf2vq864I4BQne4Gmwa" 'False) (C1 ('MetaCons "SocketConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "host") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "port") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

runClient :: MonadIO m => SocketConfig -> ClientApp () -> m () Source #

Run a client app.

runServer :: MonadIO m => SocketConfig -> ServerApp -> m () Source #

Run a server app.

connect :: (MonadIO m, MonadConc m) => PendingConnection -> Codensity m Connection Source #

Connection continuation.

clientApp :: (MonadIO m, MonadConc m) => Box m (Either Text Text) Text -> Connection -> m () Source #

A simple client app for a box with Left debug messages.

responderApp :: (Text -> Either Text Text) -> PendingConnection -> IO () Source #

Canned response function.

serverApp :: (MonadConc m, MonadIO m) => Box m Text Text -> PendingConnection -> m () Source #

Standard server app for a box.

receiver' :: MonadIO m => Committer m (Either Text Text) -> Connection -> m Bool Source #

default websocket receiver with messages Lefts are info/debug

receiver :: MonadIO m => Committer m Text -> Connection -> m () Source #

Receiver that only commits.

sender :: (MonadIO m, WebSocketsData a, Show a) => Box m Text a -> Connection -> m () Source #

Sender that only emits.

responder :: MonadIO m => (Text -> Either Text Text) -> Committer m Text -> Connection -> m () Source #

A receiver that responds based on received Text. lefts are quit signals. Rights are response text.