2022-03-16 03:39:21 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
2019-03-25 20:10:52 +03:00
|
|
|
module Hasura.RQL.DDL.EventTrigger
|
2021-09-24 01:56:37 +03:00
|
|
|
( CreateEventTriggerQuery,
|
|
|
|
runCreateEventTriggerQuery,
|
|
|
|
DeleteEventTriggerQuery,
|
|
|
|
runDeleteEventTriggerQuery,
|
|
|
|
dropEventTriggerInMetadata,
|
|
|
|
RedeliverEventQuery,
|
|
|
|
runRedeliverEvent,
|
|
|
|
InvokeEventTriggerQuery,
|
|
|
|
runInvokeEventTrigger,
|
|
|
|
-- TODO(from master): review
|
|
|
|
getHeaderInfosFromConf,
|
|
|
|
getWebhookInfoFromConf,
|
|
|
|
buildEventTriggerInfo,
|
2022-04-11 14:24:11 +03:00
|
|
|
getTriggerNames,
|
|
|
|
getTriggersMap,
|
2022-04-21 10:19:37 +03:00
|
|
|
getTableNameFromTrigger,
|
2022-09-09 11:26:44 +03:00
|
|
|
getTabInfoFromSchemaCache,
|
2022-03-11 02:22:54 +03:00
|
|
|
cetqSource,
|
|
|
|
cetqName,
|
|
|
|
cetqTable,
|
|
|
|
cetqInsert,
|
|
|
|
cetqUpdate,
|
|
|
|
cetqDelete,
|
|
|
|
cetqEnableManual,
|
|
|
|
cetqRetryConf,
|
|
|
|
cetqWebhook,
|
|
|
|
cetqWebhookFromEnv,
|
|
|
|
cetqHeaders,
|
|
|
|
cetqReplace,
|
|
|
|
cetqRequestTransform,
|
|
|
|
cetqResponseTrasnform,
|
2022-09-09 11:26:44 +03:00
|
|
|
cteqCleanupConfig,
|
|
|
|
runCleanupEventTriggerLog,
|
2022-09-13 11:33:44 +03:00
|
|
|
runEventTriggerStartCleanup,
|
|
|
|
runEventTriggerPauseCleanup,
|
2022-09-09 11:26:44 +03:00
|
|
|
MonadEventLogCleanup (..),
|
2022-09-13 11:33:44 +03:00
|
|
|
getAllEventTriggersWithCleanupConfig,
|
2021-09-24 01:56:37 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2022-09-13 11:33:44 +03:00
|
|
|
import Control.Lens (ifor_, makeLenses, (.~))
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Aeson
|
|
|
|
import Data.ByteString.Lazy qualified as LBS
|
|
|
|
import Data.Environment qualified as Env
|
|
|
|
import Data.HashMap.Strict qualified as HM
|
2022-09-13 11:33:44 +03:00
|
|
|
import Data.HashMap.Strict qualified as Map
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
2022-03-15 11:41:03 +03:00
|
|
|
import Data.HashSet qualified as Set
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Text qualified as T
|
|
|
|
import Data.Text.Extended
|
2022-06-05 23:27:09 +03:00
|
|
|
import Data.URL.Template (printURLTemplate)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.EncJSON
|
2022-09-09 11:26:44 +03:00
|
|
|
import Hasura.Metadata.Class (MetadataStorageT)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.Headers
|
2022-03-08 03:42:06 +03:00
|
|
|
import Hasura.RQL.DDL.Webhook.Transform (MetadataResponseTransform, RequestTransform)
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
import Hasura.RQL.Types.EventTrigger
|
|
|
|
import Hasura.RQL.Types.Eventing
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.RQL.Types.Eventing.Backend
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Metadata
|
|
|
|
import Hasura.RQL.Types.Metadata.Backend
|
|
|
|
import Hasura.RQL.Types.Metadata.Object
|
|
|
|
import Hasura.RQL.Types.SchemaCache
|
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
import Hasura.RQL.Types.SchemaCacheTypes
|
|
|
|
import Hasura.RQL.Types.Source
|
|
|
|
import Hasura.RQL.Types.Table
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.SQL.Backend
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Session
|
2022-09-09 11:26:44 +03:00
|
|
|
import Hasura.Tracing (TraceT)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.Tracing qualified as Tracing
|
|
|
|
import Text.Regex.TDFA qualified as TDFA
|
|
|
|
|
|
|
|
data CreateEventTriggerQuery (b :: BackendType) = CreateEventTriggerQuery
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _cetqSource :: SourceName,
|
|
|
|
_cetqName :: TriggerName,
|
|
|
|
_cetqTable :: TableName b,
|
|
|
|
_cetqInsert :: Maybe (SubscribeOpSpec b),
|
|
|
|
_cetqUpdate :: Maybe (SubscribeOpSpec b),
|
|
|
|
_cetqDelete :: Maybe (SubscribeOpSpec b),
|
|
|
|
_cetqEnableManual :: Maybe Bool,
|
|
|
|
_cetqRetryConf :: Maybe RetryConf,
|
|
|
|
_cetqWebhook :: Maybe InputWebhook,
|
|
|
|
_cetqWebhookFromEnv :: Maybe Text,
|
|
|
|
_cetqHeaders :: Maybe [HeaderConf],
|
|
|
|
_cetqReplace :: Bool,
|
|
|
|
_cetqRequestTransform :: Maybe RequestTransform,
|
2022-09-09 11:26:44 +03:00
|
|
|
_cetqResponseTrasnform :: Maybe MetadataResponseTransform,
|
|
|
|
_cteqCleanupConfig :: Maybe AutoTriggerLogCleanupConfig
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
|
|
|
|
2022-03-11 02:22:54 +03:00
|
|
|
$(makeLenses ''CreateEventTriggerQuery)
|
|
|
|
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
instance Backend b => FromJSON (CreateEventTriggerQuery b) where
|
2021-09-24 01:56:37 +03:00
|
|
|
parseJSON = withObject "CreateEventTriggerQuery" \o -> do
|
|
|
|
sourceName <- o .:? "source" .!= defaultSource
|
|
|
|
name <- o .: "name"
|
|
|
|
table <- o .: "table"
|
|
|
|
insert <- o .:? "insert"
|
|
|
|
update <- o .:? "update"
|
|
|
|
delete <- o .:? "delete"
|
|
|
|
enableManual <- o .:? "enable_manual" .!= False
|
|
|
|
retryConf <- o .:? "retry_conf"
|
|
|
|
webhook <- o .:? "webhook"
|
|
|
|
webhookFromEnv <- o .:? "webhook_from_env"
|
|
|
|
headers <- o .:? "headers"
|
|
|
|
replace <- o .:? "replace" .!= False
|
2021-09-29 11:13:30 +03:00
|
|
|
requestTransform <- o .:? "request_transform"
|
2022-01-19 07:46:42 +03:00
|
|
|
responseTransform <- o .:? "response_transform"
|
2022-09-09 11:26:44 +03:00
|
|
|
cleanupConfig <- o .:? "cleanup_config"
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
let regex = "^[A-Za-z]+[A-Za-z0-9_\\-]*$" :: LBS.ByteString
|
|
|
|
compiledRegex = TDFA.makeRegex regex :: TDFA.Regex
|
|
|
|
isMatch = TDFA.match compiledRegex . T.unpack $ triggerNameToTxt name
|
|
|
|
unless isMatch $
|
|
|
|
fail "only alphanumeric and underscore and hyphens allowed for name"
|
|
|
|
unless (T.length (triggerNameToTxt name) <= maxTriggerNameLength) $
|
|
|
|
fail "event trigger name can be at most 42 characters"
|
|
|
|
unless (any isJust [insert, update, delete] || enableManual) $
|
|
|
|
fail "atleast one amongst insert/update/delete/enable_manual spec must be provided"
|
|
|
|
case (webhook, webhookFromEnv) of
|
|
|
|
(Just _, Nothing) -> return ()
|
|
|
|
(Nothing, Just _) -> return ()
|
2021-09-24 01:56:37 +03:00
|
|
|
(Just _, Just _) -> fail "only one of webhook or webhook_from_env should be given"
|
|
|
|
_ -> fail "must provide webhook or webhook_from_env"
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
mapM_ checkEmptyCols [insert, update, delete]
|
2022-09-09 11:26:44 +03:00
|
|
|
return $ CreateEventTriggerQuery sourceName name table insert update delete (Just enableManual) retryConf webhook webhookFromEnv headers replace requestTransform responseTransform cleanupConfig
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
checkEmptyCols spec =
|
|
|
|
case spec of
|
|
|
|
Just (SubscribeOpSpec (SubCArray cols) _) -> when (null cols) (fail "found empty column specification")
|
|
|
|
Just (SubscribeOpSpec _ (Just (SubCArray cols))) -> when (null cols) (fail "found empty payload specification")
|
|
|
|
_ -> return ()
|
|
|
|
|
|
|
|
data DeleteEventTriggerQuery (b :: BackendType) = DeleteEventTriggerQuery
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _detqSource :: SourceName,
|
|
|
|
_detqName :: TriggerName
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
instance FromJSON (DeleteEventTriggerQuery b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "DeleteEventTriggerQuery" $ \o ->
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
DeleteEventTriggerQuery
|
|
|
|
<$> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "name"
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data RedeliverEventQuery (b :: BackendType) = RedeliverEventQuery
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _rdeqEventId :: EventId,
|
|
|
|
_rdeqSource :: SourceName
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
instance FromJSON (RedeliverEventQuery b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "RedeliverEventQuery" $ \o ->
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
RedeliverEventQuery
|
|
|
|
<$> o .: "event_id"
|
|
|
|
<*> o .:? "source" .!= defaultSource
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
data InvokeEventTriggerQuery (b :: BackendType) = InvokeEventTriggerQuery
|
2022-08-01 12:32:04 +03:00
|
|
|
{ _ietqName :: TriggerName,
|
|
|
|
_ietqSource :: SourceName,
|
|
|
|
_ietqPayload :: Value
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
instance Backend b => FromJSON (InvokeEventTriggerQuery b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "InvokeEventTriggerQuery" $ \o ->
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
InvokeEventTriggerQuery
|
|
|
|
<$> o .: "name"
|
|
|
|
<*> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "payload"
|
|
|
|
|
2022-09-09 11:26:44 +03:00
|
|
|
-- | This typeclass have the implementation logic for the event trigger log cleanup
|
|
|
|
class Monad m => MonadEventLogCleanup m where
|
|
|
|
runLogCleaner ::
|
|
|
|
TriggerLogCleanupConfig -> m (Either QErr EncJSON)
|
|
|
|
|
|
|
|
instance (MonadEventLogCleanup m) => MonadEventLogCleanup (ReaderT r m) where
|
|
|
|
runLogCleaner conf = lift $ runLogCleaner conf
|
|
|
|
|
|
|
|
instance (MonadEventLogCleanup m) => MonadEventLogCleanup (MetadataT m) where
|
|
|
|
runLogCleaner conf = lift $ runLogCleaner conf
|
|
|
|
|
|
|
|
instance (MonadEventLogCleanup m) => MonadEventLogCleanup (MetadataStorageT m) where
|
|
|
|
runLogCleaner conf = lift $ runLogCleaner conf
|
|
|
|
|
|
|
|
instance (MonadEventLogCleanup m) => MonadEventLogCleanup (TraceT m) where
|
|
|
|
runLogCleaner conf = lift $ runLogCleaner conf
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
resolveEventTriggerQuery ::
|
|
|
|
forall b m.
|
|
|
|
(Backend b, UserInfoM m, QErrM m, CacheRM m) =>
|
|
|
|
CreateEventTriggerQuery b ->
|
2022-03-15 11:41:03 +03:00
|
|
|
m (Bool, EventTriggerConf b)
|
2022-09-09 11:26:44 +03:00
|
|
|
resolveEventTriggerQuery (CreateEventTriggerQuery source name qt insert update delete enableManual retryConf webhook webhookFromEnv mheaders replace reqTransform respTransform cleanupConfig) = do
|
2020-12-28 15:56:00 +03:00
|
|
|
ti <- askTableCoreInfo source qt
|
2018-09-19 15:12:57 +03:00
|
|
|
-- can only replace for same table
|
|
|
|
when replace $ do
|
2021-09-06 14:15:36 +03:00
|
|
|
ti' <- _tiCoreInfo <$> askTabInfoFromTrigger @b source name
|
2019-11-20 21:21:30 +03:00
|
|
|
when (_tciName ti' /= _tciName ti) $ throw400 NotSupported "cannot replace table or schema for trigger"
|
2018-09-19 15:12:57 +03:00
|
|
|
|
2018-09-05 14:26:46 +03:00
|
|
|
assertCols ti insert
|
|
|
|
assertCols ti update
|
|
|
|
assertCols ti delete
|
2018-09-19 15:12:57 +03:00
|
|
|
|
2019-02-14 10:37:59 +03:00
|
|
|
let rconf = fromMaybe defaultRetryConf retryConf
|
2022-09-09 11:26:44 +03:00
|
|
|
return (replace, EventTriggerConf name (TriggerOpsDef insert update delete enableManual) webhook webhookFromEnv rconf mheaders reqTransform respTransform cleanupConfig)
|
2018-09-05 14:26:46 +03:00
|
|
|
where
|
2021-09-20 10:34:59 +03:00
|
|
|
assertCols :: TableCoreInfo b -> Maybe (SubscribeOpSpec b) -> m ()
|
2021-01-20 03:31:53 +03:00
|
|
|
assertCols ti opSpec = onJust opSpec \sos -> case sosColumns sos of
|
2021-09-24 01:56:37 +03:00
|
|
|
SubCStar -> return ()
|
2021-09-09 14:54:19 +03:00
|
|
|
SubCArray columns -> forM_ columns (assertColumnExists @b (_tciFieldInfoMap ti) "")
|
2018-11-23 16:02:46 +03:00
|
|
|
|
2022-03-15 11:41:03 +03:00
|
|
|
droppedTriggerOps :: TriggerOpsDef b -> TriggerOpsDef b -> HashSet Ops
|
|
|
|
droppedTriggerOps oldEventTriggerOps newEventTriggerOps =
|
|
|
|
Set.fromList $
|
|
|
|
catMaybes $
|
|
|
|
[ (bool Nothing (Just INSERT) (isDroppedOp (tdInsert oldEventTriggerOps) (tdInsert newEventTriggerOps))),
|
|
|
|
(bool Nothing (Just UPDATE) (isDroppedOp (tdUpdate oldEventTriggerOps) (tdUpdate newEventTriggerOps))),
|
|
|
|
(bool Nothing (Just DELETE) (isDroppedOp (tdDelete oldEventTriggerOps) (tdDelete newEventTriggerOps)))
|
|
|
|
]
|
|
|
|
where
|
|
|
|
isDroppedOp old new = isJust old && isNothing new
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
createEventTriggerQueryMetadata ::
|
|
|
|
forall b m.
|
2022-03-15 11:41:03 +03:00
|
|
|
(BackendMetadata b, QErrM m, UserInfoM m, CacheRWM m, MetadataM m, BackendEventTrigger b, MonadIO m) =>
|
2021-09-24 01:56:37 +03:00
|
|
|
CreateEventTriggerQuery b ->
|
2022-03-15 11:41:03 +03:00
|
|
|
m ()
|
2020-12-28 15:56:00 +03:00
|
|
|
createEventTriggerQueryMetadata q = do
|
2022-03-15 11:41:03 +03:00
|
|
|
(replace, triggerConf) <- resolveEventTriggerQuery q
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
let table = _cetqTable q
|
|
|
|
source = _cetqSource q
|
2020-12-28 15:56:00 +03:00
|
|
|
triggerName = etcName triggerConf
|
2021-03-15 16:02:58 +03:00
|
|
|
metadataObj =
|
2021-09-24 01:56:37 +03:00
|
|
|
MOSourceObjId source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b table $
|
|
|
|
MTOTrigger triggerName
|
2022-03-15 11:41:03 +03:00
|
|
|
sourceInfo <- askSourceInfo @b source
|
2022-08-23 11:49:51 +03:00
|
|
|
let sourceConfig = (_siConfiguration sourceInfo)
|
|
|
|
|
|
|
|
-- Check for existence of a trigger with 'triggerName' only when 'replace' is not set
|
|
|
|
if replace
|
|
|
|
then do
|
|
|
|
existingEventTriggerOps <- etiOpsDef <$> askEventTriggerInfo @b source triggerName
|
|
|
|
let droppedOps = droppedTriggerOps existingEventTriggerOps (etcDefinition triggerConf)
|
|
|
|
dropDanglingSQLTrigger @b (_siConfiguration sourceInfo) triggerName table droppedOps
|
|
|
|
else do
|
|
|
|
doesTriggerExists <- checkIfTriggerExists @b sourceConfig triggerName (Set.fromList [INSERT, UPDATE, DELETE])
|
|
|
|
when doesTriggerExists $
|
|
|
|
throw400 AlreadyExists ("Event trigger with name " <> triggerNameToTxt triggerName <<> " already exists")
|
2022-03-15 11:41:03 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b source table . tmEventTriggers
|
|
|
|
%~ if replace
|
|
|
|
then ix triggerName .~ triggerConf
|
|
|
|
else OMap.insert triggerName triggerConf
|
2020-12-28 15:56:00 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runCreateEventTriggerQuery ::
|
|
|
|
forall b m.
|
2022-03-15 11:41:03 +03:00
|
|
|
(BackendMetadata b, BackendEventTrigger b, QErrM m, UserInfoM m, CacheRWM m, MetadataM m, MonadIO m) =>
|
2021-09-24 01:56:37 +03:00
|
|
|
CreateEventTriggerQuery b ->
|
|
|
|
m EncJSON
|
2018-12-13 10:26:15 +03:00
|
|
|
runCreateEventTriggerQuery q = do
|
2022-03-15 11:41:03 +03:00
|
|
|
createEventTriggerQueryMetadata @b q
|
2020-12-08 17:22:31 +03:00
|
|
|
pure successMsg
|
2018-09-05 14:26:46 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runDeleteEventTriggerQuery ::
|
|
|
|
forall b m.
|
2021-10-22 17:49:15 +03:00
|
|
|
(BackendEventTrigger b, MonadError QErr m, CacheRWM m, MonadIO m, MetadataM m) =>
|
2021-09-24 01:56:37 +03:00
|
|
|
DeleteEventTriggerQuery b ->
|
|
|
|
m EncJSON
|
2022-04-21 10:19:37 +03:00
|
|
|
runDeleteEventTriggerQuery (DeleteEventTriggerQuery sourceName triggerName) = do
|
|
|
|
sourceConfig <- askSourceConfig @b sourceName
|
|
|
|
tableName <- (_tciName . _tiCoreInfo) <$> askTabInfoFromTrigger @b sourceName triggerName
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
withNewInconsistentObjsCheck $
|
|
|
|
buildSchemaCache $
|
|
|
|
MetadataModifier $
|
2022-04-21 10:19:37 +03:00
|
|
|
tableMetadataSetter @b sourceName tableName %~ dropEventTriggerInMetadata triggerName
|
2021-09-09 14:54:19 +03:00
|
|
|
|
2022-04-21 10:19:37 +03:00
|
|
|
dropTriggerAndArchiveEvents @b sourceConfig triggerName tableName
|
2020-12-28 15:56:00 +03:00
|
|
|
|
2019-11-20 21:21:30 +03:00
|
|
|
pure successMsg
|
2018-09-07 14:51:01 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runRedeliverEvent ::
|
|
|
|
forall b m.
|
|
|
|
(BackendEventTrigger b, MonadIO m, CacheRM m, QErrM m, MetadataM m) =>
|
|
|
|
RedeliverEventQuery b ->
|
|
|
|
m EncJSON
|
2020-12-28 15:56:00 +03:00
|
|
|
runRedeliverEvent (RedeliverEventQuery eventId source) = do
|
2021-09-06 14:15:36 +03:00
|
|
|
sourceConfig <- askSourceConfig @b source
|
|
|
|
redeliverEvent @b sourceConfig eventId
|
2020-12-28 15:56:00 +03:00
|
|
|
pure successMsg
|
2018-09-19 15:12:57 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runInvokeEventTrigger ::
|
|
|
|
forall b m.
|
|
|
|
( MonadIO m,
|
|
|
|
QErrM m,
|
|
|
|
CacheRM m,
|
|
|
|
MetadataM m,
|
|
|
|
Tracing.MonadTrace m,
|
|
|
|
UserInfoM m,
|
|
|
|
BackendEventTrigger b
|
|
|
|
) =>
|
|
|
|
InvokeEventTriggerQuery b ->
|
|
|
|
m EncJSON
|
2020-12-28 15:56:00 +03:00
|
|
|
runInvokeEventTrigger (InvokeEventTriggerQuery name source payload) = do
|
2021-09-06 14:15:36 +03:00
|
|
|
trigInfo <- askEventTriggerInfo @b source name
|
2019-05-13 12:41:07 +03:00
|
|
|
assertManual $ etiOpsDef trigInfo
|
2021-09-24 01:56:37 +03:00
|
|
|
ti <- askTabInfoFromTrigger source name
|
2021-09-06 14:15:36 +03:00
|
|
|
sourceConfig <- askSourceConfig @b source
|
2021-07-27 11:05:33 +03:00
|
|
|
traceCtx <- Tracing.currentContext
|
|
|
|
userInfo <- askUserInfo
|
2021-09-06 14:15:36 +03:00
|
|
|
eid <- insertManualEvent @b sourceConfig (tableInfoName @b ti) name (makePayload payload) userInfo traceCtx
|
2019-05-13 12:41:07 +03:00
|
|
|
return $ encJFromJValue $ object ["event_id" .= eid]
|
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
makePayload o = object ["old" .= Null, "new" .= o]
|
2021-08-17 13:21:56 +03:00
|
|
|
|
2019-05-13 12:41:07 +03:00
|
|
|
assertManual (TriggerOpsDef _ _ _ man) = case man of
|
|
|
|
Just True -> return ()
|
2021-09-24 01:56:37 +03:00
|
|
|
_ -> throw400 NotSupported "manual mode is not enabled for event trigger"
|
2019-05-13 12:41:07 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
askTabInfoFromTrigger ::
|
|
|
|
(Backend b, QErrM m, CacheRM m) =>
|
|
|
|
SourceName ->
|
|
|
|
TriggerName ->
|
|
|
|
m (TableInfo b)
|
2021-09-06 14:15:36 +03:00
|
|
|
askTabInfoFromTrigger sourceName triggerName = do
|
2022-04-21 10:19:37 +03:00
|
|
|
schemaCache <- askSchemaCache
|
|
|
|
getTabInfoFromSchemaCache schemaCache sourceName triggerName
|
|
|
|
|
|
|
|
getTabInfoFromSchemaCache ::
|
|
|
|
(Backend b, QErrM m) =>
|
|
|
|
SchemaCache ->
|
|
|
|
SourceName ->
|
|
|
|
TriggerName ->
|
|
|
|
m (TableInfo b)
|
|
|
|
getTabInfoFromSchemaCache schemaCache sourceName triggerName = do
|
|
|
|
let tabInfos = HM.elems $ fromMaybe mempty $ unsafeTableCache sourceName $ scSources schemaCache
|
2021-09-06 14:15:36 +03:00
|
|
|
find (isJust . HM.lookup triggerName . _tiEventTriggerInfoMap) tabInfos
|
2021-01-09 02:09:15 +03:00
|
|
|
`onNothing` throw400 NotExists errMsg
|
|
|
|
where
|
2021-09-06 14:15:36 +03:00
|
|
|
errMsg = "event trigger " <> triggerName <<> " does not exist"
|
2021-01-09 02:09:15 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
askEventTriggerInfo ::
|
|
|
|
forall b m.
|
|
|
|
(QErrM m, CacheRM m, Backend b) =>
|
|
|
|
SourceName ->
|
|
|
|
TriggerName ->
|
|
|
|
m (EventTriggerInfo b)
|
2021-09-06 14:15:36 +03:00
|
|
|
askEventTriggerInfo sourceName triggerName = do
|
|
|
|
triggerInfo <- askTabInfoFromTrigger @b sourceName triggerName
|
|
|
|
let eventTriggerInfoMap = _tiEventTriggerInfoMap triggerInfo
|
|
|
|
HM.lookup triggerName eventTriggerInfoMap `onNothing` throw400 NotExists errMsg
|
2021-01-09 02:09:15 +03:00
|
|
|
where
|
2021-09-06 14:15:36 +03:00
|
|
|
errMsg = "event trigger " <> triggerName <<> " does not exist"
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
|
|
|
|
-- This change helps us create functions for the event triggers
|
|
|
|
-- without the function name being truncated by PG, since PG allows
|
|
|
|
-- for only 63 chars for identifiers.
|
|
|
|
-- Reasoning for the 42 characters:
|
|
|
|
-- 63 - (notify_hasura_) - (_INSERT | _UPDATE | _DELETE)
|
|
|
|
maxTriggerNameLength :: Int
|
|
|
|
maxTriggerNameLength = 42
|
2021-09-09 14:54:19 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
getHeaderInfosFromConf ::
|
|
|
|
QErrM m =>
|
|
|
|
Env.Environment ->
|
|
|
|
[HeaderConf] ->
|
|
|
|
m [EventHeaderInfo]
|
2021-09-09 14:54:19 +03:00
|
|
|
getHeaderInfosFromConf env = mapM getHeader
|
|
|
|
where
|
|
|
|
getHeader :: QErrM m => HeaderConf -> m EventHeaderInfo
|
|
|
|
getHeader hconf = case hconf of
|
|
|
|
(HeaderConf _ (HVValue val)) -> return $ EventHeaderInfo hconf val
|
2021-09-24 01:56:37 +03:00
|
|
|
(HeaderConf _ (HVEnv val)) -> do
|
2021-09-09 14:54:19 +03:00
|
|
|
envVal <- getEnv env val
|
|
|
|
return $ EventHeaderInfo hconf envVal
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
getWebhookInfoFromConf ::
|
|
|
|
QErrM m =>
|
|
|
|
Env.Environment ->
|
|
|
|
WebhookConf ->
|
|
|
|
m WebhookConfInfo
|
2021-09-20 16:14:28 +03:00
|
|
|
getWebhookInfoFromConf env webhookConf = case webhookConf of
|
2021-09-09 14:54:19 +03:00
|
|
|
WCValue w -> do
|
|
|
|
resolvedWebhook <- resolveWebhook env w
|
2022-06-05 23:27:09 +03:00
|
|
|
let urlTemplate = printURLTemplate $ unInputWebhook w
|
|
|
|
-- `urlTemplate` can either be the template value({{TEST}}) or a plain text.
|
|
|
|
-- When `urlTemplate` is a template value then '_envVarName' of the 'EnvRecord'
|
|
|
|
-- will be the template value i.e '{{TEST}}'
|
|
|
|
-- When `urlTemplate` is a plain text then '_envVarName' of the 'EnvRecord' will be the plain text value.
|
|
|
|
return $ WebhookConfInfo webhookConf (EnvRecord urlTemplate resolvedWebhook)
|
2021-09-20 16:14:28 +03:00
|
|
|
WCEnv webhookEnvVar -> do
|
|
|
|
envVal <- getEnv env webhookEnvVar
|
2022-06-05 23:27:09 +03:00
|
|
|
return $ WebhookConfInfo webhookConf (EnvRecord webhookEnvVar (ResolvedWebhook envVal))
|
2021-09-09 14:54:19 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
buildEventTriggerInfo ::
|
|
|
|
forall b m.
|
|
|
|
(Backend b, QErrM m) =>
|
|
|
|
Env.Environment ->
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
EventTriggerConf b ->
|
|
|
|
m (EventTriggerInfo b, [SchemaDependency])
|
2022-09-09 11:26:44 +03:00
|
|
|
buildEventTriggerInfo env source tableName (EventTriggerConf name def webhook webhookFromEnv rconf mheaders reqTransform respTransform cleanupConfig) = do
|
2021-09-09 14:54:19 +03:00
|
|
|
webhookConf <- case (webhook, webhookFromEnv) of
|
2021-09-24 01:56:37 +03:00
|
|
|
(Just w, Nothing) -> return $ WCValue w
|
2021-09-09 14:54:19 +03:00
|
|
|
(Nothing, Just wEnv) -> return $ WCEnv wEnv
|
2021-09-24 01:56:37 +03:00
|
|
|
_ -> throw500 "expected webhook or webhook_from_env"
|
2021-09-09 14:54:19 +03:00
|
|
|
let headerConfs = fromMaybe [] mheaders
|
|
|
|
webhookInfo <- getWebhookInfoFromConf env webhookConf
|
|
|
|
headerInfos <- getHeaderInfosFromConf env headerConfs
|
2022-09-09 11:26:44 +03:00
|
|
|
let eTrigInfo = EventTriggerInfo name def rconf webhookInfo headerInfos reqTransform respTransform cleanupConfig
|
2021-09-24 01:56:37 +03:00
|
|
|
tabDep =
|
|
|
|
SchemaDependency
|
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITable @b tableName
|
|
|
|
)
|
|
|
|
DRParent
|
|
|
|
pure (eTrigInfo, tabDep : getTrigDefDeps @b source tableName def)
|
|
|
|
|
|
|
|
getTrigDefDeps ::
|
|
|
|
forall b.
|
|
|
|
Backend b =>
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
TriggerOpsDef b ->
|
|
|
|
[SchemaDependency]
|
2021-09-09 14:54:19 +03:00
|
|
|
getTrigDefDeps source tableName (TriggerOpsDef mIns mUpd mDel _) =
|
2021-09-24 01:56:37 +03:00
|
|
|
mconcat $
|
|
|
|
catMaybes
|
|
|
|
[ subsOpSpecDeps <$> mIns,
|
|
|
|
subsOpSpecDeps <$> mUpd,
|
|
|
|
subsOpSpecDeps <$> mDel
|
|
|
|
]
|
2021-09-09 14:54:19 +03:00
|
|
|
where
|
|
|
|
subsOpSpecDeps :: SubscribeOpSpec b -> [SchemaDependency]
|
|
|
|
subsOpSpecDeps os =
|
|
|
|
let cols = getColsFromSub $ sosColumns os
|
|
|
|
mkColDependency dependencyReason col =
|
|
|
|
SchemaDependency
|
2021-09-24 01:56:37 +03:00
|
|
|
( SOSourceObj source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SOITableObj @b tableName (TOCol @b col)
|
|
|
|
)
|
2021-09-09 14:54:19 +03:00
|
|
|
dependencyReason
|
|
|
|
colDeps = map (mkColDependency DRColumn) cols
|
|
|
|
payload = maybe [] getColsFromSub (sosPayload os)
|
|
|
|
payloadDeps = map (mkColDependency DRPayload) payload
|
2021-09-24 01:56:37 +03:00
|
|
|
in colDeps <> payloadDeps
|
2021-09-09 14:54:19 +03:00
|
|
|
getColsFromSub sc = case sc of
|
2021-09-24 01:56:37 +03:00
|
|
|
SubCStar -> []
|
2021-09-09 14:54:19 +03:00
|
|
|
SubCArray cols -> cols
|
2022-04-11 14:24:11 +03:00
|
|
|
|
|
|
|
getTriggersMap ::
|
|
|
|
SourceMetadata b ->
|
|
|
|
InsOrdHashMap TriggerName (EventTriggerConf b)
|
|
|
|
getTriggersMap = OMap.unions . map _tmEventTriggers . OMap.elems . _smTables
|
|
|
|
|
|
|
|
getTriggerNames ::
|
|
|
|
SourceMetadata b ->
|
|
|
|
Set.HashSet TriggerName
|
|
|
|
getTriggerNames = Set.fromList . OMap.keys . getTriggersMap
|
2022-04-21 10:19:37 +03:00
|
|
|
|
|
|
|
getTableNameFromTrigger ::
|
|
|
|
forall b m.
|
|
|
|
(Backend b, QErrM m) =>
|
|
|
|
SchemaCache ->
|
|
|
|
SourceName ->
|
|
|
|
TriggerName ->
|
|
|
|
m (TableName b)
|
|
|
|
getTableNameFromTrigger schemaCache sourceName triggerName =
|
|
|
|
(_tciName . _tiCoreInfo) <$> getTabInfoFromSchemaCache @b schemaCache sourceName triggerName
|
2022-09-09 11:26:44 +03:00
|
|
|
|
|
|
|
runCleanupEventTriggerLog ::
|
|
|
|
(MonadEventLogCleanup m, MonadError QErr m) =>
|
|
|
|
TriggerLogCleanupConfig ->
|
|
|
|
m EncJSON
|
|
|
|
runCleanupEventTriggerLog conf = runLogCleaner conf >>= (flip onLeft) throwError
|
2022-09-13 11:33:44 +03:00
|
|
|
|
|
|
|
-- | Updates the cleanup switch in metadata given the source, table and trigger name
|
|
|
|
-- The Bool value represents the status of the cleaner, whether to start or pause it
|
|
|
|
updateCleanupStatusInMetadata ::
|
|
|
|
forall b m.
|
|
|
|
(Backend b, QErrM m, CacheRWM m, MetadataM m) =>
|
|
|
|
AutoTriggerLogCleanupConfig ->
|
|
|
|
EventTriggerCleanupStatus ->
|
|
|
|
SourceName ->
|
|
|
|
TableName b ->
|
|
|
|
TriggerName ->
|
|
|
|
m ()
|
|
|
|
updateCleanupStatusInMetadata cleanupConfig cleanupSwitch sourceName tableName triggerName = do
|
|
|
|
let newCleanupConfig = Just $ cleanupConfig {_atlccPaused = cleanupSwitch}
|
|
|
|
metadataObj =
|
|
|
|
MOSourceObjId sourceName $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOTableObj @b tableName $
|
|
|
|
MTOTrigger triggerName
|
|
|
|
|
|
|
|
buildSchemaCacheFor metadataObj $
|
|
|
|
MetadataModifier $
|
|
|
|
tableMetadataSetter @b sourceName tableName . tmEventTriggers . ix triggerName %~ updateCleanupConfig newCleanupConfig
|
|
|
|
|
|
|
|
-- | Function to start/stop the cleanup action based on the event triggers supplied in
|
|
|
|
-- TriggerLogCleanupToggleConfig conf
|
|
|
|
toggleEventTriggerCleanupAction ::
|
|
|
|
forall m.
|
|
|
|
(MonadIO m, QErrM m, CacheRWM m, MetadataM m) =>
|
|
|
|
TriggerLogCleanupToggleConfig ->
|
|
|
|
EventTriggerCleanupStatus ->
|
|
|
|
m EncJSON
|
|
|
|
toggleEventTriggerCleanupAction conf cleanupSwitch = do
|
|
|
|
schemaCache <- askSchemaCache
|
|
|
|
case conf of
|
|
|
|
TriggerLogCleanupSources tlcs -> do
|
|
|
|
case tlcs of
|
|
|
|
TriggerAllSource -> do
|
|
|
|
ifor_ (scSources schemaCache) $ \sourceName backendSourceInfo -> do
|
|
|
|
AB.dispatchAnyBackend @BackendEventTrigger backendSourceInfo \(SourceInfo _ tableCache _ _ _ _ :: SourceInfo b) -> do
|
|
|
|
traverseTableHelper tableCache cleanupSwitch sourceName
|
|
|
|
TriggerSource sourceNameLst -> do
|
|
|
|
forM_ sourceNameLst $ \sourceName -> do
|
|
|
|
backendSourceInfo <-
|
|
|
|
HM.lookup sourceName (scSources schemaCache)
|
|
|
|
`onNothing` throw400 NotExists ("source with name " <> sourceNameToText sourceName <> " does not exists")
|
|
|
|
|
|
|
|
AB.dispatchAnyBackend @BackendEventTrigger backendSourceInfo \(SourceInfo _ tableCache _ _ _ _ :: SourceInfo b) -> do
|
|
|
|
traverseTableHelper tableCache cleanupSwitch sourceName
|
|
|
|
TriggerQualifier qualifierLst -> do
|
|
|
|
forM_ qualifierLst $ \qualifier -> do
|
|
|
|
let sourceName = _etqSourceName qualifier
|
|
|
|
triggerNames = _etqEventTriggers qualifier
|
|
|
|
|
|
|
|
backendSourceInfo <-
|
|
|
|
HM.lookup sourceName (scSources schemaCache)
|
|
|
|
`onNothing` throw400 NotExists ("source with name " <> sourceNameToText sourceName <> " does not exists")
|
|
|
|
|
|
|
|
AB.dispatchAnyBackend @BackendEventTrigger backendSourceInfo \(SourceInfo {} :: SourceInfo b) -> do
|
|
|
|
forM_ triggerNames $ \triggerName -> do
|
|
|
|
eventTriggerInfo <- askEventTriggerInfo @b sourceName triggerName
|
|
|
|
tableName <- getTableNameFromTrigger @b schemaCache sourceName triggerName
|
|
|
|
cleanupConfig <-
|
|
|
|
(etiCleanupConfig eventTriggerInfo)
|
|
|
|
`onNothing` throw400 NotExists ("cleanup config does not exist for " <> triggerNameToTxt triggerName)
|
|
|
|
updateCleanupStatusInMetadata @b cleanupConfig cleanupSwitch sourceName tableName triggerName
|
|
|
|
pure successMsg
|
|
|
|
where
|
|
|
|
traverseTableHelper ::
|
|
|
|
forall b.
|
|
|
|
(Backend b) =>
|
|
|
|
TableCache b ->
|
|
|
|
EventTriggerCleanupStatus ->
|
|
|
|
SourceName ->
|
|
|
|
m ()
|
|
|
|
traverseTableHelper tableCache switch sourceName = forM_ tableCache $ \tableInfo -> do
|
|
|
|
let tableName = (_tciName . _tiCoreInfo) tableInfo
|
|
|
|
eventTriggerInfoMap = _tiEventTriggerInfoMap tableInfo
|
|
|
|
ifor_ eventTriggerInfoMap $ \triggerName eventTriggerInfo -> do
|
|
|
|
onJust (etiCleanupConfig eventTriggerInfo) $ \cleanupConfig ->
|
|
|
|
updateCleanupStatusInMetadata @b cleanupConfig switch sourceName tableName triggerName
|
|
|
|
|
|
|
|
runEventTriggerStartCleanup ::
|
|
|
|
forall m.
|
|
|
|
(MonadIO m, QErrM m, CacheRWM m, MetadataM m) =>
|
|
|
|
TriggerLogCleanupToggleConfig ->
|
|
|
|
m EncJSON
|
|
|
|
runEventTriggerStartCleanup conf = toggleEventTriggerCleanupAction conf ETCSUnpaused
|
|
|
|
|
|
|
|
runEventTriggerPauseCleanup ::
|
|
|
|
(MonadError QErr m, CacheRWM m, MonadIO m, MetadataM m) =>
|
|
|
|
TriggerLogCleanupToggleConfig ->
|
|
|
|
m EncJSON
|
|
|
|
runEventTriggerPauseCleanup conf = toggleEventTriggerCleanupAction conf ETCSPaused
|
|
|
|
|
|
|
|
-- | Collects and returns all the event triggers with cleanup config
|
|
|
|
getAllEventTriggersWithCleanupConfig :: TableInfo b -> [(TriggerName, AutoTriggerLogCleanupConfig)]
|
|
|
|
getAllEventTriggersWithCleanupConfig tInfo = mapMaybe (\(triggerName, triggerInfo) -> (triggerName,) <$> etiCleanupConfig triggerInfo) $ Map.toList $ _tiEventTriggerInfoMap tInfo
|