HsOpenSSL-0.11.6.2: Partial OpenSSL binding for Haskell
Safe HaskellNone
LanguageHaskell2010

OpenSSL.Session

Description

Functions for handling SSL connections. These functions use GHC specific calls to cooperative the with the scheduler so that blocking functions only actually block the Haskell thread, not a whole OS thread.

Synopsis

Contexts

data SSLContext Source #

An SSL context. Contexts carry configuration such as a server's private key, root CA certiifcates etc. Contexts are stateful IO objects; they start empty and various options are set on them by the functions in this module. Note that an empty context will pretty much cause any operation to fail since it doesn't even have any ciphers enabled.

context :: IO SSLContext Source #

Create a new SSL context.

contextAddOption :: SSLContext -> SSLOption -> IO () Source #

Add a protocol option to the context.

contextRemoveOption :: SSLContext -> SSLOption -> IO () Source #

Remove a protocol option from the context.

contextSetPrivateKey :: KeyPair k => SSLContext -> k -> IO () Source #

Install a private key into a context.

contextSetCertificate :: SSLContext -> X509 -> IO () Source #

Install a certificate (public key) into a context.

contextSetPrivateKeyFile :: SSLContext -> FilePath -> IO () Source #

Install a private key file in a context. The key is given as a path to the file which contains the key. The file is parsed first as PEM and, if that fails, as ASN1. If both fail, an exception is raised.

contextSetCertificateFile :: SSLContext -> FilePath -> IO () Source #

Install a certificate (public key) file in a context. The key is given as a path to the file which contains the key. The file is parsed first as PEM and, if that fails, as ASN1. If both fail, an exception is raised.

contextSetCertificateChainFile :: SSLContext -> FilePath -> IO () Source #

Install a certificate chain in a context. The certificates must be in PEM format and must be sorted starting with the subject's certificate (actual client or server certificate), followed by intermediate CA certificates if applicable, and ending at the highest level (root) CA.

contextSetCiphers :: SSLContext -> String -> IO () Source #

Set the ciphers to be used by the given context. The string argument is a list of ciphers, comma separated, as given at http://www.openssl.org/docs/apps/ciphers.html

Unrecognised ciphers are ignored. If no ciphers from the list are recognised, an exception is raised.

contextCheckPrivateKey :: SSLContext -> IO Bool Source #

Return true iff the private key installed in the given context matches the certificate also installed.

data VerificationMode Source #

Constructors

VerifyNone 
VerifyPeer 

Fields

contextSetCAFile :: SSLContext -> FilePath -> IO () Source #

Set the location of a PEM encoded list of CA certificates to be used when verifying a server's certificate

contextSetCADirectory :: SSLContext -> FilePath -> IO () Source #

Set the path to a directory which contains the PEM encoded CA root certificates. This is an alternative to contextSetCAFile. See http://www.openssl.org/docs/ssl/SSL_CTX_load_verify_locations.html for details of the file naming scheme

contextGetCAStore :: SSLContext -> IO X509Store Source #

Get a reference to, not a copy of, the X.509 certificate storage in the SSL context.

contextSetSessionIdContext :: SSLContext -> ByteString -> IO () Source #

Set context within which session can be reused (server side only).

If client certificates are used and the session id context is not set, attempts by the clients to reuse a session will make the handshake fail.

SSL connections

data SSL Source #

This is the type of an SSL connection

IO with SSL objects is non-blocking and many SSL functions return a error code which signifies that it needs to read or write more data. We handle these calls and call threadWaitRead and threadWaitWrite at the correct times. Thus multiple OS threads can be blocked inside IO in the same SSL object at a time, because they aren't really in the SSL object, they are waiting for the RTS to wake the Haskell thread.

data SSLResult a Source #

This is the type of an SSL IO operation. Errors are handled by exceptions while everything else is one of these. Note that reading from an SSL socket can result in WantWrite and vice versa.

Constructors

SSLDone a

operation finished successfully

WantRead

needs more data from the network

WantWrite

needs more outgoing buffer space

Instances

Instances details
Functor SSLResult Source # 
Instance details

Defined in OpenSSL.Session

Methods

