module Network.Connection.Types
where
import Control.Concurrent.MVar (MVar)
import Data.Default.Class
import Data.X509.CertificateStore
import Data.ByteString (ByteString)
import Network.Socket (PortNumber, Socket)
import qualified Network.TLS as TLS
import qualified Network.TLS.Extra as TLS
import System.IO (Handle)
data ConnectionBackend = ConnectionStream Handle
| ConnectionSocket Socket
| ConnectionTLS TLS.Context
type HostName = String
data ConnectionParams = ConnectionParams
{ ConnectionParams -> HostName
connectionHostname :: HostName
, ConnectionParams -> PortNumber
connectionPort :: PortNumber
, ConnectionParams -> Maybe TLSSettings
connectionUseSecure :: Maybe TLSSettings
, ConnectionParams -> Maybe ProxySettings
connectionUseSocks :: Maybe ProxySettings
}
data ProxySettings =
SockSettingsSimple HostName PortNumber
| SockSettingsEnvironment (Maybe String)
| OtherProxy HostName PortNumber
type SockSettings = ProxySettings
data TLSSettings
= TLSSettingsSimple
{ TLSSettings -> Bool
settingDisableCertificateValidation :: Bool
, TLSSettings -> Bool
settingDisableSession :: Bool
, TLSSettings -> Bool
settingUseServerName :: Bool
, TLSSettings -> Supported
settingClientSupported :: TLS.Supported
}
| TLSSettings TLS.ClientParams
deriving (Int -> TLSSettings -> ShowS
[TLSSettings] -> ShowS
TLSSettings -> HostName
(Int -> TLSSettings -> ShowS)
-> (TLSSettings -> HostName)
-> ([TLSSettings] -> ShowS)
-> Show TLSSettings
forall a.
(Int -> a -> ShowS) -> (a -> HostName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TLSSettings -> ShowS
showsPrec :: Int -> TLSSettings -> ShowS
$cshow :: TLSSettings -> HostName
show :: TLSSettings -> HostName
$cshowList :: [TLSSettings] -> ShowS
showList :: [TLSSettings] -> ShowS
Show)
instance Default TLSSettings where
def :: TLSSettings
def = Bool -> Bool -> Bool -> Supported -> TLSSettings
TLSSettingsSimple Bool
False Bool
False Bool
False Supported
forall a. Default a => a
def { TLS.supportedCiphers = TLS.ciphersuite_default }
type ConnectionID = (HostName, PortNumber)
data Connection = Connection
{ Connection -> MVar ConnectionBackend
connectionBackend :: MVar ConnectionBackend
, Connection -> MVar (Maybe ByteString)
connectionBuffer :: MVar (Maybe ByteString)
, Connection -> ConnectionID
connectionID :: ConnectionID
}
data ConnectionContext = ConnectionContext
{ ConnectionContext -> CertificateStore
globalCertificateStore :: !CertificateStore
}