{-# LANGUAGE CPP #-}
module Network.WebSockets.Connection.Options
( ConnectionOptions (..)
, defaultConnectionOptions
, CompressionOptions (..)
, PermessageDeflate (..)
, defaultPermessageDeflate
, SizeLimit (..)
, atMostSizeLimit
) where
import Data.Int (Int64)
import Data.Monoid (Monoid (..))
import Prelude
data ConnectionOptions = ConnectionOptions
{ ConnectionOptions -> IO ()
connectionOnPong :: !(IO ())
, ConnectionOptions -> Int
connectionTimeout :: !Int
, ConnectionOptions -> CompressionOptions
connectionCompressionOptions :: !CompressionOptions
, ConnectionOptions -> Bool
connectionStrictUnicode :: !Bool
, ConnectionOptions -> SizeLimit
connectionFramePayloadSizeLimit :: !SizeLimit
, ConnectionOptions -> SizeLimit
connectionMessageDataSizeLimit :: !SizeLimit
}
defaultConnectionOptions :: ConnectionOptions
defaultConnectionOptions :: ConnectionOptions
defaultConnectionOptions = ConnectionOptions
{ connectionOnPong :: IO ()
connectionOnPong = forall (m :: * -> *) a. Monad m => a -> m a
return ()
, connectionTimeout :: Int
connectionTimeout = Int
30
, connectionCompressionOptions :: CompressionOptions
connectionCompressionOptions = CompressionOptions
NoCompression
, connectionStrictUnicode :: Bool
connectionStrictUnicode = Bool
False
, connectionFramePayloadSizeLimit :: SizeLimit
connectionFramePayloadSizeLimit = forall a. Monoid a => a
mempty
, connectionMessageDataSizeLimit :: SizeLimit
connectionMessageDataSizeLimit = forall a. Monoid a => a
mempty
}
data CompressionOptions
= NoCompression
| PermessageDeflateCompression PermessageDeflate
deriving (CompressionOptions -> CompressionOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompressionOptions -> CompressionOptions -> Bool
$c/= :: CompressionOptions -> CompressionOptions -> Bool
== :: CompressionOptions -> CompressionOptions -> Bool
$c== :: CompressionOptions -> CompressionOptions -> Bool
Eq, Int -> CompressionOptions -> ShowS
[CompressionOptions] -> ShowS
CompressionOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompressionOptions] -> ShowS
$cshowList :: [CompressionOptions] -> ShowS
show :: CompressionOptions -> String
$cshow :: CompressionOptions -> String
showsPrec :: Int -> CompressionOptions -> ShowS
$cshowsPrec :: Int -> CompressionOptions -> ShowS
Show)
data PermessageDeflate = PermessageDeflate
{ PermessageDeflate -> Bool
serverNoContextTakeover :: Bool
, PermessageDeflate -> Bool
clientNoContextTakeover :: Bool
, PermessageDeflate -> Int
serverMaxWindowBits :: Int
, PermessageDeflate -> Int
clientMaxWindowBits :: Int
, PermessageDeflate -> Int
pdCompressionLevel :: Int
} deriving (PermessageDeflate -> PermessageDeflate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PermessageDeflate -> PermessageDeflate -> Bool
$c/= :: PermessageDeflate -> PermessageDeflate -> Bool
== :: PermessageDeflate -> PermessageDeflate -> Bool
$c== :: PermessageDeflate -> PermessageDeflate -> Bool
Eq, Int -> PermessageDeflate -> ShowS
[PermessageDeflate] -> ShowS
PermessageDeflate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PermessageDeflate] -> ShowS
$cshowList :: [PermessageDeflate] -> ShowS
show :: PermessageDeflate -> String
$cshow :: PermessageDeflate -> String
showsPrec :: Int -> PermessageDeflate -> ShowS
$cshowsPrec :: Int -> PermessageDeflate -> ShowS
Show)
defaultPermessageDeflate :: PermessageDeflate
defaultPermessageDeflate :: PermessageDeflate
defaultPermessageDeflate = Bool -> Bool -> Int -> Int -> Int -> PermessageDeflate
PermessageDeflate Bool
False Bool
False Int
15 Int
15 Int
8
data SizeLimit
= NoSizeLimit
| SizeLimit !Int64
deriving (SizeLimit -> SizeLimit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SizeLimit -> SizeLimit -> Bool
$c/= :: SizeLimit -> SizeLimit -> Bool
== :: SizeLimit -> SizeLimit -> Bool
$c== :: SizeLimit -> SizeLimit -> Bool
Eq, Int -> SizeLimit -> ShowS
[SizeLimit] -> ShowS
SizeLimit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SizeLimit] -> ShowS
$cshowList :: [SizeLimit] -> ShowS
show :: SizeLimit -> String
$cshow :: SizeLimit -> String
showsPrec :: Int -> SizeLimit -> ShowS
$cshowsPrec :: Int -> SizeLimit -> ShowS
Show)
instance Monoid SizeLimit where
mempty :: SizeLimit
mempty = SizeLimit
NoSizeLimit
#if !MIN_VERSION_base(4,11,0)
mappend NoSizeLimit y = y
mappend x NoSizeLimit = x
mappend (SizeLimit x) (SizeLimit y) = SizeLimit (min x y)
#else
instance Semigroup SizeLimit where
<> :: SizeLimit -> SizeLimit -> SizeLimit
(<>) SizeLimit
NoSizeLimit SizeLimit
y = SizeLimit
y
(<>) SizeLimit
x SizeLimit
NoSizeLimit = SizeLimit
x
(<>) (SizeLimit Int64
x) (SizeLimit Int64
y) = Int64 -> SizeLimit
SizeLimit (forall a. Ord a => a -> a -> a
min Int64
x Int64
y)
#endif
atMostSizeLimit :: Int64 -> SizeLimit -> Bool
atMostSizeLimit :: Int64 -> SizeLimit -> Bool
atMostSizeLimit Int64
_ SizeLimit
NoSizeLimit = Bool
True
atMostSizeLimit Int64
s (SizeLimit Int64
l) = Int64
s forall a. Ord a => a -> a -> Bool
<= Int64
l
{-# INLINE atMostSizeLimit #-}