mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 08:02:15 +03:00
server: refactor Hasura.Metadata.Class
- Remove `MonadMetadataStorageQueryAPI` which was only implemented by a default implementation - Introduce `TransT` which can be used to easily derive `lift`ing implementations for `MonadBlaBlaBla` classes PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8579 GitOrigin-RevId: 4f804fda7e2de5c9d75ee4df269f500ebd46b8c9
This commit is contained in:
parent
ed4f3b7406
commit
7cc33dd8ec
@ -490,6 +490,7 @@ library
|
||||
, Control.Monad.Circular
|
||||
, Control.Monad.Memoize
|
||||
, Control.Monad.Stateless
|
||||
, Control.Monad.Trans.Extended
|
||||
, Control.Monad.Trans.Managed
|
||||
, Data.Aeson.Extended
|
||||
, Data.Aeson.Kriti.Functions
|
||||
|
21
server/src-lib/Control/Monad/Trans/Extended.hs
Normal file
21
server/src-lib/Control/Monad/Trans/Extended.hs
Normal file
@ -0,0 +1,21 @@
|
||||
module Control.Monad.Trans.Extended
|
||||
( TransT (..),
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad.Morph
|
||||
import Data.Kind
|
||||
import Prelude
|
||||
|
||||
-- | Utility newtype that can be used to derive type class instances just using
|
||||
-- `MonadTrans`.
|
||||
--
|
||||
-- We often derive some `MonadBlaBla` instance for `ReaderT` by using `lift`
|
||||
-- from `MonadTrans`. Which is fine, but it gets laborious if you do the same
|
||||
-- for `ExceptT`, `StateT` and `WriterT`, even though the method implementations
|
||||
-- are exactly the same. `TransT` allows you to write one `MonadTrans`-based
|
||||
-- instance, which can then be used with `DerivingVia` to use that one
|
||||
-- implementation for all monad transformers that use that same lifting
|
||||
-- implementation.
|
||||
newtype TransT t (m :: Type -> Type) a = TransT (t m a)
|
||||
deriving (Functor, Applicative, Monad, MonadTrans, MFunctor, MMonad)
|
@ -804,8 +804,6 @@ instance MonadMetadataStorage AppM where
|
||||
clearActionData = runInSeparateTx . clearActionDataTx
|
||||
setProcessingActionLogsToPending = runInSeparateTx . setProcessingActionLogsToPendingTx
|
||||
|
||||
instance MonadMetadataStorageQueryAPI AppM
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- misc
|
||||
|
||||
@ -891,7 +889,7 @@ runHGEServer ::
|
||||
WS.MonadWSLog m,
|
||||
MonadExecuteQuery m,
|
||||
HasResourceLimits m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
MonadQueryTags m,
|
||||
MonadEventLogCleanup m,
|
||||
@ -983,7 +981,7 @@ mkHGEServer ::
|
||||
WS.MonadWSLog m,
|
||||
MonadExecuteQuery m,
|
||||
HasResourceLimits m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
MonadQueryTags m,
|
||||
MonadEventLogCleanup m,
|
||||
|
@ -2,13 +2,21 @@
|
||||
module Hasura.Metadata.Class
|
||||
( SchemaSyncEventProcessResult (..),
|
||||
MonadMetadataStorage (..),
|
||||
MonadMetadataStorageQueryAPI (..),
|
||||
createOneOffScheduledEvent,
|
||||
createCronEvents,
|
||||
dropFutureCronEvents,
|
||||
deleteActionData,
|
||||
fetchScheduledEventInvocations,
|
||||
fetchScheduledEvents,
|
||||
dropEvent,
|
||||
fetchCatalogState,
|
||||
updateCatalogState,
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad.Trans.Extended
|
||||
import Control.Monad.Trans.Managed
|
||||
import Data.Aeson
|
||||
import Database.PG.Query qualified as PG
|
||||
import Hasura.Base.Error
|
||||
import Hasura.Eventing.ScheduledTrigger.Types
|
||||
import Hasura.Prelude
|
||||
@ -21,7 +29,6 @@ import Hasura.RQL.Types.SchemaCache
|
||||
import Hasura.RQL.Types.SchemaCache.Build
|
||||
import Hasura.Server.Types
|
||||
import Hasura.Session
|
||||
import Hasura.Tracing qualified as Tracing
|
||||
import Network.HTTP.Types qualified as HTTP
|
||||
|
||||
data SchemaSyncEventProcessResult = SchemaSyncEventProcessResult
|
||||
@ -136,7 +143,7 @@ class Monad m => MonadMetadataStorage m where
|
||||
clearActionData :: ActionName -> m (Either QErr ())
|
||||
setProcessingActionLogsToPending :: LockedActionIdArray -> m (Either QErr ())
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (ReaderT r m) where
|
||||
instance (MonadMetadataStorage m, MonadTrans t, Monad (t m)) => MonadMetadataStorage (TransT t m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
@ -169,258 +176,57 @@ instance (MonadMetadataStorage m) => MonadMetadataStorage (ReaderT r m) where
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (StateT s m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
setMetadata r = lift . setMetadata r
|
||||
notifySchemaCacheSync a b c = lift $ notifySchemaCacheSync a b c
|
||||
getCatalogState = lift getCatalogState
|
||||
setCatalogState a b = lift $ setCatalogState a b
|
||||
deriving via (TransT (ReaderT r) m) instance (MonadMetadataStorage m) => MonadMetadataStorage (ReaderT r m)
|
||||
|
||||
getMetadataDbUid = lift getMetadataDbUid
|
||||
checkMetadataStorageHealth = lift checkMetadataStorageHealth
|
||||
deriving via (TransT (StateT s) m) instance (MonadMetadataStorage m) => MonadMetadataStorage (StateT s m)
|
||||
|
||||
getDeprivedCronTriggerStats = lift . getDeprivedCronTriggerStats
|
||||
getScheduledEventsForDelivery = lift getScheduledEventsForDelivery
|
||||
insertCronEvents = lift . insertCronEvents
|
||||
insertOneOffScheduledEvent = lift . insertOneOffScheduledEvent
|
||||
insertScheduledEventInvocation a b = lift $ insertScheduledEventInvocation a b
|
||||
setScheduledEventOp a b c = lift $ setScheduledEventOp a b c
|
||||
unlockScheduledEvents a b = lift $ unlockScheduledEvents a b
|
||||
unlockAllLockedScheduledEvents = lift $ unlockAllLockedScheduledEvents
|
||||
clearFutureCronEvents = lift . clearFutureCronEvents
|
||||
getOneOffScheduledEvents a b c = lift $ getOneOffScheduledEvents a b c
|
||||
getCronEvents a b c d = lift $ getCronEvents a b c d
|
||||
getScheduledEventInvocations a = lift $ getScheduledEventInvocations a
|
||||
deleteScheduledEvent a b = lift $ deleteScheduledEvent a b
|
||||
deriving via (TransT (ExceptT e) m) instance (MonadMetadataStorage m) => MonadMetadataStorage (ExceptT e m)
|
||||
|
||||
insertAction a b c d = lift $ insertAction a b c d
|
||||
fetchUndeliveredActionEvents = lift fetchUndeliveredActionEvents
|
||||
setActionStatus a b = lift $ setActionStatus a b
|
||||
fetchActionResponse = lift . fetchActionResponse
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
deriving via (TransT MetadataT m) instance (MonadMetadataStorage m) => MonadMetadataStorage (MetadataT m)
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (ExceptT e m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
setMetadata r = lift . setMetadata r
|
||||
notifySchemaCacheSync a b c = lift $ notifySchemaCacheSync a b c
|
||||
getCatalogState = lift getCatalogState
|
||||
setCatalogState a b = lift $ setCatalogState a b
|
||||
deriving via (TransT ManagedT m) instance (MonadMetadataStorage m) => MonadMetadataStorage (ManagedT m)
|
||||
|
||||
getMetadataDbUid = lift getMetadataDbUid
|
||||
checkMetadataStorageHealth = lift checkMetadataStorageHealth
|
||||
-- | Record a one-off event
|
||||
createOneOffScheduledEvent :: MonadMetadataStorage m => OneOffEvent -> m (Either QErr EventId)
|
||||
createOneOffScheduledEvent = insertOneOffScheduledEvent
|
||||
|
||||
getDeprivedCronTriggerStats = lift . getDeprivedCronTriggerStats
|
||||
getScheduledEventsForDelivery = lift getScheduledEventsForDelivery
|
||||
insertCronEvents = lift . insertCronEvents
|
||||
insertOneOffScheduledEvent = lift . insertOneOffScheduledEvent
|
||||
insertScheduledEventInvocation a b = lift $ insertScheduledEventInvocation a b
|
||||
setScheduledEventOp a b c = lift $ setScheduledEventOp a b c
|
||||
unlockScheduledEvents a b = lift $ unlockScheduledEvents a b
|
||||
unlockAllLockedScheduledEvents = lift $ unlockAllLockedScheduledEvents
|
||||
clearFutureCronEvents = lift . clearFutureCronEvents
|
||||
getOneOffScheduledEvents a b c = lift $ getOneOffScheduledEvents a b c
|
||||
getCronEvents a b c d = lift $ getCronEvents a b c d
|
||||
getScheduledEventInvocations a = lift $ getScheduledEventInvocations a
|
||||
deleteScheduledEvent a b = lift $ deleteScheduledEvent a b
|
||||
-- | Record a cron event
|
||||
createCronEvents :: MonadMetadataStorage m => [CronEventSeed] -> m (Either QErr ())
|
||||
createCronEvents = insertCronEvents
|
||||
|
||||
insertAction a b c d = lift $ insertAction a b c d
|
||||
fetchUndeliveredActionEvents = lift fetchUndeliveredActionEvents
|
||||
setActionStatus a b = lift $ setActionStatus a b
|
||||
fetchActionResponse = lift . fetchActionResponse
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
-- | Clear cron events
|
||||
dropFutureCronEvents :: MonadMetadataStorage m => ClearCronEvents -> m (Either QErr ())
|
||||
dropFutureCronEvents = clearFutureCronEvents
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (Tracing.TraceT m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
setMetadata r = lift . setMetadata r
|
||||
notifySchemaCacheSync a b c = lift $ notifySchemaCacheSync a b c
|
||||
getCatalogState = lift getCatalogState
|
||||
setCatalogState a b = lift $ setCatalogState a b
|
||||
-- | Delete async action logs
|
||||
deleteActionData :: MonadMetadataStorage m => ActionName -> m (Either QErr ())
|
||||
deleteActionData = clearActionData
|
||||
|
||||
getMetadataDbUid = lift getMetadataDbUid
|
||||
checkMetadataStorageHealth = lift checkMetadataStorageHealth
|
||||
-- | Fetch cron/oneoff scheduled event invocations
|
||||
fetchScheduledEventInvocations ::
|
||||
MonadMetadataStorage m =>
|
||||
GetScheduledEventInvocations ->
|
||||
m (Either QErr (WithOptionalTotalCount [ScheduledEventInvocation]))
|
||||
fetchScheduledEventInvocations = getScheduledEventInvocations
|
||||
|
||||
getDeprivedCronTriggerStats = lift . getDeprivedCronTriggerStats
|
||||
getScheduledEventsForDelivery = lift getScheduledEventsForDelivery
|
||||
insertCronEvents = lift . insertCronEvents
|
||||
insertOneOffScheduledEvent = lift . insertOneOffScheduledEvent
|
||||
insertScheduledEventInvocation a b = lift $ insertScheduledEventInvocation a b
|
||||
setScheduledEventOp a b c = lift $ setScheduledEventOp a b c
|
||||
unlockScheduledEvents a b = lift $ unlockScheduledEvents a b
|
||||
unlockAllLockedScheduledEvents = lift $ unlockAllLockedScheduledEvents
|
||||
clearFutureCronEvents = lift . clearFutureCronEvents
|
||||
getOneOffScheduledEvents a b c = lift $ getOneOffScheduledEvents a b c
|
||||
getCronEvents a b c d = lift $ getCronEvents a b c d
|
||||
getScheduledEventInvocations a = lift $ getScheduledEventInvocations a
|
||||
deleteScheduledEvent a b = lift $ deleteScheduledEvent a b
|
||||
-- | Fetch cron/oneoff scheduled events
|
||||
fetchScheduledEvents :: MonadMetadataStorage m => GetScheduledEvents -> m (Either QErr Value)
|
||||
fetchScheduledEvents GetScheduledEvents {..} = do
|
||||
let totalCountToJSON WithOptionalTotalCount {..} =
|
||||
object $
|
||||
("events" .= _wtcData) : (maybe mempty (\count -> ["count" .= count]) _wtcCount)
|
||||
case _gseScheduledEvent of
|
||||
SEOneOff -> (fmap . fmap) totalCountToJSON $ getOneOffScheduledEvents _gsePagination _gseStatus _gseGetRowsCount
|
||||
SECron name -> (fmap . fmap) totalCountToJSON $ getCronEvents name _gsePagination _gseStatus _gseGetRowsCount
|
||||
|
||||
insertAction a b c d = lift $ insertAction a b c d
|
||||
fetchUndeliveredActionEvents = lift fetchUndeliveredActionEvents
|
||||
setActionStatus a b = lift $ setActionStatus a b
|
||||
fetchActionResponse = lift . fetchActionResponse
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
-- | Drop a cron/oneoff scheduled event
|
||||
dropEvent :: MonadMetadataStorage m => ScheduledEventId -> ScheduledEventType -> m (Either QErr ())
|
||||
dropEvent = deleteScheduledEvent
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (MetadataT m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
setMetadata r = lift . setMetadata r
|
||||
notifySchemaCacheSync a b c = lift $ notifySchemaCacheSync a b c
|
||||
getCatalogState = lift getCatalogState
|
||||
setCatalogState a b = lift $ setCatalogState a b
|
||||
-- | Retrieve the state from metadata storage catalog
|
||||
fetchCatalogState :: MonadMetadataStorage m => m (Either QErr CatalogState)
|
||||
fetchCatalogState = getCatalogState
|
||||
|
||||
getMetadataDbUid = lift getMetadataDbUid
|
||||
checkMetadataStorageHealth = lift checkMetadataStorageHealth
|
||||
|
||||
getDeprivedCronTriggerStats = lift . getDeprivedCronTriggerStats
|
||||
getScheduledEventsForDelivery = lift getScheduledEventsForDelivery
|
||||
insertCronEvents = lift . insertCronEvents
|
||||
insertOneOffScheduledEvent = lift . insertOneOffScheduledEvent
|
||||
insertScheduledEventInvocation a b = lift $ insertScheduledEventInvocation a b
|
||||
setScheduledEventOp a b c = lift $ setScheduledEventOp a b c
|
||||
unlockScheduledEvents a b = lift $ unlockScheduledEvents a b
|
||||
unlockAllLockedScheduledEvents = lift $ unlockAllLockedScheduledEvents
|
||||
clearFutureCronEvents = lift . clearFutureCronEvents
|
||||
getOneOffScheduledEvents a b c = lift $ getOneOffScheduledEvents a b c
|
||||
getCronEvents a b c d = lift $ getCronEvents a b c d
|
||||
getScheduledEventInvocations a = lift $ getScheduledEventInvocations a
|
||||
deleteScheduledEvent a b = lift $ deleteScheduledEvent a b
|
||||
|
||||
insertAction a b c d = lift $ insertAction a b c d
|
||||
fetchUndeliveredActionEvents = lift fetchUndeliveredActionEvents
|
||||
setActionStatus a b = lift $ setActionStatus a b
|
||||
fetchActionResponse = lift . fetchActionResponse
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (PG.TxET e m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
setMetadata r = lift . setMetadata r
|
||||
notifySchemaCacheSync a b c = lift $ notifySchemaCacheSync a b c
|
||||
getCatalogState = lift getCatalogState
|
||||
setCatalogState a b = lift $ setCatalogState a b
|
||||
|
||||
getMetadataDbUid = lift getMetadataDbUid
|
||||
checkMetadataStorageHealth = lift checkMetadataStorageHealth
|
||||
|
||||
getDeprivedCronTriggerStats = lift . getDeprivedCronTriggerStats
|
||||
getScheduledEventsForDelivery = lift getScheduledEventsForDelivery
|
||||
insertCronEvents = lift . insertCronEvents
|
||||
insertOneOffScheduledEvent = lift . insertOneOffScheduledEvent
|
||||
insertScheduledEventInvocation a b = lift $ insertScheduledEventInvocation a b
|
||||
setScheduledEventOp a b c = lift $ setScheduledEventOp a b c
|
||||
unlockScheduledEvents a b = lift $ unlockScheduledEvents a b
|
||||
unlockAllLockedScheduledEvents = lift $ unlockAllLockedScheduledEvents
|
||||
clearFutureCronEvents = lift . clearFutureCronEvents
|
||||
getOneOffScheduledEvents a b c = lift $ getOneOffScheduledEvents a b c
|
||||
getCronEvents a b c d = lift $ getCronEvents a b c d
|
||||
getScheduledEventInvocations a = lift $ getScheduledEventInvocations a
|
||||
deleteScheduledEvent a b = lift $ deleteScheduledEvent a b
|
||||
|
||||
insertAction a b c d = lift $ insertAction a b c d
|
||||
fetchUndeliveredActionEvents = lift fetchUndeliveredActionEvents
|
||||
setActionStatus a b = lift $ setActionStatus a b
|
||||
fetchActionResponse = lift . fetchActionResponse
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
|
||||
instance (MonadMetadataStorage m) => MonadMetadataStorage (ManagedT m) where
|
||||
fetchMetadataResourceVersion = lift fetchMetadataResourceVersion
|
||||
fetchMetadata = lift fetchMetadata
|
||||
fetchMetadataNotifications a b = lift $ fetchMetadataNotifications a b
|
||||
setMetadata r = lift . setMetadata r
|
||||
notifySchemaCacheSync a b c = lift $ notifySchemaCacheSync a b c
|
||||
getCatalogState = lift getCatalogState
|
||||
setCatalogState a b = lift $ setCatalogState a b
|
||||
|
||||
getMetadataDbUid = lift getMetadataDbUid
|
||||
checkMetadataStorageHealth = lift checkMetadataStorageHealth
|
||||
|
||||
getDeprivedCronTriggerStats = lift . getDeprivedCronTriggerStats
|
||||
getScheduledEventsForDelivery = lift getScheduledEventsForDelivery
|
||||
insertCronEvents = lift . insertCronEvents
|
||||
insertOneOffScheduledEvent = lift . insertOneOffScheduledEvent
|
||||
insertScheduledEventInvocation a b = lift $ insertScheduledEventInvocation a b
|
||||
setScheduledEventOp a b c = lift $ setScheduledEventOp a b c
|
||||
unlockScheduledEvents a b = lift $ unlockScheduledEvents a b
|
||||
unlockAllLockedScheduledEvents = lift $ unlockAllLockedScheduledEvents
|
||||
clearFutureCronEvents = lift . clearFutureCronEvents
|
||||
getOneOffScheduledEvents a b c = lift $ getOneOffScheduledEvents a b c
|
||||
getCronEvents a b c d = lift $ getCronEvents a b c d
|
||||
getScheduledEventInvocations a = lift $ getScheduledEventInvocations a
|
||||
deleteScheduledEvent a b = lift $ deleteScheduledEvent a b
|
||||
|
||||
insertAction a b c d = lift $ insertAction a b c d
|
||||
fetchUndeliveredActionEvents = lift fetchUndeliveredActionEvents
|
||||
setActionStatus a b = lift $ setActionStatus a b
|
||||
fetchActionResponse = lift . fetchActionResponse
|
||||
clearActionData = lift . clearActionData
|
||||
setProcessingActionLogsToPending = lift . setProcessingActionLogsToPending
|
||||
|
||||
-- | Operations from @'MonadMetadataStorage' used in '/v1/query' and '/v1/metadata' APIs
|
||||
class (MonadMetadataStorage m) => MonadMetadataStorageQueryAPI m where
|
||||
-- | Record a one-off event
|
||||
createOneOffScheduledEvent :: OneOffEvent -> m (Either QErr EventId)
|
||||
createOneOffScheduledEvent = insertOneOffScheduledEvent
|
||||
|
||||
-- | Record a cron event
|
||||
createCronEvents :: [CronEventSeed] -> m (Either QErr ())
|
||||
createCronEvents = insertCronEvents
|
||||
|
||||
-- | Clear cron events
|
||||
dropFutureCronEvents :: ClearCronEvents -> m (Either QErr ())
|
||||
dropFutureCronEvents = clearFutureCronEvents
|
||||
|
||||
-- | Delete async action logs
|
||||
deleteActionData :: ActionName -> m (Either QErr ())
|
||||
deleteActionData = clearActionData
|
||||
|
||||
-- | Fetch cron/oneoff scheduled event invocations
|
||||
fetchScheduledEventInvocations ::
|
||||
GetScheduledEventInvocations ->
|
||||
m (Either QErr (WithOptionalTotalCount [ScheduledEventInvocation]))
|
||||
fetchScheduledEventInvocations = getScheduledEventInvocations
|
||||
|
||||
-- | Fetch cron/oneoff scheduled events
|
||||
fetchScheduledEvents :: GetScheduledEvents -> m (Either QErr Value)
|
||||
fetchScheduledEvents GetScheduledEvents {..} = do
|
||||
let totalCountToJSON WithOptionalTotalCount {..} =
|
||||
object $
|
||||
("events" .= _wtcData) : (maybe mempty (\count -> ["count" .= count]) _wtcCount)
|
||||
case _gseScheduledEvent of
|
||||
SEOneOff -> (fmap . fmap) totalCountToJSON $ getOneOffScheduledEvents _gsePagination _gseStatus _gseGetRowsCount
|
||||
SECron name -> (fmap . fmap) totalCountToJSON $ getCronEvents name _gsePagination _gseStatus _gseGetRowsCount
|
||||
|
||||
-- | Drop a cron/oneoff scheduled event
|
||||
dropEvent :: ScheduledEventId -> ScheduledEventType -> m (Either QErr ())
|
||||
dropEvent = deleteScheduledEvent
|
||||
|
||||
-- | Retrieve the state from metadata storage catalog
|
||||
fetchCatalogState :: m (Either QErr CatalogState)
|
||||
fetchCatalogState = getCatalogState
|
||||
|
||||
-- | Update the state from metadata storage catalog
|
||||
updateCatalogState :: CatalogStateType -> Value -> m (Either QErr ())
|
||||
updateCatalogState = setCatalogState
|
||||
|
||||
instance (MonadMetadataStorageQueryAPI m) => MonadMetadataStorageQueryAPI (ReaderT r m)
|
||||
|
||||
instance (MonadMetadataStorageQueryAPI m) => MonadMetadataStorageQueryAPI (StateT s m)
|
||||
|
||||
instance (MonadMetadataStorageQueryAPI m) => MonadMetadataStorageQueryAPI (ExceptT s m)
|
||||
|
||||
instance (MonadMetadataStorageQueryAPI m) => MonadMetadataStorageQueryAPI (Tracing.TraceT m)
|
||||
|
||||
instance (MonadMetadataStorageQueryAPI m) => MonadMetadataStorageQueryAPI (MetadataT m)
|
||||
|
||||
instance (MonadMetadataStorageQueryAPI m) => MonadMetadataStorageQueryAPI (PG.TxET QErr m)
|
||||
-- | Update the state from metadata storage catalog
|
||||
updateCatalogState :: MonadMetadataStorage m => CatalogStateType -> Value -> m (Either QErr ())
|
||||
updateCatalogState = setCatalogState
|
||||
|
@ -261,7 +261,7 @@ runDropAction ::
|
||||
( MonadError QErr m,
|
||||
CacheRWM m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
DropAction ->
|
||||
m EncJSON
|
||||
|
@ -122,7 +122,7 @@ runClearMetadata ::
|
||||
( MonadIO m,
|
||||
CacheRWM m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadBaseControl IO m,
|
||||
MonadReader r m,
|
||||
MonadError QErr m,
|
||||
@ -195,7 +195,7 @@ runReplaceMetadata ::
|
||||
MetadataM m,
|
||||
MonadIO m,
|
||||
MonadBaseControl IO m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadReader r m,
|
||||
MonadError QErr m,
|
||||
Has (HL.Logger HL.Hasura) r,
|
||||
@ -213,7 +213,7 @@ runReplaceMetadataV1 ::
|
||||
MetadataM m,
|
||||
MonadIO m,
|
||||
MonadBaseControl IO m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadReader r m,
|
||||
MonadError QErr m,
|
||||
Has (HL.Logger HL.Hasura) r,
|
||||
@ -231,7 +231,7 @@ runReplaceMetadataV2 ::
|
||||
MetadataM m,
|
||||
MonadIO m,
|
||||
MonadBaseControl IO m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadReader r m,
|
||||
MonadError QErr m,
|
||||
Has (HL.Logger HL.Hasura) r,
|
||||
@ -255,7 +255,7 @@ runReplaceMetadataV2' ::
|
||||
MetadataM m,
|
||||
MonadIO m,
|
||||
MonadBaseControl IO m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadReader r m,
|
||||
MonadError QErr m,
|
||||
Has (HL.Logger HL.Hasura) r,
|
||||
@ -760,12 +760,12 @@ purgeMetadataObj = \case
|
||||
}
|
||||
|
||||
runGetCatalogState ::
|
||||
(MonadMetadataStorageQueryAPI m, MonadError QErr m) => GetCatalogState -> m EncJSON
|
||||
(MonadMetadataStorage m, MonadError QErr m) => GetCatalogState -> m EncJSON
|
||||
runGetCatalogState _ =
|
||||
encJFromJValue <$> liftEitherM fetchCatalogState
|
||||
|
||||
runSetCatalogState ::
|
||||
(MonadMetadataStorageQueryAPI m, MonadError QErr m) => SetCatalogState -> m EncJSON
|
||||
(MonadMetadataStorage m, MonadError QErr m) => SetCatalogState -> m EncJSON
|
||||
runSetCatalogState SetCatalogState {..} = do
|
||||
liftEitherM $ updateCatalogState _scsType _scsState
|
||||
pure successMsg
|
||||
|
@ -36,7 +36,7 @@ import System.Cron.Types (CronSchedule)
|
||||
populateInitialCronTriggerEvents ::
|
||||
( MonadIO m,
|
||||
MonadError QErr m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
CronSchedule ->
|
||||
TriggerName ->
|
||||
@ -54,7 +54,7 @@ runCreateCronTrigger ::
|
||||
CacheRWM m,
|
||||
MonadIO m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
CreateCronTrigger ->
|
||||
m EncJSON
|
||||
@ -128,7 +128,7 @@ updateCronTrigger ::
|
||||
CacheRWM m,
|
||||
MonadIO m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
CronTriggerMetadata ->
|
||||
m EncJSON
|
||||
@ -148,7 +148,7 @@ runDeleteCronTrigger ::
|
||||
( MonadError QErr m,
|
||||
CacheRWM m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
ScheduledTriggerName ->
|
||||
m EncJSON
|
||||
@ -165,7 +165,7 @@ dropCronTriggerInMetadata name =
|
||||
MetadataModifier $ metaCronTriggers %~ OMap.delete name
|
||||
|
||||
runCreateScheduledEvent ::
|
||||
(MonadError QErr m, MonadMetadataStorageQueryAPI m) =>
|
||||
(MonadError QErr m, MonadMetadataStorage m) =>
|
||||
CreateScheduledEvent ->
|
||||
m EncJSON
|
||||
runCreateScheduledEvent scheduledEvent = do
|
||||
@ -181,7 +181,7 @@ checkExists name = do
|
||||
"cron trigger with name: " <> triggerNameToTxt name <> " does not exist"
|
||||
|
||||
runDeleteScheduledEvent ::
|
||||
(MonadMetadataStorageQueryAPI m, MonadError QErr m) => DeleteScheduledEvent -> m EncJSON
|
||||
(MonadMetadataStorage m, MonadError QErr m) => DeleteScheduledEvent -> m EncJSON
|
||||
runDeleteScheduledEvent DeleteScheduledEvent {..} = do
|
||||
liftEitherM $ dropEvent _dseEventId _dseType
|
||||
pure successMsg
|
||||
@ -189,7 +189,7 @@ runDeleteScheduledEvent DeleteScheduledEvent {..} = do
|
||||
runGetScheduledEvents ::
|
||||
( MonadError QErr m,
|
||||
CacheRM m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
GetScheduledEvents ->
|
||||
m EncJSON
|
||||
@ -202,7 +202,7 @@ runGetScheduledEvents gse = do
|
||||
runGetScheduledEventInvocations ::
|
||||
( MonadError QErr m,
|
||||
CacheRM m,
|
||||
MonadMetadataStorageQueryAPI m
|
||||
MonadMetadataStorage m
|
||||
) =>
|
||||
GetScheduledEventInvocations ->
|
||||
m EncJSON
|
||||
|
@ -185,7 +185,6 @@ newtype CacheRWT m a
|
||||
MonadError e,
|
||||
UserInfoM,
|
||||
MonadMetadataStorage,
|
||||
MonadMetadataStorageQueryAPI,
|
||||
Tracing.MonadTrace,
|
||||
MonadBase b,
|
||||
MonadBaseControl b,
|
||||
|
@ -391,7 +391,7 @@ runMetadataQuery ::
|
||||
MonadBaseControl IO m,
|
||||
HasAppEnv m,
|
||||
Tracing.MonadTrace m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
MonadEventLogCleanup m,
|
||||
ProvidesHasuraServices m,
|
||||
@ -610,7 +610,7 @@ runMetadataQueryM ::
|
||||
Tracing.MonadTrace m,
|
||||
UserInfoM m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
HasServerConfigCtx m,
|
||||
MonadReader r m,
|
||||
Has (L.Logger L.Hasura) r,
|
||||
@ -642,7 +642,7 @@ runMetadataQueryV1M ::
|
||||
Tracing.MonadTrace m,
|
||||
UserInfoM m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
HasServerConfigCtx m,
|
||||
MonadReader r m,
|
||||
Has (L.Logger L.Hasura) r,
|
||||
@ -819,7 +819,7 @@ runMetadataQueryV2M ::
|
||||
CacheRWM m,
|
||||
MonadBaseControl IO m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadReader r m,
|
||||
Has (L.Logger L.Hasura) r,
|
||||
MonadError QErr m,
|
||||
|
@ -182,7 +182,7 @@ runQuery ::
|
||||
HasAppEnv m,
|
||||
Tracing.MonadTrace m,
|
||||
MonadBaseControl IO m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
MonadQueryTags m,
|
||||
MonadEventLogCleanup m,
|
||||
@ -394,7 +394,7 @@ runQueryM ::
|
||||
HasServerConfigCtx m,
|
||||
Tracing.MonadTrace m,
|
||||
MetadataM m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadQueryTags m,
|
||||
MonadReader r m,
|
||||
MonadError QErr m,
|
||||
|
@ -144,7 +144,6 @@ newtype Handler m a = Handler (ReaderT HandlerCtx (ExceptT QErr m) a)
|
||||
GH.MonadExecuteQuery,
|
||||
MonadMetadataApiAuthorization,
|
||||
MonadMetadataStorage,
|
||||
MonadMetadataStorageQueryAPI,
|
||||
ProvidesNetwork,
|
||||
MonadGetApiTimeLimit
|
||||
)
|
||||
@ -421,7 +420,7 @@ v1QueryHandler ::
|
||||
MonadMetadataApiAuthorization m,
|
||||
MonadTrace m,
|
||||
MonadReader HandlerCtx m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
HasAppEnv m,
|
||||
MonadQueryTags m,
|
||||
@ -453,7 +452,7 @@ v1MetadataHandler ::
|
||||
MonadBaseControl IO m,
|
||||
MonadReader HandlerCtx m,
|
||||
MonadTrace m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
MonadMetadataApiAuthorization m,
|
||||
MonadEventLogCleanup m,
|
||||
@ -724,7 +723,7 @@ mkWaiApp ::
|
||||
MonadTrace m,
|
||||
GH.MonadExecuteQuery m,
|
||||
HasResourceLimits m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadResolveSource m,
|
||||
MonadQueryTags m,
|
||||
MonadEventLogCleanup m,
|
||||
@ -768,7 +767,7 @@ httpApp ::
|
||||
MonadExecutionLog m,
|
||||
MonadTrace m,
|
||||
GH.MonadExecuteQuery m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
HasResourceLimits m,
|
||||
MonadResolveSource m,
|
||||
MonadQueryTags m,
|
||||
|
@ -51,7 +51,6 @@ newtype CacheRefT m a = CacheRefT {runCacheRefT :: (ServerConfigCtx, MVar Rebuil
|
||||
MonadTx,
|
||||
UserInfoM,
|
||||
MonadMetadataStorage,
|
||||
MonadMetadataStorageQueryAPI,
|
||||
MonadResolveSource,
|
||||
ProvidesNetwork,
|
||||
MonadGetApiTimeLimit
|
||||
@ -112,7 +111,7 @@ suite ::
|
||||
MonadError QErr m,
|
||||
MonadBaseControl IO m,
|
||||
MonadResolveSource m,
|
||||
MonadMetadataStorageQueryAPI m,
|
||||
MonadMetadataStorage m,
|
||||
MonadEventLogCleanup m,
|
||||
ProvidesNetwork m,
|
||||
MonadGetApiTimeLimit m
|
||||
|
Loading…
Reference in New Issue
Block a user