{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasura.GraphQL.Execute.Subscription.Plan
( CohortId,
dummyCohortId,
newCohortId,
CohortIdArray (..),
CohortVariablesArray (..),
CohortVariables,
_cvCursorVariables,
mkCohortVariables,
ValidatedVariables (..),
mkUnsafeValidateVariables,
modifyCursorCohortVariables,
ValidatedQueryVariables,
ValidatedSyntheticVariables,
ValidatedCursorVariables,
SubscriptionQueryPlan (..),
SubscriptionQueryPlanExplanation (..),
ParameterizedSubscriptionQueryPlan (..),
CursorVariableValues (..),
cvSessionVariables,
cvCursorVariables,
cvQueryVariables,
cvSyntheticVariables,
unValidatedVariables,
applyModifier,
)
where
import Control.Lens (makeLenses)
import Data.Aeson.Extended qualified as J
import Data.Aeson.Ordered qualified as JO
import Data.Aeson.TH qualified as J
import Data.ByteString qualified as BS
import Data.HashMap.Strict qualified as HashMap
import Data.HashSet qualified as Set
import Data.Monoid (Endo (..))
import Data.UUID (UUID)
import Data.UUID qualified as UUID
import Data.UUID.V4 qualified as UUID
import Database.PG.Query qualified as PG
import Database.PG.Query.PTI qualified as PTI
import Hasura.Backends.Postgres.SQL.Value
import Hasura.EncJSON
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Roles (RoleName)
import Hasura.Session (SessionVariable, SessionVariables, filterSessionVariables)
import Language.GraphQL.Draft.Syntax qualified as G
import PostgreSQL.Binary.Encoding qualified as PE
newtype ValidatedVariables f = ValidatedVariables {forall (f :: * -> *). ValidatedVariables f -> f TxtEncodedVal
_unValidatedVariables :: (f TxtEncodedVal)}
deriving instance (Show (f TxtEncodedVal)) => Show (ValidatedVariables f)
deriving instance (Eq (f TxtEncodedVal)) => Eq (ValidatedVariables f)
deriving instance (Hashable (f TxtEncodedVal)) => Hashable (ValidatedVariables f)
deriving instance (J.ToJSON (f TxtEncodedVal)) => J.ToJSON (ValidatedVariables f)
deriving instance (Semigroup (f TxtEncodedVal)) => Semigroup (ValidatedVariables f)
deriving instance (Monoid (f TxtEncodedVal)) => Monoid (ValidatedVariables f)
$(makeLenses 'ValidatedVariables)
type ValidatedQueryVariables = ValidatedVariables (HashMap.HashMap G.Name)
type ValidatedSyntheticVariables = ValidatedVariables []
type ValidatedCursorVariables = ValidatedVariables (HashMap.HashMap G.Name)
mkUnsafeValidateVariables :: f TxtEncodedVal -> ValidatedVariables f
mkUnsafeValidateVariables :: forall (f :: * -> *). f TxtEncodedVal -> ValidatedVariables f
mkUnsafeValidateVariables = f TxtEncodedVal -> ValidatedVariables f
forall (f :: * -> *). f TxtEncodedVal -> ValidatedVariables f
ValidatedVariables
newtype CohortId = CohortId {CohortId -> UUID
unCohortId :: UUID}
deriving (Int -> CohortId -> ShowS
[CohortId] -> ShowS
CohortId -> String
(Int -> CohortId -> ShowS)
-> (CohortId -> String) -> ([CohortId] -> ShowS) -> Show CohortId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CohortId -> ShowS
showsPrec :: Int -> CohortId -> ShowS
$cshow :: CohortId -> String
show :: CohortId -> String
$cshowList :: [CohortId] -> ShowS
showList :: [CohortId] -> ShowS
Show, CohortId -> CohortId -> Bool
(CohortId -> CohortId -> Bool)
-> (CohortId -> CohortId -> Bool) -> Eq CohortId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CohortId -> CohortId -> Bool
== :: CohortId -> CohortId -> Bool
$c/= :: CohortId -> CohortId -> Bool
/= :: CohortId -> CohortId -> Bool
Eq, Eq CohortId
Eq CohortId
-> (Int -> CohortId -> Int)
-> (CohortId -> Int)
-> Hashable CohortId
Int -> CohortId -> Int
CohortId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> CohortId -> Int
hashWithSalt :: Int -> CohortId -> Int
$chash :: CohortId -> Int
hash :: CohortId -> Int
Hashable, [CohortId] -> Value
[CohortId] -> Encoding
CohortId -> Value
CohortId -> Encoding
(CohortId -> Value)
-> (CohortId -> Encoding)
-> ([CohortId] -> Value)
-> ([CohortId] -> Encoding)
-> ToJSON CohortId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: CohortId -> Value
toJSON :: CohortId -> Value
$ctoEncoding :: CohortId -> Encoding
toEncoding :: CohortId -> Encoding
$ctoJSONList :: [CohortId] -> Value
toJSONList :: [CohortId] -> Value
$ctoEncodingList :: [CohortId] -> Encoding
toEncodingList :: [CohortId] -> Encoding
J.ToJSON, Value -> Parser [CohortId]
Value -> Parser CohortId
(Value -> Parser CohortId)
-> (Value -> Parser [CohortId]) -> FromJSON CohortId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser CohortId
parseJSON :: Value -> Parser CohortId
$cparseJSONList :: Value -> Parser [CohortId]
parseJSONList :: Value -> Parser [CohortId]
J.FromJSON, Maybe ByteString -> Either Text CohortId
(Maybe ByteString -> Either Text CohortId) -> FromCol CohortId
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
$cfromCol :: Maybe ByteString -> Either Text CohortId
fromCol :: Maybe ByteString -> Either Text CohortId
PG.FromCol)
newCohortId :: (MonadIO m) => m CohortId
newCohortId :: forall (m :: * -> *). MonadIO m => m CohortId
newCohortId = UUID -> CohortId
CohortId (UUID -> CohortId) -> m UUID -> m CohortId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID -> m UUID
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UUID
UUID.nextRandom
dummyCohortId :: CohortId
dummyCohortId :: CohortId
dummyCohortId = UUID -> CohortId
CohortId UUID
UUID.nil
data CohortVariables = CohortVariables
{ CohortVariables -> SessionVariables
_cvSessionVariables :: !SessionVariables,
CohortVariables -> ValidatedQueryVariables
_cvQueryVariables :: !ValidatedQueryVariables,
CohortVariables -> ValidatedSyntheticVariables
_cvSyntheticVariables :: !ValidatedSyntheticVariables,
CohortVariables -> ValidatedQueryVariables
_cvCursorVariables :: !ValidatedCursorVariables
}
deriving (Int -> CohortVariables -> ShowS
[CohortVariables] -> ShowS
CohortVariables -> String
(Int -> CohortVariables -> ShowS)
-> (CohortVariables -> String)
-> ([CohortVariables] -> ShowS)
-> Show CohortVariables
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CohortVariables -> ShowS
showsPrec :: Int -> CohortVariables -> ShowS
$cshow :: CohortVariables -> String
show :: CohortVariables -> String
$cshowList :: [CohortVariables] -> ShowS
showList :: [CohortVariables] -> ShowS
Show, CohortVariables -> CohortVariables -> Bool
(CohortVariables -> CohortVariables -> Bool)
-> (CohortVariables -> CohortVariables -> Bool)
-> Eq CohortVariables
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CohortVariables -> CohortVariables -> Bool
== :: CohortVariables -> CohortVariables -> Bool
$c/= :: CohortVariables -> CohortVariables -> Bool
/= :: CohortVariables -> CohortVariables -> Bool
Eq, (forall x. CohortVariables -> Rep CohortVariables x)
-> (forall x. Rep CohortVariables x -> CohortVariables)
-> Generic CohortVariables
forall x. Rep CohortVariables x -> CohortVariables
forall x. CohortVariables -> Rep CohortVariables x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CohortVariables -> Rep CohortVariables x
from :: forall x. CohortVariables -> Rep CohortVariables x
$cto :: forall x. Rep CohortVariables x -> CohortVariables
to :: forall x. Rep CohortVariables x -> CohortVariables
Generic)
instance Hashable CohortVariables
$(makeLenses 'CohortVariables)
modifyCursorCohortVariables ::
ValidatedCursorVariables ->
CohortVariables ->
CohortVariables
modifyCursorCohortVariables :: ValidatedQueryVariables -> CohortVariables -> CohortVariables
modifyCursorCohortVariables ValidatedQueryVariables
validatedCursorVariables CohortVariables
cohortVariables =
CohortVariables
cohortVariables {_cvCursorVariables :: ValidatedQueryVariables
_cvCursorVariables = ValidatedQueryVariables
validatedCursorVariables}
mkCohortVariables ::
Set.HashSet SessionVariable ->
SessionVariables ->
ValidatedQueryVariables ->
ValidatedSyntheticVariables ->
ValidatedCursorVariables ->
CohortVariables
mkCohortVariables :: HashSet SessionVariable
-> SessionVariables
-> ValidatedQueryVariables
-> ValidatedSyntheticVariables
-> ValidatedQueryVariables
-> CohortVariables
mkCohortVariables HashSet SessionVariable
requiredSessionVariables SessionVariables
sessionVariableValues =
SessionVariables
-> ValidatedQueryVariables
-> ValidatedSyntheticVariables
-> ValidatedQueryVariables
-> CohortVariables
CohortVariables
(SessionVariables
-> ValidatedQueryVariables
-> ValidatedSyntheticVariables
-> ValidatedQueryVariables
-> CohortVariables)
-> SessionVariables
-> ValidatedQueryVariables
-> ValidatedSyntheticVariables
-> ValidatedQueryVariables
-> CohortVariables
forall a b. (a -> b) -> a -> b
$ (SessionVariable -> Text -> Bool)
-> SessionVariables -> SessionVariables
filterSessionVariables
(\SessionVariable
k Text
_ -> SessionVariable -> HashSet SessionVariable -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
Set.member SessionVariable
k HashSet SessionVariable
requiredSessionVariables)
SessionVariables
sessionVariableValues
instance J.ToJSON CohortVariables where
toJSON :: CohortVariables -> Value
toJSON (CohortVariables SessionVariables
sessionVars ValidatedQueryVariables
queryVars ValidatedSyntheticVariables
syntheticVars ValidatedQueryVariables
cursorVars) =
[Pair] -> Value
J.object
[ Key
"session" Key -> SessionVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
J..= SessionVariables
sessionVars,
Key
"query" Key -> ValidatedQueryVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
J..= ValidatedQueryVariables
queryVars,
Key
"synthetic" Key -> ValidatedSyntheticVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
J..= ValidatedSyntheticVariables
syntheticVars,
Key
"cursor" Key -> ValidatedQueryVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
J..= ValidatedQueryVariables
cursorVars
]
newtype CohortIdArray = CohortIdArray {CohortIdArray -> [CohortId]
unCohortIdArray :: [CohortId]}
deriving (Int -> CohortIdArray -> ShowS
[CohortIdArray] -> ShowS
CohortIdArray -> String
(Int -> CohortIdArray -> ShowS)
-> (CohortIdArray -> String)
-> ([CohortIdArray] -> ShowS)
-> Show CohortIdArray
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CohortIdArray -> ShowS
showsPrec :: Int -> CohortIdArray -> ShowS
$cshow :: CohortIdArray -> String
show :: CohortIdArray -> String
$cshowList :: [CohortIdArray] -> ShowS
showList :: [CohortIdArray] -> ShowS
Show, CohortIdArray -> CohortIdArray -> Bool
(CohortIdArray -> CohortIdArray -> Bool)
-> (CohortIdArray -> CohortIdArray -> Bool) -> Eq CohortIdArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CohortIdArray -> CohortIdArray -> Bool
== :: CohortIdArray -> CohortIdArray -> Bool
$c/= :: CohortIdArray -> CohortIdArray -> Bool
/= :: CohortIdArray -> CohortIdArray -> Bool
Eq)
instance PG.ToPrepArg CohortIdArray where
toPrepVal :: CohortIdArray -> PrepArg
toPrepVal (CohortIdArray [CohortId]
l) = Oid -> ([UUID] -> Encoding) -> [UUID] -> PrepArg
forall a. Oid -> (a -> Encoding) -> a -> PrepArg
PG.toPrepValHelper Oid
PTI.unknown [UUID] -> Encoding
encoder ([UUID] -> PrepArg) -> [UUID] -> PrepArg
forall a b. (a -> b) -> a -> b
$ (CohortId -> UUID) -> [CohortId] -> [UUID]
forall a b. (a -> b) -> [a] -> [b]
map CohortId -> UUID
unCohortId [CohortId]
l
where
encoder :: [UUID] -> Encoding
encoder = Word32 -> Array -> Encoding
PE.array (Oid -> Word32
forall n. Integral n => Oid -> n
PTI.unOid Oid
PTI.uuid) (Array -> Encoding) -> ([UUID] -> Array) -> [UUID] -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall b. (b -> UUID -> b) -> b -> [UUID] -> b)
-> (UUID -> Array) -> [UUID] -> Array
forall a c.
(forall b. (b -> a -> b) -> b -> c -> b)
-> (a -> Array) -> c -> Array
PE.dimensionArray (b -> UUID -> b) -> b -> [UUID] -> b
forall b. (b -> UUID -> b) -> b -> [UUID] -> b
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Encoding -> Array
PE.encodingArray (Encoding -> Array) -> (UUID -> Encoding) -> UUID -> Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> Encoding
PE.uuid)
newtype CohortVariablesArray = CohortVariablesArray {CohortVariablesArray -> [CohortVariables]
unCohortVariablesArray :: [CohortVariables]}
deriving (Int -> CohortVariablesArray -> ShowS
[CohortVariablesArray] -> ShowS
CohortVariablesArray -> String
(Int -> CohortVariablesArray -> ShowS)
-> (CohortVariablesArray -> String)
-> ([CohortVariablesArray] -> ShowS)
-> Show CohortVariablesArray
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CohortVariablesArray -> ShowS
showsPrec :: Int -> CohortVariablesArray -> ShowS
$cshow :: CohortVariablesArray -> String
show :: CohortVariablesArray -> String
$cshowList :: [CohortVariablesArray] -> ShowS
showList :: [CohortVariablesArray] -> ShowS
Show, CohortVariablesArray -> CohortVariablesArray -> Bool
(CohortVariablesArray -> CohortVariablesArray -> Bool)
-> (CohortVariablesArray -> CohortVariablesArray -> Bool)
-> Eq CohortVariablesArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CohortVariablesArray -> CohortVariablesArray -> Bool
== :: CohortVariablesArray -> CohortVariablesArray -> Bool
$c/= :: CohortVariablesArray -> CohortVariablesArray -> Bool
/= :: CohortVariablesArray -> CohortVariablesArray -> Bool
Eq)
instance PG.ToPrepArg CohortVariablesArray where
toPrepVal :: CohortVariablesArray -> PrepArg
toPrepVal (CohortVariablesArray [CohortVariables]
l) =
Oid -> ([Value] -> Encoding) -> [Value] -> PrepArg
forall a. Oid -> (a -> Encoding) -> a -> PrepArg
PG.toPrepValHelper Oid
PTI.jsonb_array [Value] -> Encoding
encoder ((CohortVariables -> Value) -> [CohortVariables] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map CohortVariables -> Value
forall a. ToJSON a => a -> Value
J.toJSON [CohortVariables]
l)
where
encoder :: [Value] -> Encoding
encoder = Word32 -> Array -> Encoding
PE.array (Oid -> Word32
forall n. Integral n => Oid -> n
PTI.unOid Oid
PTI.jsonb) (Array -> Encoding) -> ([Value] -> Array) -> [Value] -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall b. (b -> Value -> b) -> b -> [Value] -> b)
-> (Value -> Array) -> [Value] -> Array
forall a c.
(forall b. (b -> a -> b) -> b -> c -> b)
-> (a -> Array) -> c -> Array
PE.dimensionArray (b -> Value -> b) -> b -> [Value] -> b
forall b. (b -> Value -> b) -> b -> [Value] -> b
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Encoding -> Array
PE.encodingArray (Encoding -> Array) -> (Value -> Encoding) -> Value -> Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Encoding
PE.jsonb_ast)
applyModifier :: (Maybe (Endo JO.Value)) -> BS.ByteString -> BS.ByteString
applyModifier :: Maybe (Endo Value) -> ByteString -> ByteString
applyModifier Maybe (Endo Value)
Nothing = ByteString -> ByteString
forall a. a -> a
id
applyModifier (Just Endo Value
modifier) = \ByteString
bs -> case ByteString -> Maybe Value
JO.decode ByteString
bs of
Maybe Value
Nothing -> ByteString
bs
Just Value
v -> EncJSON -> ByteString
encJToBS (EncJSON -> ByteString)
-> (Value -> EncJSON) -> Value -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> EncJSON
encJFromOrderedValue (Value -> ByteString) -> Value -> ByteString
forall a b. (a -> b) -> a -> b
$ Endo Value -> Value -> Value
forall a. Endo a -> a -> a
appEndo Endo Value
modifier Value
v
data SubscriptionQueryPlan (b :: BackendType) q = SubscriptionQueryPlan
{ forall (b :: BackendType) q.
SubscriptionQueryPlan b q -> ParameterizedSubscriptionQueryPlan b q
_sqpParameterizedPlan :: ParameterizedSubscriptionQueryPlan b q,
forall (b :: BackendType) q.
SubscriptionQueryPlan b q -> SourceConfig b
_sqpSourceConfig :: SourceConfig b,
forall (b :: BackendType) q. SubscriptionQueryPlan b q -> CohortId
_sqpCohortId :: CohortId,
forall (b :: BackendType) q.
SubscriptionQueryPlan b q -> ResolvedConnectionTemplate b
_sqpResolvedConnectionTemplate :: ResolvedConnectionTemplate b,
forall (b :: BackendType) q.
SubscriptionQueryPlan b q -> CohortVariables
_sqpVariables :: CohortVariables,
forall (b :: BackendType) q.
SubscriptionQueryPlan b q -> Maybe Name
_sqpNamespace :: Maybe G.Name
}
data ParameterizedSubscriptionQueryPlan (b :: BackendType) q = ParameterizedSubscriptionQueryPlan
{ forall (b :: BackendType) q.
ParameterizedSubscriptionQueryPlan b q -> RoleName
_plqpRole :: !RoleName,
forall (b :: BackendType) q.
ParameterizedSubscriptionQueryPlan b q -> q
_plqpQuery :: !q
}
deriving (Int -> ParameterizedSubscriptionQueryPlan b q -> ShowS
[ParameterizedSubscriptionQueryPlan b q] -> ShowS
ParameterizedSubscriptionQueryPlan b q -> String
(Int -> ParameterizedSubscriptionQueryPlan b q -> ShowS)
-> (ParameterizedSubscriptionQueryPlan b q -> String)
-> ([ParameterizedSubscriptionQueryPlan b q] -> ShowS)
-> Show (ParameterizedSubscriptionQueryPlan b q)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType) q.
Show q =>
Int -> ParameterizedSubscriptionQueryPlan b q -> ShowS
forall (b :: BackendType) q.
Show q =>
[ParameterizedSubscriptionQueryPlan b q] -> ShowS
forall (b :: BackendType) q.
Show q =>
ParameterizedSubscriptionQueryPlan b q -> String
$cshowsPrec :: forall (b :: BackendType) q.
Show q =>
Int -> ParameterizedSubscriptionQueryPlan b q -> ShowS
showsPrec :: Int -> ParameterizedSubscriptionQueryPlan b q -> ShowS
$cshow :: forall (b :: BackendType) q.
Show q =>
ParameterizedSubscriptionQueryPlan b q -> String
show :: ParameterizedSubscriptionQueryPlan b q -> String
$cshowList :: forall (b :: BackendType) q.
Show q =>
[ParameterizedSubscriptionQueryPlan b q] -> ShowS
showList :: [ParameterizedSubscriptionQueryPlan b q] -> ShowS
Show)
$(J.deriveToJSON hasuraJSON ''ParameterizedSubscriptionQueryPlan)
data SubscriptionQueryPlanExplanation = SubscriptionQueryPlanExplanation
{ SubscriptionQueryPlanExplanation -> Text
_sqpeSql :: !Text,
SubscriptionQueryPlanExplanation -> [Text]
_sqpePlan :: ![Text],
SubscriptionQueryPlanExplanation -> CohortVariables
_sqpeVariables :: !CohortVariables
}
deriving (Int -> SubscriptionQueryPlanExplanation -> ShowS
[SubscriptionQueryPlanExplanation] -> ShowS
SubscriptionQueryPlanExplanation -> String
(Int -> SubscriptionQueryPlanExplanation -> ShowS)
-> (SubscriptionQueryPlanExplanation -> String)
-> ([SubscriptionQueryPlanExplanation] -> ShowS)
-> Show SubscriptionQueryPlanExplanation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionQueryPlanExplanation -> ShowS
showsPrec :: Int -> SubscriptionQueryPlanExplanation -> ShowS
$cshow :: SubscriptionQueryPlanExplanation -> String
show :: SubscriptionQueryPlanExplanation -> String
$cshowList :: [SubscriptionQueryPlanExplanation] -> ShowS
showList :: [SubscriptionQueryPlanExplanation] -> ShowS
Show)
$(J.deriveToJSON hasuraJSON ''SubscriptionQueryPlanExplanation)
newtype CursorVariableValues = CursorVariableValues (HashMap G.Name TxtEncodedVal)
deriving (Value -> Parser [CursorVariableValues]
Value -> Parser CursorVariableValues
(Value -> Parser CursorVariableValues)
-> (Value -> Parser [CursorVariableValues])
-> FromJSON CursorVariableValues
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser CursorVariableValues
parseJSON :: Value -> Parser CursorVariableValues
$cparseJSONList :: Value -> Parser [CursorVariableValues]
parseJSONList :: Value -> Parser [CursorVariableValues]
J.FromJSON, [CursorVariableValues] -> Value
[CursorVariableValues] -> Encoding
CursorVariableValues -> Value
CursorVariableValues -> Encoding
(CursorVariableValues -> Value)
-> (CursorVariableValues -> Encoding)
-> ([CursorVariableValues] -> Value)
-> ([CursorVariableValues] -> Encoding)
-> ToJSON CursorVariableValues
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: CursorVariableValues -> Value
toJSON :: CursorVariableValues -> Value
$ctoEncoding :: CursorVariableValues -> Encoding
toEncoding :: CursorVariableValues -> Encoding
$ctoJSONList :: [CursorVariableValues] -> Value
toJSONList :: [CursorVariableValues] -> Value
$ctoEncodingList :: [CursorVariableValues] -> Encoding
toEncodingList :: [CursorVariableValues] -> Encoding
J.ToJSON, CursorVariableValues -> CursorVariableValues -> Bool
(CursorVariableValues -> CursorVariableValues -> Bool)
-> (CursorVariableValues -> CursorVariableValues -> Bool)
-> Eq CursorVariableValues
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CursorVariableValues -> CursorVariableValues -> Bool
== :: CursorVariableValues -> CursorVariableValues -> Bool
$c/= :: CursorVariableValues -> CursorVariableValues -> Bool
/= :: CursorVariableValues -> CursorVariableValues -> Bool
Eq, Int -> CursorVariableValues -> ShowS
[CursorVariableValues] -> ShowS
CursorVariableValues -> String
(Int -> CursorVariableValues -> ShowS)
-> (CursorVariableValues -> String)
-> ([CursorVariableValues] -> ShowS)
-> Show CursorVariableValues
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CursorVariableValues -> ShowS
showsPrec :: Int -> CursorVariableValues -> ShowS
$cshow :: CursorVariableValues -> String
show :: CursorVariableValues -> String
$cshowList :: [CursorVariableValues] -> ShowS
showList :: [CursorVariableValues] -> ShowS
Show)