Safe Haskell | None |
---|---|
Language | Haskell2010 |
HTTP over TLS support for Warp via the TLS package.
If HTTP/2 is negotiated by ALPN, HTTP/2 over TLS is used. Otherwise HTTP/1.1 over TLS is used.
Support for SSL is now obsoleted.
Synopsis
- data TLSSettings
- defaultTlsSettings :: TLSSettings
- tlsSettings :: FilePath -> FilePath -> TLSSettings
- tlsSettingsMemory :: ByteString -> ByteString -> TLSSettings
- tlsSettingsChain :: FilePath -> [FilePath] -> FilePath -> TLSSettings
- tlsSettingsChainMemory :: ByteString -> [ByteString] -> ByteString -> TLSSettings
- certFile :: TLSSettings -> FilePath
- keyFile :: TLSSettings -> FilePath
- tlsLogging :: TLSSettings -> Logging
- tlsAllowedVersions :: TLSSettings -> [Version]
- tlsCiphers :: TLSSettings -> [Cipher]
- tlsWantClientCert :: TLSSettings -> Bool
- tlsServerHooks :: TLSSettings -> ServerHooks
- tlsServerDHEParams :: TLSSettings -> Maybe Params
- tlsSessionManagerConfig :: TLSSettings -> Maybe Config
- onInsecure :: TLSSettings -> OnInsecure
- data OnInsecure
- runTLS :: TLSSettings -> Settings -> Application -> IO ()
- runTLSSocket :: TLSSettings -> Settings -> Socket -> Application -> IO ()
- data WarpTLSException = InsecureConnectionDenied
- data Params
- generateParams :: MonadRandom m => Int -> Integer -> m Params
Settings
data TLSSettings Source #
Settings for WarpTLS.
defaultTlsSettings :: TLSSettings Source #
Default TLSSettings
. Use this to create TLSSettings
with the field record name (aka accessors).
Smart constructors
:: FilePath | Certificate file |
-> FilePath | Key file |
-> TLSSettings |
A smart constructor for TLSSettings
based on defaultTlsSettings
.
:: ByteString | Certificate bytes |
-> ByteString | Key bytes |
-> TLSSettings |
A smart constructor for TLSSettings
, but uses in-memory representations
of the certificate and key based on defaultTlsSettings
.
Since 3.0.1
:: FilePath | Certificate file |
-> [FilePath] | Chain certificate files |
-> FilePath | Key file |
-> TLSSettings |
A smart constructor for TLSSettings
that allows specifying
chain certificates based on defaultTlsSettings
.
Since 3.0.3
tlsSettingsChainMemory Source #
:: ByteString | Certificate bytes |
-> [ByteString] | Chain certificate bytes |
-> ByteString | Key bytes |
-> TLSSettings |
A smart constructor for TLSSettings
, but uses in-memory representations
of the certificate and key based on defaultTlsSettings
.
Since 3.0.3
Accessors
certFile :: TLSSettings -> FilePath Source #
File containing the certificate.
keyFile :: TLSSettings -> FilePath Source #
File containing the key
tlsLogging :: TLSSettings -> Logging Source #
tlsAllowedVersions :: TLSSettings -> [Version] Source #
The TLS versions this server accepts.
>>>
tlsAllowedVersions defaultTlsSettings
[TLS13,TLS12,TLS11,TLS10]
Since 1.4.2
tlsCiphers :: TLSSettings -> [Cipher] Source #
The TLS ciphers this server accepts.
>>>
tlsCiphers defaultTlsSettings
[ECDHE-ECDSA-AES256GCM-SHA384,ECDHE-ECDSA-AES128GCM-SHA256,ECDHE-RSA-AES256GCM-SHA384,ECDHE-RSA-AES128GCM-SHA256,DHE-RSA-AES256GCM-SHA384,DHE-RSA-AES128GCM-SHA256,ECDHE-ECDSA-AES256CBC-SHA384,ECDHE-RSA-AES256CBC-SHA384,DHE-RSA-AES256-SHA256,ECDHE-ECDSA-AES256CBC-SHA,ECDHE-RSA-AES256CBC-SHA,DHE-RSA-AES256-SHA1,RSA-AES256GCM-SHA384,RSA-AES256-SHA256,RSA-AES256-SHA1,AES128GCM-SHA256,AES256GCM-SHA384]
Since 1.4.2
tlsWantClientCert :: TLSSettings -> Bool Source #
Whether or not to demand a certificate from the client. If this is set to True, you must handle received certificates in a server hook or all connections will fail.
>>>
tlsWantClientCert defaultTlsSettings
False
Since 3.0.2
tlsServerHooks :: TLSSettings -> ServerHooks Source #
The server-side hooks called by the tls package, including actions to take when a client certificate is received. See the Network.TLS module for details.
Default: def
Since 3.0.2
tlsServerDHEParams :: TLSSettings -> Maybe Params Source #
Configuration for ServerDHEParams
more function lives in cryptonite
package
Default: Nothing
Since 3.2.2
tlsSessionManagerConfig :: TLSSettings -> Maybe Config Source #
Configuration for in-memory TLS session manager.
If Nothing, noSessionManager
is used.
Otherwise, an in-memory TLS session manager is created
according to Config
.
Default: Nothing
Since 3.2.4
onInsecure :: TLSSettings -> OnInsecure Source #
Do we allow insecure connections with this server as well?
>>>
onInsecure defaultTlsSettings
DenyInsecure "This server only accepts secure HTTPS connections."
Since 1.4.0
data OnInsecure Source #
An action when a plain HTTP comes to HTTP over TLS/SSL port.
Instances
Show OnInsecure Source # | |
Defined in Network.Wai.Handler.WarpTLS showsPrec :: Int -> OnInsecure -> ShowS # show :: OnInsecure -> String # showList :: [OnInsecure] -> ShowS # |
Runner
runTLS :: TLSSettings -> Settings -> Application -> IO () Source #
Running Application
with TLSSettings
and Settings
.
runTLSSocket :: TLSSettings -> Settings -> Socket -> Application -> IO () Source #
Running Application
with TLSSettings
and Settings
using
specified Socket
.
Exception
data WarpTLSException Source #
Instances
Show WarpTLSException Source # | |
Defined in Network.Wai.Handler.WarpTLS showsPrec :: Int -> WarpTLSException -> ShowS # show :: WarpTLSException -> String # showList :: [WarpTLSException] -> ShowS # | |
Exception WarpTLSException Source # | |
Defined in Network.Wai.Handler.WarpTLS |
Represent Diffie Hellman parameters namely P (prime), and G (generator).
Instances
Eq Params | |
Data Params | |
Defined in Crypto.PubKey.DH gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params -> c Params # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Params # toConstr :: Params -> Constr # dataTypeOf :: Params -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Params) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Params) # gmapT :: (forall b. Data b => b -> b) -> Params -> Params # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r # gmapQ :: (forall d. Data d => d -> u) -> Params -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Params -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params -> m Params # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params # | |
Read Params | |
Show Params | |
NFData Params | |
Defined in Crypto.PubKey.DH |
:: MonadRandom m | |
=> Int | number of bits |
-> Integer | generator |
-> m Params |
generate params from a specific generator (2 or 5 are common values) we generate a safe prime (a prime number of the form 2p+1 where p is also prime)