fmap :: (a -> b) -> SSLResult a -> SSLResult b #

(<$) :: a -> SSLResult b -> SSLResult a #

Foldable SSLResult Source # 
Instance details

Defined in OpenSSL.Session

Methods

fold :: Monoid m => SSLResult m -> m #

foldMap :: Monoid m => (a -> m) -> SSLResult a -> m #

foldMap' :: Monoid m => (a -> m) -> SSLResult a -> m #

foldr :: (a -> b -> b) -> b -> SSLResult a -> b #

foldr' :: (a -> b -> b) -> b -> SSLResult a -> b #

foldl :: (b -> a -> b) -> b -> SSLResult a -> b #

foldl' :: (b -> a -> b) -> b -> SSLResult a -> b #

foldr1 :: (a -> a -> a) -> SSLResult a -> a #

foldl1 :: (a -> a -> a) -> SSLResult a -> a #

toList :: SSLResult a -> [a] #

null :: SSLResult a -> Bool #

length :: SSLResult a -> Int #

elem :: Eq a => a -> SSLResult a -> Bool #

maximum :: Ord a => SSLResult a -> a #

minimum :: Ord a => SSLResult a -> a #

sum :: Num a => SSLResult a -> a #

product :: Num a => SSLResult a -> a #

Traversable SSLResult Source # 
Instance details

Defined in OpenSSL.Session

Methods

traverse :: Applicative f => (a -> f b) -> SSLResult a -> f (SSLResult b) #

sequenceA :: Applicative f => SSLResult (f a) -> f (SSLResult a) #

mapM :: Monad m => (a -> m b) -> SSLResult a -> m (SSLResult b) #

sequence :: Monad m => SSLResult (m a) -> m (SSLResult a) #

Eq a => Eq (SSLResult a) Source # 
Instance details

Defined in OpenSSL.Session

Methods

(==) :: SSLResult a -> SSLResult a -> Bool #

(/=) :: SSLResult a -> SSLResult a -> Bool #

Show a => Show (SSLResult a) Source # 
Instance details

Defined in OpenSSL.Session

connection :: SSLContext -> Socket -> IO SSL Source #

Wrap a Socket in an SSL connection. Reading and writing to the Socket after this will cause weird errors in the SSL code. The SSL object carries a handle to the Socket so you need not worry about the garbage collector closing the file descriptor out from under you.

fdConnection :: SSLContext -> Fd -> IO SSL Source #

Wrap a socket Fd in an SSL connection.

addOption :: SSL -> SSLOption -> IO () Source #

Add a protocol option to the SSL connection.

removeOption :: SSL -> SSLOption -> IO () Source #

Remove a protocol option from the SSL connection.

setTlsextHostName :: SSL -> String -> IO () Source #

Set host name for Server Name Indication (SNI)

enableHostnameValidation :: SSL -> String -> IO () Source #

Enable hostname validation. Also see setTlsextHostName.

This uses the built-in mechanism introduced in 1.0.2/1.1.0, and will fail otherwise.

accept :: SSL -> IO () Source #

Perform an SSL server handshake

tryAccept :: SSL -> IO (SSLResult ()) Source #

Try to perform an SSL server handshake without blocking

connect :: SSL -> IO () Source #

Perform an SSL client handshake

tryConnect :: SSL -> IO (SSLResult ()) Source #

Try to perform an SSL client handshake without blocking

read :: SSL -> Int -> IO ByteString Source #

Try to read the given number of bytes from an SSL connection. On EOF an empty ByteString is returned. If the connection dies without a graceful SSL shutdown, an exception is raised.

tryRead :: SSL -> Int -> IO (SSLResult ByteString) Source #

Try to read the given number of bytes from an SSL connection without blocking.

readPtr :: SSL -> Ptr a -> Int -> IO Int Source #

Read some data into a raw pointer buffer. Retrns the number of bytes read.

tryReadPtr :: SSL -> Ptr a -> Int -> IO (SSLResult Int) Source #

Try to read some data into a raw pointer buffer, without blocking.

write :: SSL -> ByteString -> IO () Source #

Write a given ByteString to the SSL connection. Either all the data is written or an exception is raised because of an error.

