{-# LANGUAGE ScopedTypeVariables #-}
module System.IO.Streams.TLS
( TLSConnection
, connect
, connectTLS
, tLsToConnection
, accept
, module Data.TLSSetting
) where
import qualified Control.Exception as E
import Data.Connection
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Data.TLSSetting
import qualified Network.Socket as N
import Network.TLS (ClientParams, Context, ServerParams)
import qualified Network.TLS as TLS
import qualified System.IO.Streams as Stream
import qualified System.IO.Streams.TCP as TCP
type TLSConnection = Connection (TLS.Context, N.SockAddr)
tLsToConnection :: (Context, N.SockAddr)
-> IO TLSConnection
tLsToConnection (ctx, addr) = do
is <- Stream.makeInputStream input
return (Connection is write (closeTLS ctx) (ctx, addr))
where
input = (do
s <- TLS.recvData ctx
return $! if B.null s then Nothing else Just s
) `E.catch` (\(_::E.SomeException) -> return Nothing)
write s = TLS.sendData ctx s
closeTLS :: Context -> IO ()
closeTLS ctx = (TLS.bye ctx >> TLS.contextClose ctx)
`E.catch` (\(_::E.SomeException) -> return ())
connectTLS :: ClientParams
-> Maybe String
-> N.HostName
-> N.PortNumber
-> IO (Context, N.SockAddr)
connectTLS prms subname host port = do
let subname' = maybe host id subname
prms' = prms { TLS.clientServerIdentification = (subname', BC.pack (show port)) }
(sock, addr) <- TCP.connectSocket host port
E.bracketOnError (TLS.contextNew sock prms') closeTLS $ \ ctx -> do
TLS.handshake ctx
return (ctx, addr)
connect :: ClientParams
-> Maybe String
-> N.HostName
-> N.PortNumber
-> IO TLSConnection
connect prms subname host port = connectTLS prms subname host port >>= tLsToConnection
accept :: ServerParams
-> N.Socket
-> IO TLSConnection
accept prms sock = do
(sock', addr) <- N.accept sock
E.bracketOnError (TLS.contextNew sock' prms) closeTLS $ \ ctx -> do
TLS.handshake ctx
conn <- tLsToConnection (ctx, addr)
return conn