module Data.TLSSetting
(
TrustedCAStore(..)
, makeClientParams
, makeClientParams'
, makeServerParams
, makeServerParams'
, mozillaCAStorePath
) where
import qualified Data.ByteString as B
import Data.Default.Class (def)
import qualified Data.PEM as X509
import qualified Data.X509 as X509
import qualified Data.X509.CertificateStore as X509
import qualified Network.TLS as TLS
import qualified Network.TLS.Extra as TLS
import Paths_tcp_streams (getDataFileName)
import qualified System.X509 as X509
data TrustedCAStore
= SystemCAStore
| MozillaCAStore
| CustomCAStore FilePath
deriving (Show, Eq)
mozillaCAStorePath :: IO FilePath
mozillaCAStorePath = getDataFileName "mozillaCAStore.pem"
makeCAStore :: TrustedCAStore -> IO X509.CertificateStore
makeCAStore SystemCAStore = X509.getSystemCertificateStore
makeCAStore MozillaCAStore = makeCAStore . CustomCAStore =<< mozillaCAStorePath
makeCAStore (CustomCAStore fp) = do
bs <- B.readFile fp
let Right pems = X509.pemParseBS bs
case mapM (X509.decodeSignedCertificate . X509.pemContent) pems of
Right cas -> return (X509.makeCertificateStore cas)
Left err -> error err
makeClientParams :: TrustedCAStore
-> IO TLS.ClientParams
makeClientParams tca = do
caStore <- makeCAStore tca
return (TLS.defaultParamsClient "" B.empty)
{ TLS.clientSupported = def { TLS.supportedCiphers = TLS.ciphersuite_all }
, TLS.clientShared = def
{ TLS.sharedCAStore = caStore
, TLS.sharedValidationCache = def
}
}
makeClientParams' :: FilePath
-> [FilePath]
-> FilePath
-> TrustedCAStore
-> IO TLS.ClientParams
makeClientParams' pub certs priv tca = do
p <- makeClientParams tca
c <- TLS.credentialLoadX509Chain pub certs priv
case c of
Right c' ->
return p
{ TLS.clientShared = (TLS.clientShared p)
{
TLS.sharedCredentials = TLS.Credentials [c']
}
}
Left err -> error err
makeServerParams :: FilePath
-> [FilePath]
-> FilePath
-> IO TLS.ServerParams
makeServerParams pub certs priv = do
c <- TLS.credentialLoadX509Chain pub certs priv
case c of
Right c'@(X509.CertificateChain c'', _) ->
return def
{ TLS.serverCACertificates = c''
, TLS.serverShared = def
{
TLS.sharedCredentials = TLS.Credentials [c']
}
, TLS.serverSupported = def { TLS.supportedCiphers = TLS.ciphersuite_strong }
}
Left err -> error err
makeServerParams' :: FilePath
-> [FilePath]
-> FilePath
-> TrustedCAStore
-> IO TLS.ServerParams
makeServerParams' pub certs priv tca = do
caStore <- makeCAStore tca
p <- makeServerParams pub certs priv
return p
{ TLS.serverWantClientCert = True
, TLS.serverShared = (TLS.serverShared p)
{ TLS.sharedCAStore = caStore
}
}