{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.EventTrigger
( SubscribeOpSpec (..),
SubscribeColumns (..),
TriggerName (..),
triggerNameToTxt,
Ops (..),
TriggerOpsDef (..),
EventTriggerConf (..),
RetryConf (..),
EventHeaderInfo (..),
WebhookConf (..),
WebhookConfInfo (..),
HeaderConf (..),
defaultRetryConf,
defaultTimeoutSeconds,
RecreateEventTriggers (..),
EventWithSource (..),
TriggerMetadata (..),
Event (..),
TriggerTypes (..),
Invocation (..),
ProcessEventError (..),
EventTriggerInfoMap,
EventTriggerInfo (..),
FetchBatchSize (..),
)
where
import Data.Aeson
import Data.Aeson.TH
import Data.HashMap.Strict qualified as M
import Data.Text.Extended
import Data.Text.NonEmpty
import Data.Time.Clock qualified as Time
import Database.PG.Query qualified as Q
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.DDL.Headers
import Hasura.RQL.DDL.Webhook.Transform (MetadataResponseTransform, RequestTransform)
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common (EnvRecord, InputWebhook, ResolvedWebhook, SourceName)
import Hasura.RQL.Types.Eventing
import Hasura.SQL.Backend
newtype TriggerName = TriggerName {TriggerName -> NonEmptyText
unTriggerName :: NonEmptyText}
deriving
( Int -> TriggerName -> ShowS
[TriggerName] -> ShowS
TriggerName -> String
(Int -> TriggerName -> ShowS)
-> (TriggerName -> String)
-> ([TriggerName] -> ShowS)
-> Show TriggerName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TriggerName] -> ShowS
$cshowList :: [TriggerName] -> ShowS
show :: TriggerName -> String
$cshow :: TriggerName -> String
showsPrec :: Int -> TriggerName -> ShowS
$cshowsPrec :: Int -> TriggerName -> ShowS
Show,
TriggerName -> TriggerName -> Bool
(TriggerName -> TriggerName -> Bool)
-> (TriggerName -> TriggerName -> Bool) -> Eq TriggerName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TriggerName -> TriggerName -> Bool
$c/= :: TriggerName -> TriggerName -> Bool
== :: TriggerName -> TriggerName -> Bool
$c== :: TriggerName -> TriggerName -> Bool
Eq,
Eq TriggerName
Eq TriggerName
-> (TriggerName -> TriggerName -> Ordering)
-> (TriggerName -> TriggerName -> Bool)
-> (TriggerName -> TriggerName -> Bool)
-> (TriggerName -> TriggerName -> Bool)
-> (TriggerName -> TriggerName -> Bool)
-> (TriggerName -> TriggerName -> TriggerName)
-> (TriggerName -> TriggerName -> TriggerName)
-> Ord TriggerName
TriggerName -> TriggerName -> Bool
TriggerName -> TriggerName -> Ordering
TriggerName -> TriggerName -> TriggerName
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
min :: TriggerName -> TriggerName -> TriggerName
$cmin :: TriggerName -> TriggerName -> TriggerName
max :: TriggerName -> TriggerName -> TriggerName
$cmax :: TriggerName -> TriggerName -> TriggerName
>= :: TriggerName -> TriggerName -> Bool
$c>= :: TriggerName -> TriggerName -> Bool
> :: TriggerName -> TriggerName -> Bool
$c> :: TriggerName -> TriggerName -> Bool
<= :: TriggerName -> TriggerName -> Bool
$c<= :: TriggerName -> TriggerName -> Bool
< :: TriggerName -> TriggerName -> Bool
$c< :: TriggerName -> TriggerName -> Bool
compare :: TriggerName -> TriggerName -> Ordering
$ccompare :: TriggerName -> TriggerName -> Ordering
$cp1Ord :: Eq TriggerName
Ord,
Int -> TriggerName -> Int
TriggerName -> Int
(Int -> TriggerName -> Int)
-> (TriggerName -> Int) -> Hashable TriggerName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TriggerName -> Int
$chash :: TriggerName -> Int
hashWithSalt :: Int -> TriggerName -> Int
$chashWithSalt :: Int -> TriggerName -> Int
Hashable,
TriggerName -> Text
(TriggerName -> Text) -> ToTxt TriggerName
forall a. (a -> Text) -> ToTxt a
toTxt :: TriggerName -> Text
$ctoTxt :: TriggerName -> Text
ToTxt,
Value -> Parser [TriggerName]
Value -> Parser TriggerName
(Value -> Parser TriggerName)
-> (Value -> Parser [TriggerName]) -> FromJSON TriggerName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TriggerName]
$cparseJSONList :: Value -> Parser [TriggerName]
parseJSON :: Value -> Parser TriggerName
$cparseJSON :: Value -> Parser TriggerName
FromJSON,
[TriggerName] -> Value
[TriggerName] -> Encoding
TriggerName -> Value
TriggerName -> Encoding
(TriggerName -> Value)
-> (TriggerName -> Encoding)
-> ([TriggerName] -> Value)
-> ([TriggerName] -> Encoding)
-> ToJSON TriggerName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TriggerName] -> Encoding
$ctoEncodingList :: [TriggerName] -> Encoding
toJSONList :: [TriggerName] -> Value
$ctoJSONList :: [TriggerName] -> Value
toEncoding :: TriggerName -> Encoding
$ctoEncoding :: TriggerName -> Encoding
toJSON :: TriggerName -> Value
$ctoJSON :: TriggerName -> Value
ToJSON,
ToJSONKeyFunction [TriggerName]
ToJSONKeyFunction TriggerName
ToJSONKeyFunction TriggerName
-> ToJSONKeyFunction [TriggerName] -> ToJSONKey TriggerName
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [TriggerName]
$ctoJSONKeyList :: ToJSONKeyFunction [TriggerName]
toJSONKey :: ToJSONKeyFunction TriggerName
$ctoJSONKey :: ToJSONKeyFunction TriggerName
ToJSONKey,
TriggerName -> PrepArg
(TriggerName -> PrepArg) -> ToPrepArg TriggerName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: TriggerName -> PrepArg
$ctoPrepVal :: TriggerName -> PrepArg
Q.ToPrepArg,
(forall x. TriggerName -> Rep TriggerName x)
-> (forall x. Rep TriggerName x -> TriggerName)
-> Generic TriggerName
forall x. Rep TriggerName x -> TriggerName
forall x. TriggerName -> Rep TriggerName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TriggerName x -> TriggerName
$cfrom :: forall x. TriggerName -> Rep TriggerName x
Generic,
TriggerName -> ()
(TriggerName -> ()) -> NFData TriggerName
forall a. (a -> ()) -> NFData a
rnf :: TriggerName -> ()
$crnf :: TriggerName -> ()
NFData,
Eq TriggerName
Eq TriggerName
-> (Accesses -> TriggerName -> TriggerName -> Bool)
-> Cacheable TriggerName
Accesses -> TriggerName -> TriggerName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> TriggerName -> TriggerName -> Bool
$cunchanged :: Accesses -> TriggerName -> TriggerName -> Bool
$cp1Cacheable :: Eq TriggerName
Cacheable,
Maybe ByteString -> Either Text TriggerName
(Maybe ByteString -> Either Text TriggerName)
-> FromCol TriggerName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text TriggerName
$cfromCol :: Maybe ByteString -> Either Text TriggerName
Q.FromCol
)
triggerNameToTxt :: TriggerName -> Text
triggerNameToTxt :: TriggerName -> Text
triggerNameToTxt = NonEmptyText -> Text
unNonEmptyText (NonEmptyText -> Text)
-> (TriggerName -> NonEmptyText) -> TriggerName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TriggerName -> NonEmptyText
unTriggerName
data Ops = INSERT | UPDATE | DELETE | MANUAL deriving (Int -> Ops -> ShowS
[Ops] -> ShowS
Ops -> String
(Int -> Ops -> ShowS)
-> (Ops -> String) -> ([Ops] -> ShowS) -> Show Ops
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ops] -> ShowS
$cshowList :: [Ops] -> ShowS
show :: Ops -> String
$cshow :: Ops -> String
showsPrec :: Int -> Ops -> ShowS
$cshowsPrec :: Int -> Ops -> ShowS
Show, Ops -> Ops -> Bool
(Ops -> Ops -> Bool) -> (Ops -> Ops -> Bool) -> Eq Ops
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ops -> Ops -> Bool
$c/= :: Ops -> Ops -> Bool
== :: Ops -> Ops -> Bool
$c== :: Ops -> Ops -> Bool
Eq, (forall x. Ops -> Rep Ops x)
-> (forall x. Rep Ops x -> Ops) -> Generic Ops
forall x. Rep Ops x -> Ops
forall x. Ops -> Rep Ops x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Ops x -> Ops
$cfrom :: forall x. Ops -> Rep Ops x
Generic)
instance Hashable Ops
data SubscribeColumns (b :: BackendType) = SubCStar | SubCArray [Column b]
deriving ((forall x. SubscribeColumns b -> Rep (SubscribeColumns b) x)
-> (forall x. Rep (SubscribeColumns b) x -> SubscribeColumns b)
-> Generic (SubscribeColumns b)
forall x. Rep (SubscribeColumns b) x -> SubscribeColumns b
forall x. SubscribeColumns b -> Rep (SubscribeColumns b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (SubscribeColumns b) x -> SubscribeColumns b
forall (b :: BackendType) x.
SubscribeColumns b -> Rep (SubscribeColumns b) x
$cto :: forall (b :: BackendType) x.
Rep (SubscribeColumns b) x -> SubscribeColumns b
$cfrom :: forall (b :: BackendType) x.
SubscribeColumns b -> Rep (SubscribeColumns b) x
Generic)
deriving instance Backend b => Show (SubscribeColumns b)
deriving instance Backend b => Eq (SubscribeColumns b)
instance Backend b => NFData (SubscribeColumns b)
instance Backend b => Cacheable (SubscribeColumns b)
instance Backend b => FromJSON (SubscribeColumns b) where
parseJSON :: Value -> Parser (SubscribeColumns b)
parseJSON (String Text
s) = case Text
s of
Text
"*" -> SubscribeColumns b -> Parser (SubscribeColumns b)
forall (m :: * -> *) a. Monad m => a -> m a
return SubscribeColumns b
forall (b :: BackendType). SubscribeColumns b
SubCStar
Text
_ -> String -> Parser (SubscribeColumns b)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"only * or [] allowed"
parseJSON v :: Value
v@(Array Array
_) = [Column b] -> SubscribeColumns b
forall (b :: BackendType). [Column b] -> SubscribeColumns b
SubCArray ([Column b] -> SubscribeColumns b)
-> Parser [Column b] -> Parser (SubscribeColumns b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Column b]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
parseJSON Value
_ = String -> Parser (SubscribeColumns b)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected columns"
instance Backend b => ToJSON (SubscribeColumns b) where
toJSON :: SubscribeColumns b -> Value
toJSON SubscribeColumns b
SubCStar = Value
"*"
toJSON (SubCArray [Column b]
cols) = [Column b] -> Value
forall a. ToJSON a => a -> Value
toJSON [Column b]
cols
data SubscribeOpSpec (b :: BackendType) = SubscribeOpSpec
{
SubscribeOpSpec b -> SubscribeColumns b
sosColumns :: SubscribeColumns b,
SubscribeOpSpec b -> Maybe (SubscribeColumns b)
sosPayload :: Maybe (SubscribeColumns b)
}
deriving (Int -> SubscribeOpSpec b -> ShowS
[SubscribeOpSpec b] -> ShowS
SubscribeOpSpec b -> String
(Int -> SubscribeOpSpec b -> ShowS)
-> (SubscribeOpSpec b -> String)
-> ([SubscribeOpSpec b] -> ShowS)
-> Show (SubscribeOpSpec b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType).
Backend b =>
Int -> SubscribeOpSpec b -> ShowS
forall (b :: BackendType).
Backend b =>
[SubscribeOpSpec b] -> ShowS
forall (b :: BackendType). Backend b => SubscribeOpSpec b -> String
showList :: [SubscribeOpSpec b] -> ShowS
$cshowList :: forall (b :: BackendType).
Backend b =>
[SubscribeOpSpec b] -> ShowS
show :: SubscribeOpSpec b -> String
$cshow :: forall (b :: BackendType). Backend b => SubscribeOpSpec b -> String
showsPrec :: Int -> SubscribeOpSpec b -> ShowS
$cshowsPrec :: forall (b :: BackendType).
Backend b =>
Int -> SubscribeOpSpec b -> ShowS
Show, SubscribeOpSpec b -> SubscribeOpSpec b -> Bool
(SubscribeOpSpec b -> SubscribeOpSpec b -> Bool)
-> (SubscribeOpSpec b -> SubscribeOpSpec b -> Bool)
-> Eq (SubscribeOpSpec b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
SubscribeOpSpec b -> SubscribeOpSpec b -> Bool
/= :: SubscribeOpSpec b -> SubscribeOpSpec b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
SubscribeOpSpec b -> SubscribeOpSpec b -> Bool
== :: SubscribeOpSpec b -> SubscribeOpSpec b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
SubscribeOpSpec b -> SubscribeOpSpec b -> Bool
Eq, (forall x. SubscribeOpSpec b -> Rep (SubscribeOpSpec b) x)
-> (forall x. Rep (SubscribeOpSpec b) x -> SubscribeOpSpec b)
-> Generic (SubscribeOpSpec b)
forall x. Rep (SubscribeOpSpec b) x -> SubscribeOpSpec b
forall x. SubscribeOpSpec b -> Rep (SubscribeOpSpec b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (SubscribeOpSpec b) x -> SubscribeOpSpec b
forall (b :: BackendType) x.
SubscribeOpSpec b -> Rep (SubscribeOpSpec b) x
$cto :: forall (b :: BackendType) x.
Rep (SubscribeOpSpec b) x -> SubscribeOpSpec b
$cfrom :: forall (b :: BackendType) x.
SubscribeOpSpec b -> Rep (SubscribeOpSpec b) x
Generic)
instance (Backend b) => NFData (SubscribeOpSpec b)
instance (Backend b) => Cacheable (SubscribeOpSpec b)
instance Backend b => FromJSON (SubscribeOpSpec b) where
parseJSON :: Value -> Parser (SubscribeOpSpec b)
parseJSON = Options -> Value -> Parser (SubscribeOpSpec b)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance Backend b => ToJSON (SubscribeOpSpec b) where
toJSON :: SubscribeOpSpec b -> Value
toJSON = Options -> SubscribeOpSpec b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
defaultNumRetries :: Int
defaultNumRetries :: Int
defaultNumRetries = Int
0
defaultRetryInterval :: Int
defaultRetryInterval :: Int
defaultRetryInterval = Int
10
defaultTimeoutSeconds :: Int
defaultTimeoutSeconds :: Int
defaultTimeoutSeconds = Int
60
defaultRetryConf :: RetryConf
defaultRetryConf :: RetryConf
defaultRetryConf = Int -> Int -> Maybe Int -> RetryConf
RetryConf Int
defaultNumRetries Int
defaultRetryInterval (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
defaultTimeoutSeconds)
data RetryConf = RetryConf
{ RetryConf -> Int
rcNumRetries :: Int,
RetryConf -> Int
rcIntervalSec :: Int,
RetryConf -> Maybe Int
rcTimeoutSec :: Maybe Int
}
deriving (Int -> RetryConf -> ShowS
[RetryConf] -> ShowS
RetryConf -> String
(Int -> RetryConf -> ShowS)
-> (RetryConf -> String)
-> ([RetryConf] -> ShowS)
-> Show RetryConf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetryConf] -> ShowS
$cshowList :: [RetryConf] -> ShowS
show :: RetryConf -> String
$cshow :: RetryConf -> String
showsPrec :: Int -> RetryConf -> ShowS
$cshowsPrec :: Int -> RetryConf -> ShowS
Show, RetryConf -> RetryConf -> Bool
(RetryConf -> RetryConf -> Bool)
-> (RetryConf -> RetryConf -> Bool) -> Eq RetryConf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetryConf -> RetryConf -> Bool
$c/= :: RetryConf -> RetryConf -> Bool
== :: RetryConf -> RetryConf -> Bool
$c== :: RetryConf -> RetryConf -> Bool
Eq, (forall x. RetryConf -> Rep RetryConf x)
-> (forall x. Rep RetryConf x -> RetryConf) -> Generic RetryConf
forall x. Rep RetryConf x -> RetryConf
forall x. RetryConf -> Rep RetryConf x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RetryConf x -> RetryConf
$cfrom :: forall x. RetryConf -> Rep RetryConf x
Generic)
instance NFData RetryConf
instance Cacheable RetryConf
$(deriveJSON hasuraJSON {omitNothingFields = True} ''RetryConf)
data =
{ :: HeaderConf,
EventHeaderInfo -> Text
ehiCachedValue :: Text
}
deriving (Int -> EventHeaderInfo -> ShowS
[EventHeaderInfo] -> ShowS
EventHeaderInfo -> String
(Int -> EventHeaderInfo -> ShowS)
-> (EventHeaderInfo -> String)
-> ([EventHeaderInfo] -> ShowS)
-> Show EventHeaderInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventHeaderInfo] -> ShowS
$cshowList :: [EventHeaderInfo] -> ShowS
show :: EventHeaderInfo -> String
$cshow :: EventHeaderInfo -> String
showsPrec :: Int -> EventHeaderInfo -> ShowS
$cshowsPrec :: Int -> EventHeaderInfo -> ShowS
Show, EventHeaderInfo -> EventHeaderInfo -> Bool
(EventHeaderInfo -> EventHeaderInfo -> Bool)
-> (EventHeaderInfo -> EventHeaderInfo -> Bool)
-> Eq EventHeaderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventHeaderInfo -> EventHeaderInfo -> Bool
$c/= :: EventHeaderInfo -> EventHeaderInfo -> Bool
== :: EventHeaderInfo -> EventHeaderInfo -> Bool
$c== :: EventHeaderInfo -> EventHeaderInfo -> Bool
Eq, (forall x. EventHeaderInfo -> Rep EventHeaderInfo x)
-> (forall x. Rep EventHeaderInfo x -> EventHeaderInfo)
-> Generic EventHeaderInfo
forall x. Rep EventHeaderInfo x -> EventHeaderInfo
forall x. EventHeaderInfo -> Rep EventHeaderInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EventHeaderInfo x -> EventHeaderInfo
$cfrom :: forall x. EventHeaderInfo -> Rep EventHeaderInfo x
Generic)
instance NFData EventHeaderInfo
$(deriveToJSON hasuraJSON {omitNothingFields = True} ''EventHeaderInfo)
data WebhookConf = WCValue InputWebhook | WCEnv Text
deriving (Int -> WebhookConf -> ShowS
[WebhookConf] -> ShowS
WebhookConf -> String
(Int -> WebhookConf -> ShowS)
-> (WebhookConf -> String)
-> ([WebhookConf] -> ShowS)
-> Show WebhookConf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebhookConf] -> ShowS
$cshowList :: [WebhookConf] -> ShowS
show :: WebhookConf -> String
$cshow :: WebhookConf -> String
showsPrec :: Int -> WebhookConf -> ShowS
$cshowsPrec :: Int -> WebhookConf -> ShowS
Show, WebhookConf -> WebhookConf -> Bool
(WebhookConf -> WebhookConf -> Bool)
-> (WebhookConf -> WebhookConf -> Bool) -> Eq WebhookConf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebhookConf -> WebhookConf -> Bool
$c/= :: WebhookConf -> WebhookConf -> Bool
== :: WebhookConf -> WebhookConf -> Bool
$c== :: WebhookConf -> WebhookConf -> Bool
Eq, (forall x. WebhookConf -> Rep WebhookConf x)
-> (forall x. Rep WebhookConf x -> WebhookConf)
-> Generic WebhookConf
forall x. Rep WebhookConf x -> WebhookConf
forall x. WebhookConf -> Rep WebhookConf x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WebhookConf x -> WebhookConf
$cfrom :: forall x. WebhookConf -> Rep WebhookConf x
Generic)
instance NFData WebhookConf
instance Cacheable WebhookConf
instance ToJSON WebhookConf where
toJSON :: WebhookConf -> Value
toJSON (WCValue InputWebhook
w) = InputWebhook -> Value
forall a. ToJSON a => a -> Value
toJSON InputWebhook
w
toJSON (WCEnv Text
wEnv) = [Pair] -> Value
object [Key
"from_env" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
wEnv]
instance FromJSON WebhookConf where
parseJSON :: Value -> Parser WebhookConf
parseJSON (Object Object
o) = Text -> WebhookConf
WCEnv (Text -> WebhookConf) -> Parser Text -> Parser WebhookConf
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"from_env"
parseJSON t :: Value
t@(String Text
_) =
case Value -> Result InputWebhook
forall a. FromJSON a => Value -> Result a
fromJSON Value
t of
Error String
s -> String -> Parser WebhookConf
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
s
Success InputWebhook
a -> WebhookConf -> Parser WebhookConf
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WebhookConf -> Parser WebhookConf)
-> WebhookConf -> Parser WebhookConf
forall a b. (a -> b) -> a -> b
$ InputWebhook -> WebhookConf
WCValue InputWebhook
a
parseJSON Value
_ = String -> Parser WebhookConf
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"one of string or object must be provided for webhook"
data WebhookConfInfo = WebhookConfInfo
{ WebhookConfInfo -> WebhookConf
wciWebhookConf :: WebhookConf,
WebhookConfInfo -> EnvRecord ResolvedWebhook
wciCachedValue :: EnvRecord ResolvedWebhook
}
deriving (Int -> WebhookConfInfo -> ShowS
[WebhookConfInfo] -> ShowS
WebhookConfInfo -> String
(Int -> WebhookConfInfo -> ShowS)
-> (WebhookConfInfo -> String)
-> ([WebhookConfInfo] -> ShowS)
-> Show WebhookConfInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebhookConfInfo] -> ShowS
$cshowList :: [WebhookConfInfo] -> ShowS
show :: WebhookConfInfo -> String
$cshow :: WebhookConfInfo -> String
showsPrec :: Int -> WebhookConfInfo -> ShowS
$cshowsPrec :: Int -> WebhookConfInfo -> ShowS
Show, WebhookConfInfo -> WebhookConfInfo -> Bool
(WebhookConfInfo -> WebhookConfInfo -> Bool)
-> (WebhookConfInfo -> WebhookConfInfo -> Bool)
-> Eq WebhookConfInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebhookConfInfo -> WebhookConfInfo -> Bool
$c/= :: WebhookConfInfo -> WebhookConfInfo -> Bool
== :: WebhookConfInfo -> WebhookConfInfo -> Bool
$c== :: WebhookConfInfo -> WebhookConfInfo -> Bool
Eq, (forall x. WebhookConfInfo -> Rep WebhookConfInfo x)
-> (forall x. Rep WebhookConfInfo x -> WebhookConfInfo)
-> Generic WebhookConfInfo
forall x. Rep WebhookConfInfo x -> WebhookConfInfo
forall x. WebhookConfInfo -> Rep WebhookConfInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WebhookConfInfo x -> WebhookConfInfo
$cfrom :: forall x. WebhookConfInfo -> Rep WebhookConfInfo x
Generic)
instance NFData WebhookConfInfo
instance Cacheable WebhookConfInfo
$(deriveToJSON hasuraJSON {omitNothingFields = True} ''WebhookConfInfo)
data TriggerOpsDef (b :: BackendType) = TriggerOpsDef
{ TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdInsert :: Maybe (SubscribeOpSpec b),
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdUpdate :: Maybe (SubscribeOpSpec b),
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdDelete :: Maybe (SubscribeOpSpec b),
TriggerOpsDef b -> Maybe Bool
tdEnableManual :: Maybe Bool
}
deriving (Int -> TriggerOpsDef b -> ShowS
[TriggerOpsDef b] -> ShowS
TriggerOpsDef b -> String
(Int -> TriggerOpsDef b -> ShowS)
-> (TriggerOpsDef b -> String)
-> ([TriggerOpsDef b] -> ShowS)
-> Show (TriggerOpsDef b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType).
Backend b =>
Int -> TriggerOpsDef b -> ShowS
forall (b :: BackendType). Backend b => [TriggerOpsDef b] -> ShowS
forall (b :: BackendType). Backend b => TriggerOpsDef b -> String
showList :: [TriggerOpsDef b] -> ShowS
$cshowList :: forall (b :: BackendType). Backend b => [TriggerOpsDef b] -> ShowS
show :: TriggerOpsDef b -> String
$cshow :: forall (b :: BackendType). Backend b => TriggerOpsDef b -> String
showsPrec :: Int -> TriggerOpsDef b -> ShowS
$cshowsPrec :: forall (b :: BackendType).
Backend b =>
Int -> TriggerOpsDef b -> ShowS
Show, TriggerOpsDef b -> TriggerOpsDef b -> Bool
(TriggerOpsDef b -> TriggerOpsDef b -> Bool)
-> (TriggerOpsDef b -> TriggerOpsDef b -> Bool)
-> Eq (TriggerOpsDef b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
TriggerOpsDef b -> TriggerOpsDef b -> Bool
/= :: TriggerOpsDef b -> TriggerOpsDef b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
TriggerOpsDef b -> TriggerOpsDef b -> Bool
== :: TriggerOpsDef b -> TriggerOpsDef b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
TriggerOpsDef b -> TriggerOpsDef b -> Bool
Eq, (forall x. TriggerOpsDef b -> Rep (TriggerOpsDef b) x)
-> (forall x. Rep (TriggerOpsDef b) x -> TriggerOpsDef b)
-> Generic (TriggerOpsDef b)
forall x. Rep (TriggerOpsDef b) x -> TriggerOpsDef b
forall x. TriggerOpsDef b -> Rep (TriggerOpsDef b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (TriggerOpsDef b) x -> TriggerOpsDef b
forall (b :: BackendType) x.
TriggerOpsDef b -> Rep (TriggerOpsDef b) x
$cto :: forall (b :: BackendType) x.
Rep (TriggerOpsDef b) x -> TriggerOpsDef b
$cfrom :: forall (b :: BackendType) x.
TriggerOpsDef b -> Rep (TriggerOpsDef b) x
Generic)
instance Backend b => NFData (TriggerOpsDef b)
instance Backend b => Cacheable (TriggerOpsDef b)
instance Backend b => FromJSON (TriggerOpsDef b) where
parseJSON :: Value -> Parser (TriggerOpsDef b)
parseJSON = Options -> Value -> Parser (TriggerOpsDef b)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance Backend b => ToJSON (TriggerOpsDef b) where
toJSON :: TriggerOpsDef b -> Value
toJSON = Options -> TriggerOpsDef b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
data EventTriggerConf (b :: BackendType) = EventTriggerConf
{ EventTriggerConf b -> TriggerName
etcName :: TriggerName,
EventTriggerConf b -> TriggerOpsDef b
etcDefinition :: TriggerOpsDef b,
EventTriggerConf b -> Maybe InputWebhook
etcWebhook :: Maybe InputWebhook,
EventTriggerConf b -> Maybe Text
etcWebhookFromEnv :: Maybe Text,
EventTriggerConf b -> RetryConf
etcRetryConf :: RetryConf,
:: Maybe [HeaderConf],
EventTriggerConf b -> Maybe RequestTransform
etcRequestTransform :: Maybe RequestTransform,
EventTriggerConf b -> Maybe MetadataResponseTransform
etcResponseTransform :: Maybe MetadataResponseTransform
}
deriving (Int -> EventTriggerConf b -> ShowS
[EventTriggerConf b] -> ShowS
EventTriggerConf b -> String
(Int -> EventTriggerConf b -> ShowS)
-> (EventTriggerConf b -> String)
-> ([EventTriggerConf b] -> ShowS)
-> Show (EventTriggerConf b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType).
Backend b =>
Int -> EventTriggerConf b -> ShowS
forall (b :: BackendType).
Backend b =>
[EventTriggerConf b] -> ShowS
forall (b :: BackendType).
Backend b =>
EventTriggerConf b -> String
showList :: [EventTriggerConf b] -> ShowS
$cshowList :: forall (b :: BackendType).
Backend b =>
[EventTriggerConf b] -> ShowS
show :: EventTriggerConf b -> String
$cshow :: forall (b :: BackendType).
Backend b =>
EventTriggerConf b -> String
showsPrec :: Int -> EventTriggerConf b -> ShowS
$cshowsPrec :: forall (b :: BackendType).
Backend b =>
Int -> EventTriggerConf b -> ShowS
Show, EventTriggerConf b -> EventTriggerConf b -> Bool
(EventTriggerConf b -> EventTriggerConf b -> Bool)
-> (EventTriggerConf b -> EventTriggerConf b -> Bool)
-> Eq (EventTriggerConf b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
EventTriggerConf b -> EventTriggerConf b -> Bool
/= :: EventTriggerConf b -> EventTriggerConf b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
EventTriggerConf b -> EventTriggerConf b -> Bool
== :: EventTriggerConf b -> EventTriggerConf b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
EventTriggerConf b -> EventTriggerConf b -> Bool
Eq, (forall x. EventTriggerConf b -> Rep (EventTriggerConf b) x)
-> (forall x. Rep (EventTriggerConf b) x -> EventTriggerConf b)
-> Generic (EventTriggerConf b)
forall x. Rep (EventTriggerConf b) x -> EventTriggerConf b
forall x. EventTriggerConf b -> Rep (EventTriggerConf b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (EventTriggerConf b) x -> EventTriggerConf b
forall (b :: BackendType) x.
EventTriggerConf b -> Rep (EventTriggerConf b) x
$cto :: forall (b :: BackendType) x.
Rep (EventTriggerConf b) x -> EventTriggerConf b
$cfrom :: forall (b :: BackendType) x.
EventTriggerConf b -> Rep (EventTriggerConf b) x
Generic)
instance Backend b => Cacheable (EventTriggerConf b)
instance Backend b => FromJSON (EventTriggerConf b) where
parseJSON :: Value -> Parser (EventTriggerConf b)
parseJSON = Options -> Value -> Parser (EventTriggerConf b)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance Backend b => ToJSON (EventTriggerConf b) where
toJSON :: EventTriggerConf b -> Value
toJSON = Options -> EventTriggerConf b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
data RecreateEventTriggers
= RETRecreate
| RETDoNothing
deriving (Int -> RecreateEventTriggers -> ShowS
[RecreateEventTriggers] -> ShowS
RecreateEventTriggers -> String
(Int -> RecreateEventTriggers -> ShowS)
-> (RecreateEventTriggers -> String)
-> ([RecreateEventTriggers] -> ShowS)
-> Show RecreateEventTriggers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecreateEventTriggers] -> ShowS
$cshowList :: [RecreateEventTriggers] -> ShowS
show :: RecreateEventTriggers -> String
$cshow :: RecreateEventTriggers -> String
showsPrec :: Int -> RecreateEventTriggers -> ShowS
$cshowsPrec :: Int -> RecreateEventTriggers -> ShowS
Show, RecreateEventTriggers -> RecreateEventTriggers -> Bool
(RecreateEventTriggers -> RecreateEventTriggers -> Bool)
-> (RecreateEventTriggers -> RecreateEventTriggers -> Bool)
-> Eq RecreateEventTriggers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
$c/= :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
== :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
$c== :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
Eq, (forall x. RecreateEventTriggers -> Rep RecreateEventTriggers x)
-> (forall x. Rep RecreateEventTriggers x -> RecreateEventTriggers)
-> Generic RecreateEventTriggers
forall x. Rep RecreateEventTriggers x -> RecreateEventTriggers
forall x. RecreateEventTriggers -> Rep RecreateEventTriggers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecreateEventTriggers x -> RecreateEventTriggers
$cfrom :: forall x. RecreateEventTriggers -> Rep RecreateEventTriggers x
Generic)
instance Cacheable RecreateEventTriggers
instance Semigroup RecreateEventTriggers where
RecreateEventTriggers
RETRecreate <> :: RecreateEventTriggers
-> RecreateEventTriggers -> RecreateEventTriggers
<> RecreateEventTriggers
RETRecreate = RecreateEventTriggers
RETRecreate
RecreateEventTriggers
RETRecreate <> RecreateEventTriggers
RETDoNothing = RecreateEventTriggers
RETRecreate
RecreateEventTriggers
RETDoNothing <> RecreateEventTriggers
RETRecreate = RecreateEventTriggers
RETRecreate
RecreateEventTriggers
RETDoNothing <> RecreateEventTriggers
RETDoNothing = RecreateEventTriggers
RETDoNothing
data TriggerMetadata = TriggerMetadata {TriggerMetadata -> TriggerName
tmName :: TriggerName}
deriving (Int -> TriggerMetadata -> ShowS
[TriggerMetadata] -> ShowS
TriggerMetadata -> String
(Int -> TriggerMetadata -> ShowS)
-> (TriggerMetadata -> String)
-> ([TriggerMetadata] -> ShowS)
-> Show TriggerMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TriggerMetadata] -> ShowS
$cshowList :: [TriggerMetadata] -> ShowS
show :: TriggerMetadata -> String
$cshow :: TriggerMetadata -> String
showsPrec :: Int -> TriggerMetadata -> ShowS
$cshowsPrec :: Int -> TriggerMetadata -> ShowS
Show, TriggerMetadata -> TriggerMetadata -> Bool
(TriggerMetadata -> TriggerMetadata -> Bool)
-> (TriggerMetadata -> TriggerMetadata -> Bool)
-> Eq TriggerMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TriggerMetadata -> TriggerMetadata -> Bool
$c/= :: TriggerMetadata -> TriggerMetadata -> Bool
== :: TriggerMetadata -> TriggerMetadata -> Bool
$c== :: TriggerMetadata -> TriggerMetadata -> Bool
Eq)
$(deriveJSON hasuraJSON {omitNothingFields = True} ''TriggerMetadata)
data Event (b :: BackendType) = Event
{ Event b -> EventId
eId :: EventId,
Event b -> SourceName
eSource :: SourceName,
Event b -> TableName b
eTable :: TableName b,
Event b -> TriggerMetadata
eTrigger :: TriggerMetadata,
Event b -> Value
eEvent :: Value,
Event b -> Int
eTries :: Int,
Event b -> UTCTime
eCreatedAt :: Time.UTCTime
}
deriving ((forall x. Event b -> Rep (Event b) x)
-> (forall x. Rep (Event b) x -> Event b) -> Generic (Event b)
forall x. Rep (Event b) x -> Event b
forall x. Event b -> Rep (Event b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (Event b) x -> Event b
forall (b :: BackendType) x. Event b -> Rep (Event b) x
$cto :: forall (b :: BackendType) x. Rep (Event b) x -> Event b
$cfrom :: forall (b :: BackendType) x. Event b -> Rep (Event b) x
Generic)
deriving instance Backend b => Show (Event b)
deriving instance Backend b => Eq (Event b)
instance Backend b => FromJSON (Event b) where
parseJSON :: Value -> Parser (Event b)
parseJSON = Options -> Value -> Parser (Event b)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
data EventWithSource (b :: BackendType) = EventWithSource
{ EventWithSource b -> Event b
_ewsEvent :: Event b,
EventWithSource b -> SourceConfig b
_ewsSourceConfig :: SourceConfig b,
EventWithSource b -> SourceName
_ewsSourceName :: SourceName,
EventWithSource b -> UTCTime
_ewsFetchTime :: Time.UTCTime
}
data ProcessEventError
= PESetRetry Time.UTCTime
| PESetError
deriving (Int -> ProcessEventError -> ShowS
[ProcessEventError] -> ShowS
ProcessEventError -> String
(Int -> ProcessEventError -> ShowS)
-> (ProcessEventError -> String)
-> ([ProcessEventError] -> ShowS)
-> Show ProcessEventError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessEventError] -> ShowS
$cshowList :: [ProcessEventError] -> ShowS
show :: ProcessEventError -> String
$cshow :: ProcessEventError -> String
showsPrec :: Int -> ProcessEventError -> ShowS
$cshowsPrec :: Int -> ProcessEventError -> ShowS
Show, ProcessEventError -> ProcessEventError -> Bool
(ProcessEventError -> ProcessEventError -> Bool)
-> (ProcessEventError -> ProcessEventError -> Bool)
-> Eq ProcessEventError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProcessEventError -> ProcessEventError -> Bool
$c/= :: ProcessEventError -> ProcessEventError -> Bool
== :: ProcessEventError -> ProcessEventError -> Bool
$c== :: ProcessEventError -> ProcessEventError -> Bool
Eq)
data EventTriggerInfo (b :: BackendType) = EventTriggerInfo
{ EventTriggerInfo b -> TriggerName
etiName :: TriggerName,
EventTriggerInfo b -> TriggerOpsDef b
etiOpsDef :: TriggerOpsDef b,
EventTriggerInfo b -> RetryConf
etiRetryConf :: RetryConf,
EventTriggerInfo b -> WebhookConfInfo
etiWebhookInfo :: WebhookConfInfo,
:: [EventHeaderInfo],
EventTriggerInfo b -> Maybe RequestTransform
etiRequestTransform :: Maybe RequestTransform,
EventTriggerInfo b -> Maybe MetadataResponseTransform
etiResponseTransform :: Maybe MetadataResponseTransform
}
deriving ((forall x. EventTriggerInfo b -> Rep (EventTriggerInfo b) x)
-> (forall x. Rep (EventTriggerInfo b) x -> EventTriggerInfo b)
-> Generic (EventTriggerInfo b)
forall x. Rep (EventTriggerInfo b) x -> EventTriggerInfo b
forall x. EventTriggerInfo b -> Rep (EventTriggerInfo b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (EventTriggerInfo b) x -> EventTriggerInfo b
forall (b :: BackendType) x.
EventTriggerInfo b -> Rep (EventTriggerInfo b) x
$cto :: forall (b :: BackendType) x.
Rep (EventTriggerInfo b) x -> EventTriggerInfo b
$cfrom :: forall (b :: BackendType) x.
EventTriggerInfo b -> Rep (EventTriggerInfo b) x
Generic, EventTriggerInfo b -> EventTriggerInfo b -> Bool
(EventTriggerInfo b -> EventTriggerInfo b -> Bool)
-> (EventTriggerInfo b -> EventTriggerInfo b -> Bool)
-> Eq (EventTriggerInfo b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
EventTriggerInfo b -> EventTriggerInfo b -> Bool
/= :: EventTriggerInfo b -> EventTriggerInfo b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
EventTriggerInfo b -> EventTriggerInfo b -> Bool
== :: EventTriggerInfo b -> EventTriggerInfo b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
EventTriggerInfo b -> EventTriggerInfo b -> Bool
Eq)
instance Backend b => NFData (EventTriggerInfo b)
instance Backend b => ToJSON (EventTriggerInfo b) where
toJSON :: EventTriggerInfo b -> Value
toJSON = Options -> EventTriggerInfo b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
type EventTriggerInfoMap b = M.HashMap TriggerName (EventTriggerInfo b)
newtype FetchBatchSize = FetchBatchSize {FetchBatchSize -> Int
_unFetchBatchSize :: Int}
deriving (Int -> FetchBatchSize -> ShowS
[FetchBatchSize] -> ShowS
FetchBatchSize -> String
(Int -> FetchBatchSize -> ShowS)
-> (FetchBatchSize -> String)
-> ([FetchBatchSize] -> ShowS)
-> Show FetchBatchSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FetchBatchSize] -> ShowS
$cshowList :: [FetchBatchSize] -> ShowS
show :: FetchBatchSize -> String
$cshow :: FetchBatchSize -> String
showsPrec :: Int -> FetchBatchSize -> ShowS
$cshowsPrec :: Int -> FetchBatchSize -> ShowS
Show, FetchBatchSize -> FetchBatchSize -> Bool
(FetchBatchSize -> FetchBatchSize -> Bool)
-> (FetchBatchSize -> FetchBatchSize -> Bool) -> Eq FetchBatchSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FetchBatchSize -> FetchBatchSize -> Bool
$c/= :: FetchBatchSize -> FetchBatchSize -> Bool
== :: FetchBatchSize -> FetchBatchSize -> Bool
$c== :: FetchBatchSize -> FetchBatchSize -> Bool
Eq)