secure-sockets-1.2.9.2: Secure point-to-point connectivity library

Safe HaskellNone

Network.Secure

Contents

Description

This library simplifies the task of securely connecting two servers to each other. It closely mimicks the regular socket API, and adds the concept of identity: each communicating server has an identity, and connections can only be established between two servers who know each other and expect to be communicating.

Under the hood, the library takes care of strongly authenticating the connection, and of encrypting all traffic. If you successfully establish a connection using this library, you have the guarantee that the connection is secure.

Synopsis

Tutorial

First, each host needs to generate a local identity for itself. A local identity allows a server to authenticate itself to remote peers.

 do
   id <- newLocalIdentity "server1.domain.com" 365
   writeIdentity id >>= writeFile "server.key"

The name is not used at all by the library, it just allows you to identify the key later on if you need to.

This identity contains secret key material that only the generating host should have. From this, we need to generate a public identity that can be given to other hosts.

 do
   id <- readFile "server.key" >>= readIdentity
   writeIdentity (toPeerIdentity id) >>= writeFile "server.pub"

This public file should be distributed to the servers with whom you want to communicate. Once everyone has the public identities of their peers, we can start connecting. First, one host needs to start listening for connections.

 do
   me     <- readFile "a.key" >>= readIdentity
   you    <- readFile "b.pub" >>= readIdentity
   server <- newServer (Nothing, "4242")
   conn   <- accept me [you] server

Then, another host needs to connect.

 do
   me   <- readFile "b.key" >>= readIdentity
   you  <- readFile "a.pub" >>= readIdentity
   conn <- connect me [you] ("a.com", "4242")

Et voila! From there on, you can communicate using the usual socket-ish API:

 do
   write conn "hello?"
   read conn 128 >>= putStrLn
   close conn

N.B. The program should start with withOpenSSL in order to initialize SSL (main = withOpenSSL $ do).

Internals and caveats

Note that this section gives out internal implementation details which are subject to change! Compatibility breakages will be indicated by appropriate version number bumps for the package, and the internal details of new versions may bear no resemblance whatsoever to the old version.

The current implementation uses OpenSSL (via HsOpenSSL) for transport security, with the AES256-SHA ciphersuite and 4096 bit RSA keys.

Due to a current limitation of the HsOpenSSL API, we do not use a ciphersuite that makes use of ephemeral keys for encryption. The consequence is that connections established with this library do not provide perfect forward secrecy.

That is, if an attacker can compromise the private keys of the communicating servers, she can decrypt all past communications that she has recorded.

This shortcoming will be fixed at some point, either by adding Diffie-Hellman keying support to HsOpenSSL, or by switching to a different underlying implementation.

Managing identities

class Identity a whereSource

An identity, public or private.

Methods

identityName :: a -> StringSource

Return the description that was associated with the identity when it was created.

writeIdentity :: (Functor m, MonadIO m) => a -> m ByteStringSource

Serialize an identity to a ByteString for storage or transmission.

readIdentity :: (Functor m, MonadIO m) => ByteString -> m aSource

Read back an identity previously serialized with writeIdentity.

data PeerIdentity Source

The public identity of a peer. This kind of identity can be used to authenticate the remote ends of connections.

data LocalIdentity Source

A local identity. This kind of identity can be used to authenticate to remote ends of connections.

toPeerIdentity :: LocalIdentity -> PeerIdentitySource

Extract the public parts of a LocalIdentity into a PeerIdentity suitable for sharing with peers. The resulting PeerIdentity will allow them to verify your identity when you authenticate using the corresponding LocalIdentity.

newLocalIdentity :: MonadIO m => String -> Int -> m LocalIdentitySource

Generate a new LocalIdentity, giving it an identifying name and a validity period in days.

Note that this function may take quite a while to execute, as it is generating key material for the identity.

Communicating

Connecting to peers

connect :: LocalIdentity -> [PeerIdentity] -> (HostName, ServiceName) -> IO ConnectionSource

Connect securely to the given host/port. The Connection is returned only if the peer accepts the given LocalIdentity, and if the remote endpoint successfully authenticates as one of the given PeerIdentity.

Accepting connections from peers

data Socket Source

A server socket that accepts only secure connections.

Instances

newServer :: (Maybe HostName, ServiceName) -> IO SocketSource

Create a new secure socket server, listening on the given address/port. The host may be Nothing to signify that the socket should listen on all available addresses.

accept :: LocalIdentity -> [PeerIdentity] -> Socket -> IO ConnectionSource

Accept one secure connection from a remote peer. The peer may authenticate as any of the given peer identities. A Connection is returned iff the autentication completes successfully.

Talking to connected peers

data Connection Source

An established authenticated connection to a peer. It is guaranteed that all Connection objects are with a known peer, and that the connection is strongly encrypted.

peer :: Connection -> PeerIdentitySource

Return the PeerIdentity of the remote end of the connection.

read :: Connection -> Int -> IO ByteStringSource

Read at most n bytes from the given connection.

readPtr :: Connection -> Ptr a -> Int -> IO IntSource

Read at most n bytes from the given connection, into the given raw buffer.

write :: Connection -> ByteString -> IO ()Source

Send data to the connected peer.

writePtr :: Connection -> Ptr a -> Int -> IO ()Source

Send data from the given raw pointer to the connected peer.

close :: Connection -> IO ()Source

Close the connection. No other operations on Connections should be used after closing it.

Misc reexports from Socket

type HostName = String

Either a host name e.g., "haskell.org" or a numeric host address string consisting of a dotted decimal IPv4 address or an IPv6 address e.g., "192.168.0.1".