module Network.Greskell.WebSocket.Connection.Type
( RawReq
, RawRes
, ReqID
, ResPack
, ReqPack (..)
, ConnectionState (..)
, Connection (..)
, GeneralException (..)
) where
import Control.Concurrent.Async (Async)
import Control.Concurrent.STM (TBQueue, TQueue, TVar)
import Control.Exception.Safe (Exception, SomeException, Typeable)
import qualified Data.ByteString.Lazy as BSL
import Data.UUID (UUID)
import Network.Greskell.WebSocket.Codec (Codec)
import Network.Greskell.WebSocket.Response (ResponseMessage)
type RawReq = BSL.ByteString
type RawRes = BSL.ByteString
type ReqID = UUID
type ResPack s = Either SomeException (ResponseMessage s)
data ReqPack s
= ReqPack
{ forall s. ReqPack s -> RawReq
reqData :: !RawReq
, forall s. ReqPack s -> ReqID
reqId :: !ReqID
, forall s. ReqPack s -> TQueue (ResPack s)
reqOutput :: !(TQueue (ResPack s))
}
data ConnectionState
= ConnOpen
| ConnClosing
| ConnClosed
deriving (ConnectionState
ConnectionState -> ConnectionState -> Bounded ConnectionState
forall a. a -> a -> Bounded a
$cminBound :: ConnectionState
minBound :: ConnectionState
$cmaxBound :: ConnectionState
maxBound :: ConnectionState
Bounded, Int -> ConnectionState
ConnectionState -> Int
ConnectionState -> [ConnectionState]
ConnectionState -> ConnectionState
ConnectionState -> ConnectionState -> [ConnectionState]
ConnectionState
-> ConnectionState -> ConnectionState -> [ConnectionState]
(ConnectionState -> ConnectionState)
-> (ConnectionState -> ConnectionState)
-> (Int -> ConnectionState)
-> (ConnectionState -> Int)
-> (ConnectionState -> [ConnectionState])
-> (ConnectionState -> ConnectionState -> [ConnectionState])
-> (ConnectionState -> ConnectionState -> [ConnectionState])
-> (ConnectionState
-> ConnectionState -> ConnectionState -> [ConnectionState])
-> Enum ConnectionState
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ConnectionState -> ConnectionState
succ :: ConnectionState -> ConnectionState
$cpred :: ConnectionState -> ConnectionState
pred :: ConnectionState -> ConnectionState
$ctoEnum :: Int -> ConnectionState
toEnum :: Int -> ConnectionState
$cfromEnum :: ConnectionState -> Int
fromEnum :: ConnectionState -> Int
$cenumFrom :: ConnectionState -> [ConnectionState]
enumFrom :: ConnectionState -> [ConnectionState]
$cenumFromThen :: ConnectionState -> ConnectionState -> [ConnectionState]
enumFromThen :: ConnectionState -> ConnectionState -> [ConnectionState]
$cenumFromTo :: ConnectionState -> ConnectionState -> [ConnectionState]
enumFromTo :: ConnectionState -> ConnectionState -> [ConnectionState]
$cenumFromThenTo :: ConnectionState
-> ConnectionState -> ConnectionState -> [ConnectionState]
enumFromThenTo :: ConnectionState
-> ConnectionState -> ConnectionState -> [ConnectionState]
Enum, ConnectionState -> ConnectionState -> Bool
(ConnectionState -> ConnectionState -> Bool)
-> (ConnectionState -> ConnectionState -> Bool)
-> Eq ConnectionState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnectionState -> ConnectionState -> Bool
== :: ConnectionState -> ConnectionState -> Bool
$c/= :: ConnectionState -> ConnectionState -> Bool
/= :: ConnectionState -> ConnectionState -> Bool
Eq, Eq ConnectionState
Eq ConnectionState =>
(ConnectionState -> ConnectionState -> Ordering)
-> (ConnectionState -> ConnectionState -> Bool)
-> (ConnectionState -> ConnectionState -> Bool)
-> (ConnectionState -> ConnectionState -> Bool)
-> (ConnectionState -> ConnectionState -> Bool)
-> (ConnectionState -> ConnectionState -> ConnectionState)
-> (ConnectionState -> ConnectionState -> ConnectionState)
-> Ord ConnectionState
ConnectionState -> ConnectionState -> Bool
ConnectionState -> ConnectionState -> Ordering
ConnectionState -> ConnectionState -> ConnectionState
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
$ccompare :: ConnectionState -> ConnectionState -> Ordering
compare :: ConnectionState -> ConnectionState -> Ordering
$c< :: ConnectionState -> ConnectionState -> Bool
< :: ConnectionState -> ConnectionState -> Bool
$c<= :: ConnectionState -> ConnectionState -> Bool
<= :: ConnectionState -> ConnectionState -> Bool
$c> :: ConnectionState -> ConnectionState -> Bool
> :: ConnectionState -> ConnectionState -> Bool
$c>= :: ConnectionState -> ConnectionState -> Bool
>= :: ConnectionState -> ConnectionState -> Bool
$cmax :: ConnectionState -> ConnectionState -> ConnectionState
max :: ConnectionState -> ConnectionState -> ConnectionState
$cmin :: ConnectionState -> ConnectionState -> ConnectionState
min :: ConnectionState -> ConnectionState -> ConnectionState
Ord, Int -> ConnectionState -> ShowS
[ConnectionState] -> ShowS
ConnectionState -> String
(Int -> ConnectionState -> ShowS)
-> (ConnectionState -> String)
-> ([ConnectionState] -> ShowS)
-> Show ConnectionState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnectionState -> ShowS
showsPrec :: Int -> ConnectionState -> ShowS
$cshow :: ConnectionState -> String
show :: ConnectionState -> String
$cshowList :: [ConnectionState] -> ShowS
showList :: [ConnectionState] -> ShowS
Show)
data Connection s
= Connection
{ forall s. Connection s -> TBQueue (ReqPack s)
connQReq :: !(TBQueue (ReqPack s))
, forall s. Connection s -> TVar ConnectionState
connState :: !(TVar ConnectionState)
, forall s. Connection s -> Async ()
connWSThread :: !(Async ())
, forall s. Connection s -> Codec s
connCodec :: !(Codec s)
}
data GeneralException
= UnexpectedRequestId UUID
| ResponseParseFailure String
deriving (GeneralException -> GeneralException -> Bool
(GeneralException -> GeneralException -> Bool)
-> (GeneralException -> GeneralException -> Bool)
-> Eq GeneralException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GeneralException -> GeneralException -> Bool
== :: GeneralException -> GeneralException -> Bool
$c/= :: GeneralException -> GeneralException -> Bool
/= :: GeneralException -> GeneralException -> Bool
Eq, Int -> GeneralException -> ShowS
[GeneralException] -> ShowS
GeneralException -> String
(Int -> GeneralException -> ShowS)
-> (GeneralException -> String)
-> ([GeneralException] -> ShowS)
-> Show GeneralException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GeneralException -> ShowS
showsPrec :: Int -> GeneralException -> ShowS
$cshow :: GeneralException -> String
show :: GeneralException -> String
$cshowList :: [GeneralException] -> ShowS
showList :: [GeneralException] -> ShowS
Show, Typeable)
instance Exception GeneralException