om-socket-1.0.0.1: Socket utilities.
Safe HaskellNone
LanguageHaskell2010

OM.Socket

Description

Socket utilities.

Synopsis

Socket Addresses

newtype AddressDescription Source #

A description of a socket address on which a socket is or should be listening. Supports both IPv4 and IPv6.

Examples:

AddressDescription "[::1]:80" -- IPv6 localhost, port 80
AddressDescription "127.0.0.1:80" -- IPv4 localhost, port 80
AddressDescription "somehost:80" -- IPv4 or IPv6 (depending on what name resolution returns), port 80

Instances

Instances details
FromJSON AddressDescription Source # 
Instance details

Defined in OM.Socket

FromJSONKey AddressDescription Source # 
Instance details

Defined in OM.Socket

ToJSON AddressDescription Source # 
Instance details

Defined in OM.Socket

ToJSONKey AddressDescription Source # 
Instance details

Defined in OM.Socket

IsString AddressDescription Source # 
Instance details

Defined in OM.Socket

Monoid AddressDescription Source # 
Instance details

Defined in OM.Socket

Semigroup AddressDescription Source # 
Instance details

Defined in OM.Socket

Generic AddressDescription Source # 
Instance details

Defined in OM.Socket

Associated Types

type Rep AddressDescription 
Instance details

Defined in OM.Socket

type Rep AddressDescription = D1 ('MetaData "AddressDescription" "OM.Socket" "om-socket-1.0.0.1-inplace" 'True) (C1 ('MetaCons "AddressDescription" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAddressDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
Show AddressDescription Source # 
Instance details

Defined in OM.Socket

Binary AddressDescription Source # 
Instance details

Defined in OM.Socket

Eq AddressDescription Source # 
Instance details

Defined in OM.Socket

Ord AddressDescription Source # 
Instance details

Defined in OM.Socket

type Rep AddressDescription Source # 
Instance details

Defined in OM.Socket

type Rep AddressDescription = D1 ('MetaData "AddressDescription" "OM.Socket" "om-socket-1.0.0.1-inplace" 'True) (C1 ('MetaCons "AddressDescription" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAddressDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

resolveAddr :: (MonadIO m, MonadFail m) => AddressDescription -> m SockAddr Source #

Resolve a host:port address into a SockAddr.

Ingress-only sockets

openIngress :: forall i (m :: Type -> Type) never_returns. (Binary i, MonadFail m, MonadIO m, Race) => AddressDescription -> Stream (Of i) m never_returns Source #

Opens an "ingress" socket, which is a socket that accepts a stream of messages without responding. In particular, we listen on a socket, accepting new connections, an each connection concurrently reads its elements off the socket and pushes them onto the stream.

Egress-only sockets

openEgress :: (Binary o, MonadFail m, MonadIO m) => AddressDescription -> Stream (Of o) m r -> m r Source #

Open an "egress" socket, which is a socket that sends a stream of messages without receiving responses.

Bidirection request/resposne servers.

openServer :: (Binary request, Binary response, MonadLogger m, MonadCatch m, MonadFail m, MonadUnliftIO m, Race) => AddressDescription -> Maybe (IO ServerParams) -> Stream (Of (request, response -> m Responded)) m never_returns Source #

Open a "server" socket, which is a socket that accepts incoming requests and provides a way to respond to those requests.

data Responded Source #

Proof that a response function was called on the server. Mainly useful for including in a type signature somewhere in your server implementation to help ensure that you actually responded to the request in all cases.

connectServer :: forall n request m response. (Binary request, Binary response, MonadIO m, MonadLoggerIO n, Show response) => AddressDescription -> Maybe ClientParams -> n (request -> m response) Source #

Connect to a server. Returns a function in MonadIO that can be used to submit requests to (and returns the corresponding response from) the server.