{-# LANGUAGE UndecidableInstances #-}
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 (..),
AutoTriggerLogCleanupConfig (..),
TriggerLogCleanupConfig (..),
EventTriggerCleanupStatus (..),
DeletedEventLogStats (..),
EventTriggerQualifier (..),
TriggerLogCleanupSources (..),
TriggerLogCleanupToggleConfig (..),
updateCleanupConfig,
isIllegalTriggerName,
EventLogStatus (..),
GetEventLogs (..),
EventLog (..),
GetEventInvocations (..),
EventInvocationLog (..),
GetEventById (..),
EventLogWithInvocations (..),
)
where
import Autodocodec (HasCodec, codec, dimapCodec, disjointEitherCodec, listCodec, literalTextCodec, optionalField', optionalFieldWithDefault', optionalFieldWithOmittedDefault', requiredField')
import Autodocodec qualified as AC
import Autodocodec.Extended (boolConstCodec)
import Data.Aeson
import Data.Aeson.Extended ((.=?))
import Data.ByteString.Lazy qualified as LBS
import Data.HashMap.Strict qualified as HashMap
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Text.Extended
import Data.Text.NonEmpty
import Data.Time.Clock qualified as Time
import Data.Time.LocalTime (LocalTime)
import Database.PG.Query qualified as PG
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendTag (backendPrefix)
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Common (EnvRecord, InputWebhook, ResolvedWebhook, SourceName (..), TriggerOnReplication (..))
import Hasura.RQL.Types.Eventing
import Hasura.RQL.Types.Headers (HeaderConf (..))
import Hasura.RQL.Types.Webhook.Transform (MetadataResponseTransform, RequestTransform)
import System.Cron (CronSchedule)
import Text.Regex.TDFA qualified as TDFA
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
$cshowsPrec :: Int -> TriggerName -> ShowS
showsPrec :: Int -> TriggerName -> ShowS
$cshow :: TriggerName -> String
show :: TriggerName -> String
$cshowList :: [TriggerName] -> ShowS
showList :: [TriggerName] -> ShowS
Show,
TriggerName -> TriggerName -> Bool
(TriggerName -> TriggerName -> Bool)
-> (TriggerName -> TriggerName -> Bool) -> Eq TriggerName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TriggerName -> TriggerName -> Bool
== :: TriggerName -> TriggerName -> Bool
$c/= :: TriggerName -> TriggerName -> Bool
/= :: 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
$ccompare :: TriggerName -> TriggerName -> Ordering
compare :: TriggerName -> TriggerName -> Ordering
$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
>= :: TriggerName -> TriggerName -> Bool
$cmax :: TriggerName -> TriggerName -> TriggerName
max :: TriggerName -> TriggerName -> TriggerName
$cmin :: TriggerName -> TriggerName -> TriggerName
min :: TriggerName -> TriggerName -> TriggerName
Ord,
Eq TriggerName
Eq TriggerName
-> (Int -> TriggerName -> Int)
-> (TriggerName -> Int)
-> Hashable TriggerName
Int -> TriggerName -> Int
TriggerName -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> TriggerName -> Int
hashWithSalt :: Int -> TriggerName -> Int
$chash :: TriggerName -> Int
hash :: TriggerName -> Int
Hashable,
TriggerName -> Text
(TriggerName -> Text) -> ToTxt TriggerName
forall a. (a -> Text) -> ToTxt a
$ctoTxt :: TriggerName -> Text
toTxt :: 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
$cparseJSON :: Value -> Parser TriggerName
parseJSON :: Value -> Parser TriggerName
$cparseJSONList :: Value -> Parser [TriggerName]
parseJSONList :: 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
$ctoJSON :: TriggerName -> Value
toJSON :: TriggerName -> Value
$ctoEncoding :: TriggerName -> Encoding
toEncoding :: TriggerName -> Encoding
$ctoJSONList :: [TriggerName] -> Value
toJSONList :: [TriggerName] -> Value
$ctoEncodingList :: [TriggerName] -> Encoding
toEncodingList :: [TriggerName] -> Encoding
ToJSON,
ToJSONKeyFunction [TriggerName]
ToJSONKeyFunction TriggerName
ToJSONKeyFunction TriggerName
-> ToJSONKeyFunction [TriggerName] -> ToJSONKey TriggerName
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
$ctoJSONKey :: ToJSONKeyFunction TriggerName
toJSONKey :: ToJSONKeyFunction TriggerName
$ctoJSONKeyList :: ToJSONKeyFunction [TriggerName]
toJSONKeyList :: ToJSONKeyFunction [TriggerName]
ToJSONKey,
TriggerName -> PrepArg
(TriggerName -> PrepArg) -> ToPrepArg TriggerName
forall a. (a -> PrepArg) -> ToPrepArg a
$ctoPrepVal :: TriggerName -> PrepArg
toPrepVal :: TriggerName -> PrepArg
PG.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
$cfrom :: forall x. TriggerName -> Rep TriggerName x
from :: forall x. TriggerName -> Rep TriggerName x
$cto :: forall x. Rep TriggerName x -> TriggerName
to :: forall x. Rep TriggerName x -> TriggerName
Generic,
TriggerName -> ()
(TriggerName -> ()) -> NFData TriggerName
forall a. (a -> ()) -> NFData a
$crnf :: TriggerName -> ()
rnf :: TriggerName -> ()
NFData,
Maybe ByteString -> Either Text TriggerName
(Maybe ByteString -> Either Text TriggerName)
-> FromCol TriggerName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
$cfromCol :: Maybe ByteString -> Either Text TriggerName
fromCol :: Maybe ByteString -> Either Text TriggerName
PG.FromCol
)
instance HasCodec TriggerName where
codec :: JSONCodec TriggerName
codec = (NonEmptyText -> TriggerName)
-> (TriggerName -> NonEmptyText)
-> Codec Value NonEmptyText NonEmptyText
-> JSONCodec TriggerName
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec NonEmptyText -> TriggerName
TriggerName TriggerName -> NonEmptyText
unTriggerName Codec Value NonEmptyText NonEmptyText
forall value. HasCodec value => JSONCodec value
codec
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
isIllegalTriggerName :: TriggerName -> Bool
isIllegalTriggerName :: TriggerName -> Bool
isIllegalTriggerName (TriggerName NonEmptyText
name) =
let regex :: ByteString
regex = ByteString
"^[A-Za-z]+[A-Za-z0-9_\\-]*$" :: LBS.ByteString
compiledRegex :: Regex
compiledRegex = ByteString -> Regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
source -> regex
TDFA.makeRegex ByteString
regex :: TDFA.Regex
in Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Regex -> String -> Bool
forall regex source target.
RegexContext regex source target =>
regex -> source -> target
TDFA.match Regex
compiledRegex (String -> Bool) -> (Text -> String) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ NonEmptyText -> Text
unNonEmptyText NonEmptyText
name
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
$cshowsPrec :: Int -> Ops -> ShowS
showsPrec :: Int -> Ops -> ShowS
$cshow :: Ops -> String
show :: Ops -> String
$cshowList :: [Ops] -> ShowS
showList :: [Ops] -> ShowS
Show, Ops -> Ops -> Bool
(Ops -> Ops -> Bool) -> (Ops -> Ops -> Bool) -> Eq Ops
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ops -> Ops -> Bool
== :: Ops -> Ops -> Bool
$c/= :: Ops -> Ops -> Bool
/= :: 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
$cfrom :: forall x. Ops -> Rep Ops x
from :: forall x. Ops -> Rep Ops x
$cto :: forall x. Rep Ops x -> Ops
to :: forall x. Rep Ops x -> Ops
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
$cfrom :: forall (b :: BackendType) x.
SubscribeColumns b -> Rep (SubscribeColumns b) x
from :: forall x. SubscribeColumns b -> Rep (SubscribeColumns b) x
$cto :: forall (b :: BackendType) x.
Rep (SubscribeColumns b) x -> SubscribeColumns b
to :: forall x. Rep (SubscribeColumns b) x -> SubscribeColumns b
Generic)
deriving instance (Backend b) => Show (SubscribeColumns b)
deriving instance (Backend b) => Eq (SubscribeColumns b)
instance (Backend b) => NFData (SubscribeColumns b)
instance (Backend b) => HasCodec (SubscribeColumns b) where
codec :: JSONCodec (SubscribeColumns b)
codec =
(Either Text [Column b] -> SubscribeColumns b)
-> (SubscribeColumns b -> Either Text [Column b])
-> Codec Value (Either Text [Column b]) (Either Text [Column b])
-> JSONCodec (SubscribeColumns b)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec
((Text -> SubscribeColumns b)
-> ([Column b] -> SubscribeColumns b)
-> Either Text [Column b]
-> SubscribeColumns b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (SubscribeColumns b -> Text -> SubscribeColumns b
forall a b. a -> b -> a
const SubscribeColumns b
forall (b :: BackendType). SubscribeColumns b
SubCStar) [Column b] -> SubscribeColumns b
forall (b :: BackendType). [Column b] -> SubscribeColumns b
SubCArray)
(\case SubscribeColumns b
SubCStar -> Text -> Either Text [Column b]
forall a b. a -> Either a b
Left Text
"*"; SubCArray [Column b]
cols -> [Column b] -> Either Text [Column b]
forall a b. b -> Either a b
Right [Column b]
cols)
(Codec Value (Either Text [Column b]) (Either Text [Column b])
-> JSONCodec (SubscribeColumns b))
-> Codec Value (Either Text [Column b]) (Either Text [Column b])
-> JSONCodec (SubscribeColumns b)
forall a b. (a -> b) -> a -> b
$ Codec Value Text Text
-> Codec Value [Column b] [Column b]
-> Codec Value (Either Text [Column b]) (Either Text [Column b])
forall context input1 output1 input2 output2.
Codec context input1 output1
-> Codec context input2 output2
-> Codec context (Either input1 input2) (Either output1 output2)
disjointEitherCodec (Text -> Codec Value Text Text
literalTextCodec Text
"*") (ValueCodec (Column b) (Column b)
-> Codec Value [Column b] [Column b]
forall input output.
ValueCodec input output -> ValueCodec [input] [output]
listCodec ValueCodec (Column b) (Column b)
forall value. HasCodec value => JSONCodec value
codec)
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 a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return SubscribeColumns b
forall (b :: BackendType). SubscribeColumns b
SubCStar
Text
_ -> String -> Parser (SubscribeColumns b)
forall a. String -> Parser a
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 a. String -> Parser a
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
{
forall (b :: BackendType). SubscribeOpSpec b -> SubscribeColumns b
sosColumns :: SubscribeColumns b,
forall (b :: BackendType).
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
$cshowsPrec :: forall (b :: BackendType).
Backend b =>
Int -> SubscribeOpSpec b -> ShowS
showsPrec :: Int -> SubscribeOpSpec b -> ShowS
$cshow :: forall (b :: BackendType). Backend b => SubscribeOpSpec b -> String
show :: SubscribeOpSpec b -> String
$cshowList :: forall (b :: BackendType).
Backend b =>
[SubscribeOpSpec b] -> ShowS
showList :: [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
$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
/= :: 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
$cfrom :: forall (b :: BackendType) x.
SubscribeOpSpec b -> Rep (SubscribeOpSpec b) x
from :: forall x. SubscribeOpSpec b -> Rep (SubscribeOpSpec b) x
$cto :: forall (b :: BackendType) x.
Rep (SubscribeOpSpec b) x -> SubscribeOpSpec b
to :: forall x. Rep (SubscribeOpSpec b) x -> SubscribeOpSpec b
Generic)
instance (Backend b) => NFData (SubscribeOpSpec b)
instance (Backend b) => HasCodec (SubscribeOpSpec b) where
codec :: JSONCodec (SubscribeOpSpec b)
codec =
Text
-> ObjectCodec (SubscribeOpSpec b) (SubscribeOpSpec b)
-> JSONCodec (SubscribeOpSpec b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"SubscribeOpSpec")
(ObjectCodec (SubscribeOpSpec b) (SubscribeOpSpec b)
-> JSONCodec (SubscribeOpSpec b))
-> ObjectCodec (SubscribeOpSpec b) (SubscribeOpSpec b)
-> JSONCodec (SubscribeOpSpec b)
forall a b. (a -> b) -> a -> b
$ SubscribeColumns b
-> Maybe (SubscribeColumns b) -> SubscribeOpSpec b
forall (b :: BackendType).
SubscribeColumns b
-> Maybe (SubscribeColumns b) -> SubscribeOpSpec b
SubscribeOpSpec
(SubscribeColumns b
-> Maybe (SubscribeColumns b) -> SubscribeOpSpec b)
-> Codec Object (SubscribeOpSpec b) (SubscribeColumns b)
-> Codec
Object
(SubscribeOpSpec b)
(Maybe (SubscribeColumns b) -> SubscribeOpSpec b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (SubscribeColumns b) (SubscribeColumns b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"columns"
ObjectCodec (SubscribeColumns b) (SubscribeColumns b)
-> (SubscribeOpSpec b -> SubscribeColumns b)
-> Codec Object (SubscribeOpSpec b) (SubscribeColumns b)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SubscribeOpSpec b -> SubscribeColumns b
forall (b :: BackendType). SubscribeOpSpec b -> SubscribeColumns b
sosColumns
Codec
Object
(SubscribeOpSpec b)
(Maybe (SubscribeColumns b) -> SubscribeOpSpec b)
-> Codec Object (SubscribeOpSpec b) (Maybe (SubscribeColumns b))
-> ObjectCodec (SubscribeOpSpec b) (SubscribeOpSpec b)
forall a b.
Codec Object (SubscribeOpSpec b) (a -> b)
-> Codec Object (SubscribeOpSpec b) a
-> Codec Object (SubscribeOpSpec b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (SubscribeColumns b)) (Maybe (SubscribeColumns b))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"payload"
ObjectCodec
(Maybe (SubscribeColumns b)) (Maybe (SubscribeColumns b))
-> (SubscribeOpSpec b -> Maybe (SubscribeColumns b))
-> Codec Object (SubscribeOpSpec b) (Maybe (SubscribeColumns b))
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SubscribeOpSpec b -> Maybe (SubscribeColumns b)
forall (b :: BackendType).
SubscribeOpSpec b -> Maybe (SubscribeColumns b)
sosPayload
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
$cshowsPrec :: Int -> RetryConf -> ShowS
showsPrec :: Int -> RetryConf -> ShowS
$cshow :: RetryConf -> String
show :: RetryConf -> String
$cshowList :: [RetryConf] -> ShowS
showList :: [RetryConf] -> ShowS
Show, RetryConf -> RetryConf -> Bool
(RetryConf -> RetryConf -> Bool)
-> (RetryConf -> RetryConf -> Bool) -> Eq RetryConf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RetryConf -> RetryConf -> Bool
== :: RetryConf -> RetryConf -> Bool
$c/= :: RetryConf -> RetryConf -> Bool
/= :: 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
$cfrom :: forall x. RetryConf -> Rep RetryConf x
from :: forall x. RetryConf -> Rep RetryConf x
$cto :: forall x. Rep RetryConf x -> RetryConf
to :: forall x. Rep RetryConf x -> RetryConf
Generic)
instance NFData RetryConf
instance HasCodec RetryConf where
codec :: JSONCodec RetryConf
codec =
Text -> ObjectCodec RetryConf RetryConf -> JSONCodec RetryConf
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"RetryConf"
(ObjectCodec RetryConf RetryConf -> JSONCodec RetryConf)
-> ObjectCodec RetryConf RetryConf -> JSONCodec RetryConf
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Maybe Int -> RetryConf
RetryConf
(Int -> Int -> Maybe Int -> RetryConf)
-> Codec Object RetryConf Int
-> Codec Object RetryConf (Int -> Maybe Int -> RetryConf)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"num_retries"
ObjectCodec Int Int
-> (RetryConf -> Int) -> Codec Object RetryConf Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= RetryConf -> Int
rcNumRetries
Codec Object RetryConf (Int -> Maybe Int -> RetryConf)
-> Codec Object RetryConf Int
-> Codec Object RetryConf (Maybe Int -> RetryConf)
forall a b.
Codec Object RetryConf (a -> b)
-> Codec Object RetryConf a -> Codec Object RetryConf b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"interval_sec"
ObjectCodec Int Int
-> (RetryConf -> Int) -> Codec Object RetryConf Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= RetryConf -> Int
rcIntervalSec
Codec Object RetryConf (Maybe Int -> RetryConf)
-> Codec Object RetryConf (Maybe Int)
-> ObjectCodec RetryConf RetryConf
forall a b.
Codec Object RetryConf (a -> b)
-> Codec Object RetryConf a -> Codec Object RetryConf b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Int) (Maybe Int)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"timeout_sec"
ObjectCodec (Maybe Int) (Maybe Int)
-> (RetryConf -> Maybe Int) -> Codec Object RetryConf (Maybe Int)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= RetryConf -> Maybe Int
rcTimeoutSec
instance FromJSON RetryConf where
parseJSON :: Value -> Parser RetryConf
parseJSON = Options -> Value -> Parser RetryConf
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance ToJSON RetryConf where
toJSON :: RetryConf -> Value
toJSON = Options -> RetryConf -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
toEncoding :: RetryConf -> Encoding
toEncoding = Options -> RetryConf -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
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
$cshowsPrec :: Int -> EventHeaderInfo -> ShowS
showsPrec :: Int -> EventHeaderInfo -> ShowS
$cshow :: EventHeaderInfo -> String
show :: EventHeaderInfo -> String
$cshowList :: [EventHeaderInfo] -> ShowS
showList :: [EventHeaderInfo] -> ShowS
Show, EventHeaderInfo -> EventHeaderInfo -> Bool
(EventHeaderInfo -> EventHeaderInfo -> Bool)
-> (EventHeaderInfo -> EventHeaderInfo -> Bool)
-> Eq EventHeaderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventHeaderInfo -> EventHeaderInfo -> Bool
== :: EventHeaderInfo -> EventHeaderInfo -> Bool
$c/= :: EventHeaderInfo -> EventHeaderInfo -> Bool
/= :: 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
$cfrom :: forall x. EventHeaderInfo -> Rep EventHeaderInfo x
from :: forall x. EventHeaderInfo -> Rep EventHeaderInfo x
$cto :: forall x. Rep EventHeaderInfo x -> EventHeaderInfo
to :: forall x. Rep EventHeaderInfo x -> EventHeaderInfo
Generic)
instance NFData EventHeaderInfo
instance ToJSON EventHeaderInfo where
toJSON :: EventHeaderInfo -> Value
toJSON = Options -> EventHeaderInfo -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
toEncoding :: EventHeaderInfo -> Encoding
toEncoding = Options -> EventHeaderInfo -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
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
$cshowsPrec :: Int -> WebhookConf -> ShowS
showsPrec :: Int -> WebhookConf -> ShowS
$cshow :: WebhookConf -> String
show :: WebhookConf -> String
$cshowList :: [WebhookConf] -> ShowS
showList :: [WebhookConf] -> ShowS
Show, WebhookConf -> WebhookConf -> Bool
(WebhookConf -> WebhookConf -> Bool)
-> (WebhookConf -> WebhookConf -> Bool) -> Eq WebhookConf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebhookConf -> WebhookConf -> Bool
== :: WebhookConf -> WebhookConf -> Bool
$c/= :: WebhookConf -> WebhookConf -> Bool
/= :: 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
$cfrom :: forall x. WebhookConf -> Rep WebhookConf x
from :: forall x. WebhookConf -> Rep WebhookConf x
$cto :: forall x. Rep WebhookConf x -> WebhookConf
to :: forall x. Rep WebhookConf x -> WebhookConf
Generic)
instance NFData 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
forall v. ToJSON v => Key -> v -> Pair
.= 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 a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
s
Success InputWebhook
a -> WebhookConf -> Parser WebhookConf
forall a. a -> Parser a
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 a. String -> Parser a
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
$cshowsPrec :: Int -> WebhookConfInfo -> ShowS
showsPrec :: Int -> WebhookConfInfo -> ShowS
$cshow :: WebhookConfInfo -> String
show :: WebhookConfInfo -> String
$cshowList :: [WebhookConfInfo] -> ShowS
showList :: [WebhookConfInfo] -> ShowS
Show, WebhookConfInfo -> WebhookConfInfo -> Bool
(WebhookConfInfo -> WebhookConfInfo -> Bool)
-> (WebhookConfInfo -> WebhookConfInfo -> Bool)
-> Eq WebhookConfInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebhookConfInfo -> WebhookConfInfo -> Bool
== :: WebhookConfInfo -> WebhookConfInfo -> Bool
$c/= :: WebhookConfInfo -> WebhookConfInfo -> Bool
/= :: 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
$cfrom :: forall x. WebhookConfInfo -> Rep WebhookConfInfo x
from :: forall x. WebhookConfInfo -> Rep WebhookConfInfo x
$cto :: forall x. Rep WebhookConfInfo x -> WebhookConfInfo
to :: forall x. Rep WebhookConfInfo x -> WebhookConfInfo
Generic)
instance NFData WebhookConfInfo
instance ToJSON WebhookConfInfo where
toJSON :: WebhookConfInfo -> Value
toJSON = Options -> WebhookConfInfo -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
toEncoding :: WebhookConfInfo -> Encoding
toEncoding = Options -> WebhookConfInfo -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
data TriggerOpsDef (b :: BackendType) = TriggerOpsDef
{ forall (b :: BackendType).
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdInsert :: Maybe (SubscribeOpSpec b),
forall (b :: BackendType).
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdUpdate :: Maybe (SubscribeOpSpec b),
forall (b :: BackendType).
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdDelete :: Maybe (SubscribeOpSpec b),
forall (b :: BackendType). 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
$cshowsPrec :: forall (b :: BackendType).
Backend b =>
Int -> TriggerOpsDef b -> ShowS
showsPrec :: Int -> TriggerOpsDef b -> ShowS
$cshow :: forall (b :: BackendType). Backend b => TriggerOpsDef b -> String
show :: TriggerOpsDef b -> String
$cshowList :: forall (b :: BackendType). Backend b => [TriggerOpsDef b] -> ShowS
showList :: [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
$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
/= :: 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
$cfrom :: forall (b :: BackendType) x.
TriggerOpsDef b -> Rep (TriggerOpsDef b) x
from :: forall x. TriggerOpsDef b -> Rep (TriggerOpsDef b) x
$cto :: forall (b :: BackendType) x.
Rep (TriggerOpsDef b) x -> TriggerOpsDef b
to :: forall x. Rep (TriggerOpsDef b) x -> TriggerOpsDef b
Generic)
instance (Backend b) => NFData (TriggerOpsDef b)
instance (Backend b) => HasCodec (TriggerOpsDef b) where
codec :: JSONCodec (TriggerOpsDef b)
codec =
Text
-> ObjectCodec (TriggerOpsDef b) (TriggerOpsDef b)
-> JSONCodec (TriggerOpsDef b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"TriggerOpsDef")
(ObjectCodec (TriggerOpsDef b) (TriggerOpsDef b)
-> JSONCodec (TriggerOpsDef b))
-> ObjectCodec (TriggerOpsDef b) (TriggerOpsDef b)
-> JSONCodec (TriggerOpsDef b)
forall a b. (a -> b) -> a -> b
$ Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b)
-> Maybe Bool
-> TriggerOpsDef b
forall (b :: BackendType).
Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b)
-> Maybe Bool
-> TriggerOpsDef b
TriggerOpsDef
(Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b)
-> Maybe Bool
-> TriggerOpsDef b)
-> Codec Object (TriggerOpsDef b) (Maybe (SubscribeOpSpec b))
-> Codec
Object
(TriggerOpsDef b)
(Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b) -> Maybe Bool -> TriggerOpsDef b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ObjectCodec
(Maybe (SubscribeOpSpec b)) (Maybe (SubscribeOpSpec b))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"insert"
ObjectCodec (Maybe (SubscribeOpSpec b)) (Maybe (SubscribeOpSpec b))
-> (TriggerOpsDef b -> Maybe (SubscribeOpSpec b))
-> Codec Object (TriggerOpsDef b) (Maybe (SubscribeOpSpec b))
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
forall (b :: BackendType).
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdInsert
Codec
Object
(TriggerOpsDef b)
(Maybe (SubscribeOpSpec b)
-> Maybe (SubscribeOpSpec b) -> Maybe Bool -> TriggerOpsDef b)
-> Codec Object (TriggerOpsDef b) (Maybe (SubscribeOpSpec b))
-> Codec
Object
(TriggerOpsDef b)
(Maybe (SubscribeOpSpec b) -> Maybe Bool -> TriggerOpsDef b)
forall a b.
Codec Object (TriggerOpsDef b) (a -> b)
-> Codec Object (TriggerOpsDef b) a
-> Codec Object (TriggerOpsDef b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (SubscribeOpSpec b)) (Maybe (SubscribeOpSpec b))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"update"
ObjectCodec (Maybe (SubscribeOpSpec b)) (Maybe (SubscribeOpSpec b))
-> (TriggerOpsDef b -> Maybe (SubscribeOpSpec b))
-> Codec Object (TriggerOpsDef b) (Maybe (SubscribeOpSpec b))
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
forall (b :: BackendType).
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdUpdate
Codec
Object
(TriggerOpsDef b)
(Maybe (SubscribeOpSpec b) -> Maybe Bool -> TriggerOpsDef b)
-> Codec Object (TriggerOpsDef b) (Maybe (SubscribeOpSpec b))
-> Codec Object (TriggerOpsDef b) (Maybe Bool -> TriggerOpsDef b)
forall a b.
Codec Object (TriggerOpsDef b) (a -> b)
-> Codec Object (TriggerOpsDef b) a
-> Codec Object (TriggerOpsDef b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (SubscribeOpSpec b)) (Maybe (SubscribeOpSpec b))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"delete"
ObjectCodec (Maybe (SubscribeOpSpec b)) (Maybe (SubscribeOpSpec b))
-> (TriggerOpsDef b -> Maybe (SubscribeOpSpec b))
-> Codec Object (TriggerOpsDef b) (Maybe (SubscribeOpSpec b))
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
forall (b :: BackendType).
TriggerOpsDef b -> Maybe (SubscribeOpSpec b)
tdDelete
Codec Object (TriggerOpsDef b) (Maybe Bool -> TriggerOpsDef b)
-> Codec Object (TriggerOpsDef b) (Maybe Bool)
-> ObjectCodec (TriggerOpsDef b) (TriggerOpsDef b)
forall a b.
Codec Object (TriggerOpsDef b) (a -> b)
-> Codec Object (TriggerOpsDef b) a
-> Codec Object (TriggerOpsDef b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"enable_manual"
ObjectCodec (Maybe Bool) (Maybe Bool)
-> (TriggerOpsDef b -> Maybe Bool)
-> Codec Object (TriggerOpsDef b) (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TriggerOpsDef b -> Maybe Bool
forall (b :: BackendType). TriggerOpsDef b -> Maybe Bool
tdEnableManual
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 EventTriggerCleanupStatus = ETCSPaused | ETCSUnpaused deriving (Int -> EventTriggerCleanupStatus -> ShowS
[EventTriggerCleanupStatus] -> ShowS
EventTriggerCleanupStatus -> String
(Int -> EventTriggerCleanupStatus -> ShowS)
-> (EventTriggerCleanupStatus -> String)
-> ([EventTriggerCleanupStatus] -> ShowS)
-> Show EventTriggerCleanupStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventTriggerCleanupStatus -> ShowS
showsPrec :: Int -> EventTriggerCleanupStatus -> ShowS
$cshow :: EventTriggerCleanupStatus -> String
show :: EventTriggerCleanupStatus -> String
$cshowList :: [EventTriggerCleanupStatus] -> ShowS
showList :: [EventTriggerCleanupStatus] -> ShowS
Show, EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool
(EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool)
-> (EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool)
-> Eq EventTriggerCleanupStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool
== :: EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool
$c/= :: EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool
/= :: EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool
Eq, (forall x.
EventTriggerCleanupStatus -> Rep EventTriggerCleanupStatus x)
-> (forall x.
Rep EventTriggerCleanupStatus x -> EventTriggerCleanupStatus)
-> Generic EventTriggerCleanupStatus
forall x.
Rep EventTriggerCleanupStatus x -> EventTriggerCleanupStatus
forall x.
EventTriggerCleanupStatus -> Rep EventTriggerCleanupStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
EventTriggerCleanupStatus -> Rep EventTriggerCleanupStatus x
from :: forall x.
EventTriggerCleanupStatus -> Rep EventTriggerCleanupStatus x
$cto :: forall x.
Rep EventTriggerCleanupStatus x -> EventTriggerCleanupStatus
to :: forall x.
Rep EventTriggerCleanupStatus x -> EventTriggerCleanupStatus
Generic)
instance NFData EventTriggerCleanupStatus
instance HasCodec EventTriggerCleanupStatus where
codec :: JSONCodec EventTriggerCleanupStatus
codec = EventTriggerCleanupStatus
-> EventTriggerCleanupStatus -> JSONCodec EventTriggerCleanupStatus
forall a. Eq a => a -> a -> JSONCodec a
boolConstCodec EventTriggerCleanupStatus
ETCSPaused EventTriggerCleanupStatus
ETCSUnpaused
instance ToJSON EventTriggerCleanupStatus where
toJSON :: EventTriggerCleanupStatus -> Value
toJSON = Bool -> Value
Bool (Bool -> Value)
-> (EventTriggerCleanupStatus -> Bool)
-> EventTriggerCleanupStatus
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EventTriggerCleanupStatus
ETCSPaused EventTriggerCleanupStatus -> EventTriggerCleanupStatus -> Bool
forall a. Eq a => a -> a -> Bool
==)
instance FromJSON EventTriggerCleanupStatus where
parseJSON :: Value -> Parser EventTriggerCleanupStatus
parseJSON =
String
-> (Bool -> Parser EventTriggerCleanupStatus)
-> Value
-> Parser EventTriggerCleanupStatus
forall a. String -> (Bool -> Parser a) -> Value -> Parser a
withBool String
"EventTriggerCleanupStatus" ((Bool -> Parser EventTriggerCleanupStatus)
-> Value -> Parser EventTriggerCleanupStatus)
-> (Bool -> Parser EventTriggerCleanupStatus)
-> Value
-> Parser EventTriggerCleanupStatus
forall a b. (a -> b) -> a -> b
$ \Bool
isPaused -> do
EventTriggerCleanupStatus -> Parser EventTriggerCleanupStatus
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EventTriggerCleanupStatus -> Parser EventTriggerCleanupStatus)
-> EventTriggerCleanupStatus -> Parser EventTriggerCleanupStatus
forall a b. (a -> b) -> a -> b
$ if Bool
isPaused then EventTriggerCleanupStatus
ETCSPaused else EventTriggerCleanupStatus
ETCSUnpaused
data AutoTriggerLogCleanupConfig = AutoTriggerLogCleanupConfig
{
AutoTriggerLogCleanupConfig -> CronSchedule
_atlccSchedule :: CronSchedule,
AutoTriggerLogCleanupConfig -> Int
_atlccBatchSize :: Int,
AutoTriggerLogCleanupConfig -> Int
_atlccClearOlderThan :: Int,
AutoTriggerLogCleanupConfig -> Int
_atlccTimeout :: Int,
AutoTriggerLogCleanupConfig -> Bool
_atlccCleanInvocationLogs :: Bool,
AutoTriggerLogCleanupConfig -> EventTriggerCleanupStatus
_atlccPaused :: EventTriggerCleanupStatus
}
deriving (Int -> AutoTriggerLogCleanupConfig -> ShowS
[AutoTriggerLogCleanupConfig] -> ShowS
AutoTriggerLogCleanupConfig -> String
(Int -> AutoTriggerLogCleanupConfig -> ShowS)
-> (AutoTriggerLogCleanupConfig -> String)
-> ([AutoTriggerLogCleanupConfig] -> ShowS)
-> Show AutoTriggerLogCleanupConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AutoTriggerLogCleanupConfig -> ShowS
showsPrec :: Int -> AutoTriggerLogCleanupConfig -> ShowS
$cshow :: AutoTriggerLogCleanupConfig -> String
show :: AutoTriggerLogCleanupConfig -> String
$cshowList :: [AutoTriggerLogCleanupConfig] -> ShowS
showList :: [AutoTriggerLogCleanupConfig] -> ShowS
Show, AutoTriggerLogCleanupConfig -> AutoTriggerLogCleanupConfig -> Bool
(AutoTriggerLogCleanupConfig
-> AutoTriggerLogCleanupConfig -> Bool)
-> (AutoTriggerLogCleanupConfig
-> AutoTriggerLogCleanupConfig -> Bool)
-> Eq AutoTriggerLogCleanupConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AutoTriggerLogCleanupConfig -> AutoTriggerLogCleanupConfig -> Bool
== :: AutoTriggerLogCleanupConfig -> AutoTriggerLogCleanupConfig -> Bool
$c/= :: AutoTriggerLogCleanupConfig -> AutoTriggerLogCleanupConfig -> Bool
/= :: AutoTriggerLogCleanupConfig -> AutoTriggerLogCleanupConfig -> Bool
Eq, (forall x.
AutoTriggerLogCleanupConfig -> Rep AutoTriggerLogCleanupConfig x)
-> (forall x.
Rep AutoTriggerLogCleanupConfig x -> AutoTriggerLogCleanupConfig)
-> Generic AutoTriggerLogCleanupConfig
forall x.
Rep AutoTriggerLogCleanupConfig x -> AutoTriggerLogCleanupConfig
forall x.
AutoTriggerLogCleanupConfig -> Rep AutoTriggerLogCleanupConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
AutoTriggerLogCleanupConfig -> Rep AutoTriggerLogCleanupConfig x
from :: forall x.
AutoTriggerLogCleanupConfig -> Rep AutoTriggerLogCleanupConfig x
$cto :: forall x.
Rep AutoTriggerLogCleanupConfig x -> AutoTriggerLogCleanupConfig
to :: forall x.
Rep AutoTriggerLogCleanupConfig x -> AutoTriggerLogCleanupConfig
Generic)
instance NFData AutoTriggerLogCleanupConfig
instance HasCodec AutoTriggerLogCleanupConfig where
codec :: JSONCodec AutoTriggerLogCleanupConfig
codec =
Text
-> ObjectCodec
AutoTriggerLogCleanupConfig AutoTriggerLogCleanupConfig
-> JSONCodec AutoTriggerLogCleanupConfig
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"AutoTriggerLogCleanupConfig"
(ObjectCodec
AutoTriggerLogCleanupConfig AutoTriggerLogCleanupConfig
-> JSONCodec AutoTriggerLogCleanupConfig)
-> ObjectCodec
AutoTriggerLogCleanupConfig AutoTriggerLogCleanupConfig
-> JSONCodec AutoTriggerLogCleanupConfig
forall a b. (a -> b) -> a -> b
$ CronSchedule
-> Int
-> Int
-> Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig
AutoTriggerLogCleanupConfig
(CronSchedule
-> Int
-> Int
-> Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
-> Codec Object AutoTriggerLogCleanupConfig CronSchedule
-> Codec
Object
AutoTriggerLogCleanupConfig
(Int
-> Int
-> Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec CronSchedule CronSchedule
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"schedule"
ObjectCodec CronSchedule CronSchedule
-> (AutoTriggerLogCleanupConfig -> CronSchedule)
-> Codec Object AutoTriggerLogCleanupConfig CronSchedule
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= AutoTriggerLogCleanupConfig -> CronSchedule
_atlccSchedule
Codec
Object
AutoTriggerLogCleanupConfig
(Int
-> Int
-> Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
-> Codec Object AutoTriggerLogCleanupConfig Int
-> Codec
Object
AutoTriggerLogCleanupConfig
(Int
-> Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
forall a b.
Codec Object AutoTriggerLogCleanupConfig (a -> b)
-> Codec Object AutoTriggerLogCleanupConfig a
-> Codec Object AutoTriggerLogCleanupConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Int -> ObjectCodec Int Int
forall output.
HasCodec output =>
Text -> output -> ObjectCodec output output
optionalFieldWithDefault' Text
"batch_size" Int
10000
ObjectCodec Int Int
-> (AutoTriggerLogCleanupConfig -> Int)
-> Codec Object AutoTriggerLogCleanupConfig Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= AutoTriggerLogCleanupConfig -> Int
_atlccBatchSize
Codec
Object
AutoTriggerLogCleanupConfig
(Int
-> Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
-> Codec Object AutoTriggerLogCleanupConfig Int
-> Codec
Object
AutoTriggerLogCleanupConfig
(Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
forall a b.
Codec Object AutoTriggerLogCleanupConfig (a -> b)
-> Codec Object AutoTriggerLogCleanupConfig a
-> Codec Object AutoTriggerLogCleanupConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"clear_older_than"
ObjectCodec Int Int
-> (AutoTriggerLogCleanupConfig -> Int)
-> Codec Object AutoTriggerLogCleanupConfig Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= AutoTriggerLogCleanupConfig -> Int
_atlccClearOlderThan
Codec
Object
AutoTriggerLogCleanupConfig
(Int
-> Bool
-> EventTriggerCleanupStatus
-> AutoTriggerLogCleanupConfig)
-> Codec Object AutoTriggerLogCleanupConfig Int
-> Codec
Object
AutoTriggerLogCleanupConfig
(Bool -> EventTriggerCleanupStatus -> AutoTriggerLogCleanupConfig)
forall a b.
Codec Object AutoTriggerLogCleanupConfig (a -> b)
-> Codec Object AutoTriggerLogCleanupConfig a
-> Codec Object AutoTriggerLogCleanupConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Int -> ObjectCodec Int Int
forall output.
HasCodec output =>
Text -> output -> ObjectCodec output output
optionalFieldWithDefault' Text
"timeout" Int
60
ObjectCodec Int Int
-> (AutoTriggerLogCleanupConfig -> Int)
-> Codec Object AutoTriggerLogCleanupConfig Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= AutoTriggerLogCleanupConfig -> Int
_atlccTimeout
Codec
Object
AutoTriggerLogCleanupConfig
(Bool -> EventTriggerCleanupStatus -> AutoTriggerLogCleanupConfig)
-> Codec Object AutoTriggerLogCleanupConfig Bool
-> Codec
Object
AutoTriggerLogCleanupConfig
(EventTriggerCleanupStatus -> AutoTriggerLogCleanupConfig)
forall a b.
Codec Object AutoTriggerLogCleanupConfig (a -> b)
-> Codec Object AutoTriggerLogCleanupConfig a
-> Codec Object AutoTriggerLogCleanupConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Bool -> ObjectCodec Bool Bool
forall output.
HasCodec output =>
Text -> output -> ObjectCodec output output
optionalFieldWithDefault' Text
"clean_invocation_logs" Bool
False
ObjectCodec Bool Bool
-> (AutoTriggerLogCleanupConfig -> Bool)
-> Codec Object AutoTriggerLogCleanupConfig Bool
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= AutoTriggerLogCleanupConfig -> Bool
_atlccCleanInvocationLogs
Codec
Object
AutoTriggerLogCleanupConfig
(EventTriggerCleanupStatus -> AutoTriggerLogCleanupConfig)
-> Codec
Object AutoTriggerLogCleanupConfig EventTriggerCleanupStatus
-> ObjectCodec
AutoTriggerLogCleanupConfig AutoTriggerLogCleanupConfig
forall a b.
Codec Object AutoTriggerLogCleanupConfig (a -> b)
-> Codec Object AutoTriggerLogCleanupConfig a
-> Codec Object AutoTriggerLogCleanupConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> EventTriggerCleanupStatus
-> ObjectCodec EventTriggerCleanupStatus EventTriggerCleanupStatus
forall output.
HasCodec output =>
Text -> output -> ObjectCodec output output
optionalFieldWithDefault' Text
"paused" EventTriggerCleanupStatus
ETCSUnpaused
ObjectCodec EventTriggerCleanupStatus EventTriggerCleanupStatus
-> (AutoTriggerLogCleanupConfig -> EventTriggerCleanupStatus)
-> Codec
Object AutoTriggerLogCleanupConfig EventTriggerCleanupStatus
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= AutoTriggerLogCleanupConfig -> EventTriggerCleanupStatus
_atlccPaused
instance FromJSON AutoTriggerLogCleanupConfig where
parseJSON :: Value -> Parser AutoTriggerLogCleanupConfig
parseJSON =
String
-> (Object -> Parser AutoTriggerLogCleanupConfig)
-> Value
-> Parser AutoTriggerLogCleanupConfig
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AutoTriggerLogCleanupConfig" ((Object -> Parser AutoTriggerLogCleanupConfig)
-> Value -> Parser AutoTriggerLogCleanupConfig)
-> (Object -> Parser AutoTriggerLogCleanupConfig)
-> Value
-> Parser AutoTriggerLogCleanupConfig
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
CronSchedule
_atlccSchedule <- Object
o Object -> Key -> Parser CronSchedule
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"schedule"
Int
_atlccBatchSize <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"batch_size" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
10000
Int
_atlccClearOlderThan <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"clear_older_than"
Int
_atlccTimeout <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"timeout" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
60
Bool
_atlccCleanInvocationLogs <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"clean_invocation_logs" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
EventTriggerCleanupStatus
_atlccPaused <- Object
o Object -> Key -> Parser (Maybe EventTriggerCleanupStatus)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"paused" Parser (Maybe EventTriggerCleanupStatus)
-> EventTriggerCleanupStatus -> Parser EventTriggerCleanupStatus
forall a. Parser (Maybe a) -> a -> Parser a
.!= EventTriggerCleanupStatus
ETCSUnpaused
AutoTriggerLogCleanupConfig -> Parser AutoTriggerLogCleanupConfig
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AutoTriggerLogCleanupConfig {Bool
Int
CronSchedule
EventTriggerCleanupStatus
_atlccSchedule :: CronSchedule
_atlccBatchSize :: Int
_atlccClearOlderThan :: Int
_atlccTimeout :: Int
_atlccCleanInvocationLogs :: Bool
_atlccPaused :: EventTriggerCleanupStatus
_atlccSchedule :: CronSchedule
_atlccBatchSize :: Int
_atlccClearOlderThan :: Int
_atlccTimeout :: Int
_atlccCleanInvocationLogs :: Bool
_atlccPaused :: EventTriggerCleanupStatus
..}
instance ToJSON AutoTriggerLogCleanupConfig where
toJSON :: AutoTriggerLogCleanupConfig -> Value
toJSON = Options -> AutoTriggerLogCleanupConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
data TriggerLogCleanupConfig = TriggerLogCleanupConfig
{
TriggerLogCleanupConfig -> TriggerName
tlccEventTriggerName :: TriggerName,
TriggerLogCleanupConfig -> SourceName
tlccSourceName :: SourceName,
TriggerLogCleanupConfig -> Int
tlccBatchSize :: Int,
TriggerLogCleanupConfig -> Int
tlccClearOlderThan :: Int,
TriggerLogCleanupConfig -> Int
tlccTimeout :: Int,
TriggerLogCleanupConfig -> Bool
tlccCleanInvocationLogs :: Bool
}
deriving (Int -> TriggerLogCleanupConfig -> ShowS
[TriggerLogCleanupConfig] -> ShowS
TriggerLogCleanupConfig -> String
(Int -> TriggerLogCleanupConfig -> ShowS)
-> (TriggerLogCleanupConfig -> String)
-> ([TriggerLogCleanupConfig] -> ShowS)
-> Show TriggerLogCleanupConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TriggerLogCleanupConfig -> ShowS
showsPrec :: Int -> TriggerLogCleanupConfig -> ShowS
$cshow :: TriggerLogCleanupConfig -> String
show :: TriggerLogCleanupConfig -> String
$cshowList :: [TriggerLogCleanupConfig] -> ShowS
showList :: [TriggerLogCleanupConfig] -> ShowS
Show, TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool
(TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool)
-> (TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool)
-> Eq TriggerLogCleanupConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool
== :: TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool
$c/= :: TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool
/= :: TriggerLogCleanupConfig -> TriggerLogCleanupConfig -> Bool
Eq, (forall x.
TriggerLogCleanupConfig -> Rep TriggerLogCleanupConfig x)
-> (forall x.
Rep TriggerLogCleanupConfig x -> TriggerLogCleanupConfig)
-> Generic TriggerLogCleanupConfig
forall x. Rep TriggerLogCleanupConfig x -> TriggerLogCleanupConfig
forall x. TriggerLogCleanupConfig -> Rep TriggerLogCleanupConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TriggerLogCleanupConfig -> Rep TriggerLogCleanupConfig x
from :: forall x. TriggerLogCleanupConfig -> Rep TriggerLogCleanupConfig x
$cto :: forall x. Rep TriggerLogCleanupConfig x -> TriggerLogCleanupConfig
to :: forall x. Rep TriggerLogCleanupConfig x -> TriggerLogCleanupConfig
Generic)
instance NFData TriggerLogCleanupConfig
instance FromJSON TriggerLogCleanupConfig where
parseJSON :: Value -> Parser TriggerLogCleanupConfig
parseJSON =
String
-> (Object -> Parser TriggerLogCleanupConfig)
-> Value
-> Parser TriggerLogCleanupConfig
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TriggerLogCleanupConfig" ((Object -> Parser TriggerLogCleanupConfig)
-> Value -> Parser TriggerLogCleanupConfig)
-> (Object -> Parser TriggerLogCleanupConfig)
-> Value
-> Parser TriggerLogCleanupConfig
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
TriggerName
tlccEventTriggerName <- Object
o Object -> Key -> Parser TriggerName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"event_trigger_name"
SourceName
tlccSourceName <- Object
o Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source" Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
SNDefault
Int
tlccBatchSize <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"batch_size" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
10000
Int
tlccClearOlderThan <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"clear_older_than"
Int
tlccTimeout <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"timeout" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
60
Bool
tlccCleanInvocationLogs <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"clean_invocation_logs" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
TriggerLogCleanupConfig -> Parser TriggerLogCleanupConfig
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TriggerLogCleanupConfig {Bool
Int
SourceName
TriggerName
tlccEventTriggerName :: TriggerName
tlccSourceName :: SourceName
tlccBatchSize :: Int
tlccClearOlderThan :: Int
tlccTimeout :: Int
tlccCleanInvocationLogs :: Bool
tlccEventTriggerName :: TriggerName
tlccSourceName :: SourceName
tlccBatchSize :: Int
tlccClearOlderThan :: Int
tlccTimeout :: Int
tlccCleanInvocationLogs :: Bool
..}
instance ToJSON TriggerLogCleanupConfig where
toJSON :: TriggerLogCleanupConfig -> Value
toJSON = Options -> TriggerLogCleanupConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
data EventTriggerQualifier = EventTriggerQualifier
{ EventTriggerQualifier -> SourceName
_etqSourceName :: SourceName,
EventTriggerQualifier -> NonEmpty TriggerName
_etqEventTriggers :: NE.NonEmpty TriggerName
}
deriving (Int -> EventTriggerQualifier -> ShowS
[EventTriggerQualifier] -> ShowS
EventTriggerQualifier -> String
(Int -> EventTriggerQualifier -> ShowS)
-> (EventTriggerQualifier -> String)
-> ([EventTriggerQualifier] -> ShowS)
-> Show EventTriggerQualifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventTriggerQualifier -> ShowS
showsPrec :: Int -> EventTriggerQualifier -> ShowS
$cshow :: EventTriggerQualifier -> String
show :: EventTriggerQualifier -> String
$cshowList :: [EventTriggerQualifier] -> ShowS
showList :: [EventTriggerQualifier] -> ShowS
Show, EventTriggerQualifier -> EventTriggerQualifier -> Bool
(EventTriggerQualifier -> EventTriggerQualifier -> Bool)
-> (EventTriggerQualifier -> EventTriggerQualifier -> Bool)
-> Eq EventTriggerQualifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventTriggerQualifier -> EventTriggerQualifier -> Bool
== :: EventTriggerQualifier -> EventTriggerQualifier -> Bool
$c/= :: EventTriggerQualifier -> EventTriggerQualifier -> Bool
/= :: EventTriggerQualifier -> EventTriggerQualifier -> Bool
Eq, (forall x. EventTriggerQualifier -> Rep EventTriggerQualifier x)
-> (forall x. Rep EventTriggerQualifier x -> EventTriggerQualifier)
-> Generic EventTriggerQualifier
forall x. Rep EventTriggerQualifier x -> EventTriggerQualifier
forall x. EventTriggerQualifier -> Rep EventTriggerQualifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventTriggerQualifier -> Rep EventTriggerQualifier x
from :: forall x. EventTriggerQualifier -> Rep EventTriggerQualifier x
$cto :: forall x. Rep EventTriggerQualifier x -> EventTriggerQualifier
to :: forall x. Rep EventTriggerQualifier x -> EventTriggerQualifier
Generic)
instance NFData EventTriggerQualifier
instance FromJSON EventTriggerQualifier where
parseJSON :: Value -> Parser EventTriggerQualifier
parseJSON =
String
-> (Object -> Parser EventTriggerQualifier)
-> Value
-> Parser EventTriggerQualifier
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"EventTriggerQualifier" ((Object -> Parser EventTriggerQualifier)
-> Value -> Parser EventTriggerQualifier)
-> (Object -> Parser EventTriggerQualifier)
-> Value
-> Parser EventTriggerQualifier
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
NonEmpty TriggerName
_etqEventTriggers <- Object
o Object -> Key -> Parser (NonEmpty TriggerName)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"event_triggers"
SourceName
_etqSourceName <- Object
o Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source_name" Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
SNDefault
EventTriggerQualifier -> Parser EventTriggerQualifier
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EventTriggerQualifier {NonEmpty TriggerName
SourceName
_etqSourceName :: SourceName
_etqEventTriggers :: NonEmpty TriggerName
_etqEventTriggers :: NonEmpty TriggerName
_etqSourceName :: SourceName
..}
instance ToJSON EventTriggerQualifier where
toJSON :: EventTriggerQualifier -> Value
toJSON = Options -> EventTriggerQualifier -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
data TriggerLogCleanupSources = TriggerAllSource | TriggerSource (NE.NonEmpty SourceName)
deriving (Int -> TriggerLogCleanupSources -> ShowS
[TriggerLogCleanupSources] -> ShowS
TriggerLogCleanupSources -> String
(Int -> TriggerLogCleanupSources -> ShowS)
-> (TriggerLogCleanupSources -> String)
-> ([TriggerLogCleanupSources] -> ShowS)
-> Show TriggerLogCleanupSources
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TriggerLogCleanupSources -> ShowS
showsPrec :: Int -> TriggerLogCleanupSources -> ShowS
$cshow :: TriggerLogCleanupSources -> String
show :: TriggerLogCleanupSources -> String
$cshowList :: [TriggerLogCleanupSources] -> ShowS
showList :: [TriggerLogCleanupSources] -> ShowS
Show, TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool
(TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool)
-> (TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool)
-> Eq TriggerLogCleanupSources
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool
== :: TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool
$c/= :: TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool
/= :: TriggerLogCleanupSources -> TriggerLogCleanupSources -> Bool
Eq, (forall x.
TriggerLogCleanupSources -> Rep TriggerLogCleanupSources x)
-> (forall x.
Rep TriggerLogCleanupSources x -> TriggerLogCleanupSources)
-> Generic TriggerLogCleanupSources
forall x.
Rep TriggerLogCleanupSources x -> TriggerLogCleanupSources
forall x.
TriggerLogCleanupSources -> Rep TriggerLogCleanupSources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
TriggerLogCleanupSources -> Rep TriggerLogCleanupSources x
from :: forall x.
TriggerLogCleanupSources -> Rep TriggerLogCleanupSources x
$cto :: forall x.
Rep TriggerLogCleanupSources x -> TriggerLogCleanupSources
to :: forall x.
Rep TriggerLogCleanupSources x -> TriggerLogCleanupSources
Generic)
instance NFData TriggerLogCleanupSources
instance ToJSON TriggerLogCleanupSources where
toJSON :: TriggerLogCleanupSources -> Value
toJSON = Options -> TriggerLogCleanupSources -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON TriggerLogCleanupSources where
parseJSON :: Value -> Parser TriggerLogCleanupSources
parseJSON (String Text
"*") = TriggerLogCleanupSources -> Parser TriggerLogCleanupSources
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TriggerLogCleanupSources
TriggerAllSource
parseJSON (Array Array
arr) = do
case [Value] -> Maybe (NonEmpty Value)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty (Array -> [Value]
forall a. Vector a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Array
arr) of
Just NonEmpty Value
lst -> NonEmpty SourceName -> TriggerLogCleanupSources
TriggerSource (NonEmpty SourceName -> TriggerLogCleanupSources)
-> Parser (NonEmpty SourceName) -> Parser TriggerLogCleanupSources
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser SourceName)
-> NonEmpty Value -> Parser (NonEmpty SourceName)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverse Value -> Parser SourceName
forall a. FromJSON a => Value -> Parser a
parseJSON NonEmpty Value
lst
Maybe (NonEmpty Value)
Nothing -> String -> Parser TriggerLogCleanupSources
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"source name list should have atleast one value"
parseJSON Value
_ = String -> Parser TriggerLogCleanupSources
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"source can be * or a list of source names"
data TriggerLogCleanupToggleConfig = TriggerLogCleanupSources TriggerLogCleanupSources | TriggerQualifier (NE.NonEmpty EventTriggerQualifier)
deriving (Int -> TriggerLogCleanupToggleConfig -> ShowS
[TriggerLogCleanupToggleConfig] -> ShowS
TriggerLogCleanupToggleConfig -> String
(Int -> TriggerLogCleanupToggleConfig -> ShowS)
-> (TriggerLogCleanupToggleConfig -> String)
-> ([TriggerLogCleanupToggleConfig] -> ShowS)
-> Show TriggerLogCleanupToggleConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TriggerLogCleanupToggleConfig -> ShowS
showsPrec :: Int -> TriggerLogCleanupToggleConfig -> ShowS
$cshow :: TriggerLogCleanupToggleConfig -> String
show :: TriggerLogCleanupToggleConfig -> String
$cshowList :: [TriggerLogCleanupToggleConfig] -> ShowS
showList :: [TriggerLogCleanupToggleConfig] -> ShowS
Show, TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool
(TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool)
-> (TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool)
-> Eq TriggerLogCleanupToggleConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool
== :: TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool
$c/= :: TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool
/= :: TriggerLogCleanupToggleConfig
-> TriggerLogCleanupToggleConfig -> Bool
Eq, (forall x.
TriggerLogCleanupToggleConfig
-> Rep TriggerLogCleanupToggleConfig x)
-> (forall x.
Rep TriggerLogCleanupToggleConfig x
-> TriggerLogCleanupToggleConfig)
-> Generic TriggerLogCleanupToggleConfig
forall x.
Rep TriggerLogCleanupToggleConfig x
-> TriggerLogCleanupToggleConfig
forall x.
TriggerLogCleanupToggleConfig
-> Rep TriggerLogCleanupToggleConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
TriggerLogCleanupToggleConfig
-> Rep TriggerLogCleanupToggleConfig x
from :: forall x.
TriggerLogCleanupToggleConfig
-> Rep TriggerLogCleanupToggleConfig x
$cto :: forall x.
Rep TriggerLogCleanupToggleConfig x
-> TriggerLogCleanupToggleConfig
to :: forall x.
Rep TriggerLogCleanupToggleConfig x
-> TriggerLogCleanupToggleConfig
Generic)
instance NFData TriggerLogCleanupToggleConfig
instance ToJSON TriggerLogCleanupToggleConfig where
toJSON :: TriggerLogCleanupToggleConfig -> Value
toJSON = Options -> TriggerLogCleanupToggleConfig -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON TriggerLogCleanupToggleConfig where
parseJSON :: Value -> Parser TriggerLogCleanupToggleConfig
parseJSON = String
-> (Object -> Parser TriggerLogCleanupToggleConfig)
-> Value
-> Parser TriggerLogCleanupToggleConfig
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TriggerLogCleanupToggleConfig" ((Object -> Parser TriggerLogCleanupToggleConfig)
-> Value -> Parser TriggerLogCleanupToggleConfig)
-> (Object -> Parser TriggerLogCleanupToggleConfig)
-> Value
-> Parser TriggerLogCleanupToggleConfig
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Value
eventTriggers <- Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"event_triggers"
case Value
eventTriggers of
(Object Object
obj) -> do
Value
sourceInfo <- Object
obj Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"sources"
TriggerLogCleanupSources -> TriggerLogCleanupToggleConfig
TriggerLogCleanupSources (TriggerLogCleanupSources -> TriggerLogCleanupToggleConfig)
-> Parser TriggerLogCleanupSources
-> Parser TriggerLogCleanupToggleConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser TriggerLogCleanupSources
forall a. FromJSON a => Value -> Parser a
parseJSON Value
sourceInfo
(Array Array
arr) -> do
[EventTriggerQualifier]
qualifiers <- Value -> Parser [EventTriggerQualifier]
forall a. FromJSON a => Value -> Parser a
parseJSON (Array -> Value
Array Array
arr)
case [EventTriggerQualifier] -> Maybe (NonEmpty EventTriggerQualifier)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [EventTriggerQualifier]
qualifiers of
Just NonEmpty EventTriggerQualifier
lst -> TriggerLogCleanupToggleConfig
-> Parser TriggerLogCleanupToggleConfig
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TriggerLogCleanupToggleConfig
-> Parser TriggerLogCleanupToggleConfig)
-> TriggerLogCleanupToggleConfig
-> Parser TriggerLogCleanupToggleConfig
forall a b. (a -> b) -> a -> b
$ NonEmpty EventTriggerQualifier -> TriggerLogCleanupToggleConfig
TriggerQualifier NonEmpty EventTriggerQualifier
lst
Maybe (NonEmpty EventTriggerQualifier)
Nothing -> String -> Parser TriggerLogCleanupToggleConfig
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"qualifier list should have atleast one value"
Value
_ -> String -> Parser TriggerLogCleanupToggleConfig
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"The event trigger cleanup argument should either be \"*\", list of sources or list of event trigger qualifiers"
data EventTriggerConf (b :: BackendType) = EventTriggerConf
{ forall (b :: BackendType). EventTriggerConf b -> TriggerName
etcName :: TriggerName,
forall (b :: BackendType). EventTriggerConf b -> TriggerOpsDef b
etcDefinition :: TriggerOpsDef b,
forall (b :: BackendType). EventTriggerConf b -> Maybe InputWebhook
etcWebhook :: Maybe InputWebhook,
forall (b :: BackendType). EventTriggerConf b -> Maybe Text
etcWebhookFromEnv :: Maybe Text,
forall (b :: BackendType). EventTriggerConf b -> RetryConf
etcRetryConf :: RetryConf,
:: Maybe [HeaderConf],
forall (b :: BackendType).
EventTriggerConf b -> Maybe RequestTransform
etcRequestTransform :: Maybe RequestTransform,
forall (b :: BackendType).
EventTriggerConf b -> Maybe MetadataResponseTransform
etcResponseTransform :: Maybe MetadataResponseTransform,
forall (b :: BackendType).
EventTriggerConf b -> Maybe AutoTriggerLogCleanupConfig
etcCleanupConfig :: Maybe AutoTriggerLogCleanupConfig,
forall (b :: BackendType).
EventTriggerConf b -> TriggerOnReplication
etcTriggerOnReplication :: TriggerOnReplication
}
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
$cshowsPrec :: forall (b :: BackendType).
Backend b =>
Int -> EventTriggerConf b -> ShowS
showsPrec :: Int -> EventTriggerConf b -> ShowS
$cshow :: forall (b :: BackendType).
Backend b =>
EventTriggerConf b -> String
show :: EventTriggerConf b -> String
$cshowList :: forall (b :: BackendType).
Backend b =>
[EventTriggerConf b] -> ShowS
showList :: [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
$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
/= :: 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
$cfrom :: forall (b :: BackendType) x.
EventTriggerConf b -> Rep (EventTriggerConf b) x
from :: forall x. EventTriggerConf b -> Rep (EventTriggerConf b) x
$cto :: forall (b :: BackendType) x.
Rep (EventTriggerConf b) x -> EventTriggerConf b
to :: forall x. Rep (EventTriggerConf b) x -> EventTriggerConf b
Generic)
instance (Backend b) => HasCodec (EventTriggerConf b) where
codec :: JSONCodec (EventTriggerConf b)
codec =
Text
-> ObjectCodec (EventTriggerConf b) (EventTriggerConf b)
-> JSONCodec (EventTriggerConf b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"EventTriggerConfEventTriggerConf")
(ObjectCodec (EventTriggerConf b) (EventTriggerConf b)
-> JSONCodec (EventTriggerConf b))
-> ObjectCodec (EventTriggerConf b) (EventTriggerConf b)
-> JSONCodec (EventTriggerConf b)
forall a b. (a -> b) -> a -> b
$ TriggerName
-> TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b
forall (b :: BackendType).
TriggerName
-> TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b
EventTriggerConf
(TriggerName
-> TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) TriggerName
-> Codec
Object
(EventTriggerConf b)
(TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TriggerName TriggerName
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"name"
ObjectCodec TriggerName TriggerName
-> (EventTriggerConf b -> TriggerName)
-> Codec Object (EventTriggerConf b) TriggerName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> TriggerName
forall (b :: BackendType). EventTriggerConf b -> TriggerName
etcName
Codec
Object
(EventTriggerConf b)
(TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) (TriggerOpsDef b)
-> Codec
Object
(EventTriggerConf b)
(Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (TriggerOpsDef b) (TriggerOpsDef b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"definition"
ObjectCodec (TriggerOpsDef b) (TriggerOpsDef b)
-> (EventTriggerConf b -> TriggerOpsDef b)
-> Codec Object (EventTriggerConf b) (TriggerOpsDef b)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> TriggerOpsDef b
forall (b :: BackendType). EventTriggerConf b -> TriggerOpsDef b
etcDefinition
Codec
Object
(EventTriggerConf b)
(Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) (Maybe InputWebhook)
-> Codec
Object
(EventTriggerConf b)
(Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe InputWebhook) (Maybe InputWebhook)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"webhook"
ObjectCodec (Maybe InputWebhook) (Maybe InputWebhook)
-> (EventTriggerConf b -> Maybe InputWebhook)
-> Codec Object (EventTriggerConf b) (Maybe InputWebhook)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> Maybe InputWebhook
forall (b :: BackendType). EventTriggerConf b -> Maybe InputWebhook
etcWebhook
Codec
Object
(EventTriggerConf b)
(Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) (Maybe Text)
-> Codec
Object
(EventTriggerConf b)
(RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"webhook_from_env"
ObjectCodec (Maybe Text) (Maybe Text)
-> (EventTriggerConf b -> Maybe Text)
-> Codec Object (EventTriggerConf b) (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> Maybe Text
forall (b :: BackendType). EventTriggerConf b -> Maybe Text
etcWebhookFromEnv
Codec
Object
(EventTriggerConf b)
(RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) RetryConf
-> Codec
Object
(EventTriggerConf b)
(Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RetryConf RetryConf
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"retry_conf"
ObjectCodec RetryConf RetryConf
-> (EventTriggerConf b -> RetryConf)
-> Codec Object (EventTriggerConf b) RetryConf
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> RetryConf
forall (b :: BackendType). EventTriggerConf b -> RetryConf
etcRetryConf
Codec
Object
(EventTriggerConf b)
(Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) (Maybe [HeaderConf])
-> Codec
Object
(EventTriggerConf b)
(Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe [HeaderConf]) (Maybe [HeaderConf])
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"headers"
ObjectCodec (Maybe [HeaderConf]) (Maybe [HeaderConf])
-> (EventTriggerConf b -> Maybe [HeaderConf])
-> Codec Object (EventTriggerConf b) (Maybe [HeaderConf])
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> Maybe [HeaderConf]
forall (b :: BackendType). EventTriggerConf b -> Maybe [HeaderConf]
etcHeaders
Codec
Object
(EventTriggerConf b)
(Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) (Maybe RequestTransform)
-> Codec
Object
(EventTriggerConf b)
(Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec (Maybe RequestTransform) (Maybe RequestTransform)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"request_transform"
ObjectCodec (Maybe RequestTransform) (Maybe RequestTransform)
-> (EventTriggerConf b -> Maybe RequestTransform)
-> Codec Object (EventTriggerConf b) (Maybe RequestTransform)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> Maybe RequestTransform
forall (b :: BackendType).
EventTriggerConf b -> Maybe RequestTransform
etcRequestTransform
Codec
Object
(EventTriggerConf b)
(Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b)
-> Codec
Object (EventTriggerConf b) (Maybe MetadataResponseTransform)
-> Codec
Object
(EventTriggerConf b)
(Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication -> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe MetadataResponseTransform) (Maybe MetadataResponseTransform)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"response_transform"
ObjectCodec
(Maybe MetadataResponseTransform) (Maybe MetadataResponseTransform)
-> (EventTriggerConf b -> Maybe MetadataResponseTransform)
-> Codec
Object (EventTriggerConf b) (Maybe MetadataResponseTransform)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> Maybe MetadataResponseTransform
forall (b :: BackendType).
EventTriggerConf b -> Maybe MetadataResponseTransform
etcResponseTransform
Codec
Object
(EventTriggerConf b)
(Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication -> EventTriggerConf b)
-> Codec
Object (EventTriggerConf b) (Maybe AutoTriggerLogCleanupConfig)
-> Codec
Object
(EventTriggerConf b)
(TriggerOnReplication -> EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe AutoTriggerLogCleanupConfig)
(Maybe AutoTriggerLogCleanupConfig)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"cleanup_config"
ObjectCodec
(Maybe AutoTriggerLogCleanupConfig)
(Maybe AutoTriggerLogCleanupConfig)
-> (EventTriggerConf b -> Maybe AutoTriggerLogCleanupConfig)
-> Codec
Object (EventTriggerConf b) (Maybe AutoTriggerLogCleanupConfig)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> Maybe AutoTriggerLogCleanupConfig
forall (b :: BackendType).
EventTriggerConf b -> Maybe AutoTriggerLogCleanupConfig
etcCleanupConfig
Codec
Object
(EventTriggerConf b)
(TriggerOnReplication -> EventTriggerConf b)
-> Codec Object (EventTriggerConf b) TriggerOnReplication
-> ObjectCodec (EventTriggerConf b) (EventTriggerConf b)
forall a b.
Codec Object (EventTriggerConf b) (a -> b)
-> Codec Object (EventTriggerConf b) a
-> Codec Object (EventTriggerConf b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Codec Object (EventTriggerConf b) TriggerOnReplication
triggerOnReplication
where
triggerOnReplication :: Codec Object (EventTriggerConf b) TriggerOnReplication
triggerOnReplication = case forall (b :: BackendType).
Backend b =>
Maybe (XEventTriggers b, TriggerOnReplication)
defaultTriggerOnReplication @b of
Just (XEventTriggers b
_, TriggerOnReplication
defTOR) -> Text
-> TriggerOnReplication
-> ObjectCodec TriggerOnReplication TriggerOnReplication
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"trigger_on_replication" TriggerOnReplication
defTOR ObjectCodec TriggerOnReplication TriggerOnReplication
-> (EventTriggerConf b -> TriggerOnReplication)
-> Codec Object (EventTriggerConf b) TriggerOnReplication
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= EventTriggerConf b -> TriggerOnReplication
forall (b :: BackendType).
EventTriggerConf b -> TriggerOnReplication
etcTriggerOnReplication
Maybe (XEventTriggers b, TriggerOnReplication)
Nothing -> String -> Codec Object (EventTriggerConf b) TriggerOnReplication
forall a. HasCallStack => String -> a
error String
"No default setting for trigger_on_replication is defined for backend type."
instance (Backend b) => FromJSON (EventTriggerConf b) where
parseJSON :: Value -> Parser (EventTriggerConf b)
parseJSON = String
-> (Object -> Parser (EventTriggerConf b))
-> Value
-> Parser (EventTriggerConf b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"EventTriggerConf" \Object
o -> do
TriggerName
name <- Object
o Object -> Key -> Parser TriggerName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
TriggerOpsDef b
definition <- Object
o Object -> Key -> Parser (TriggerOpsDef b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"definition"
Maybe InputWebhook
webhook <- Object
o Object -> Key -> Parser (Maybe InputWebhook)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"webhook"
Maybe Text
webhookFromEnv <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"webhook_from_env"
RetryConf
retryConf <- Object
o Object -> Key -> Parser RetryConf
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"retry_conf"
Maybe [HeaderConf]
headers <- Object
o Object -> Key -> Parser (Maybe [HeaderConf])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"headers"
Maybe RequestTransform
requestTransform <- Object
o Object -> Key -> Parser (Maybe RequestTransform)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"request_transform"
Maybe MetadataResponseTransform
responseTransform <- Object
o Object -> Key -> Parser (Maybe MetadataResponseTransform)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"response_transform"
Maybe AutoTriggerLogCleanupConfig
cleanupConfig <- Object
o Object -> Key -> Parser (Maybe AutoTriggerLogCleanupConfig)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"cleanup_config"
TriggerOnReplication
defTOR <- case forall (b :: BackendType).
Backend b =>
Maybe (XEventTriggers b, TriggerOnReplication)
defaultTriggerOnReplication @b of
Just (XEventTriggers b
_, TriggerOnReplication
dt) -> TriggerOnReplication -> Parser TriggerOnReplication
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TriggerOnReplication
dt
Maybe (XEventTriggers b, TriggerOnReplication)
Nothing -> String -> Parser TriggerOnReplication
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"No default setting for trigger_on_replication is defined for backend type."
TriggerOnReplication
triggerOnReplication <- Object
o Object -> Key -> Parser (Maybe TriggerOnReplication)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"trigger_on_replication" Parser (Maybe TriggerOnReplication)
-> TriggerOnReplication -> Parser TriggerOnReplication
forall a. Parser (Maybe a) -> a -> Parser a
.!= TriggerOnReplication
defTOR
EventTriggerConf b -> Parser (EventTriggerConf b)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (EventTriggerConf b -> Parser (EventTriggerConf b))
-> EventTriggerConf b -> Parser (EventTriggerConf b)
forall a b. (a -> b) -> a -> b
$ TriggerName
-> TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b
forall (b :: BackendType).
TriggerName
-> TriggerOpsDef b
-> Maybe InputWebhook
-> Maybe Text
-> RetryConf
-> Maybe [HeaderConf]
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe AutoTriggerLogCleanupConfig
-> TriggerOnReplication
-> EventTriggerConf b
EventTriggerConf TriggerName
name TriggerOpsDef b
definition Maybe InputWebhook
webhook Maybe Text
webhookFromEnv RetryConf
retryConf Maybe [HeaderConf]
headers Maybe RequestTransform
requestTransform Maybe MetadataResponseTransform
responseTransform Maybe AutoTriggerLogCleanupConfig
cleanupConfig TriggerOnReplication
triggerOnReplication
instance (Backend b) => ToJSON (EventTriggerConf b) where
toJSON :: EventTriggerConf b -> Value
toJSON (EventTriggerConf TriggerName
name TriggerOpsDef b
definition Maybe InputWebhook
webhook Maybe Text
webhookFromEnv RetryConf
retryConf Maybe [HeaderConf]
headers Maybe RequestTransform
requestTransform Maybe MetadataResponseTransform
responseTransform Maybe AutoTriggerLogCleanupConfig
cleanupConfig TriggerOnReplication
triggerOnReplication) =
[Pair] -> Value
object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"name" Key -> TriggerName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= TriggerName
name,
Key
"definition" Key -> TriggerOpsDef b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= TriggerOpsDef b
definition,
Key
"retry_conf" Key -> RetryConf -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= RetryConf
retryConf
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[ Key
"webhook" Key -> Maybe InputWebhook -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? Maybe InputWebhook
webhook,
Key
"webhook_from_env" Key -> Maybe Text -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? Maybe Text
webhookFromEnv,
Key
"headers" Key -> Maybe [HeaderConf] -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? Maybe [HeaderConf]
headers,
Key
"request_transform" Key -> Maybe RequestTransform -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? Maybe RequestTransform
requestTransform,
Key
"response_transform" Key -> Maybe MetadataResponseTransform -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? Maybe MetadataResponseTransform
responseTransform,
Key
"cleanup_config" Key -> Maybe AutoTriggerLogCleanupConfig -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? Maybe AutoTriggerLogCleanupConfig
cleanupConfig,
Key
"trigger_on_replication"
Key -> Maybe TriggerOnReplication -> Maybe Pair
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.=? case forall (b :: BackendType).
Backend b =>
Maybe (XEventTriggers b, TriggerOnReplication)
defaultTriggerOnReplication @b of
Just (XEventTriggers b
_, TriggerOnReplication
defTOR) -> if TriggerOnReplication
triggerOnReplication TriggerOnReplication -> TriggerOnReplication -> Bool
forall a. Eq a => a -> a -> Bool
== TriggerOnReplication
defTOR then Maybe TriggerOnReplication
forall a. Maybe a
Nothing else TriggerOnReplication -> Maybe TriggerOnReplication
forall a. a -> Maybe a
Just TriggerOnReplication
triggerOnReplication
Maybe (XEventTriggers b, TriggerOnReplication)
Nothing -> TriggerOnReplication -> Maybe TriggerOnReplication
forall a. a -> Maybe a
Just TriggerOnReplication
triggerOnReplication
]
updateCleanupConfig :: Maybe AutoTriggerLogCleanupConfig -> EventTriggerConf b -> EventTriggerConf b
updateCleanupConfig :: forall (b :: BackendType).
Maybe AutoTriggerLogCleanupConfig
-> EventTriggerConf b -> EventTriggerConf b
updateCleanupConfig Maybe AutoTriggerLogCleanupConfig
cleanupConfig EventTriggerConf b
etConf = EventTriggerConf b
etConf {etcCleanupConfig :: Maybe AutoTriggerLogCleanupConfig
etcCleanupConfig = Maybe AutoTriggerLogCleanupConfig
cleanupConfig}
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
$cshowsPrec :: Int -> RecreateEventTriggers -> ShowS
showsPrec :: Int -> RecreateEventTriggers -> ShowS
$cshow :: RecreateEventTriggers -> String
show :: RecreateEventTriggers -> String
$cshowList :: [RecreateEventTriggers] -> ShowS
showList :: [RecreateEventTriggers] -> ShowS
Show, RecreateEventTriggers -> RecreateEventTriggers -> Bool
(RecreateEventTriggers -> RecreateEventTriggers -> Bool)
-> (RecreateEventTriggers -> RecreateEventTriggers -> Bool)
-> Eq RecreateEventTriggers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
== :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
$c/= :: RecreateEventTriggers -> RecreateEventTriggers -> Bool
/= :: 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
$cfrom :: forall x. RecreateEventTriggers -> Rep RecreateEventTriggers x
from :: forall x. RecreateEventTriggers -> Rep RecreateEventTriggers x
$cto :: forall x. Rep RecreateEventTriggers x -> RecreateEventTriggers
to :: forall x. Rep RecreateEventTriggers x -> RecreateEventTriggers
Generic)
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
$cshowsPrec :: Int -> TriggerMetadata -> ShowS
showsPrec :: Int -> TriggerMetadata -> ShowS
$cshow :: TriggerMetadata -> String
show :: TriggerMetadata -> String
$cshowList :: [TriggerMetadata] -> ShowS
showList :: [TriggerMetadata] -> ShowS
Show, TriggerMetadata -> TriggerMetadata -> Bool
(TriggerMetadata -> TriggerMetadata -> Bool)
-> (TriggerMetadata -> TriggerMetadata -> Bool)
-> Eq TriggerMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TriggerMetadata -> TriggerMetadata -> Bool
== :: TriggerMetadata -> TriggerMetadata -> Bool
$c/= :: TriggerMetadata -> TriggerMetadata -> Bool
/= :: TriggerMetadata -> TriggerMetadata -> Bool
Eq, (forall x. TriggerMetadata -> Rep TriggerMetadata x)
-> (forall x. Rep TriggerMetadata x -> TriggerMetadata)
-> Generic TriggerMetadata
forall x. Rep TriggerMetadata x -> TriggerMetadata
forall x. TriggerMetadata -> Rep TriggerMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TriggerMetadata -> Rep TriggerMetadata x
from :: forall x. TriggerMetadata -> Rep TriggerMetadata x
$cto :: forall x. Rep TriggerMetadata x -> TriggerMetadata
to :: forall x. Rep TriggerMetadata x -> TriggerMetadata
Generic)
instance FromJSON TriggerMetadata where
parseJSON :: Value -> Parser TriggerMetadata
parseJSON = Options -> Value -> Parser TriggerMetadata
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance ToJSON TriggerMetadata where
toJSON :: TriggerMetadata -> Value
toJSON = Options -> TriggerMetadata -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
toEncoding :: TriggerMetadata -> Encoding
toEncoding = Options -> TriggerMetadata -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
data Event (b :: BackendType) = Event
{ forall (b :: BackendType). Event b -> EventId
eId :: EventId,
forall (b :: BackendType). Event b -> SourceName
eSource :: SourceName,
forall (b :: BackendType). Event b -> TableName b
eTable :: TableName b,
forall (b :: BackendType). Event b -> TriggerMetadata
eTrigger :: TriggerMetadata,
forall (b :: BackendType). Event b -> Value
eEvent :: Value,
forall (b :: BackendType). Event b -> Int
eTries :: Int,
forall (b :: BackendType). Event b -> LocalTime
eCreatedAt :: LocalTime,
forall (b :: BackendType). Event b -> Maybe UTCTime
eRetryAt :: Maybe Time.UTCTime,
forall (b :: BackendType). Event b -> UTCTime
eCreatedAtUTC :: Time.UTCTime,
forall (b :: BackendType). Event b -> Maybe UTCTime
eRetryAtUTC :: Maybe 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
$cfrom :: forall (b :: BackendType) x. Event b -> Rep (Event b) x
from :: forall x. Event b -> Rep (Event b) x
$cto :: forall (b :: BackendType) x. Rep (Event b) x -> Event b
to :: forall x. Rep (Event b) x -> Event b
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
{ forall (b :: BackendType). EventWithSource b -> Event b
_ewsEvent :: Event b,
forall (b :: BackendType). EventWithSource b -> SourceConfig b
_ewsSourceConfig :: SourceConfig b,
forall (b :: BackendType). EventWithSource b -> SourceName
_ewsSourceName :: SourceName,
forall (b :: BackendType). 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
$cshowsPrec :: Int -> ProcessEventError -> ShowS
showsPrec :: Int -> ProcessEventError -> ShowS
$cshow :: ProcessEventError -> String
show :: ProcessEventError -> String
$cshowList :: [ProcessEventError] -> ShowS
showList :: [ProcessEventError] -> ShowS
Show, ProcessEventError -> ProcessEventError -> Bool
(ProcessEventError -> ProcessEventError -> Bool)
-> (ProcessEventError -> ProcessEventError -> Bool)
-> Eq ProcessEventError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProcessEventError -> ProcessEventError -> Bool
== :: ProcessEventError -> ProcessEventError -> Bool
$c/= :: ProcessEventError -> ProcessEventError -> Bool
/= :: ProcessEventError -> ProcessEventError -> Bool
Eq)
data EventTriggerInfo (b :: BackendType) = EventTriggerInfo
{ forall (b :: BackendType). EventTriggerInfo b -> TriggerName
etiName :: TriggerName,
forall (b :: BackendType). EventTriggerInfo b -> TriggerOpsDef b
etiOpsDef :: TriggerOpsDef b,
forall (b :: BackendType). EventTriggerInfo b -> RetryConf
etiRetryConf :: RetryConf,
forall (b :: BackendType). EventTriggerInfo b -> WebhookConfInfo
etiWebhookInfo :: WebhookConfInfo,
:: [EventHeaderInfo],
forall (b :: BackendType).
EventTriggerInfo b -> Maybe RequestTransform
etiRequestTransform :: Maybe RequestTransform,
forall (b :: BackendType).
EventTriggerInfo b -> Maybe MetadataResponseTransform
etiResponseTransform :: Maybe MetadataResponseTransform,
forall (b :: BackendType).
EventTriggerInfo b -> Maybe AutoTriggerLogCleanupConfig
etiCleanupConfig :: Maybe AutoTriggerLogCleanupConfig,
forall (b :: BackendType).
EventTriggerInfo b -> TriggerOnReplication
etiTriggerOnReplication :: TriggerOnReplication
}
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
$cfrom :: forall (b :: BackendType) x.
EventTriggerInfo b -> Rep (EventTriggerInfo b) x
from :: forall x. EventTriggerInfo b -> Rep (EventTriggerInfo b) x
$cto :: forall (b :: BackendType) x.
Rep (EventTriggerInfo b) x -> EventTriggerInfo b
to :: forall x. Rep (EventTriggerInfo b) x -> EventTriggerInfo b
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
$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
/= :: 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 = HashMap.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
$cshowsPrec :: Int -> FetchBatchSize -> ShowS
showsPrec :: Int -> FetchBatchSize -> ShowS
$cshow :: FetchBatchSize -> String
show :: FetchBatchSize -> String
$cshowList :: [FetchBatchSize] -> ShowS
showList :: [FetchBatchSize] -> ShowS
Show, FetchBatchSize -> FetchBatchSize -> Bool
(FetchBatchSize -> FetchBatchSize -> Bool)
-> (FetchBatchSize -> FetchBatchSize -> Bool) -> Eq FetchBatchSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FetchBatchSize -> FetchBatchSize -> Bool
== :: FetchBatchSize -> FetchBatchSize -> Bool
$c/= :: FetchBatchSize -> FetchBatchSize -> Bool
/= :: FetchBatchSize -> FetchBatchSize -> Bool
Eq)
data DeletedEventLogStats = DeletedEventLogStats
{ DeletedEventLogStats -> Int
deletedEventLogs :: Int,
DeletedEventLogStats -> Int
deletedInvocationLogs :: Int
}
deriving (Int -> DeletedEventLogStats -> ShowS
[DeletedEventLogStats] -> ShowS
DeletedEventLogStats -> String
(Int -> DeletedEventLogStats -> ShowS)
-> (DeletedEventLogStats -> String)
-> ([DeletedEventLogStats] -> ShowS)
-> Show DeletedEventLogStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeletedEventLogStats -> ShowS
showsPrec :: Int -> DeletedEventLogStats -> ShowS
$cshow :: DeletedEventLogStats -> String
show :: DeletedEventLogStats -> String
$cshowList :: [DeletedEventLogStats] -> ShowS
showList :: [DeletedEventLogStats] -> ShowS
Show, DeletedEventLogStats -> DeletedEventLogStats -> Bool
(DeletedEventLogStats -> DeletedEventLogStats -> Bool)
-> (DeletedEventLogStats -> DeletedEventLogStats -> Bool)
-> Eq DeletedEventLogStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeletedEventLogStats -> DeletedEventLogStats -> Bool
== :: DeletedEventLogStats -> DeletedEventLogStats -> Bool
$c/= :: DeletedEventLogStats -> DeletedEventLogStats -> Bool
/= :: DeletedEventLogStats -> DeletedEventLogStats -> Bool
Eq)
data EventLogStatus
= Processed
| Pending
| All
deriving (Int -> EventLogStatus -> ShowS
[EventLogStatus] -> ShowS
EventLogStatus -> String
(Int -> EventLogStatus -> ShowS)
-> (EventLogStatus -> String)
-> ([EventLogStatus] -> ShowS)
-> Show EventLogStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventLogStatus -> ShowS
showsPrec :: Int -> EventLogStatus -> ShowS
$cshow :: EventLogStatus -> String
show :: EventLogStatus -> String
$cshowList :: [EventLogStatus] -> ShowS
showList :: [EventLogStatus] -> ShowS
Show, EventLogStatus -> EventLogStatus -> Bool
(EventLogStatus -> EventLogStatus -> Bool)
-> (EventLogStatus -> EventLogStatus -> Bool) -> Eq EventLogStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventLogStatus -> EventLogStatus -> Bool
== :: EventLogStatus -> EventLogStatus -> Bool
$c/= :: EventLogStatus -> EventLogStatus -> Bool
/= :: EventLogStatus -> EventLogStatus -> Bool
Eq)
instance ToJSON EventLogStatus where
toJSON :: EventLogStatus -> Value
toJSON EventLogStatus
Processed = Text -> Value
String Text
"processed"
toJSON EventLogStatus
Pending = Text -> Value
String Text
"pending"
toJSON EventLogStatus
All = Text -> Value
String Text
"all"
instance FromJSON EventLogStatus where
parseJSON :: Value -> Parser EventLogStatus
parseJSON (String Text
"processed") = EventLogStatus -> Parser EventLogStatus
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EventLogStatus
Processed
parseJSON (String Text
"pending") = EventLogStatus -> Parser EventLogStatus
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EventLogStatus
Pending
parseJSON Value
_ = String -> Parser EventLogStatus
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"event logs status can only be one of the following: processed or pending"
data GetEventLogs (b :: BackendType) = GetEventLogs
{ forall (b :: BackendType). GetEventLogs b -> TriggerName
_gelName :: TriggerName,
forall (b :: BackendType). GetEventLogs b -> SourceName
_gelSourceName :: SourceName,
forall (b :: BackendType). GetEventLogs b -> Int
_gelLimit :: Int,
forall (b :: BackendType). GetEventLogs b -> Int
_gelOffset :: Int,
forall (b :: BackendType). GetEventLogs b -> EventLogStatus
_gelStatus :: EventLogStatus
}
deriving (Int -> GetEventLogs b -> ShowS
[GetEventLogs b] -> ShowS
GetEventLogs b -> String
(Int -> GetEventLogs b -> ShowS)
-> (GetEventLogs b -> String)
-> ([GetEventLogs b] -> ShowS)
-> Show (GetEventLogs b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Int -> GetEventLogs b -> ShowS
forall (b :: BackendType). [GetEventLogs b] -> ShowS
forall (b :: BackendType). GetEventLogs b -> String
$cshowsPrec :: forall (b :: BackendType). Int -> GetEventLogs b -> ShowS
showsPrec :: Int -> GetEventLogs b -> ShowS
$cshow :: forall (b :: BackendType). GetEventLogs b -> String
show :: GetEventLogs b -> String
$cshowList :: forall (b :: BackendType). [GetEventLogs b] -> ShowS
showList :: [GetEventLogs b] -> ShowS
Show)
instance ToJSON (GetEventLogs b) where
toJSON :: GetEventLogs b -> Value
toJSON GetEventLogs {Int
SourceName
EventLogStatus
TriggerName
_gelName :: forall (b :: BackendType). GetEventLogs b -> TriggerName
_gelSourceName :: forall (b :: BackendType). GetEventLogs b -> SourceName
_gelLimit :: forall (b :: BackendType). GetEventLogs b -> Int
_gelOffset :: forall (b :: BackendType). GetEventLogs b -> Int
_gelStatus :: forall (b :: BackendType). GetEventLogs b -> EventLogStatus
_gelName :: TriggerName
_gelSourceName :: SourceName
_gelLimit :: Int
_gelOffset :: Int
_gelStatus :: EventLogStatus
..} =
[Pair] -> Value
object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"name" Key -> TriggerName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= TriggerName
_gelName,
Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
_gelSourceName,
Key
"limit" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
_gelLimit,
Key
"offset" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
_gelOffset,
Key
"status" Key -> EventLogStatus -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= EventLogStatus
_gelStatus
]
instance FromJSON (GetEventLogs b) where
parseJSON :: Value -> Parser (GetEventLogs b)
parseJSON = String
-> (Object -> Parser (GetEventLogs b))
-> Value
-> Parser (GetEventLogs b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetEventLogs" ((Object -> Parser (GetEventLogs b))
-> Value -> Parser (GetEventLogs b))
-> (Object -> Parser (GetEventLogs b))
-> Value
-> Parser (GetEventLogs b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
TriggerName
-> SourceName -> Int -> Int -> EventLogStatus -> GetEventLogs b
forall (b :: BackendType).
TriggerName
-> SourceName -> Int -> Int -> EventLogStatus -> GetEventLogs b
GetEventLogs
(TriggerName
-> SourceName -> Int -> Int -> EventLogStatus -> GetEventLogs b)
-> Parser TriggerName
-> Parser
(SourceName -> Int -> Int -> EventLogStatus -> GetEventLogs b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser TriggerName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser
(SourceName -> Int -> Int -> EventLogStatus -> GetEventLogs b)
-> Parser SourceName
-> Parser (Int -> Int -> EventLogStatus -> GetEventLogs b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source"
Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
SNDefault
Parser (Int -> Int -> EventLogStatus -> GetEventLogs b)
-> Parser Int -> Parser (Int -> EventLogStatus -> GetEventLogs b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"limit"
Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
100
Parser (Int -> EventLogStatus -> GetEventLogs b)
-> Parser Int -> Parser (EventLogStatus -> GetEventLogs b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"offset"
Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
Parser (EventLogStatus -> GetEventLogs b)
-> Parser EventLogStatus -> Parser (GetEventLogs b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe EventLogStatus)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"status"
Parser (Maybe EventLogStatus)
-> EventLogStatus -> Parser EventLogStatus
forall a. Parser (Maybe a) -> a -> Parser a
.!= EventLogStatus
All
data EventLog = EventLog
{ EventLog -> EventId
elId :: EventId,
EventLog -> Text
elSchemaName :: Text,
EventLog -> Text
elTableName :: Text,
EventLog -> TriggerName
elTriggerName :: TriggerName,
EventLog -> Value
elPayload :: Value,
EventLog -> Bool
elDelivered :: Bool,
EventLog -> Bool
elError :: Bool,
EventLog -> Int
elTries :: Int,
EventLog -> UTCTime
elCreatedAt :: Time.UTCTime,
EventLog -> Maybe UTCTime
elLocked :: Maybe Time.UTCTime,
EventLog -> Maybe UTCTime
elNextRetryAt :: Maybe Time.UTCTime,
EventLog -> Bool
elArchived :: Bool
}
deriving (EventLog -> EventLog -> Bool
(EventLog -> EventLog -> Bool)
-> (EventLog -> EventLog -> Bool) -> Eq EventLog
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventLog -> EventLog -> Bool
== :: EventLog -> EventLog -> Bool
$c/= :: EventLog -> EventLog -> Bool
/= :: EventLog -> EventLog -> Bool
Eq, (forall x. EventLog -> Rep EventLog x)
-> (forall x. Rep EventLog x -> EventLog) -> Generic EventLog
forall x. Rep EventLog x -> EventLog
forall x. EventLog -> Rep EventLog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventLog -> Rep EventLog x
from :: forall x. EventLog -> Rep EventLog x
$cto :: forall x. Rep EventLog x -> EventLog
to :: forall x. Rep EventLog x -> EventLog
Generic)
instance ToJSON EventLog where
toJSON :: EventLog -> Value
toJSON = Options -> EventLog -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
toEncoding :: EventLog -> Encoding
toEncoding = Options -> EventLog -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON
data GetEventInvocations (b :: BackendType) = GetEventInvocations
{ forall (b :: BackendType). GetEventInvocations b -> TriggerName
_geiName :: TriggerName,
forall (b :: BackendType). GetEventInvocations b -> SourceName
_geiSourceName :: SourceName,
forall (b :: BackendType). GetEventInvocations b -> Int
_geiLimit :: Int,
forall (b :: BackendType). GetEventInvocations b -> Int
_geiOffset :: Int
}
deriving (Int -> GetEventInvocations b -> ShowS
[GetEventInvocations b] -> ShowS
GetEventInvocations b -> String
(Int -> GetEventInvocations b -> ShowS)
-> (GetEventInvocations b -> String)
-> ([GetEventInvocations b] -> ShowS)
-> Show (GetEventInvocations b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Int -> GetEventInvocations b -> ShowS
forall (b :: BackendType). [GetEventInvocations b] -> ShowS
forall (b :: BackendType). GetEventInvocations b -> String
$cshowsPrec :: forall (b :: BackendType). Int -> GetEventInvocations b -> ShowS
showsPrec :: Int -> GetEventInvocations b -> ShowS
$cshow :: forall (b :: BackendType). GetEventInvocations b -> String
show :: GetEventInvocations b -> String
$cshowList :: forall (b :: BackendType). [GetEventInvocations b] -> ShowS
showList :: [GetEventInvocations b] -> ShowS
Show)
instance ToJSON (GetEventInvocations b) where
toJSON :: GetEventInvocations b -> Value
toJSON GetEventInvocations {Int
SourceName
TriggerName
_geiName :: forall (b :: BackendType). GetEventInvocations b -> TriggerName
_geiSourceName :: forall (b :: BackendType). GetEventInvocations b -> SourceName
_geiLimit :: forall (b :: BackendType). GetEventInvocations b -> Int
_geiOffset :: forall (b :: BackendType). GetEventInvocations b -> Int
_geiName :: TriggerName
_geiSourceName :: SourceName
_geiLimit :: Int
_geiOffset :: Int
..} =
[Pair] -> Value
object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"name" Key -> TriggerName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= TriggerName
_geiName,
Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
_geiSourceName,
Key
"limit" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
_geiLimit,
Key
"offset" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
_geiOffset
]
instance FromJSON (GetEventInvocations b) where
parseJSON :: Value -> Parser (GetEventInvocations b)
parseJSON = String
-> (Object -> Parser (GetEventInvocations b))
-> Value
-> Parser (GetEventInvocations b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetEventInvocations" ((Object -> Parser (GetEventInvocations b))
-> Value -> Parser (GetEventInvocations b))
-> (Object -> Parser (GetEventInvocations b))
-> Value
-> Parser (GetEventInvocations b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
TriggerName -> SourceName -> Int -> Int -> GetEventInvocations b
forall (b :: BackendType).
TriggerName -> SourceName -> Int -> Int -> GetEventInvocations b
GetEventInvocations
(TriggerName -> SourceName -> Int -> Int -> GetEventInvocations b)
-> Parser TriggerName
-> Parser (SourceName -> Int -> Int -> GetEventInvocations b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser TriggerName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (SourceName -> Int -> Int -> GetEventInvocations b)
-> Parser SourceName
-> Parser (Int -> Int -> GetEventInvocations b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source"
Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
SNDefault
Parser (Int -> Int -> GetEventInvocations b)
-> Parser Int -> Parser (Int -> GetEventInvocations b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"limit"
Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
100
Parser (Int -> GetEventInvocations b)
-> Parser Int -> Parser (GetEventInvocations b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"offset"
Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
data EventInvocationLog = EventInvocationLog
{ EventInvocationLog -> Text
eilId :: Text,
EventInvocationLog -> TriggerName
eilTriggerName :: TriggerName,
EventInvocationLog -> EventId
eilEventId :: EventId,
EventInvocationLog -> Maybe Int
eilHttpStatus :: Maybe Int,
EventInvocationLog -> Value
eilRequest :: Value,
EventInvocationLog -> Value
eilResponse :: Value,
EventInvocationLog -> UTCTime
eilCreatedAt :: Time.UTCTime
}
deriving ((forall x. EventInvocationLog -> Rep EventInvocationLog x)
-> (forall x. Rep EventInvocationLog x -> EventInvocationLog)
-> Generic EventInvocationLog
forall x. Rep EventInvocationLog x -> EventInvocationLog
forall x. EventInvocationLog -> Rep EventInvocationLog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventInvocationLog -> Rep EventInvocationLog x
from :: forall x. EventInvocationLog -> Rep EventInvocationLog x
$cto :: forall x. Rep EventInvocationLog x -> EventInvocationLog
to :: forall x. Rep EventInvocationLog x -> EventInvocationLog
Generic)
instance ToJSON EventInvocationLog where
toJSON :: EventInvocationLog -> Value
toJSON = Options -> EventInvocationLog -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
toEncoding :: EventInvocationLog -> Encoding
toEncoding = Options -> EventInvocationLog -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON
data GetEventById (b :: BackendType) = GetEventById
{ forall (b :: BackendType). GetEventById b -> SourceName
_gebiSourceName :: SourceName,
forall (b :: BackendType). GetEventById b -> EventId
_gebiEventId :: EventId,
forall (b :: BackendType). GetEventById b -> Int
_gebiInvocationLogLimit :: Int,
forall (b :: BackendType). GetEventById b -> Int
_gebiInvocationLogOffset :: Int
}
deriving (Int -> GetEventById b -> ShowS
[GetEventById b] -> ShowS
GetEventById b -> String
(Int -> GetEventById b -> ShowS)
-> (GetEventById b -> String)
-> ([GetEventById b] -> ShowS)
-> Show (GetEventById b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Int -> GetEventById b -> ShowS
forall (b :: BackendType). [GetEventById b] -> ShowS
forall (b :: BackendType). GetEventById b -> String
$cshowsPrec :: forall (b :: BackendType). Int -> GetEventById b -> ShowS
showsPrec :: Int -> GetEventById b -> ShowS
$cshow :: forall (b :: BackendType). GetEventById b -> String
show :: GetEventById b -> String
$cshowList :: forall (b :: BackendType). [GetEventById b] -> ShowS
showList :: [GetEventById b] -> ShowS
Show)
instance ToJSON (GetEventById b) where
toJSON :: GetEventById b -> Value
toJSON GetEventById {Int
EventId
SourceName
_gebiSourceName :: forall (b :: BackendType). GetEventById b -> SourceName
_gebiEventId :: forall (b :: BackendType). GetEventById b -> EventId
_gebiInvocationLogLimit :: forall (b :: BackendType). GetEventById b -> Int
_gebiInvocationLogOffset :: forall (b :: BackendType). GetEventById b -> Int
_gebiSourceName :: SourceName
_gebiEventId :: EventId
_gebiInvocationLogLimit :: Int
_gebiInvocationLogOffset :: Int
..} =
[Pair] -> Value
object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
_gebiSourceName,
Key
"event_id" Key -> EventId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= EventId
_gebiEventId,
Key
"invocation_log_limit" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
_gebiInvocationLogLimit,
Key
"invocation_log_offset" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
_gebiInvocationLogOffset
]
instance FromJSON (GetEventById b) where
parseJSON :: Value -> Parser (GetEventById b)
parseJSON = String
-> (Object -> Parser (GetEventById b))
-> Value
-> Parser (GetEventById b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetEventById" ((Object -> Parser (GetEventById b))
-> Value -> Parser (GetEventById b))
-> (Object -> Parser (GetEventById b))
-> Value
-> Parser (GetEventById b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
SourceName -> EventId -> Int -> Int -> GetEventById b
forall (b :: BackendType).
SourceName -> EventId -> Int -> Int -> GetEventById b
GetEventById
(SourceName -> EventId -> Int -> Int -> GetEventById b)
-> Parser SourceName
-> Parser (EventId -> Int -> Int -> GetEventById b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source"
Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
SNDefault
Parser (EventId -> Int -> Int -> GetEventById b)
-> Parser EventId -> Parser (Int -> Int -> GetEventById b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser EventId
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"event_id"
Parser (Int -> Int -> GetEventById b)
-> Parser Int -> Parser (Int -> GetEventById b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"invocation_log_limit"
Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
100
Parser (Int -> GetEventById b)
-> Parser Int -> Parser (GetEventById b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"invocation_log_offset"
Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
0
data EventLogWithInvocations = EventLogWithInvocations
{ EventLogWithInvocations -> Maybe EventLog
elwiEvent :: Maybe EventLog,
EventLogWithInvocations -> [EventInvocationLog]
elwiInvocations :: [EventInvocationLog]
}
deriving ((forall x.
EventLogWithInvocations -> Rep EventLogWithInvocations x)
-> (forall x.
Rep EventLogWithInvocations x -> EventLogWithInvocations)
-> Generic EventLogWithInvocations
forall x. Rep EventLogWithInvocations x -> EventLogWithInvocations
forall x. EventLogWithInvocations -> Rep EventLogWithInvocations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventLogWithInvocations -> Rep EventLogWithInvocations x
from :: forall x. EventLogWithInvocations -> Rep EventLogWithInvocations x
$cto :: forall x. Rep EventLogWithInvocations x -> EventLogWithInvocations
to :: forall x. Rep EventLogWithInvocations x -> EventLogWithInvocations
Generic)
instance ToJSON EventLogWithInvocations where
toJSON :: EventLogWithInvocations -> Value
toJSON = Options -> EventLogWithInvocations -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
toEncoding :: EventLogWithInvocations -> Encoding
toEncoding = Options -> EventLogWithInvocations -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
hasuraJSON