{-# 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,
  )
where
import Control.Lens (makeLenses)
import Data.Aeson.Extended qualified as J
import Data.Aeson.TH qualified as J
import Data.HashMap.Strict qualified as Map
import Data.HashSet qualified as Set
import Data.UUID (UUID)
import Data.UUID qualified as UUID
import Data.UUID.V4 qualified as UUID
import Database.PG.Query qualified as Q
import Database.PG.Query.PTI qualified as PTI
import Hasura.Backends.Postgres.SQL.Value
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.SQL.Backend
import Hasura.Session
import Language.GraphQL.Draft.Syntax qualified as G
import PostgreSQL.Binary.Encoding qualified as PE
newtype ValidatedVariables f = ValidatedVariables {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 (Map.HashMap G.Name)
type ValidatedSyntheticVariables = ValidatedVariables []
type ValidatedCursorVariables = ValidatedVariables (Map.HashMap G.Name)
mkUnsafeValidateVariables :: f TxtEncodedVal -> ValidatedVariables f
mkUnsafeValidateVariables :: 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
showList :: [CohortId] -> ShowS
$cshowList :: [CohortId] -> ShowS
show :: CohortId -> String
$cshow :: CohortId -> String
showsPrec :: Int -> CohortId -> ShowS
$cshowsPrec :: Int -> CohortId -> ShowS
Show, CohortId -> CohortId -> Bool
(CohortId -> CohortId -> Bool)
-> (CohortId -> CohortId -> Bool) -> Eq CohortId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CohortId -> CohortId -> Bool
$c/= :: CohortId -> CohortId -> Bool
== :: CohortId -> CohortId -> Bool
$c== :: CohortId -> CohortId -> Bool
Eq, Int -> CohortId -> Int
CohortId -> Int
(Int -> CohortId -> Int) -> (CohortId -> Int) -> Hashable CohortId
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: CohortId -> Int
$chash :: CohortId -> Int
hashWithSalt :: Int -> CohortId -> Int
$chashWithSalt :: Int -> 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
toEncodingList :: [CohortId] -> Encoding
$ctoEncodingList :: [CohortId] -> Encoding
toJSONList :: [CohortId] -> Value
$ctoJSONList :: [CohortId] -> Value
toEncoding :: CohortId -> Encoding
$ctoEncoding :: CohortId -> Encoding
toJSON :: CohortId -> Value
$ctoJSON :: CohortId -> Value
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
parseJSONList :: Value -> Parser [CohortId]
$cparseJSONList :: Value -> Parser [CohortId]
parseJSON :: Value -> Parser CohortId
$cparseJSON :: 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
fromCol :: Maybe ByteString -> Either Text CohortId
$cfromCol :: Maybe ByteString -> Either Text CohortId
Q.FromCol)
newCohortId :: (MonadIO m) => m CohortId
newCohortId :: 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 (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
showList :: [CohortVariables] -> ShowS
$cshowList :: [CohortVariables] -> ShowS
show :: CohortVariables -> String
$cshow :: CohortVariables -> String
showsPrec :: Int -> CohortVariables -> ShowS
$cshowsPrec :: Int -> CohortVariables -> ShowS
Show, CohortVariables -> CohortVariables -> Bool
(CohortVariables -> CohortVariables -> Bool)
-> (CohortVariables -> CohortVariables -> Bool)
-> Eq CohortVariables
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CohortVariables -> CohortVariables -> Bool
$c/= :: CohortVariables -> CohortVariables -> Bool
== :: CohortVariables -> CohortVariables -> Bool
$c== :: 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
$cto :: forall x. Rep CohortVariables x -> CohortVariables
$cfrom :: forall x. CohortVariables -> Rep CohortVariables x
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
J..= SessionVariables
sessionVars,
        Key
"query" Key -> ValidatedQueryVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
J..= ValidatedQueryVariables
queryVars,
        Key
"synthetic" Key -> ValidatedSyntheticVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
J..= ValidatedSyntheticVariables
syntheticVars,
        Key
"cursor" Key -> ValidatedQueryVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
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
showList :: [CohortIdArray] -> ShowS
$cshowList :: [CohortIdArray] -> ShowS
show :: CohortIdArray -> String
$cshow :: CohortIdArray -> String
showsPrec :: Int -> CohortIdArray -> ShowS
$cshowsPrec :: Int -> CohortIdArray -> ShowS
Show, CohortIdArray -> CohortIdArray -> Bool
(CohortIdArray -> CohortIdArray -> Bool)
-> (CohortIdArray -> CohortIdArray -> Bool) -> Eq CohortIdArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CohortIdArray -> CohortIdArray -> Bool
$c/= :: CohortIdArray -> CohortIdArray -> Bool
== :: CohortIdArray -> CohortIdArray -> Bool
$c== :: CohortIdArray -> CohortIdArray -> Bool
Eq)
instance Q.ToPrepArg CohortIdArray where
  toPrepVal :: CohortIdArray -> PrepArg