tryWrite :: SSL -> ByteString -> IO (SSLResult ()) Source #

Try to write a given ByteString to the SSL connection without blocking.

writePtr :: SSL -> Ptr a -> Int -> IO () Source #

Send some data from a raw pointer buffer.

tryWritePtr :: SSL -> Ptr a -> Int -> IO (SSLResult ()) Source #

Send some data from a raw pointer buffer, without blocking.

lazyRead :: SSL -> IO ByteString Source #

Lazily read all data until reaching EOF. If the connection dies without a graceful SSL shutdown, an exception is raised.

lazyWrite :: SSL -> ByteString -> IO () Source #

Write a lazy ByteString to the SSL connection. In contrast to write, there is a chance that the string is written partway and then an exception is raised for an error. The string doesn't necessarily have to be finite.

shutdown :: SSL -> ShutdownType -> IO () Source #

Cleanly shutdown an SSL connection. Note that SSL has a concept of a secure shutdown, which is distinct from just closing the TCP connection. This performs the former and should always be preferred.

This can either just send a shutdown, or can send and wait for the peer's shutdown message.

tryShutdown :: SSL -> ShutdownType -> IO (SSLResult ()) Source #

Try to cleanly shutdown an SSL connection without blocking.

data ShutdownType Source #

Constructors

Bidirectional

wait for the peer to also shutdown

Unidirectional

only send our shutdown

Instances

Instances details
Eq ShutdownType Source # 
Instance details

Defined in OpenSSL.Session

Show ShutdownType Source # 
Instance details

Defined in OpenSSL.Session

getPeerCertificate :: SSL -> IO (Maybe X509) Source #

After a successful connection, get the certificate of the other party. If this is a server connection, you probably won't get a certificate unless you asked for it with contextSetVerificationMode

getVerifyResult :: SSL -> IO Bool Source #

Get the result of verifing the peer's certificate. This is mostly for clients to verify the certificate of the server that they have connected it. You must set a list of root CA certificates with contextSetCA... for this to make sense.

Note that this returns True iff the peer's certificate has a valid chain to a root CA. You also need to check that the certificate is correct (i.e. has the correct hostname in it) with getPeerCertificate.

sslSocket :: SSL -> Maybe Socket Source #

Get the socket underlying an SSL connection

sslFd :: SSL -> Fd Source #

Get the underlying socket Fd

Protocol Options

data SSLOption Source #

The behaviour of the SSL library can be changed by setting several options. During a handshake, the option settings of the SSL object are used. When a new SSL object is created from a SSLContext, the current option setting is copied. Changes to SSLContext do not affect already created SSL objects.

Constructors

SSL_OP_MICROSOFT_SESS_ID_BUG

As of OpenSSL 1.0.0 this option has no effect.

SSL_OP_NETSCAPE_CHALLENGE_BUG

As of OpenSSL 1.0.0 this option has no effect.

SSL_OP_NETSCAPE_REUSE_CIPHER_CHANGE_BUG

As of OpenSSL 0.9.8q and 1.0.0c, this option has no effect.

SSL_OP_SSLREF2_REUSE_CERT_TYPE_BUG 
SSL_OP_MICROSOFT_BIG_SSLV3_BUFFER 
SSL_OP_SAFARI_ECDHE_ECDSA_BUG

Don't prefer ECDHE-ECDSA ciphers when the client appears to be Safari on OS X. OS X 10.8..10.8.3 has broken support for ECDHE-ECDSA ciphers.

SSL_OP_SSLEAY_080_CLIENT_DH_BUG 
SSL_OP_TLS_D5_BUG 
SSL_OP_TLS_BLOCK_PADDING_BUG 
SSL_OP_DONT_INSERT_EMPTY_FRAGMENTS

Disables a countermeasure against a SSL 3.0/TLS 1.0 protocol vulnerability affecting CBC ciphers, which cannot be handled by some broken SSL implementations. This option has no effect for connections using other ciphers.

SSL_OP_TLSEXT_PADDING

Adds a padding extension to ensure the ClientHello size is never between 256 and 511 bytes in length. This is needed as a workaround for some implementations.

SSL_OP_ALL

All of the above bug workarounds.

