{-# LANGUAGE CPP #-}
module Network.HaskellNet.SSL
( Settings (..)
, defaultSettingsWithPort
) where
#if MIN_VERSION_network(3,0,0)
import Network.Socket (PortNumber)
#else
import Network.Socket.Internal (PortNumber)
#endif
data Settings = Settings
{ Settings -> PortNumber
sslPort :: PortNumber
, Settings -> Int
sslMaxLineLength :: Int
, Settings -> Bool
sslLogToConsole :: Bool
, Settings -> Bool
sslDisableCertificateValidation :: Bool
} deriving(Settings -> Settings -> Bool
(Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool) -> Eq Settings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Settings -> Settings -> Bool
$c/= :: Settings -> Settings -> Bool
== :: Settings -> Settings -> Bool
$c== :: Settings -> Settings -> Bool
Eq, Eq Settings
Eq Settings
-> (Settings -> Settings -> Ordering)
-> (Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool)
-> (Settings -> Settings -> Settings)
-> (Settings -> Settings -> Settings)
-> Ord Settings
Settings -> Settings -> Bool
Settings -> Settings -> Ordering
Settings -> Settings -> Settings
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Settings -> Settings -> Settings
$cmin :: Settings -> Settings -> Settings
max :: Settings -> Settings -> Settings
$cmax :: Settings -> Settings -> Settings
>= :: Settings -> Settings -> Bool
$c>= :: Settings -> Settings -> Bool
> :: Settings -> Settings -> Bool
$c> :: Settings -> Settings -> Bool
<= :: Settings -> Settings -> Bool
$c<= :: Settings -> Settings -> Bool
< :: Settings -> Settings -> Bool
$c< :: Settings -> Settings -> Bool
compare :: Settings -> Settings -> Ordering
$ccompare :: Settings -> Settings -> Ordering
$cp1Ord :: Eq Settings
Ord, Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> String
(Int -> Settings -> ShowS)
-> (Settings -> String) -> ([Settings] -> ShowS) -> Show Settings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Settings] -> ShowS
$cshowList :: [Settings] -> ShowS
show :: Settings -> String
$cshow :: Settings -> String
showsPrec :: Int -> Settings -> ShowS
$cshowsPrec :: Int -> Settings -> ShowS
Show)
defaultSettingsWithPort :: PortNumber -> Settings
defaultSettingsWithPort :: PortNumber -> Settings
defaultSettingsWithPort PortNumber
p = Settings :: PortNumber -> Int -> Bool -> Bool -> Settings
Settings
{ sslPort :: PortNumber
sslPort = PortNumber
p
, sslMaxLineLength :: Int
sslMaxLineLength = Int
10000
, sslLogToConsole :: Bool
sslLogToConsole = Bool
False
, sslDisableCertificateValidation :: Bool
sslDisableCertificateValidation = Bool
False
}