| Safe Haskell | None |
|---|
Network.Simple.TCP.TLS
Contents
Description
This module exports simple tools for establishing TLS-secured TCP connections, relevant to both the client side and server side of the connection.
This module re-exports some functions from the Network.Simple.TCP module
in the network-simple package. Consider using that module directly if you
need a similar API without TLS support.
This module uses MonadIO and MonadCatch extensively so that you can
reuse these functions in monads other than IO. However, if you don't care
about any of that, just pretend you are using the IO monad all the time
and everything will work as expected.
- serve :: MonadIO m => ServerSettings -> HostPreference -> ServiceName -> ((Context, SockAddr) -> IO ()) -> m ()
- listen :: (MonadIO m, MonadCatch m) => HostPreference -> ServiceName -> ((Socket, SockAddr) -> m r) -> m r
- accept :: (MonadIO m, MonadCatch m) => ServerSettings -> Socket -> ((Context, SockAddr) -> m r) -> m r
- acceptFork :: MonadIO m => ServerSettings -> Socket -> ((Context, SockAddr) -> IO ()) -> m ThreadId
- data ServerSettings
- makeServerSettings :: Credential -> Maybe CertificateStore -> ServerSettings
- updateServerParams :: (Params -> Params) -> ServerSettings -> ServerSettings
- serverParams :: Functor f => (Params -> f Params) -> ServerSettings -> f ServerSettings
- connect :: (MonadIO m, MonadCatch m) => ClientSettings -> HostName -> ServiceName -> ((Context, SockAddr) -> m r) -> m r
- data ClientSettings
- makeClientSettings :: [Credential] -> Maybe HostName -> CertificateStore -> ClientSettings
- getDefaultClientSettings :: MonadIO m => m ClientSettings
- updateClientParams :: (Params -> Params) -> ClientSettings -> ClientSettings
- clientParams :: Functor f => (Params -> f Params) -> ClientSettings -> f ClientSettings
- data Credential = Credential !X509 !PrivateKey [X509]
- credentialToCertList :: Credential -> [(X509, Maybe PrivateKey)]
- recv :: MonadIO m => Context -> m (Maybe ByteString)
- send :: MonadIO m => Context -> ByteString -> m ()
- useTls :: (MonadIO m, MonadCatch m) => ((Context, SockAddr) -> m a) -> (Context, SockAddr) -> m a
- useTlsThenClose :: (MonadIO m, MonadCatch m) => ((Context, SockAddr) -> m a) -> (Context, SockAddr) -> m a
- useTlsThenCloseFork :: MonadIO m => ((Context, SockAddr) -> IO ()) -> (Context, SockAddr) -> m ThreadId
- connectTls :: MonadIO m => ClientSettings -> HostName -> ServiceName -> m (Context, SockAddr)
- acceptTls :: MonadIO m => ServerSettings -> Socket -> m (Context, SockAddr)
- makeClientContext :: MonadIO m => ClientSettings -> Socket -> m Context
- makeServerContext :: MonadIO m => ServerSettings -> Socket -> m Context
- withSocketsDo :: IO a -> IO a
- module Network.Simple.TCP
- module Network.Socket
- module Network.TLS
Server side
Arguments
| :: MonadIO m | |
| => ServerSettings | TLS settings. |
| -> HostPreference | Preferred host to bind. |
| -> ServiceName | Service port to bind. |
| -> ((Context, SockAddr) -> IO ()) | Computation to run in a different thread once an incomming connection is accepted and a TLS-secured communication is established. Takes the TLS connection context and remote end address. |
| -> m () |
Start a TLS-secured 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. This function binds a listening socket, accepts an incoming connection, performs a TLS handshake and then safely closes the connection when done or in case of exceptions. You don't need to perform any of those steps manually.
Listening
Arguments
| :: (MonadIO m, MonadCatch m) | |
| => HostPreference | Preferred host to bind. |
| -> ServiceName | Service port to bind. |
| -> ((Socket, SockAddr) -> m r) | Computation taking the listening socket and the address it's bound to. |
| -> 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,
closeSock and the listen function 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. The NoDelay and
ReuseAddr options are set on the socket.
Accepting
Arguments
| :: (MonadIO m, MonadCatch m) | |
| => ServerSettings | TLS settings. |
| -> Socket | Listening and bound socket. |
| -> ((Context, SockAddr) -> m r) | Computation to run in a different thread once an incomming connection is accepted and a TLS-secured communication is established. Takes the TLS connection context and remote end address. |
| -> m r |
Accepts a single incomming TLS-secured TCP connection and use it.
A TLS handshake is performed immediately after establishing the TCP
connection and the TLS and TCP connections are properly closed when done or
in case of exceptions. If you need to manage the lifetime of the connection
resources yourself, then use acceptTls instead.
Arguments
| :: MonadIO m | |
| => ServerSettings | TLS settings. |
| -> Socket | Listening and bound socket. |
| -> ((Context, SockAddr) -> IO ()) | Computation to run in a different thread once an incomming connection is accepted and a TLS-secured communication is established. Takes the TLS connection context and remote end address. |
| -> m ThreadId |
Like accept, except it uses a different thread to performs the TLS
handshake and run the given computation.
Server TLS Settings
data ServerSettings Source
Abstract type representing the configuration settings for a TLS server.
Use makeServerSettings to obtain your ServerSettings value, and
updateServerParams to update it.
Arguments
| :: Credential | Server credential. |
| -> Maybe CertificateStore | CAs used to verify the client certificate. If specified, then a valid client certificate will be expected during on handshake. |
| -> ServerSettings |
Make default ServerSettings.
The following TLS settings are used by default:
- Supported versions
-
TLS10,TLS11,TLS12. - Supported cipher suites for
TLS10 -
In decreasing order of preference:
cipher_AES256_SHA256,cipher_AES256_SHA1,cipher_AES128_SHA256,cipher_AES128_SHA1,cipher_RC4_128_SHA1,cipher_RC4_128_MD5. The cipher suite preferred by the client is used. - Supported cipher suites for
TLS11andTLS12 -
In decreasing order of preference:
cipher_AES256_SHA256,cipher_AES256_SHA1,cipher_AES128_SHA256,cipher_AES128_SHA1. The cipher suite preferred by the client is used.
updateServerParams :: (Params -> Params) -> ServerSettings -> ServerSettingsSource
Update advanced TLS server configuration Params.
See the Network.TLS module for details.
serverParams :: Functor f => (Params -> f Params) -> ServerSettings -> f ServerSettingsSource
A Lens into the TLS server configuration Params.
See the Network.TLS and the lens package for details.
Client side
Arguments
| :: (MonadIO m, MonadCatch m) | |
| => ClientSettings | TLS settings. |
| -> HostName | Server hostname. |
| -> ServiceName | Server service port. |
| -> ((Context, SockAddr) -> m r) | Computation to run after establishing TLS-secured TCP connection to the remote server. Takes the TLS connection context and remote end address. |
| -> m r |
Connect to a TLS-secured TCP server and use the connection
A TLS handshake is performed immediately after establishing the TCP
connection and the TLS and TCP connections are properly closed when done or
in case of exceptions. If you need to manage the lifetime of the connection
resources yourself, then use connectTls instead.
Client TLS Settings
data ClientSettings Source
Abstract type representing the configuration settings for a TLS client.
Use makeClientSettings or getDefaultClientSettings to obtain your
ClientSettings value.
Arguments
| :: [Credential] | Credentials to provide to the server, if requested. The first one is used in case we can't choose one based on information provided by the server. |
| -> Maybe HostName | Explicit Server Name Identification (SNI). |
| -> CertificateStore | CAs used to verify the server certificate.
Use |
| -> ClientSettings |
Make defaults ClientSettings.
The following TLS settings are used by default:
- Supported versions
-
TLS10,TLS11,TLS12. - Version reported during ClientHello
-
TLS10. - Supported cipher suites
- In decreasing order of preference:
cipher_AES256_SHA256,cipher_AES256_SHA1,cipher_AES128_SHA256,cipher_AES128_SHA1,cipher_RC4_128_SHA1,cipher_RC4_128_MD5.
getDefaultClientSettings :: MonadIO m => m ClientSettingsSource
Get the system default ClientSettings.
See makeClientSettings for the for the default TLS settings used.
updateClientParams :: (Params -> Params) -> ClientSettings -> ClientSettingsSource
Update advanced TLS client configuration Params.
See the Network.TLS module for details.
clientParams :: Functor f => (Params -> f Params) -> ClientSettings -> f ClientSettingsSource
A Lens into the TLS client configuration Params.
See the Network.TLS and the lens package for details.
Credentials
data Credential Source
Primary certificate, private key and the rest of the certificate chain.
Constructors
| Credential !X509 !PrivateKey [X509] |
Instances
credentialToCertList :: Credential -> [(X509, Maybe PrivateKey)]Source
Convert client Credential to the format expected by pCertificates.
Utils
send :: MonadIO m => Context -> ByteString -> m ()Source
Encrypts the given strict ByteString and sends it through the
Context.
Low level support
useTls :: (MonadIO m, MonadCatch m) => ((Context, SockAddr) -> m a) -> (Context, SockAddr) -> m aSource
Perform a TLS handshake on the given Context, then perform the
given action and at last gracefully close the TLS session using bye.
This function does not close the underlying TCP connection when done.
Prefer to use useTlsThenClose or useTlsThenCloseFork if you need that
behavior. Otherwise, you must call contextClose yourself at some point.
useTlsThenClose :: (MonadIO m, MonadCatch m) => ((Context, SockAddr) -> m a) -> (Context, SockAddr) -> m aSource
Like useTls, except it also fully closes the TCP connection when done.
useTlsThenCloseFork :: MonadIO m => ((Context, SockAddr) -> IO ()) -> (Context, SockAddr) -> m ThreadIdSource
Similar to useTlsThenClose, except it performs the all the IO actions
in a new thread.
Use this instead of forking useTlsThenClose yourself, as that won't give
the right behavior.
Arguments
| :: MonadIO m | |
| => ClientSettings | TLS settings. |
| -> HostName | Server hostname. |
| -> ServiceName | Service port to bind. |
| -> m (Context, SockAddr) |
Estalbishes a TCP connection to a remote server and returns a TLS
Context configured on top of it using the given ClientSettings.
The remote end address is also returned.
Prefer to use connect if you will be using the obtained Context within a
limited scope.
You need to perform a TLS handshake on the resulting Context before using
it for communication purposes, and gracefully close the TLS and TCP
connections afterwards using. The useTls, useTlsThenClose and
useTlsThenCloseFork can help you with that.
Arguments
| :: MonadIO m | |
| => ServerSettings | TLS settings. |
| -> Socket | Listening and bound socket. |
| -> m (Context, SockAddr) |
Accepts an incoming TCP connection and returns a TLS Context configured
on top of it using the given ServerSettings. The remote end address is also
returned.
Prefer to use accept if you will be using the obtained Context within a
limited scope.
You need to perform a TLS handshake on the resulting Context before using
it for communication purposes, and gracefully close the TLS and TCP
connections afterwards using. The useTls, useTlsThenClose and
useTlsThenCloseFork can help you with that.
makeClientContext :: MonadIO m => ClientSettings -> Socket -> m ContextSource
makeServerContext :: MonadIO m => ServerSettings -> Socket -> m ContextSource
Note to Windows users
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
For your convenience, this module module also re-exports the following types from other modules:
- From Network.Socket
-
HostName,ServiceName,Socket,SockAddr. - From Network.Simple.TCP
-
.HostPreference(Host,HostAny,HostIPv4,HostIPv6) - From Network.TLS
-
Context.
module Network.Simple.TCP
module Network.Socket
module Network.TLS