SSL_OP_TLS_ROLLBACK_BUG

Disable version rollback attack detection.

During the client key exchange, the client must send the same information about acceptable SSL/TLS protocol levels as during the first hello. Some clients violate this rule by adapting to the server's answer. (Example: the client sends a SSLv2 hello and accepts up to SSLv3.1=TLSv1, the server only understands up to SSLv3. In this case the client must still use the same SSLv3.1=TLSv1 announcement. Some clients step down to SSLv3 with respect to the server's answer and violate the version rollback protection.)

SSL_OP_SINGLE_DH_USE

Always create a new key when using temporary/ephemeral DH parameters. This option must be used to prevent small subgroup attacks, when the DH parameters were not generated using "strong" primes (e.g. when using DSA-parameters). If "strong" primes were used, it is not strictly necessary to generate a new DH key during each handshake but it is also recommended. SSL_OP_SINGLE_DH_USE should therefore be enabled whenever temporary/ephemeral DH parameters are used.

SSL_OP_EPHEMERAL_RSA

Always use ephemeral (temporary) RSA key when doing RSA operations. According to the specifications this is only done, when a RSA key can only be used for signature operations (namely under export ciphers with restricted RSA keylength). By setting this option, ephemeral RSA keys are always used. This option breaks compatibility with the SSL/TLS specifications and may lead to interoperability problems with clients and should therefore never be used. Ciphers with DHE (ephemeral Diffie-Hellman) key exchange should be used instead.

SSL_OP_CIPHER_SERVER_PREFERENCE

When choosing a cipher, use the server's preferences instead of the client preferences. When not set, the SSL server will always follow the clients preferences. When set, the SSLv3/TLSv1 server will choose following its own preferences. Because of the different protocol, for SSLv2 the server will send its list of preferences to the client and the client chooses.

SSL_OP_PKCS1_CHECK_1 
SSL_OP_PKCS1_CHECK_2 
SSL_OP_NETSCAPE_CA_DN_BUG

If we accept a netscape connection, demand a client cert, have a non-self-signed CA which does not have its CA in netscape, and the browser has a cert, it will crash/hang. Works for 3.x and 4.xbeta

SSL_OP_NETSCAPE_DEMO_CIPHER_CHANGE_BUG 
SSL_OP_NO_SSLv2

Do not use the SSLv2 protocol.

SSL_OP_NO_SSLv3

Do not use the SSLv3 protocol.

SSL_OP_NO_TLSv1

Do not use the TLSv1 protocol.

SSL_OP_NO_SESSION_RESUMPTION_ON_RENEGOTIATION

When performing renegotiation as a server, always start a new session (i.e., session resumption requests are only accepted in the initial handshake). This option is not needed for clients.

SSL_OP_NO_TICKET

Normally clients and servers will, where possible, transparently make use of RFC 4507 tickets for stateless session resumption.

If this option is set this functionality is disabled and tickets will not be used by clients or servers.

SSL_OP_ALLOW_UNSAFE_LEGACY_RENEGOTIATION

Allow legacy insecure renegotiation between OpenSSL and unpatched clients or servers. See SECURE RENEGOTIATION for more details.

SSL_OP_LEGACY_SERVER_CONNECT

Allow legacy insecure renegotiation between OpenSSL and unpatched servers _only_. See SECURE RENEGOTIATION for more details.

Instances

Instances details
Eq SSLOption Source # 
Instance details

Defined in OpenSSL.SSL.Option

Ord SSLOption Source # 
Instance details

Defined in OpenSSL.SSL.Option

Show SSLOption Source # 
Instance details

Defined in OpenSSL.SSL.Option

SSL Exceptions

data SomeSSLException Source #

The root exception type for all SSL exceptions.

data ProtocolError Source #

A failure in the SSL library occurred, usually a protocol error.

Constructors

ProtocolError !String 

Direct access to OpenSSL objects

withContext :: SSLContext -> (Ptr SSLContext_ -> IO a) -> IO a Source #

Run the given action with the raw context pointer and obtain the lock while doing so.

withSSL :: SSL -> (Ptr SSL_ -> IO a) -> IO a Source #

Run continuation with exclusive access to the underlying SSL object.