2022-03-16 03:39:21 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
-- | This file contains types for both the websocket protocols (Apollo) and (graphql-ws)
|
|
|
|
-- | See Apollo: https://github.com/apollographql/subscriptions-transport-ws/blob/master/PROTOCOL.md
|
|
|
|
-- | See graphql-ws: https://github.com/enisdenjo/graphql-ws/blob/master/PROTOCOL.md
|
2021-11-04 19:08:33 +03:00
|
|
|
module Hasura.GraphQL.Transport.WebSocket.Protocol
|
|
|
|
( ClientMsg (CMConnInit, CMConnTerm, CMPing, CMPong, CMStart, CMStop),
|
|
|
|
CompletionMsg (CompletionMsg),
|
|
|
|
ConnErrMsg (ConnErrMsg, unConnErrMsg),
|
|
|
|
ConnParams (_cpHeaders),
|
|
|
|
DataMsg (DataMsg),
|
|
|
|
ErrorMsg (ErrorMsg),
|
|
|
|
OperationId (unOperationId),
|
|
|
|
PingPongPayload,
|
|
|
|
ServerErrorCode (..),
|
|
|
|
ServerMsg (SMComplete, SMConnAck, SMConnErr, SMConnKeepAlive, SMData, SMErr, SMNext, SMPing, SMPong),
|
|
|
|
ServerMsgType (..),
|
|
|
|
StartMsg (StartMsg),
|
|
|
|
StopMsg (StopMsg),
|
|
|
|
WSConnInitTimerStatus (Done),
|
|
|
|
WSSubProtocol (..),
|
|
|
|
encodeServerErrorMsg,
|
|
|
|
encodeServerMsg,
|
|
|
|
getNewWSTimer,
|
|
|
|
getWSTimerState,
|
|
|
|
keepAliveMessage,
|
|
|
|
showSubProtocol,
|
|
|
|
toWSSubProtocol,
|
2022-04-07 17:41:43 +03:00
|
|
|
|
|
|
|
-- * exported for testing
|
|
|
|
unsafeMkOperationId,
|
2021-11-04 19:08:33 +03:00
|
|
|
)
|
|
|
|
where
|
2021-08-24 19:25:12 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
import Control.Concurrent
|
|
|
|
import Control.Concurrent.Extended (sleep)
|
|
|
|
import Control.Concurrent.STM
|
|
|
|
import Data.Aeson qualified as J
|
|
|
|
import Data.Aeson.TH qualified as J
|
|
|
|
import Data.ByteString.Lazy qualified as BL
|
|
|
|
import Data.Text (pack)
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.GraphQL.Transport.HTTP.Protocol
|
|
|
|
import Hasura.Prelude
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
-- NOTE: the `subProtocol` is decided based on the `Sec-WebSocket-Protocol`
|
|
|
|
-- header on every request sent to the server.
|
|
|
|
data WSSubProtocol = Apollo | GraphQLWS
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- NOTE: Please do not change them, as they're used for to identify the type of client
|
|
|
|
-- on every request that reaches the server. They are unique to each of the protocols.
|
|
|
|
showSubProtocol :: WSSubProtocol -> String
|
|
|
|
showSubProtocol subProtocol = case subProtocol of
|
|
|
|
-- REF: https://github.com/apollographql/subscriptions-transport-ws/blob/master/src/server.ts#L144
|
2021-09-24 01:56:37 +03:00
|
|
|
Apollo -> "graphql-ws"
|
2021-08-24 19:25:12 +03:00
|
|
|
-- REF: https://github.com/enisdenjo/graphql-ws/blob/master/PROTOCOL.md#communication
|
|
|
|
GraphQLWS -> "graphql-transport-ws"
|
|
|
|
|
|
|
|
toWSSubProtocol :: String -> WSSubProtocol
|
|
|
|
toWSSubProtocol str = case str of
|
|
|
|
"graphql-transport-ws" -> GraphQLWS
|
2021-09-24 01:56:37 +03:00
|
|
|
_ -> Apollo
|
2021-08-24 19:25:12 +03:00
|
|
|
|
|
|
|
-- This is set by the client when it connects to the server
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype OperationId = OperationId {unOperationId :: Text}
|
2021-08-24 19:25:12 +03:00
|
|
|
deriving (Show, Eq, J.ToJSON, J.FromJSON, IsString, Hashable)
|
|
|
|
|
2022-04-07 17:41:43 +03:00
|
|
|
unsafeMkOperationId :: Text -> OperationId
|
|
|
|
unsafeMkOperationId = OperationId
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data ServerMsgType
|
|
|
|
= -- specific to `Apollo` clients
|
2021-08-24 19:25:12 +03:00
|
|
|
SMT_GQL_CONNECTION_KEEP_ALIVE
|
|
|
|
| SMT_GQL_CONNECTION_ERROR
|
|
|
|
| SMT_GQL_DATA
|
2021-09-24 01:56:37 +03:00
|
|
|
| -- specific to `graphql-ws` clients
|
|
|
|
SMT_GQL_NEXT
|
2021-08-24 19:25:12 +03:00
|
|
|
| SMT_GQL_PING
|
|
|
|
| SMT_GQL_PONG
|
2021-09-24 01:56:37 +03:00
|
|
|
| -- common to clients of both protocols
|
|
|
|
SMT_GQL_CONNECTION_ACK
|
2021-08-24 19:25:12 +03:00
|
|
|
| SMT_GQL_ERROR
|
|
|
|
| SMT_GQL_COMPLETE
|
|
|
|
deriving (Eq)
|
|
|
|
|
|
|
|
instance Show ServerMsgType where
|
|
|
|
show = \case
|
|
|
|
-- specific to `Apollo` clients
|
|
|
|
SMT_GQL_CONNECTION_KEEP_ALIVE -> "ka"
|
2021-09-24 01:56:37 +03:00
|
|
|
SMT_GQL_CONNECTION_ERROR -> "connection_error"
|
|
|
|
SMT_GQL_DATA -> "data"
|
2021-08-24 19:25:12 +03:00
|
|
|
-- specific to `graphql-ws` clients
|
2021-09-24 01:56:37 +03:00
|
|
|
SMT_GQL_NEXT -> "next"
|
|
|
|
SMT_GQL_PING -> "ping"
|
|
|
|
SMT_GQL_PONG -> "pong"
|
2021-08-24 19:25:12 +03:00
|
|
|
-- common to clients of both protocols
|
2021-09-24 01:56:37 +03:00
|
|
|
SMT_GQL_CONNECTION_ACK -> "connection_ack"
|
|
|
|
SMT_GQL_ERROR -> "error"
|
|
|
|
SMT_GQL_COMPLETE -> "complete"
|
2021-08-24 19:25:12 +03:00
|
|
|
|
|
|
|
instance J.ToJSON ServerMsgType where
|
|
|
|
toJSON = J.toJSON . show
|
|
|
|
|
|
|
|
data ConnParams = ConnParams
|
2021-09-24 01:56:37 +03:00
|
|
|
{_cpHeaders :: Maybe (HashMap Text Text)}
|
2021-08-24 19:25:12 +03:00
|
|
|
deriving stock (Show, Eq)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
$(J.deriveJSON hasuraJSON ''ConnParams)
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data StartMsg = StartMsg
|
|
|
|
{ _smId :: !OperationId,
|
|
|
|
_smPayload :: !GQLReqUnparsed
|
|
|
|
}
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
2021-01-19 22:14:42 +03:00
|
|
|
$(J.deriveJSON hasuraJSON ''StartMsg)
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data StopMsg = StopMsg
|
2018-07-20 10:22:46 +03:00
|
|
|
{ _stId :: OperationId
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
2021-01-19 22:14:42 +03:00
|
|
|
$(J.deriveJSON hasuraJSON ''StopMsg)
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
-- Specific to graphql-ws
|
2021-09-24 01:56:37 +03:00
|
|
|
data PingPongPayload = PingPongPayload
|
|
|
|
{ _smMessage :: !(Maybe Text) -- NOTE: this is not within the spec, but is specific to our usecase
|
|
|
|
}
|
|
|
|
deriving stock (Show, Eq)
|
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
$(J.deriveJSON hasuraJSON ''PingPongPayload)
|
|
|
|
|
|
|
|
-- Specific to graphql-ws
|
|
|
|
keepAliveMessage :: PingPongPayload
|
|
|
|
keepAliveMessage = PingPongPayload . Just . pack $ "keepalive"
|
|
|
|
|
|
|
|
-- Specific to graphql-ws
|
2021-09-24 01:56:37 +03:00
|
|
|
data SubscribeMsg = SubscribeMsg
|
|
|
|
{ _subId :: !OperationId,
|
|
|
|
_subPayload :: !GQLReqUnparsed
|
|
|
|
}
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
$(J.deriveJSON hasuraJSON ''SubscribeMsg)
|
|
|
|
|
2018-07-20 10:22:46 +03:00
|
|
|
data ClientMsg
|
2018-09-18 10:43:30 +03:00
|
|
|
= CMConnInit !(Maybe ConnParams)
|
2018-07-20 10:22:46 +03:00
|
|
|
| CMStart !StartMsg
|
|
|
|
| CMStop !StopMsg
|
2021-09-24 01:56:37 +03:00
|
|
|
| -- specific to apollo clients
|
|
|
|
CMConnTerm
|
|
|
|
| -- specific to graphql-ws clients
|
|
|
|
CMPing !(Maybe PingPongPayload)
|
2021-08-24 19:25:12 +03:00
|
|
|
| CMPong !(Maybe PingPongPayload)
|
2018-07-20 10:22:46 +03:00
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
|
|
instance J.FromJSON ClientMsg where
|
|
|
|
parseJSON = J.withObject "ClientMessage" $ \obj -> do
|
|
|
|
t <- obj J..: "type"
|
2021-08-24 19:25:12 +03:00
|
|
|
case (t :: String) of
|
2021-09-24 01:56:37 +03:00
|
|
|
"connection_init" -> CMConnInit <$> parsePayload obj
|
|
|
|
"start" -> CMStart <$> parseObj obj
|
|
|
|
"stop" -> CMStop <$> parseObj obj
|
2021-08-24 19:25:12 +03:00
|
|
|
"connection_terminate" -> pure CMConnTerm
|
|
|
|
-- graphql-ws specific message types
|
2021-09-24 01:56:37 +03:00
|
|
|
"complete" -> CMStop <$> parseObj obj
|
|
|
|
"subscribe" -> CMStart <$> parseObj obj
|
|
|
|
"ping" -> CMPing <$> parsePayload obj
|
|
|
|
"pong" -> CMPong <$> parsePayload obj
|
|
|
|
_ -> fail $ "unexpected type for ClientMessage: " <> t
|
|
|
|
where
|
|
|
|
parseObj o = J.parseJSON (J.Object o)
|
|
|
|
|
|
|
|
parsePayload py = py J..:? "payload"
|
|
|
|
|
|
|
|
data DataMsg = DataMsg
|
|
|
|
{ _dmId :: !OperationId,
|
|
|
|
_dmPayload :: !GQResponse
|
2019-03-18 19:22:21 +03:00
|
|
|
}
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data ErrorMsg = ErrorMsg
|
|
|
|
{ _emId :: !OperationId,
|
|
|
|
_emPayload :: !J.Value
|
|
|
|
}
|
|
|
|
deriving (Show, Eq)
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype CompletionMsg = CompletionMsg {unCompletionMsg :: OperationId}
|
2018-07-20 10:22:46 +03:00
|
|
|
deriving (Show, Eq)
|
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
instance J.FromJSON CompletionMsg where
|
|
|
|
parseJSON = J.withObject "CompletionMsg" $ \t ->
|
|
|
|
CompletionMsg <$> t J..: "id"
|
|
|
|
|
|
|
|
instance J.ToJSON CompletionMsg where
|
|
|
|
toJSON (CompletionMsg opId) = J.String $ tshow opId
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype ConnErrMsg = ConnErrMsg {unConnErrMsg :: Text}
|
2018-07-20 10:22:46 +03:00
|
|
|
deriving (Show, Eq, J.ToJSON, J.FromJSON, IsString)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data ServerErrorMsg = ServerErrorMsg {unServerErrorMsg :: Text}
|
|
|
|
deriving stock (Show, Eq)
|
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
$(J.deriveJSON hasuraJSON ''ServerErrorMsg)
|
|
|
|
|
2018-07-20 10:22:46 +03:00
|
|
|
data ServerMsg
|
|
|
|
= SMConnAck
|
|
|
|
| SMConnKeepAlive
|
|
|
|
| SMConnErr !ConnErrMsg
|
|
|
|
| SMData !DataMsg
|
|
|
|
| SMErr !ErrorMsg
|
|
|
|
| SMComplete !CompletionMsg
|
2021-09-24 01:56:37 +03:00
|
|
|
| -- graphql-ws specific values
|
|
|
|
SMNext !DataMsg
|
2021-08-24 19:25:12 +03:00
|
|
|
| SMPing !(Maybe PingPongPayload)
|
|
|
|
| SMPong !(Maybe PingPongPayload)
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
-- | This is sent from the server to the client while closing the websocket
|
|
|
|
-- on encountering an error.
|
2021-09-24 01:56:37 +03:00
|
|
|
data ServerErrorCode
|
|
|
|
= ProtocolError1002
|
2021-08-24 19:25:12 +03:00
|
|
|
| GenericError4400 !String
|
2021-11-04 15:38:57 +03:00
|
|
|
| Unauthorized4401
|
2021-08-24 19:25:12 +03:00
|
|
|
| Forbidden4403
|
|
|
|
| ConnectionInitTimeout4408
|
|
|
|
| NonUniqueSubscription4409 !OperationId
|
|
|
|
| TooManyRequests4429
|
|
|
|
deriving stock (Show)
|
2018-07-20 10:22:46 +03:00
|
|
|
|
2021-08-24 19:25:12 +03:00
|
|
|
encodeServerErrorMsg :: ServerErrorCode -> BL.ByteString
|
|
|
|
encodeServerErrorMsg ecode = encJToLBS . encJFromJValue $ case ecode of
|
2021-09-24 01:56:37 +03:00
|
|
|
ProtocolError1002 -> packMsg "1002: Protocol Error"
|
|
|
|
GenericError4400 msg -> packMsg $ "4400: " <> msg
|
2021-11-04 15:38:57 +03:00
|
|
|
Unauthorized4401 -> packMsg "4401: Unauthorized"
|
2021-09-24 01:56:37 +03:00
|
|
|
Forbidden4403 -> packMsg "4403: Forbidden"
|
|
|
|
ConnectionInitTimeout4408 -> packMsg "4408: Connection initialisation timeout"
|
2021-08-24 19:25:12 +03:00
|
|
|
NonUniqueSubscription4409 opId -> packMsg $ "4409: Subscriber for " <> show opId <> " already exists"
|
2021-09-24 01:56:37 +03:00
|
|
|
TooManyRequests4429 -> packMsg "4429: Too many requests"
|
2021-08-24 19:25:12 +03:00
|
|
|
where
|
|
|
|
packMsg = ServerErrorMsg . pack
|
2018-07-20 10:22:46 +03:00
|
|
|
|
|
|
|
encodeServerMsg :: ServerMsg -> BL.ByteString
|
|
|
|
encodeServerMsg msg =
|
2021-09-24 01:56:37 +03:00
|
|
|
encJToLBS $
|
|
|
|
encJFromAssocList $ case msg of
|
|
|
|
SMConnAck ->
|
|
|
|
[encTy SMT_GQL_CONNECTION_ACK]
|
|
|
|
SMConnKeepAlive ->
|
|
|
|
[encTy SMT_GQL_CONNECTION_KEEP_ALIVE]
|
|
|
|
SMConnErr connErr ->
|
|
|
|
[ encTy SMT_GQL_CONNECTION_ERROR,
|
|
|
|
("payload", encJFromJValue connErr)
|
|
|
|
]
|
|
|
|
SMData (DataMsg opId payload) ->
|
|
|
|
[ encTy SMT_GQL_DATA,
|
|
|
|
("id", encJFromJValue opId),
|
|
|
|
("payload", encodeGQResp payload)
|
|
|
|
]
|
|
|
|
SMErr (ErrorMsg opId payload) ->
|
|
|
|
[ encTy SMT_GQL_ERROR,
|
|
|
|
("id", encJFromJValue opId),
|
|
|
|
("payload", encJFromJValue payload)
|
|
|
|
]
|
|
|
|
SMComplete compMsg ->
|
|
|
|
[ encTy SMT_GQL_COMPLETE,
|
|
|
|
("id", encJFromJValue $ unCompletionMsg compMsg)
|
|
|
|
]
|
|
|
|
SMPing mPayload ->
|
|
|
|
encodePingPongPayload mPayload SMT_GQL_PING
|
|
|
|
SMPong mPayload ->
|
|
|
|
encodePingPongPayload mPayload SMT_GQL_PONG
|
|
|
|
SMNext (DataMsg opId payload) ->
|
|
|
|
[ encTy SMT_GQL_NEXT,
|
|
|
|
("id", encJFromJValue opId),
|
|
|
|
("payload", encodeGQResp payload)
|
|
|
|
]
|
2018-07-20 10:22:46 +03:00
|
|
|
where
|
2019-03-18 19:22:21 +03:00
|
|
|
encTy ty = ("type", encJFromJValue ty)
|
2021-08-24 19:25:12 +03:00
|
|
|
|
|
|
|
encodePingPongPayload mPayload msgType = case mPayload of
|
|
|
|
Just payload ->
|
2021-09-24 01:56:37 +03:00
|
|
|
[ encTy msgType,
|
|
|
|
("payload", encJFromJValue payload)
|
2021-08-24 19:25:12 +03:00
|
|
|
]
|
2021-09-24 01:56:37 +03:00
|
|
|
Nothing -> [encTy msgType]
|
2021-08-24 19:25:12 +03:00
|
|
|
|
|
|
|
-- This "timer" is necessary while initialising the connection
|
|
|
|
-- with the server. Also, this is specific to the GraphQL-WS protocol.
|
|
|
|
data WSConnInitTimerStatus = Running | Done
|
|
|
|
deriving stock (Show, Eq)
|
|
|
|
|
|
|
|
type WSConnInitTimer = (TVar WSConnInitTimerStatus, TMVar ())
|
|
|
|
|
|
|
|
getWSTimerState :: WSConnInitTimer -> IO WSConnInitTimerStatus
|
|
|
|
getWSTimerState (timerState, _) = readTVarIO timerState
|
|
|
|
|
|
|
|
getNewWSTimer :: Seconds -> IO WSConnInitTimer
|
|
|
|
getNewWSTimer timeout = do
|
2021-09-24 01:56:37 +03:00
|
|
|
timerState <- newTVarIO Running
|
|
|
|
timer <- newEmptyTMVarIO
|
|
|
|
void $
|
|
|
|
forkIO $ do
|
|
|
|
sleep (seconds timeout)
|
|
|
|
atomically $ do
|
|
|
|
runTimerState <- readTVar timerState
|
|
|
|
case runTimerState of
|
|
|
|
Running -> do
|
|
|
|
-- time's up, we set status to "Done"
|
|
|
|
writeTVar timerState Done
|
|
|
|
putTMVar timer ()
|
|
|
|
Done -> pure ()
|
|
|
|
pure (timerState, timer)
|