{-# LANGUAGE ExistentialQuantification #-}
module Network.WebSockets.Protocol
    ( Protocol (..)
    , defaultProtocol
    , protocols
    , compatible
    , headerVersions
    , finishRequest
    , finishResponse
    , encodeMessages
    , decodeMessages
    , createRequest
    ) where
import           Data.ByteString                       (ByteString)
import qualified Data.ByteString                       as B
import           Network.WebSockets.Connection.Options
import           Network.WebSockets.Http
import qualified Network.WebSockets.Hybi13             as Hybi13
import           Network.WebSockets.Stream             (Stream)
import           Network.WebSockets.Types
data Protocol
    = Hybi13
    deriving (Int -> Protocol -> ShowS
[Protocol] -> ShowS
Protocol -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Protocol] -> ShowS
$cshowList :: [Protocol] -> ShowS
show :: Protocol -> String
$cshow :: Protocol -> String
showsPrec :: Int -> Protocol -> ShowS
$cshowsPrec :: Int -> Protocol -> ShowS
Show)
defaultProtocol :: Protocol
defaultProtocol :: Protocol
defaultProtocol = Protocol
Hybi13
protocols :: [Protocol]
protocols :: [Protocol]
protocols = [Protocol
Hybi13]
headerVersions :: Protocol -> [ByteString]
 Protocol
Hybi13 = [ByteString]
Hybi13.headerVersions
compatible :: Protocol -> RequestHead -> Bool
compatible :: Protocol -> RequestHead -> Bool
compatible Protocol
protocol RequestHead
req = case RequestHead -> Maybe ByteString
getRequestSecWebSocketVersion RequestHead
req of
    Just ByteString
v -> ByteString
v forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Protocol -> [ByteString]
headerVersions Protocol
protocol
    Maybe ByteString
_      -> Bool
True  
finishRequest
    :: Protocol -> RequestHead -> Headers -> Either HandshakeException Response
finishRequest :: Protocol
-> RequestHead -> Headers -> Either HandshakeException Response
finishRequest Protocol
Hybi13 = RequestHead -> Headers -> Either HandshakeException Response
Hybi13.finishRequest
finishResponse
    :: Protocol -> RequestHead -> ResponseHead
    -> Either HandshakeException Response
finishResponse :: Protocol
-> RequestHead
-> ResponseHead
-> Either HandshakeException Response
finishResponse Protocol
Hybi13 = RequestHead -> ResponseHead -> Either HandshakeException Response
Hybi13.finishResponse
encodeMessages
    :: Protocol -> ConnectionType -> Stream
    -> IO ([Message] -> IO ())
encodeMessages :: Protocol -> ConnectionType -> Stream -> IO ([Message] -> IO ())
encodeMessages Protocol
Hybi13 = ConnectionType -> Stream -> IO ([Message] -> IO ())
Hybi13.encodeMessages
decodeMessages
    :: Protocol -> SizeLimit -> SizeLimit -> Stream
    -> IO (IO (Maybe Message))
decodeMessages :: Protocol
-> SizeLimit -> SizeLimit -> Stream -> IO (IO (Maybe Message))
decodeMessages Protocol
Hybi13 SizeLimit
frameLimit SizeLimit
messageLimit =
    SizeLimit -> SizeLimit -> Stream -> IO (IO (Maybe Message))
Hybi13.decodeMessages SizeLimit
frameLimit SizeLimit
messageLimit
createRequest
    :: Protocol -> B.ByteString -> B.ByteString -> Bool -> Headers
    -> IO RequestHead
createRequest :: Protocol
-> ByteString -> ByteString -> Bool -> Headers -> IO RequestHead
createRequest Protocol
Hybi13 = ByteString -> ByteString -> Bool -> Headers -> IO RequestHead
Hybi13.createRequest