Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type ApplicationStartTLS = GeneralApplicationStartTLS IO ()
- type GeneralApplicationStartTLS m a = (AppData, (AppData -> m ()) -> m ()) -> m a
- data TLSConfig
- tlsConfigBS :: HostPreference -> Int -> ByteString -> ByteString -> TLSConfig
- tlsConfig :: HostPreference -> Int -> FilePath -> FilePath -> TLSConfig
- tlsConfigChainBS :: HostPreference -> Int -> ByteString -> [ByteString] -> ByteString -> TLSConfig
- tlsConfigChain :: HostPreference -> Int -> FilePath -> [FilePath] -> FilePath -> TLSConfig
- tlsHost :: TLSConfig -> HostPreference
- tlsPort :: TLSConfig -> Int
- tlsNeedLocalAddr :: TLSConfig -> Bool
- tlsAppData :: Context -> SockAddr -> Maybe SockAddr -> AppData
- runTCPServerTLS :: TLSConfig -> (AppData -> IO ()) -> IO ()
- runGeneralTCPServerTLS :: MonadUnliftIO m => TLSConfig -> (AppData -> m ()) -> m ()
- runTCPServerStartTLS :: MonadUnliftIO m => TLSConfig -> GeneralApplicationStartTLS m () -> m ()
- data TLSClientConfig
- tlsClientConfig :: Int -> ByteString -> TLSClientConfig
- runTLSClient :: MonadUnliftIO m => TLSClientConfig -> (AppData -> m a) -> m a
- runTLSClientStartTLS :: MonadUnliftIO m => TLSClientConfig -> GeneralApplicationStartTLS m a -> m a
- tlsClientPort :: TLSClientConfig -> Int
- tlsClientHost :: TLSClientConfig -> ByteString
- tlsClientUseTLS :: TLSClientConfig -> Bool
- tlsClientTLSSettings :: TLSClientConfig -> TLSSettings
- tlsClientSockSettings :: TLSClientConfig -> Maybe SockSettings
- tlsClientConnectionContext :: TLSClientConfig -> Maybe ConnectionContext
- sourceConnection :: MonadIO m => Connection -> ConduitT i ByteString m ()
- sinkConnection :: MonadIO m => Connection -> ConduitT ByteString o m ()
Common
type ApplicationStartTLS = GeneralApplicationStartTLS IO () Source #
type GeneralApplicationStartTLS m a = (AppData, (AppData -> m ()) -> m ()) -> m a Source #
Since: 1.2.2
Server
:: HostPreference | |
-> Int | port |
-> ByteString | Certificate raw data |
-> ByteString | Key file raw data |
-> TLSConfig |
allow to build a server config directly from raw bytestring data (exact same string as if the certificates were read from the filesystem). this enables to plug another backend to fetch certifcates (other than FS)
:: HostPreference | |
-> Int | Port |
-> ByteString | Certificate raw data |
-> [ByteString] | Chain certificate raw data |
-> ByteString | Key file raw data |
-> TLSConfig |
Like tlsConfigBS
, but also allow specifying chain certificates.
Since 1.1.1
:: HostPreference | |
-> Int | Port |
-> FilePath | Certificate |
-> [FilePath] | Chain certificates |
-> FilePath | Key |
-> TLSConfig |
Like tlsConfig
, but also allow specifying chain certificates.
Since 1.1.1
tlsHost :: TLSConfig -> HostPreference Source #
tlsNeedLocalAddr :: TLSConfig -> Bool Source #
Create an AppData
from an existing tls Context
value. This is a lower level function, allowing you to create a connection in any way you want.
Sample usage:
import Network.Simple.TCP.TLS myapp :: Application IO ... main = do cset <- getDefaultClientSettings connect cset "host" "port" $ (\(ctx, addr) -> myapp $ tlsAppData ctx addr Nothing)
Since 1.0.1
runGeneralTCPServerTLS :: MonadUnliftIO m => TLSConfig -> (AppData -> m ()) -> m () Source #
Like runTCPServerTLS
, but monad can be any instance of MonadUnliftIO
.
Note that any changes to the monadic state performed by individual client handlers will be discarded. If you have mutable state you want to share among multiple handlers, you need to use some kind of mutable variables.
Since 1.1.2
runTCPServerStartTLS :: MonadUnliftIO m => TLSConfig -> GeneralApplicationStartTLS m () -> m () Source #
run a server un-crypted but also pass a call-back to trigger a StartTLS handshake on the underlying connection
Sample usage:
runTCPServerStartTLS serverConfig $ \(appData,startTLS) -> do abortTLS <- doSomethingInClear appData unless abortTLS $ startTls $ \appDataTls -> do doSomethingSSL appDataTls
Client
data TLSClientConfig Source #
Settings type for TLS client connection.
Since 1.0.2
:: Int | port |
-> ByteString | host |
-> TLSClientConfig |
Smart constructor for TLSClientConfig
.
Since 1.0.2
runTLSClient :: MonadUnliftIO m => TLSClientConfig -> (AppData -> m a) -> m a Source #
Run an application with the given configuration.
Since 1.0.2
runTLSClientStartTLS :: MonadUnliftIO m => TLSClientConfig -> GeneralApplicationStartTLS m a -> m a Source #
Run an application with the given configuration. starting with a clear connection but provide also a call back to trigger a StartTLS handshake on the connection
Since 1.0.2
tlsClientPort :: TLSClientConfig -> Int Source #
Since 1.0.2
tlsClientHost :: TLSClientConfig -> ByteString Source #
Since 1.0.2
tlsClientUseTLS :: TLSClientConfig -> Bool Source #
Default is True. If set to False
, will make a non-TLS connection.
Since 1.0.2
tlsClientTLSSettings :: TLSClientConfig -> TLSSettings Source #
TLS settings to use. If not provided, defaults will be provided.
Since 1.0.2
tlsClientSockSettings :: TLSClientConfig -> Maybe SockSettings Source #
Socks configuration; default is Nothing
. If absent, Socks will not be used.
Since 1.0.2
tlsClientConnectionContext :: TLSClientConfig -> Maybe ConnectionContext Source #
Connection context. Default is Nothing
, which will generate a new
context automatically. If you will be making many connections, it's
recommended to call initConnectionContext
yourself.
Since 1.0.2
Misc
sourceConnection :: MonadIO m => Connection -> ConduitT i ByteString m () Source #
Read from a Connection
.
Since: 1.3.0
sinkConnection :: MonadIO m => Connection -> ConduitT ByteString o m () Source #
Write to a Connection
.
Since: 1.3.0