toPrepVal (CohortIdArray [CohortId]
l) = Oid -> ([UUID] -> Encoding) -> [UUID] -> PrepArg
forall a. Oid -> (a -> Encoding) -> a -> PrepArg
Q.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 Word32
2950 (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 forall b. (b -> UUID -> b) -> b -> [UUID] -> 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
showList :: [CohortVariablesArray] -> ShowS
$cshowList :: [CohortVariablesArray] -> ShowS
show :: CohortVariablesArray -> String
$cshow :: CohortVariablesArray -> String
showsPrec :: Int -> CohortVariablesArray -> ShowS
$cshowsPrec :: Int -> CohortVariablesArray -> ShowS
Show, CohortVariablesArray -> CohortVariablesArray -> Bool
(CohortVariablesArray -> CohortVariablesArray -> Bool)
-> (CohortVariablesArray -> CohortVariablesArray -> Bool)
-> Eq CohortVariablesArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CohortVariablesArray -> CohortVariablesArray -> Bool
$c/= :: CohortVariablesArray -> CohortVariablesArray -> Bool
== :: CohortVariablesArray -> CohortVariablesArray -> Bool
$c== :: CohortVariablesArray -> CohortVariablesArray -> Bool
Eq)
instance Q.ToPrepArg CohortVariablesArray where
  toPrepVal :: CohortVariablesArray -> PrepArg
toPrepVal (CohortVariablesArray [CohortVariables]
l) =
    Oid -> ([Value] -> Encoding) -> [Value] -> PrepArg
forall a. Oid -> (a -> Encoding) -> a -> PrepArg
Q.toPrepValHelper Oid
PTI.unknown [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 Word32
114 (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 forall b. (b -> Value -> b) -> b -> [Value] -> 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.json_ast)
data SubscriptionQueryPlan (b :: BackendType) q = SubscriptionQueryPlan
  { SubscriptionQueryPlan b q -> ParameterizedSubscriptionQueryPlan b q
_sqpParameterizedPlan :: !(ParameterizedSubscriptionQueryPlan b q),
    SubscriptionQueryPlan b q -> SourceConfig b
_sqpSourceConfig :: !(SourceConfig b),
    SubscriptionQueryPlan b q -> CohortVariables
_sqpVariables :: !CohortVariables,
    
    
    SubscriptionQueryPlan b q -> Maybe Name
_sqpNamespace :: !(Maybe G.Name)
  }
data ParameterizedSubscriptionQueryPlan (b :: BackendType) q = ParameterizedSubscriptionQueryPlan
  { ParameterizedSubscriptionQueryPlan b q -> RoleName
_plqpRole :: !RoleName,
    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
showList :: [ParameterizedSubscriptionQueryPlan b q] -> ShowS
$cshowList :: forall (b :: BackendType) q.
Show q =>
[ParameterizedSubscriptionQueryPlan b q] -> ShowS
show :: ParameterizedSubscriptionQueryPlan b q -> String
$cshow :: forall (b :: BackendType) q.
Show q =>
ParameterizedSubscriptionQueryPlan b q -> String
showsPrec :: Int -> ParameterizedSubscriptionQueryPlan b q -> ShowS
$cshowsPrec :: forall (b :: BackendType) q.
Show q =>
Int -> 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
showList :: [SubscriptionQueryPlanExplanation] -> ShowS
$cshowList :: [SubscriptionQueryPlanExplanation] -> ShowS
show :: SubscriptionQueryPlanExplanation -> String
$cshow :: SubscriptionQueryPlanExplanation -> String
showsPrec :: Int -> SubscriptionQueryPlanExplanation -> ShowS
$cshowsPrec :: Int -> 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
parseJSONList :: Value -> Parser [CursorVariableValues]
$cparseJSONList :: Value -> Parser [CursorVariableValues]
parseJSON :: Value -> Parser CursorVariableValues
$cparseJSON :: 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
toEncodingList :: [CursorVariableValues] -> Encoding
$ctoEncodingList :: [CursorVariableValues] -> Encoding
toJSONList :: [CursorVariableValues] -> Value
$ctoJSONList :: [CursorVariableValues] -> Value
toEncoding :: CursorVariableValues -> Encoding
$ctoEncoding :: CursorVariableValues -> Encoding
toJSON :: CursorVariableValues -> Value
$ctoJSON :: CursorVariableValues -> Value
J.ToJSON, CursorVariableValues -> CursorVariableValues -> Bool
(CursorVariableValues -> CursorVariableValues -> Bool)
-> (CursorVariableValues -> CursorVariableValues -> Bool)
-> Eq CursorVariableValues
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CursorVariableValues -> CursorVariableValues -> Bool
$c/= :: CursorVariableValues -> CursorVariableValues -> Bool
== :: CursorVariableValues -> CursorVariableValues -> Bool
$c== :: 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
showList :: [CursorVariableValues] -> ShowS
$cshowList :: [CursorVariableValues] -> ShowS
show :: CursorVariableValues -> String
$cshow :: CursorVariableValues -> String
showsPrec :: Int -> CursorVariableValues -> ShowS
$cshowsPrec :: Int -> CursorVariableValues -> ShowS
Show)