| Safe Haskell | None | 
|---|
Control.Proxy.TCP.Safe
Contents
Description
This module exports functions that allow you to safely use Socket
 resources within a Proxy pipeline, possibly acquiring and releasing such
 resources within the pipeline itself, using the facilities provided by
 ExceptionP from the pipes-safe library.
Instead, if just want to use resources already acquired or released outside the pipeline, then you could use the simpler functions exported by Control.Proxy.TCP.
- connect :: (Proxy p, Monad m) => (forall x. SafeIO x -> m x) -> HostName -> ServiceName -> ((Socket, SockAddr) -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r
- connectReadS :: Proxy p => Maybe Int -> Int -> HostName -> ServiceName -> () -> Producer (ExceptionP p) ByteString SafeIO ()
- connectWriteD :: Proxy p => Maybe Int -> HostName -> ServiceName -> x -> ExceptionP p x ByteString x ByteString SafeIO r
- serve :: (Proxy p, Monad m) => (forall x. SafeIO x -> m x) -> HostPreference -> ServiceName -> ((Socket, SockAddr) -> IO ()) -> ExceptionP p a' a b' b m r
- listen :: (Proxy p, Monad m) => (forall x. SafeIO x -> m x) -> HostPreference -> ServiceName -> ((Socket, SockAddr) -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r
- accept :: (Proxy p, Monad m) => (forall x. SafeIO x -> m x) -> Socket -> ((Socket, SockAddr) -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r
- acceptFork :: (Proxy p, Monad m) => (forall x. SafeIO x -> m x) -> Socket -> ((Socket, SockAddr) -> IO ()) -> ExceptionP p a' a b' b m ThreadId
- serveReadS :: Proxy p => Maybe Int -> Int -> HostPreference -> ServiceName -> () -> Producer (ExceptionP p) ByteString SafeIO ()
- serveWriteD :: Proxy p => Maybe Int -> HostPreference -> ServiceName -> x -> ExceptionP p x ByteString x ByteString SafeIO r
- socketReadS :: Proxy p => Maybe Int -> Int -> Socket -> () -> Producer (ExceptionP p) ByteString SafeIO ()
- nsocketReadS :: Proxy p => Maybe Int -> Socket -> Int -> Server (ExceptionP p) Int ByteString SafeIO ()
- socketWriteD :: Proxy p => Maybe Int -> Socket -> x -> ExceptionP p x ByteString x ByteString SafeIO r
- withSocketsDo :: IO a -> IO a
- data HostPreference
- data Timeout = Timeout String
Client side
Here's how you could run a TCP client:
connect"www.example.org" "80" $ (connectionSocket, remoteAddr) -> do putStrLn $ "Connection established to " ++ show remoteAddr -- Now you may use connectionSocket as you please within this scope, -- possibly usingsocketReadS,socketWriteDor similar proxies -- explained below.
You might instead prefer the simpler but less general solutions offered by
 connectReadS and connectWriteD, so check those too.
Arguments
| :: (Proxy p, Monad m) | |
| => (forall x. SafeIO x -> m x) | Monad morphism. | 
| -> HostName | Server hostname. | 
| -> ServiceName | Server service port. | 
| -> ((Socket, SockAddr) -> ExceptionP p a' a b' b m r) | Computation taking the communication socket and the server address. | 
| -> ExceptionP p a' a b' b m r | 
Connect to a TCP server and use the connection.
The connection socket is closed when done or in case of exceptions.
If you prefer to acquire close the socket yourself, then use
 connectSock and the sClose from Network.Socket instead.
Streaming
The following proxies allow you to easily connect to a TCP server and immediately interact with it using streams, all at once, instead of having to perform the individual steps separately.
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> Int | Maximum number of bytes to receive and send
 dowstream at once. Any positive value is fine, the
 optimal value depends on how you deal with the
 received data. Try using  | 
| -> HostName | Server host name. | 
| -> ServiceName | Server service port. | 
| -> () | |
| -> Producer (ExceptionP p) ByteString SafeIO () | 
Connect to a TCP server and send downstream the bytes received from the remote end.
If an optional timeout is given and receiveing data from the remote end takes
 more time that such timeout, then throw a Timeout exception in the
 ExceptionP proxy transformer.
The connection socket is closed when done or in case of exceptions.
Using this proxy you can write straightforward code like the following, which prints whatever is received from a single TCP connection to a given server listening locally on port 9000, in chunks of up to 4096 bytes:
>>>runSafeIO . runProxy . runEitherK $ connectReadS Nothing 4096 "127.0.0.1" "9000" >-> tryK printD
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> HostName | Server host name. | 
| -> ServiceName | Server service port. | 
| -> x | |
| -> ExceptionP p x ByteString x ByteString SafeIO r | 
Connects to a TCP server, sends to the remote end the bytes received from upstream, then forwards such same bytes downstream.
Requests from downstream are forwarded upstream.
If an optional timeout is given and sending data to the remote end takes
 more time that such timeout, then throw a Timeout exception in the
 ExceptionP proxy transformer.
The connection socket is closed when done or in case of exceptions.
Using this proxy you can write straightforward code like the following, which greets a TCP client listening locally at port 9000:
>>>:set -XOverloadedStrings>>>runSafeIO . runProxy . runEitherK $ fromListS ["He","llo\r\n"] >-> connectWriteD Nothing "127.0.0.1" "9000"
Server side
Here's how you can run a TCP server that handles in different threads each
 incoming connection to port 8000 at IPv4 address 127.0.0.1:
serve(Host"127.0.0.1") "8000" $ (connectionSocket, remoteAddr) -> do putStrLn $ "TCP connection established from " ++ show remoteAddr -- Now you may use connectionSocket as you please within this scope, -- possibly usingsocketReadS,socketWriteDor similar proxies -- explained below.
You might instead prefer the simpler but less general solutions offered by
 serveReadS and serveWriteD, so check those too. On the other hand,
 if you need more control on the way your server runs, then you can use more
 advanced functions such as listen, accept and acceptFork.
Arguments
| :: (Proxy p, Monad m) | |
| => (forall x. SafeIO x -> m x) | Monad morphism. | 
| -> HostPreference | Preferred host to bind. | 
| -> ServiceName | Service port to bind. | 
| -> ((Socket, SockAddr) -> IO ()) | Computation to run in a different thread once an incoming connection is accepted. Takes the connection socket and remote end address. | 
| -> ExceptionP p a' a b' b m r | 
Start a TCP server that accepts incoming connections and handles each of them concurrently in different threads.
Any acquired network resources are properly closed and discarded when done or in case of exceptions.
Note: This function performs listen and acceptFork, so you don't need to
 perform those manually.
Listening
Arguments
| :: (Proxy p, Monad m) | |
| => (forall x. SafeIO x -> m x) | Monad morphism. | 
| -> HostPreference | Preferred host to bind. | 
| -> ServiceName | Service port to bind. | 
| -> ((Socket, SockAddr) -> ExceptionP p a' a b' b m r) | Computation taking the listening socket and the address it's bound to. | 
| -> ExceptionP p a' a b' b m r | 
Bind a TCP listening socket and use it.
The listening socket is closed when done or in case of exceptions.
If you prefer to acquire and close the socket yourself, then use
 bindSock and the listen and sClose functions from
 Network.Socket instead.
Note: maxListenQueue is tipically 128, which is too small for high
 performance servers. So, we use the maximum between maxListenQueue and
 2048 as the default size of the listening queue.
Accepting
Arguments
| :: (Proxy p, Monad m) | |
| => (forall x. SafeIO x -> m x) | Monad morphism. | 
| -> Socket | Listening and bound socket. | 
| -> ((Socket, SockAddr) -> ExceptionP p a' a b' b m r) | Computation to run once an incoming connection is accepted. Takes the connection socket and remote end address. | 
| -> ExceptionP p a' a b' b m r | 
Accept a single incoming connection and use it.
The connection socket is closed when done or in case of exceptions.
Arguments
| :: (Proxy p, Monad m) | |
| => (forall x. SafeIO x -> m x) | Monad morphism. | 
| -> Socket | Listening and bound socket. | 
| -> ((Socket, SockAddr) -> IO ()) | Computation to run in a different thread once an incoming connection is accepted. Takes the connection socket and remote end address. | 
| -> ExceptionP p a' a b' b m ThreadId | 
Accept a single incoming connection and use it in a different thread.
The connection socket is closed when done or in case of exceptions.
Streaming
The following proxies allow you to easily run a TCP server and immediately interact with incoming connections using streams, all at once, instead of having to perform the individual steps separately.
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> Int | Maximum number of bytes to receive and send
 dowstream at once. Any positive value is fine, the
 optimal value depends on how you deal with the
 received data. Try using  | 
| -> HostPreference | Preferred host to bind. | 
| -> ServiceName | Service port to bind. | 
| -> () | |
| -> Producer (ExceptionP p) ByteString SafeIO () | 
Binds a listening socket, accepts a single connection and sends downstream any bytes received from the remote end.
If an optional timeout is given and receiveing data from the remote end takes
 more time that such timeout, then throw a Timeout exception in the
 ExceptionP proxy transformer.
Less than the specified maximum number of bytes might be received at once.
This proxy returns if the remote peer closes its side of the connection or EOF is received.
Both the listening and connection sockets are closed when done or in case of exceptions.
Using this proxy you can write straightforward code like the following, which prints whatever is received from a single TCP connection to port 9000, in chunks of up to 4096 bytes.
>>>:set -XOverloadedStrings>>>runSafeIO . runProxy . runEitherK $ serveReadS Nothing 4096 "127.0.0.1" "9000" >-> tryK printD
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> HostPreference | Preferred host to bind. | 
| -> ServiceName | Service port to bind. | 
| -> x | |
| -> ExceptionP p x ByteString x ByteString SafeIO r | 
Binds a listening socket, accepts a single connection, sends to the remote end the bytes received from upstream, then forwards such sames bytes downstream.
Requests from downstream are forwarded upstream.
If an optional timeout is given and sending data to the remote end takes
 more time that such timeout, then throw a Timeout exception in the
 ExceptionP proxy transformer.
Both the listening and connection sockets are closed when done or in case of exceptions.
Using this proxy you can write straightforward code like the following, which greets a TCP client connecting to port 9000:
>>>:set -XOverloadedStrings>>>runSafeIO . runProxy . runEitherK $ fromListS ["He","llo\r\n"] >-> serveWriteD Nothing "127.0.0.1" "9000"
Socket streams
Once you have a connected Socket, you can use the following Proxys
 to interact with the other connection end using streams.
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> Int | Maximum number of bytes to receive and send
 dowstream at once. Any positive value is fine, the
 optimal value depends on how you deal with the
 received data. Try using  | 
| -> Socket | Connected socket. | 
| -> () | |
| -> Producer (ExceptionP p) ByteString SafeIO () | 
Receives bytes from the remote end and sends them downstream.
If an optional timeout is given and receiveing data from the remote end takes
 more time that such timeout, then throw a Timeout exception in the
 ExceptionP proxy transformer.
Less than the specified maximum number of bytes might be received at once.
This proxy returns if the remote peer closes its side of the connection or EOF is received.
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> Socket | Connected socket. | 
| -> Int | |
| -> Server (ExceptionP p) Int ByteString SafeIO () | 
Just like socketReadS, except each request from downstream specifies the
 maximum number of bytes to receive.
Arguments
| :: Proxy p | |
| => Maybe Int | Optional timeout in microseconds (1/10^6 seconds). | 
| -> Socket | Connected socket. | 
| -> x | |
| -> ExceptionP p x ByteString x ByteString SafeIO r | 
Sends to the remote end the bytes received from upstream, then forwards such same bytes downstream.
If an optional timeout is given and sending data to the remote end takes
 more time that such timeout, then throw a Timeout exception in the
 ExceptionP proxy transformer.
Requests from downstream are forwarded upstream.
Note to Windows users
If you are running Windows, then you must call withSocketsDo, just
 once, right at the beginning of your program. That is, change your program's
 main function from:
main = do print "Hello world" -- rest of the program...
To:
 main = withSocketsDo $ do
   print "Hello world"
   -- rest of the program...
If you don't do this, your networking code won't work and you will get many unexpected errors at runtime. If you use an operating system other than Windows then you don't need to do this, but it is harmless to do it, so it's recommended that you do for portability reasons.
withSocketsDo :: IO a -> IO a
On Windows operating systems, the networking subsystem has to be
initialised using withSocketsDo before any networking operations can
be used.  eg.
 main = withSocketsDo $ do {...}
Although this is only strictly necessary on Windows platforms, it is harmless on other platforms, so for portability it is good practice to use it all the time.
Exports
data HostPreference
Preferred host to bind.
Constructors
| HostAny | Any available host. | 
| HostIPv4 | Any available IPv4 host. | 
| HostIPv6 | Any available IPv6 host. | 
| Host HostName | An explicit host name. | 
Instances
| Eq HostPreference | |
| Ord HostPreference | |
| Read HostPreference | |
| Show HostPreference | |
| IsString HostPreference | The following special values are recognized: |