2021-09-29 11:13:30 +03:00
|
|
|
|
{-# LANGUAGE PatternSynonyms #-}
|
2022-03-16 03:39:21 +03:00
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
2021-09-29 11:13:30 +03:00
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- |
|
|
|
|
|
-- = Scheduled Triggers
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- This module implements the functionality of invoking webhooks during specified
|
|
|
|
|
-- time events aka scheduled events. The scheduled events are the events generated
|
|
|
|
|
-- by the graphql-engine using the cron triggers or/and a scheduled event can
|
|
|
|
|
-- be created by the user at a specified time with the payload, webhook, headers
|
|
|
|
|
-- and the retry configuration. Scheduled events are modeled using rows in Postgres
|
|
|
|
|
-- with a @timestamp@ column.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- This module implements scheduling and delivery of scheduled
|
|
|
|
|
-- events:
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- 1. Scheduling a cron event involves creating new cron events. New
|
|
|
|
|
-- cron events are created based on the cron schedule and the number of
|
|
|
|
|
-- scheduled events that are already present in the scheduled events buffer.
|
|
|
|
|
-- The graphql-engine computes the new scheduled events and writes them to
|
|
|
|
|
-- the database.(Generator)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- 2. Delivering a scheduled event involves reading undelivered scheduled events
|
|
|
|
|
-- from the database and delivering them to the webhook server. (Processor)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- The rationale behind separating the event scheduling and event delivery
|
|
|
|
|
-- mechanism into two different threads is that the scheduling and delivering of
|
|
|
|
|
-- the scheduled events are not directly dependent on each other. The generator
|
|
|
|
|
-- will almost always try to create scheduled events which are supposed to be
|
|
|
|
|
-- delivered in the future (timestamp > current_timestamp) and the processor
|
|
|
|
|
-- will fetch scheduled events of the past (timestamp < current_timestamp). So,
|
|
|
|
|
-- the set of the scheduled events generated by the generator and the processor
|
|
|
|
|
-- will never be the same. The point here is that they're not correlated to each
|
|
|
|
|
-- other. They can be split into different threads for a better performance.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- == Implementation
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-11-25 13:56:44 +03:00
|
|
|
|
-- The scheduled triggers eventing is being implemented in the metadata storage.
|
|
|
|
|
-- All functions that make interaction to storage system are abstracted in
|
|
|
|
|
-- the @'MonadMetadataStorage' class.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- During the startup, two threads are started:
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- 1. Generator: Fetches the list of scheduled triggers from cache and generates
|
|
|
|
|
-- the scheduled events.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- - Additional events will be generated only if there are fewer than 100
|
|
|
|
|
-- scheduled events.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- - The upcoming events timestamp will be generated using:
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- - cron schedule of the scheduled trigger
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- - max timestamp of the scheduled events that already exist or
|
|
|
|
|
-- current_timestamp(when no scheduled events exist)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- - The timestamp of the scheduled events is stored with timezone because
|
|
|
|
|
-- `SELECT NOW()` returns timestamp with timezone, so it's good to
|
|
|
|
|
-- compare two things of the same type.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- This effectively corresponds to doing an INSERT with values containing
|
|
|
|
|
-- specific timestamp.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- 2. Processor: Fetches the undelivered cron events and the scheduled events
|
|
|
|
|
-- from the database and which have timestamp lesser than the
|
|
|
|
|
-- current timestamp and then process them.
|
2021-09-24 01:56:37 +03:00
|
|
|
|
--
|
2021-04-27 08:34:14 +03:00
|
|
|
|
-- TODO
|
|
|
|
|
-- - Consider and document ordering guarantees
|
|
|
|
|
-- - do we have any in the presence of multiple hasura instances?
|
|
|
|
|
-- - If we have nothing useful to say about ordering, then consider processing
|
|
|
|
|
-- events asynchronously, so that a slow webhook doesn't cause everything
|
|
|
|
|
-- subsequent to be delayed
|
2020-05-13 15:33:16 +03:00
|
|
|
|
module Hasura.Eventing.ScheduledTrigger
|
|
|
|
|
( runCronEventsGenerator,
|
|
|
|
|
processScheduledTriggers,
|
2020-11-25 13:56:44 +03:00
|
|
|
|
generateScheduleTimes,
|
2020-05-13 15:33:16 +03:00
|
|
|
|
CronEventSeed (..),
|
2020-07-02 14:57:09 +03:00
|
|
|
|
LockedEventsCtx (..),
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2023-02-07 15:22:08 +03:00
|
|
|
|
-- * Cron trigger stats logger
|
|
|
|
|
createFetchedCronTriggerStatsLogger,
|
|
|
|
|
closeFetchedCronTriggersStatsLogger,
|
|
|
|
|
|
2023-01-30 09:06:45 +03:00
|
|
|
|
-- * Scheduled events stats logger
|
|
|
|
|
createFetchedScheduledEventsStatsLogger,
|
|
|
|
|
closeFetchedScheduledEventsStatsLogger,
|
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
-- * Database interactions
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
-- Following function names are similar to those present in
|
|
|
|
|
-- 'MonadMetadataStorage' type class. To avoid duplication,
|
|
|
|
|
-- 'Tx' is suffixed to identify as database transactions
|
|
|
|
|
getDeprivedCronTriggerStatsTx,
|
|
|
|
|
getScheduledEventsForDeliveryTx,
|
|
|
|
|
insertInvocationTx,
|
|
|
|
|
setScheduledEventOpTx,
|
|
|
|
|
unlockScheduledEventsTx,
|
|
|
|
|
unlockAllLockedScheduledEventsTx,
|
2021-09-13 21:00:53 +03:00
|
|
|
|
insertCronEventsTx,
|
|
|
|
|
insertOneOffScheduledEventTx,
|
2020-12-14 07:30:19 +03:00
|
|
|
|
dropFutureCronEventsTx,
|
2021-01-07 12:04:22 +03:00
|
|
|
|
getOneOffScheduledEventsTx,
|
|
|
|
|
getCronEventsTx,
|
|
|
|
|
deleteScheduledEventTx,
|
2022-11-03 13:21:56 +03:00
|
|
|
|
getScheduledEventInvocationsTx,
|
|
|
|
|
getScheduledEventsInvocationsQuery,
|
|
|
|
|
getScheduledEventsInvocationsQueryNoPagination,
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2021-01-07 12:04:22 +03:00
|
|
|
|
-- * Export utility functions which are useful to build
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2021-01-07 12:04:22 +03:00
|
|
|
|
-- SQLs for fetching data from metadata storage
|
|
|
|
|
mkScheduledEventStatusFilter,
|
|
|
|
|
scheduledTimeOrderBy,
|
2022-09-15 22:10:53 +03:00
|
|
|
|
executeWithOptionalTotalCount,
|
2021-01-07 12:04:22 +03:00
|
|
|
|
mkPaginationSelectExp,
|
|
|
|
|
withCount,
|
|
|
|
|
invocationFieldExtractors,
|
|
|
|
|
mkEventIdBoolExp,
|
2021-02-22 19:02:04 +03:00
|
|
|
|
EventTables (..),
|
2020-05-13 15:33:16 +03:00
|
|
|
|
)
|
|
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2023-03-29 14:24:35 +03:00
|
|
|
|
import Control.Concurrent.Async.Lifted (forConcurrently_)
|
2021-05-14 12:38:37 +03:00
|
|
|
|
import Control.Concurrent.Extended (Forever (..), sleep)
|
|
|
|
|
import Control.Concurrent.STM
|
2023-03-22 02:59:42 +03:00
|
|
|
|
import Control.Lens (preview)
|
2023-03-29 14:24:35 +03:00
|
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Data.Aeson qualified as J
|
|
|
|
|
import Data.Environment qualified as Env
|
|
|
|
|
import Data.Has
|
2020-05-13 15:33:16 +03:00
|
|
|
|
import Data.HashMap.Strict qualified as Map
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Data.Int (Int64)
|
2021-01-07 12:04:22 +03:00
|
|
|
|
import Data.List.NonEmpty qualified as NE
|
2022-06-17 12:56:38 +03:00
|
|
|
|
import Data.SerializableBlob qualified as SB
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Data.Set qualified as Set
|
2023-03-14 15:27:17 +03:00
|
|
|
|
import Data.Text qualified as T
|
|
|
|
|
import Data.Text.Extended (ToTxt (..), (<<>))
|
|
|
|
|
import Data.These
|
2020-05-13 15:33:16 +03:00
|
|
|
|
import Data.Time.Clock
|
2022-06-05 23:27:09 +03:00
|
|
|
|
import Data.URL.Template (printURLTemplate)
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
import Database.PG.Query qualified as PG
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.Backends.Postgres.Execute.Types
|
2021-01-07 12:04:22 +03:00
|
|
|
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
2020-10-27 16:53:49 +03:00
|
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
2021-05-11 18:18:31 +03:00
|
|
|
|
import Hasura.Base.Error
|
2020-07-14 22:00:58 +03:00
|
|
|
|
import Hasura.Eventing.Common
|
2020-05-13 15:33:16 +03:00
|
|
|
|
import Hasura.Eventing.HTTP
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Hasura.Eventing.ScheduledTrigger.Types
|
2021-09-20 16:14:28 +03:00
|
|
|
|
import Hasura.HTTP (getHTTPExceptionStatus)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Hasura.Logging qualified as L
|
|
|
|
|
import Hasura.Metadata.Class
|
2020-08-27 19:36:39 +03:00
|
|
|
|
import Hasura.Prelude
|
2023-03-14 15:27:17 +03:00
|
|
|
|
import Hasura.RQL.DDL.EventTrigger (ResolveHeaderError, getHeaderInfosFromConfEither)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
import Hasura.RQL.DDL.Webhook.Transform
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
|
import Hasura.RQL.Types.EventTrigger
|
|
|
|
|
import Hasura.RQL.Types.Eventing
|
|
|
|
|
import Hasura.RQL.Types.ScheduledTrigger
|
|
|
|
|
import Hasura.RQL.Types.SchemaCache
|
2020-05-13 15:33:16 +03:00
|
|
|
|
import Hasura.SQL.Types
|
2023-03-30 08:51:18 +03:00
|
|
|
|
import Hasura.Server.Prometheus (ScheduledTriggerMetrics (..))
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Hasura.Tracing qualified as Tracing
|
2021-09-16 14:03:01 +03:00
|
|
|
|
import Network.HTTP.Client.Transformable qualified as HTTP
|
2022-09-21 21:01:48 +03:00
|
|
|
|
import Refined (unrefine)
|
2022-12-28 06:47:42 +03:00
|
|
|
|
import System.Metrics.Prometheus.Counter as Prometheus.Counter
|
2023-03-29 14:24:35 +03:00
|
|
|
|
import System.Timeout.Lifted (timeout)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
import Text.Builder qualified as TB
|
2020-07-03 03:55:07 +03:00
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- | runCronEventsGenerator makes sure that all the cron triggers
|
|
|
|
|
-- have an adequate buffer of cron events.
|
2020-11-25 13:56:44 +03:00
|
|
|
|
runCronEventsGenerator ::
|
|
|
|
|
( MonadIO m,
|
2023-02-03 04:03:23 +03:00
|
|
|
|
MonadMetadataStorage m
|
2020-11-25 13:56:44 +03:00
|
|
|
|
) =>
|
|
|
|
|
L.Logger L.Hasura ->
|
2023-02-07 15:22:08 +03:00
|
|
|
|
FetchedCronTriggerStatsLogger ->
|
2020-05-13 15:33:16 +03:00
|
|
|
|
IO SchemaCache ->
|
2020-11-25 13:56:44 +03:00
|
|
|
|
m void
|
2023-02-07 15:22:08 +03:00
|
|
|
|
runCronEventsGenerator logger cronTriggerStatsLogger getSC = do
|
2020-05-13 15:33:16 +03:00
|
|
|
|
forever $ do
|
2020-11-25 13:56:44 +03:00
|
|
|
|
sc <- liftIO getSC
|
2020-05-13 15:33:16 +03:00
|
|
|
|
-- get cron triggers from cache
|
|
|
|
|
let cronTriggersCache = scCronTriggers sc
|
|
|
|
|
|
2021-04-27 08:34:14 +03:00
|
|
|
|
unless (Map.null cronTriggersCache) $ do
|
2021-03-30 15:57:38 +03:00
|
|
|
|
-- Poll the DB only when there's at-least one cron trigger present
|
|
|
|
|
-- in the schema cache
|
|
|
|
|
-- get cron trigger stats from db
|
2021-05-14 12:38:37 +03:00
|
|
|
|
-- When shutdown is initiated, we stop generating new cron events
|
2023-02-03 04:03:23 +03:00
|
|
|
|
eitherRes <- runExceptT $ do
|
|
|
|
|
deprivedCronTriggerStats <- liftEitherM $ getDeprivedCronTriggerStats $ Map.keys cronTriggersCache
|
2023-02-07 15:22:08 +03:00
|
|
|
|
-- Log fetched deprived cron trigger stats
|
|
|
|
|
logFetchedCronTriggersStats cronTriggerStatsLogger deprivedCronTriggerStats
|
2021-03-30 15:57:38 +03:00
|
|
|
|
-- join stats with cron triggers and produce @[(CronTriggerInfo, CronTriggerStats)]@
|
|
|
|
|
cronTriggersForHydrationWithStats <-
|
|
|
|
|
catMaybes
|
|
|
|
|
<$> mapM (withCronTrigger cronTriggersCache) deprivedCronTriggerStats
|
|
|
|
|
insertCronEventsFor cronTriggersForHydrationWithStats
|
|
|
|
|
|
2022-07-01 14:47:20 +03:00
|
|
|
|
onLeft eitherRes $ L.unLogger logger . ScheduledTriggerInternalErr
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2021-04-27 08:34:14 +03:00
|
|
|
|
-- See discussion: https://github.com/hasura/graphql-engine-mono/issues/1001
|
2020-11-25 13:56:44 +03:00
|
|
|
|
liftIO $ sleep (minutes 1)
|
|
|
|
|
where
|
2020-05-13 15:33:16 +03:00
|
|
|
|
withCronTrigger cronTriggerCache cronTriggerStat = do
|
2022-07-01 14:47:20 +03:00
|
|
|
|
case Map.lookup (_ctsName cronTriggerStat) cronTriggerCache of
|
2020-05-13 15:33:16 +03:00
|
|
|
|
Nothing -> do
|
|
|
|
|
L.unLogger logger $
|
|
|
|
|
ScheduledTriggerInternalErr $
|
2020-11-25 13:56:44 +03:00
|
|
|
|
err500 Unexpected "could not find scheduled trigger in the schema cache"
|
2020-05-13 15:33:16 +03:00
|
|
|
|
pure Nothing
|
|
|
|
|
Just cronTrigger ->
|
|
|
|
|
pure $
|
|
|
|
|
Just (cronTrigger, cronTriggerStat)
|
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
insertCronEventsFor ::
|
2023-02-03 04:03:23 +03:00
|
|
|
|
(MonadMetadataStorage m, MonadError QErr m) =>
|
2020-11-25 13:56:44 +03:00
|
|
|
|
[(CronTriggerInfo, CronTriggerStats)] ->
|
|
|
|
|
m ()
|
2020-05-13 15:33:16 +03:00
|
|
|
|
insertCronEventsFor cronTriggersWithStats = do
|
|
|
|
|
let scheduledEvents = flip concatMap cronTriggersWithStats $ \(cti, stats) ->
|
2022-07-01 14:47:20 +03:00
|
|
|
|
generateCronEventsFrom (_ctsMaxScheduledTime stats) cti
|
2020-05-13 15:33:16 +03:00
|
|
|
|
case scheduledEvents of
|
|
|
|
|
[] -> pure ()
|
2023-02-03 04:03:23 +03:00
|
|
|
|
events -> liftEitherM $ insertCronEvents events
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
|
|
generateCronEventsFrom :: UTCTime -> CronTriggerInfo -> [CronEventSeed]
|
|
|
|
|
generateCronEventsFrom startTime CronTriggerInfo {..} =
|
|
|
|
|
map (CronEventSeed ctiName) $
|
2021-04-27 08:34:14 +03:00
|
|
|
|
-- generate next 100 events; see getDeprivedCronTriggerStatsTx:
|
|
|
|
|
generateScheduleTimes startTime 100 ctiSchedule
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2023-03-29 14:24:35 +03:00
|
|
|
|
-- | `upperBoundScheduledEventTimeout` is the maximum amount of time
|
|
|
|
|
-- a scheduled event can take to process. This function is intended
|
|
|
|
|
-- to use with a timeout.
|
|
|
|
|
upperBoundScheduledEventTimeout :: DiffTime
|
|
|
|
|
upperBoundScheduledEventTimeout = minutes 30
|
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
processCronEvents ::
|
2021-10-13 19:38:56 +03:00
|
|
|
|
( MonadIO m,
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
|
MonadMetadataStorage m,
|
2023-03-29 14:24:35 +03:00
|
|
|
|
Tracing.MonadTrace m,
|
|
|
|
|
MonadBaseControl IO m
|
2020-11-25 13:56:44 +03:00
|
|
|
|
) =>
|
2020-05-13 15:33:16 +03:00
|
|
|
|
L.Logger L.Hasura ->
|
|
|
|
|
HTTP.Manager ->
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-11-25 13:56:44 +03:00
|
|
|
|
[CronEvent] ->
|
2023-04-10 15:25:44 +03:00
|
|
|
|
HashMap TriggerName CronTriggerInfo ->
|
2020-07-02 14:57:09 +03:00
|
|
|
|
TVar (Set.Set CronEventId) ->
|
2020-07-14 22:00:58 +03:00
|
|
|
|
m ()
|
2023-04-10 15:25:44 +03:00
|
|
|
|
processCronEvents logger httpMgr scheduledTriggerMetrics cronEvents cronTriggersInfo lockedCronEvents = do
|
2020-11-25 13:56:44 +03:00
|
|
|
|
-- save the locked cron events that have been fetched from the
|
|
|
|
|
-- database, the events stored here will be unlocked in case a
|
|
|
|
|
-- graceful shutdown is initiated in midst of processing these events
|
|
|
|
|
saveLockedEvents (map _ceId cronEvents) lockedCronEvents
|
|
|
|
|
-- The `createdAt` of a cron event is the `created_at` of the cron trigger
|
2023-03-29 14:24:35 +03:00
|
|
|
|
forConcurrently_ cronEvents $ \(CronEvent id' name st _ tries _ _) -> do
|
2020-11-25 13:56:44 +03:00
|
|
|
|
case Map.lookup name cronTriggersInfo of
|
|
|
|
|
Nothing ->
|
|
|
|
|
logInternalError $
|
2023-02-13 10:10:23 +03:00
|
|
|
|
err500 Unexpected $
|
|
|
|
|
"could not find cron trigger " <> name <<> " in the schema cache"
|
2020-11-25 13:56:44 +03:00
|
|
|
|
Just CronTriggerInfo {..} -> do
|
2021-09-20 16:14:28 +03:00
|
|
|
|
let payload =
|
|
|
|
|
ScheduledEventWebhookPayload
|
|
|
|
|
id'
|
|
|
|
|
(Just name)
|
|
|
|
|
st
|
2020-11-25 13:56:44 +03:00
|
|
|
|
(fromMaybe J.Null ctiPayload)
|
|
|
|
|
ctiComment
|
|
|
|
|
Nothing
|
2022-01-19 07:46:42 +03:00
|
|
|
|
ctiRequestTransform
|
|
|
|
|
ctiResponseTransform
|
2020-11-25 13:56:44 +03:00
|
|
|
|
retryCtx = RetryContext tries ctiRetryConf
|
2023-03-29 14:24:35 +03:00
|
|
|
|
eventProcessingTimeout = min upperBoundScheduledEventTimeout (unrefine $ strcTimeoutSeconds $ ctiRetryConf)
|
|
|
|
|
processScheduledEventAction =
|
|
|
|
|
runExceptT $
|
|
|
|
|
flip runReaderT (logger, httpMgr) $
|
|
|
|
|
processScheduledEvent
|
2023-03-30 08:51:18 +03:00
|
|
|
|
scheduledTriggerMetrics
|
2023-03-29 14:24:35 +03:00
|
|
|
|
id'
|
|
|
|
|
ctiHeaders
|
|
|
|
|
retryCtx
|
|
|
|
|
payload
|
|
|
|
|
ctiWebhookInfo
|
|
|
|
|
Cron
|
|
|
|
|
eventProcessedMaybe <-
|
|
|
|
|
timeout (fromInteger (diffTimeToMicroSeconds eventProcessingTimeout)) $ processScheduledEventAction
|
|
|
|
|
case eventProcessedMaybe of
|
|
|
|
|
Nothing -> do
|
|
|
|
|
let eventTimeoutMessage = "Cron Scheduled event " <> id' <<> " of cron trigger " <> name <<> " timed out while processing."
|
2023-04-10 15:25:44 +03:00
|
|
|
|
eventTimeoutError = err500 TimeoutErrorCode eventTimeoutMessage
|
2023-03-29 14:24:35 +03:00
|
|
|
|
logInternalError eventTimeoutError
|
2023-03-30 08:51:18 +03:00
|
|
|
|
runExceptT (processError id' retryCtx [] Cron (mkErrorObject eventTimeoutMessage) (HOther $ T.unpack eventTimeoutMessage) scheduledTriggerMetrics)
|
2023-03-29 14:24:35 +03:00
|
|
|
|
>>= (`onLeft` logInternalError)
|
|
|
|
|
Just finally -> onLeft finally logInternalError
|
2020-11-25 13:56:44 +03:00
|
|
|
|
removeEventFromLockedEvents id' lockedCronEvents
|
2020-05-13 15:33:16 +03:00
|
|
|
|
where
|
2020-07-14 22:00:58 +03:00
|
|
|
|
logInternalError err = liftIO . L.unLogger logger $ ScheduledTriggerInternalErr err
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2023-03-29 14:24:35 +03:00
|
|
|
|
mkErrorObject :: Text -> J.Value
|
|
|
|
|
mkErrorObject errorMessage =
|
|
|
|
|
J.object $ ["error" J..= errorMessage]
|
|
|
|
|
|
2021-07-02 20:24:49 +03:00
|
|
|
|
processOneOffScheduledEvents ::
|
2021-10-13 19:38:56 +03:00
|
|
|
|
( MonadIO m,
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
|
Tracing.MonadTrace m,
|
2023-03-29 14:24:35 +03:00
|
|
|
|
MonadMetadataStorage m,
|
|
|
|
|
MonadBaseControl IO m
|
2021-09-24 01:56:37 +03:00
|
|
|
|
) =>
|
2020-07-14 22:00:58 +03:00
|
|
|
|
Env.Environment ->
|
|
|
|
|
L.Logger L.Hasura ->
|
2020-05-13 15:33:16 +03:00
|
|
|
|
HTTP.Manager ->
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-11-25 13:56:44 +03:00
|
|
|
|
[OneOffScheduledEvent] ->
|
2020-09-07 09:15:15 +03:00
|
|
|
|
TVar (Set.Set OneOffScheduledEventId) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
|
m ()
|
2020-09-09 09:47:34 +03:00
|
|
|
|
processOneOffScheduledEvents
|
2020-07-14 22:00:58 +03:00
|
|
|
|
env
|
|
|
|
|
logger
|
2021-07-02 20:24:49 +03:00
|
|
|
|
httpMgr
|
2023-03-30 08:51:18 +03:00
|
|
|
|
scheduledTriggerMetrics
|
2021-07-02 20:24:49 +03:00
|
|
|
|
oneOffEvents
|
|
|
|
|
lockedOneOffScheduledEvents = do
|
2020-11-25 13:56:44 +03:00
|
|
|
|
-- save the locked one-off events that have been fetched from the
|
|
|
|
|
-- database, the events stored here will be unlocked in case a
|
|
|
|
|
-- graceful shutdown is initiated in midst of processing these events
|
|
|
|
|
saveLockedEvents (map _ooseId oneOffEvents) lockedOneOffScheduledEvents
|
2023-03-29 14:24:35 +03:00
|
|
|
|
forConcurrently_ oneOffEvents $ \OneOffScheduledEvent {..} -> do
|
2023-02-03 04:03:23 +03:00
|
|
|
|
(either logInternalError pure) =<< runExceptT do
|
2021-09-20 16:14:28 +03:00
|
|
|
|
let payload =
|
|
|
|
|
ScheduledEventWebhookPayload
|
|
|
|
|
_ooseId
|
|
|
|
|
Nothing
|
2020-11-25 13:56:44 +03:00
|
|
|
|
_ooseScheduledTime
|
|
|
|
|
(fromMaybe J.Null _oosePayload)
|
|
|
|
|
_ooseComment
|
|
|
|
|
(Just _ooseCreatedAt)
|
2022-01-19 07:46:42 +03:00
|
|
|
|
_ooseRequestTransform
|
|
|
|
|
_ooseResponseTransform
|
2020-11-25 13:56:44 +03:00
|
|
|
|
retryCtx = RetryContext _ooseTries _ooseRetryConf
|
2023-03-14 15:27:17 +03:00
|
|
|
|
resolvedWebhookInfoEither = resolveWebhookEither env _ooseWebhookConf
|
|
|
|
|
resolvedHeaderInfoEither = getHeaderInfosFromConfEither env _ooseHeaderConf
|
|
|
|
|
-- `webhookAndHeaderInfo` returns webhook and header info (and errors)
|
|
|
|
|
webhookAndHeaderInfo = case (resolvedWebhookInfoEither, resolvedHeaderInfoEither) of
|
|
|
|
|
(Right resolvedEventWebhookInfo, Right resolvedEventHeaderInfo) -> do
|
|
|
|
|
let resolvedWebhookEnvRecord = EnvRecord (getTemplateFromUrl _ooseWebhookConf) resolvedEventWebhookInfo
|
|
|
|
|
Right (resolvedWebhookEnvRecord, resolvedEventHeaderInfo)
|
|
|
|
|
(Left eventWebhookErrorVars, Right _) -> Left $ This eventWebhookErrorVars
|
|
|
|
|
(Right _, Left eventHeaderErrorVars) -> Left $ That eventHeaderErrorVars
|
|
|
|
|
(Left eventWebhookErrors, Left eventHeaderErrorVars) -> Left $ These eventWebhookErrors eventHeaderErrorVars
|
|
|
|
|
case webhookAndHeaderInfo of
|
|
|
|
|
Right (webhookEnvRecord, eventHeaderInfo) -> do
|
2023-03-29 14:24:35 +03:00
|
|
|
|
let processScheduledEventAction =
|
|
|
|
|
flip runReaderT (logger, httpMgr) $
|
2023-03-30 08:51:18 +03:00
|
|
|
|
processScheduledEvent scheduledTriggerMetrics _ooseId eventHeaderInfo retryCtx payload webhookEnvRecord OneOff
|
2023-03-29 14:24:35 +03:00
|
|
|
|
|
|
|
|
|
eventTimeout = unrefine $ strcTimeoutSeconds $ _ooseRetryConf
|
|
|
|
|
|
|
|
|
|
-- Try to process the event with a timeout of min(`uppserBoundScheduledEventTimeout`, event's response timeout),
|
|
|
|
|
-- so that we're never blocked forever while processing a single event.
|
|
|
|
|
--
|
|
|
|
|
-- If the request times out, then process it as an erroneous invocation and move on.
|
|
|
|
|
timeout (fromInteger (diffTimeToMicroSeconds (min upperBoundScheduledEventTimeout eventTimeout))) processScheduledEventAction
|
|
|
|
|
`onNothingM` ( do
|
|
|
|
|
let eventTimeoutMessage = "One-off Scheduled event " <> _ooseId <<> " timed out while processing."
|
2023-04-10 15:25:44 +03:00
|
|
|
|
eventTimeoutError = err500 TimeoutErrorCode eventTimeoutMessage
|
2023-03-29 14:24:35 +03:00
|
|
|
|
lift $ logInternalError eventTimeoutError
|
2023-03-30 08:51:18 +03:00
|
|
|
|
processError _ooseId retryCtx [] OneOff (mkErrorObject eventTimeoutMessage) (HOther $ T.unpack eventTimeoutMessage) scheduledTriggerMetrics
|
2023-03-29 14:24:35 +03:00
|
|
|
|
)
|
2023-03-14 15:27:17 +03:00
|
|
|
|
removeEventFromLockedEvents _ooseId lockedOneOffScheduledEvents
|
|
|
|
|
Left envVarError ->
|
|
|
|
|
processError
|
|
|
|
|
_ooseId
|
|
|
|
|
retryCtx
|
|
|
|
|
[]
|
|
|
|
|
OneOff
|
2023-03-29 14:24:35 +03:00
|
|
|
|
(mkErrorObject $ "Error creating the request. " <> (mkInvalidEnvVarErrMsg $ envVarError))
|
2023-03-14 15:27:17 +03:00
|
|
|
|
(HOther $ T.unpack $ qeError (err400 NotFound (mkInvalidEnvVarErrMsg envVarError)))
|
2023-03-30 08:51:18 +03:00
|
|
|
|
scheduledTriggerMetrics
|
2020-05-13 15:33:16 +03:00
|
|
|
|
where
|
2020-07-14 22:00:58 +03:00
|
|
|
|
logInternalError err = liftIO . L.unLogger logger $ ScheduledTriggerInternalErr err
|
2022-06-05 23:27:09 +03:00
|
|
|
|
getTemplateFromUrl url = printURLTemplate $ unInputWebhook url
|
2023-03-14 15:27:17 +03:00
|
|
|
|
mkInvalidEnvVarErrMsg envVarErrorValues = "The value for environment variables not found: " <> (getInvalidEnvVarText envVarErrorValues)
|
2023-03-29 14:24:35 +03:00
|
|
|
|
mkErrorObject :: Text -> J.Value
|
|
|
|
|
mkErrorObject errorMessage =
|
|
|
|
|
J.object $ ["error" J..= errorMessage]
|
2023-03-14 15:27:17 +03:00
|
|
|
|
getInvalidEnvVarText :: These ResolveWebhookError ResolveHeaderError -> Text
|
|
|
|
|
getInvalidEnvVarText (This a) = toTxt a
|
|
|
|
|
getInvalidEnvVarText (That b) = toTxt b
|
|
|
|
|
getInvalidEnvVarText (These a b) = toTxt a <> ", " <> toTxt b
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
processScheduledTriggers ::
|
2021-10-13 19:38:56 +03:00
|
|
|
|
( MonadIO m,
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
|
Tracing.MonadTrace m,
|
2023-03-29 14:24:35 +03:00
|
|
|
|
MonadMetadataStorage m,
|
|
|
|
|
MonadBaseControl IO m
|
2020-11-25 13:56:44 +03:00
|
|
|
|
) =>
|
2023-03-30 19:31:50 +03:00
|
|
|
|
IO Env.Environment ->
|
2020-07-14 22:00:58 +03:00
|
|
|
|
L.Logger L.Hasura ->
|
2023-01-30 09:06:45 +03:00
|
|
|
|
FetchedScheduledEventsStatsLogger ->
|
2020-05-13 15:33:16 +03:00
|
|
|
|
HTTP.Manager ->
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-05-13 15:33:16 +03:00
|
|
|
|
IO SchemaCache ->
|
2020-07-02 14:57:09 +03:00
|
|
|
|
LockedEventsCtx ->
|
2021-05-14 12:38:37 +03:00
|
|
|
|
m (Forever m)
|
2023-03-30 19:31:50 +03:00
|
|
|
|
processScheduledTriggers getEnvHook logger statsLogger httpMgr scheduledTriggerMetrics getSC LockedEventsCtx {..} = do
|
2021-05-14 12:38:37 +03:00
|
|
|
|
return $
|
|
|
|
|
Forever () $
|
2023-02-03 04:03:23 +03:00
|
|
|
|
const do
|
2023-04-10 15:25:44 +03:00
|
|
|
|
cronTriggersInfo <- scCronTriggers <$> liftIO getSC
|
2023-03-30 19:31:50 +03:00
|
|
|
|
env <- liftIO getEnvHook
|
2023-04-10 15:25:44 +03:00
|
|
|
|
getScheduledEventsForDelivery (Map.keys cronTriggersInfo) >>= \case
|
2020-11-25 13:56:44 +03:00
|
|
|
|
Left e -> logInternalError e
|
|
|
|
|
Right (cronEvents, oneOffEvents) -> do
|
2023-01-30 09:06:45 +03:00
|
|
|
|
logFetchedScheduledEventsStats statsLogger (CronEventsCount $ length cronEvents) (OneOffScheduledEventsCount $ length oneOffEvents)
|
2023-04-10 15:25:44 +03:00
|
|
|
|
processCronEvents logger httpMgr scheduledTriggerMetrics cronEvents cronTriggersInfo leCronEvents
|
2023-03-30 08:51:18 +03:00
|
|
|
|
processOneOffScheduledEvents env logger httpMgr scheduledTriggerMetrics oneOffEvents leOneOffEvents
|
2021-05-14 12:38:37 +03:00
|
|
|
|
-- NOTE: cron events are scheduled at times with minute resolution (as on
|
|
|
|
|
-- unix), while one-off events can be set for arbitrary times. The sleep
|
|
|
|
|
-- time here determines how overdue a scheduled event (cron or one-off)
|
|
|
|
|
-- might be before we begin processing:
|
2021-04-27 08:34:14 +03:00
|
|
|
|
liftIO $ sleep (seconds 10)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
where
|
|
|
|
|
logInternalError err = liftIO . L.unLogger logger $ ScheduledTriggerInternalErr err
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
processScheduledEvent ::
|
|
|
|
|
( MonadReader r m,
|
|
|
|
|
Has HTTP.Manager r,
|
|
|
|
|
Has (L.Logger L.Hasura) r,
|
|
|
|
|
MonadIO m,
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
|
Tracing.MonadTrace m,
|
2023-02-03 04:03:23 +03:00
|
|
|
|
MonadMetadataStorage m,
|
|
|
|
|
MonadError QErr m
|
2020-11-25 13:56:44 +03:00
|
|
|
|
) =>
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-11-25 13:56:44 +03:00
|
|
|
|
ScheduledEventId ->
|
|
|
|
|
[EventHeaderInfo] ->
|
|
|
|
|
RetryContext ->
|
|
|
|
|
ScheduledEventWebhookPayload ->
|
2022-06-05 23:27:09 +03:00
|
|
|
|
EnvRecord ResolvedWebhook ->
|
2020-05-13 15:33:16 +03:00
|
|
|
|
ScheduledEventType ->
|
|
|
|
|
m ()
|
2023-03-30 08:51:18 +03:00
|
|
|
|
processScheduledEvent scheduledTriggerMetrics eventId eventHeaders retryCtx payload webhookUrl type' =
|
Rewrite `Tracing` to allow for only one `TraceT` in the entire stack.
This PR is on top of #7789.
### Description
This PR entirely rewrites the API of the Tracing library, to make `interpTraceT` a thing of the past. Before this change, we ran traces by sticking a `TraceT` on top of whatever we were doing. This had several major drawbacks:
- we were carrying a bunch of `TraceT` across the codebase, and the entire codebase had to know about it
- we needed to carry a second class constraint around (`HasReporterM`) to be able to run all of those traces
- we kept having to do stack rewriting with `interpTraceT`, which went from inconvenient to horrible
- we had to declare several behavioral instances on `TraceT m`
This PR rewrite all of `Tracing` using a more conventional model: there is ONE `TraceT` at the bottom of the stack, and there is an associated class constraint `MonadTrace`: any part of the code that happens to satisfy `MonadTrace` is able to create new traces. We NEVER have to do stack rewriting, `interpTraceT` is gone, and `TraceT` and `Reporter` become implementation details that 99% of the code is blissfully unaware of: code that needs to do tracing only needs to declare that the monad in which it operates implements `MonadTrace`.
In doing so, this PR revealed **several bugs in the codebase**: places where we were expecting to trace something, but due to the default instance of `HasReporterM IO` we would actually not do anything. This PR also splits the code of `Tracing` in more byte-sized modules, with the goal of potentially moving to `server/lib` down the line.
### Remaining work
This PR is a draft; what's left to do is:
- [x] make Pro compile; i haven't updated `HasuraPro/Main` yet
- [x] document Tracing by writing a note that explains how to use the library, and the meaning of "reporter", "trace" and "span", as well as the pitfalls
- [x] discuss some of the trade-offs in the implementation, which is why i'm opening this PR already despite it not fully building yet
- [x] it depends on #7789 being merged first
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7791
GitOrigin-RevId: cadd32d039134c93ddbf364599a2f4dd988adea8
2023-03-13 20:37:16 +03:00
|
|
|
|
Tracing.newTrace Tracing.sampleAlways traceNote do
|
2020-05-13 15:33:16 +03:00
|
|
|
|
currentTime <- liftIO getCurrentTime
|
2020-11-25 13:56:44 +03:00
|
|
|
|
let retryConf = _rctxConf retryCtx
|
|
|
|
|
scheduledTime = sewpScheduledTime payload
|
|
|
|
|
if convertDuration (diffUTCTime currentTime scheduledTime)
|
2022-09-21 21:01:48 +03:00
|
|
|
|
> unrefine (strcToleranceSeconds retryConf)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
then processDead eventId type'
|
2020-05-13 15:33:16 +03:00
|
|
|
|
else do
|
2022-09-21 21:01:48 +03:00
|
|
|
|
let timeoutSeconds = round $ unrefine (strcTimeoutSeconds retryConf)
|
2020-05-13 15:33:16 +03:00
|
|
|
|
httpTimeout = HTTP.responseTimeoutMicro (timeoutSeconds * 1000000)
|
2022-06-05 23:27:09 +03:00
|
|
|
|
(headers, decodedHeaders) = prepareHeaders eventHeaders
|
2021-07-05 10:47:45 +03:00
|
|
|
|
extraLogCtx = ExtraLogContext eventId (sewpName payload)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
webhookReqBodyJson = J.toJSON payload
|
2020-07-28 20:52:44 +03:00
|
|
|
|
webhookReqBody = J.encode webhookReqBodyJson
|
2022-03-08 03:42:06 +03:00
|
|
|
|
requestTransform = sewpRequestTransform payload
|
2022-01-19 07:46:42 +03:00
|
|
|
|
responseTransform = mkResponseTransform <$> sewpResponseTransform payload
|
|
|
|
|
|
2021-12-07 01:39:29 +03:00
|
|
|
|
eitherReqRes <-
|
2021-09-29 11:13:30 +03:00
|
|
|
|
runExceptT $
|
2022-06-05 23:27:09 +03:00
|
|
|
|
mkRequest headers httpTimeout webhookReqBody requestTransform (_envVarValue webhookUrl) >>= \reqDetails -> do
|
2021-12-07 01:39:29 +03:00
|
|
|
|
let request = extractRequest reqDetails
|
2022-12-28 06:47:42 +03:00
|
|
|
|
logger e d = do
|
|
|
|
|
logHTTPForST e extraLogCtx d (_envVarName webhookUrl) decodedHeaders
|
|
|
|
|
liftIO $ do
|
|
|
|
|
case e of
|
|
|
|
|
Left _err -> pure ()
|
|
|
|
|
Right response ->
|
|
|
|
|
Prometheus.Counter.add
|
2023-03-30 08:51:18 +03:00
|
|
|
|
(stmScheduledTriggerBytesReceived scheduledTriggerMetrics)
|
2022-12-28 06:47:42 +03:00
|
|
|
|
(hrsSize response)
|
|
|
|
|
let RequestDetails {_rdOriginalSize, _rdTransformedSize} = d
|
|
|
|
|
in Prometheus.Counter.add
|
2023-03-30 08:51:18 +03:00
|
|
|
|
(stmScheduledTriggerBytesSent scheduledTriggerMetrics)
|
2022-12-28 06:47:42 +03:00
|
|
|
|
(fromMaybe _rdOriginalSize _rdTransformedSize)
|
2023-03-30 08:51:18 +03:00
|
|
|
|
case (type', e) of
|
|
|
|
|
(Cron, Left _err) -> Prometheus.Counter.inc (stmCronEventsInvocationTotalFailure scheduledTriggerMetrics)
|
|
|
|
|
(Cron, Right _) -> Prometheus.Counter.inc (stmCronEventsInvocationTotalSuccess scheduledTriggerMetrics)
|
|
|
|
|
(OneOff, Left _err) -> Prometheus.Counter.inc (stmOneOffEventsInvocationTotalFailure scheduledTriggerMetrics)
|
|
|
|
|
(OneOff, Right _) -> Prometheus.Counter.inc (stmOneOffEventsInvocationTotalSuccess scheduledTriggerMetrics)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
sessionVars = _rdSessionVars reqDetails
|
|
|
|
|
resp <- invokeRequest reqDetails responseTransform sessionVars logger
|
2021-12-07 01:39:29 +03:00
|
|
|
|
pure (request, resp)
|
|
|
|
|
case eitherReqRes of
|
|
|
|
|
Right (req, resp) ->
|
2023-03-22 02:59:42 +03:00
|
|
|
|
let reqBody = fromMaybe J.Null $ preview (HTTP.body . HTTP._RequestBodyLBS) req >>= J.decode @J.Value
|
2023-03-30 08:51:18 +03:00
|
|
|
|
in processSuccess eventId decodedHeaders type' reqBody resp scheduledTriggerMetrics
|
|
|
|
|
Left (HTTPError reqBody e) -> processError eventId retryCtx decodedHeaders type' reqBody e scheduledTriggerMetrics
|
2021-12-07 01:39:29 +03:00
|
|
|
|
Left (TransformationError _ e) -> do
|
2021-09-29 11:13:30 +03:00
|
|
|
|
-- Log The Transformation Error
|
|
|
|
|
logger :: L.Logger L.Hasura <- asks getter
|
2022-06-17 12:56:38 +03:00
|
|
|
|
L.unLogger logger $ L.UnstructuredLog L.LevelError (SB.fromLBS $ J.encode e)
|
2021-09-29 11:13:30 +03:00
|
|
|
|
|
|
|
|
|
-- Set event state to Error
|
2023-02-03 04:03:23 +03:00
|
|
|
|
liftEitherM $ setScheduledEventOp eventId (SEOpStatus SESError) type'
|
2020-09-16 01:03:41 +03:00
|
|
|
|
where
|
2020-11-25 13:56:44 +03:00
|
|
|
|
traceNote = "Scheduled trigger" <> foldMap ((": " <>) . triggerNameToTxt) (sewpName payload)
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
|
|
processError ::
|
2020-11-25 13:56:44 +03:00
|
|
|
|
( MonadIO m,
|
2023-02-03 04:03:23 +03:00
|
|
|
|
MonadMetadataStorage m,
|
|
|
|
|
MonadError QErr m
|
2020-11-25 13:56:44 +03:00
|
|
|
|
) =>
|
|
|
|
|
ScheduledEventId ->
|
|
|
|
|
RetryContext ->
|
2020-07-03 03:55:07 +03:00
|
|
|
|
[HeaderConf] ->
|
|
|
|
|
ScheduledEventType ->
|
|
|
|
|
J.Value ->
|
|
|
|
|
HTTPErr a ->
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-07-03 03:55:07 +03:00
|
|
|
|
m ()
|
2023-03-30 08:51:18 +03:00
|
|
|
|
processError eventId retryCtx decodedHeaders type' reqJson err scheduledTriggerMetric = do
|
2020-05-13 15:33:16 +03:00
|
|
|
|
let invocation = case err of
|
2021-09-20 16:14:28 +03:00
|
|
|
|
HClient httpException ->
|
|
|
|
|
let statusMaybe = getHTTPExceptionStatus httpException
|
2023-03-21 14:58:16 +03:00
|
|
|
|
in mkInvocation eventId statusMaybe decodedHeaders (SB.fromLBS $ httpExceptionErrorEncoding httpException) [] reqJson
|
2020-05-13 15:33:16 +03:00
|
|
|
|
HStatus errResp -> do
|
|
|
|
|
let respPayload = hrsBody errResp
|
|
|
|
|
respHeaders = hrsHeaders errResp
|
|
|
|
|
respStatus = hrsStatus errResp
|
2021-09-20 16:14:28 +03:00
|
|
|
|
mkInvocation eventId (Just respStatus) decodedHeaders respPayload respHeaders reqJson
|
2020-05-13 15:33:16 +03:00
|
|
|
|
HOther detail -> do
|
2022-06-17 12:56:38 +03:00
|
|
|
|
let errMsg = (SB.fromLBS $ J.encode detail)
|
2021-09-20 16:14:28 +03:00
|
|
|
|
mkInvocation eventId (Just 500) decodedHeaders errMsg [] reqJson
|
2023-02-03 04:03:23 +03:00
|
|
|
|
liftEitherM $ insertScheduledEventInvocation invocation type'
|
2023-03-30 08:51:18 +03:00
|
|
|
|
retryOrMarkError eventId retryCtx err type' scheduledTriggerMetric
|
2020-11-25 13:56:44 +03:00
|
|
|
|
|
|
|
|
|
retryOrMarkError ::
|
2023-02-03 04:03:23 +03:00
|
|
|
|
(MonadIO m, MonadMetadataStorage m, MonadError QErr m) =>
|
2020-11-25 13:56:44 +03:00
|
|
|
|
ScheduledEventId ->
|
|
|
|
|
RetryContext ->
|
|
|
|
|
HTTPErr a ->
|
|
|
|
|
ScheduledEventType ->
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-11-25 13:56:44 +03:00
|
|
|
|
m ()
|
2023-03-30 08:51:18 +03:00
|
|
|
|
retryOrMarkError eventId retryCtx err type' scheduledTriggerMetric = do
|
2020-11-25 13:56:44 +03:00
|
|
|
|
let RetryContext tries retryConf = retryCtx
|
|
|
|
|
mRetryHeader = getRetryAfterHeaderFromHTTPErr err
|
2020-05-13 15:33:16 +03:00
|
|
|
|
mRetryHeaderSeconds = parseRetryHeaderValue =<< mRetryHeader
|
2020-11-25 13:56:44 +03:00
|
|
|
|
triesExhausted = tries >= strcNumRetries retryConf
|
2020-05-13 15:33:16 +03:00
|
|
|
|
noRetryHeader = isNothing mRetryHeaderSeconds
|
|
|
|
|
if triesExhausted && noRetryHeader
|
2023-03-30 08:51:18 +03:00
|
|
|
|
then do
|
|
|
|
|
liftEitherM $ setScheduledEventOp eventId (SEOpStatus SESError) type'
|
|
|
|
|
case type' of
|
|
|
|
|
Cron -> liftIO $ Prometheus.Counter.inc (stmCronEventsProcessedTotalFailure scheduledTriggerMetric)
|
|
|
|
|
OneOff -> liftIO $ Prometheus.Counter.inc (stmOneOffEventsProcessedTotalFailure scheduledTriggerMetric)
|
2020-05-13 15:33:16 +03:00
|
|
|
|
else do
|
|
|
|
|
currentTime <- liftIO getCurrentTime
|
|
|
|
|
let delay =
|
|
|
|
|
fromMaybe
|
2022-09-21 21:01:48 +03:00
|
|
|
|
( round $ unrefine (strcRetryIntervalSeconds retryConf)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
)
|
|
|
|
|
mRetryHeaderSeconds
|
2020-05-13 15:33:16 +03:00
|
|
|
|
diff = fromIntegral delay
|
|
|
|
|
retryTime = addUTCTime diff currentTime
|
2023-02-03 04:03:23 +03:00
|
|
|
|
liftEitherM $ setScheduledEventOp eventId (SEOpRetry retryTime) type'
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
|
|
{- Note [Scheduled event lifecycle]
|
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
|
Scheduled events move between six different states over the course of their
|
|
|
|
|
lifetime, as represented by the following flowchart:
|
Deploy server documentation to github page in CI
_(This PR is on top of #3352.)_
## Description
This PR overhauls our documentation CI steps to push all generated server documentation to the `gh-pages` branch of the OSS repo. The goal of this PR is to arrive in the situation where `https://hasura.github.io/graphql-engine/server/` is automatically populated to contain the following:
- all the markdown files from `server/documentation`, copied verbatim, no transformation applied
- all the notes, collected from the code by the `extract-notes.sh` script, in `server/notes`
- the generated haddock documentation for each major release or branch in `server/haddock`.
To do so, this PR does the following:
- it includes the script to extract notes from #3352,
- it rewrites the documentation checking CI step, to generate the notes and publish the resulting "server/documentation" folder,
- it includes a new CI step to deploy the documentation to the `gh-pages` branch
Of note:
- we will generate a different haddock folder for each main branch and release; in practice, that means the _main_, _stable_, _alpha_, _beta_ branches, and every build tagged with a version number
- the step that builds the haddock documentation checks that ALL projects in the repo build, including pro, but the deploy only deploys the graphql-engine documentation, as it pushes it to a publicly-accessible place
## Required work
**DO NOT MERGE THIS PR IT IS NOT READY**. Some work needs to go into this PR before it is ready.
First of all: the `gh-pages` branch of the OSS repo does NOT yet contain the documentation scaffolding that this new process assumes. At the bare minimum, it should be a orphan branch that contains a top-level README.md file, and a _server_ folder. An example of the bare minimum required can be previewed [on my fork](https://nicuveo.github.io/graphql-engine/server/).
The content of the `server/documentation` folder needs to be adjusted to reflect this; at the very least, a `README.md` file needs to be added to do the indexing (again, see the placeholder [on my fork](https://nicuveo.github.io/graphql-engine/server/) for an example).
This way of publishing documentation must be validated against [proposed changes to the documentation](https://github.com/hasura/graphql-engine-mono/pull/3294). @marionschleifer what do you think?
~~The buildkite code in this branch is currently untested, and I am not sure how to test it.~~
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3380
GitOrigin-RevId: b24f6759c64ae29886c1f1b481b172febc512032
2022-01-31 16:15:31 +03:00
|
|
|
|
|
|
|
|
|
┌───────────┐ ┌────────┐ ┌───────────┐
|
|
|
|
|
│ scheduled │─(1)─→│ locked │─(2)─→│ delivered │
|
|
|
|
|
└───────────┘ └────────┘ └───────────┘
|
|
|
|
|
↑ │ ┌───────┐
|
|
|
|
|
└────(3)───────┼─────(4)──→│ error │
|
|
|
|
|
│ └───────┘
|
|
|
|
|
│ ┌──────┐
|
|
|
|
|
└─────(5)──→│ dead │
|
|
|
|
|
└──────┘
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
|
|
When a scheduled event is first created, it starts in the 'scheduled' state,
|
|
|
|
|
and it can transition to other states in the following ways:
|
Deploy server documentation to github page in CI
_(This PR is on top of #3352.)_
## Description
This PR overhauls our documentation CI steps to push all generated server documentation to the `gh-pages` branch of the OSS repo. The goal of this PR is to arrive in the situation where `https://hasura.github.io/graphql-engine/server/` is automatically populated to contain the following:
- all the markdown files from `server/documentation`, copied verbatim, no transformation applied
- all the notes, collected from the code by the `extract-notes.sh` script, in `server/notes`
- the generated haddock documentation for each major release or branch in `server/haddock`.
To do so, this PR does the following:
- it includes the script to extract notes from #3352,
- it rewrites the documentation checking CI step, to generate the notes and publish the resulting "server/documentation" folder,
- it includes a new CI step to deploy the documentation to the `gh-pages` branch
Of note:
- we will generate a different haddock folder for each main branch and release; in practice, that means the _main_, _stable_, _alpha_, _beta_ branches, and every build tagged with a version number
- the step that builds the haddock documentation checks that ALL projects in the repo build, including pro, but the deploy only deploys the graphql-engine documentation, as it pushes it to a publicly-accessible place
## Required work
**DO NOT MERGE THIS PR IT IS NOT READY**. Some work needs to go into this PR before it is ready.
First of all: the `gh-pages` branch of the OSS repo does NOT yet contain the documentation scaffolding that this new process assumes. At the bare minimum, it should be a orphan branch that contains a top-level README.md file, and a _server_ folder. An example of the bare minimum required can be previewed [on my fork](https://nicuveo.github.io/graphql-engine/server/).
The content of the `server/documentation` folder needs to be adjusted to reflect this; at the very least, a `README.md` file needs to be added to do the indexing (again, see the placeholder [on my fork](https://nicuveo.github.io/graphql-engine/server/) for an example).
This way of publishing documentation must be validated against [proposed changes to the documentation](https://github.com/hasura/graphql-engine-mono/pull/3294). @marionschleifer what do you think?
~~The buildkite code in this branch is currently untested, and I am not sure how to test it.~~
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3380
GitOrigin-RevId: b24f6759c64ae29886c1f1b481b172febc512032
2022-01-31 16:15:31 +03:00
|
|
|
|
1. When graphql-engine fetches a scheduled event from the database to process
|
2020-05-13 15:33:16 +03:00
|
|
|
|
it, it sets its state to 'locked'. This prevents multiple graphql-engine
|
|
|
|
|
instances running on the same database from processing the same
|
|
|
|
|
scheduled event concurrently.
|
Deploy server documentation to github page in CI
_(This PR is on top of #3352.)_
## Description
This PR overhauls our documentation CI steps to push all generated server documentation to the `gh-pages` branch of the OSS repo. The goal of this PR is to arrive in the situation where `https://hasura.github.io/graphql-engine/server/` is automatically populated to contain the following:
- all the markdown files from `server/documentation`, copied verbatim, no transformation applied
- all the notes, collected from the code by the `extract-notes.sh` script, in `server/notes`
- the generated haddock documentation for each major release or branch in `server/haddock`.
To do so, this PR does the following:
- it includes the script to extract notes from #3352,
- it rewrites the documentation checking CI step, to generate the notes and publish the resulting "server/documentation" folder,
- it includes a new CI step to deploy the documentation to the `gh-pages` branch
Of note:
- we will generate a different haddock folder for each main branch and release; in practice, that means the _main_, _stable_, _alpha_, _beta_ branches, and every build tagged with a version number
- the step that builds the haddock documentation checks that ALL projects in the repo build, including pro, but the deploy only deploys the graphql-engine documentation, as it pushes it to a publicly-accessible place
## Required work
**DO NOT MERGE THIS PR IT IS NOT READY**. Some work needs to go into this PR before it is ready.
First of all: the `gh-pages` branch of the OSS repo does NOT yet contain the documentation scaffolding that this new process assumes. At the bare minimum, it should be a orphan branch that contains a top-level README.md file, and a _server_ folder. An example of the bare minimum required can be previewed [on my fork](https://nicuveo.github.io/graphql-engine/server/).
The content of the `server/documentation` folder needs to be adjusted to reflect this; at the very least, a `README.md` file needs to be added to do the indexing (again, see the placeholder [on my fork](https://nicuveo.github.io/graphql-engine/server/) for an example).
This way of publishing documentation must be validated against [proposed changes to the documentation](https://github.com/hasura/graphql-engine-mono/pull/3294). @marionschleifer what do you think?
~~The buildkite code in this branch is currently untested, and I am not sure how to test it.~~
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3380
GitOrigin-RevId: b24f6759c64ae29886c1f1b481b172febc512032
2022-01-31 16:15:31 +03:00
|
|
|
|
2. When a scheduled event is processed successfully, it is marked 'delivered'.
|
|
|
|
|
3. If a scheduled event fails to be processed, but it hasn’t yet reached
|
2020-05-13 15:33:16 +03:00
|
|
|
|
its maximum retry limit, its retry counter is incremented and
|
|
|
|
|
it is returned to the 'scheduled' state.
|
Deploy server documentation to github page in CI
_(This PR is on top of #3352.)_
## Description
This PR overhauls our documentation CI steps to push all generated server documentation to the `gh-pages` branch of the OSS repo. The goal of this PR is to arrive in the situation where `https://hasura.github.io/graphql-engine/server/` is automatically populated to contain the following:
- all the markdown files from `server/documentation`, copied verbatim, no transformation applied
- all the notes, collected from the code by the `extract-notes.sh` script, in `server/notes`
- the generated haddock documentation for each major release or branch in `server/haddock`.
To do so, this PR does the following:
- it includes the script to extract notes from #3352,
- it rewrites the documentation checking CI step, to generate the notes and publish the resulting "server/documentation" folder,
- it includes a new CI step to deploy the documentation to the `gh-pages` branch
Of note:
- we will generate a different haddock folder for each main branch and release; in practice, that means the _main_, _stable_, _alpha_, _beta_ branches, and every build tagged with a version number
- the step that builds the haddock documentation checks that ALL projects in the repo build, including pro, but the deploy only deploys the graphql-engine documentation, as it pushes it to a publicly-accessible place
## Required work
**DO NOT MERGE THIS PR IT IS NOT READY**. Some work needs to go into this PR before it is ready.
First of all: the `gh-pages` branch of the OSS repo does NOT yet contain the documentation scaffolding that this new process assumes. At the bare minimum, it should be a orphan branch that contains a top-level README.md file, and a _server_ folder. An example of the bare minimum required can be previewed [on my fork](https://nicuveo.github.io/graphql-engine/server/).
The content of the `server/documentation` folder needs to be adjusted to reflect this; at the very least, a `README.md` file needs to be added to do the indexing (again, see the placeholder [on my fork](https://nicuveo.github.io/graphql-engine/server/) for an example).
This way of publishing documentation must be validated against [proposed changes to the documentation](https://github.com/hasura/graphql-engine-mono/pull/3294). @marionschleifer what do you think?
~~The buildkite code in this branch is currently untested, and I am not sure how to test it.~~
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3380
GitOrigin-RevId: b24f6759c64ae29886c1f1b481b172febc512032
2022-01-31 16:15:31 +03:00
|
|
|
|
4. If a scheduled event fails to be processed and *has* reached its
|
2020-05-13 15:33:16 +03:00
|
|
|
|
retry limit, its state is set to 'error'.
|
Deploy server documentation to github page in CI
_(This PR is on top of #3352.)_
## Description
This PR overhauls our documentation CI steps to push all generated server documentation to the `gh-pages` branch of the OSS repo. The goal of this PR is to arrive in the situation where `https://hasura.github.io/graphql-engine/server/` is automatically populated to contain the following:
- all the markdown files from `server/documentation`, copied verbatim, no transformation applied
- all the notes, collected from the code by the `extract-notes.sh` script, in `server/notes`
- the generated haddock documentation for each major release or branch in `server/haddock`.
To do so, this PR does the following:
- it includes the script to extract notes from #3352,
- it rewrites the documentation checking CI step, to generate the notes and publish the resulting "server/documentation" folder,
- it includes a new CI step to deploy the documentation to the `gh-pages` branch
Of note:
- we will generate a different haddock folder for each main branch and release; in practice, that means the _main_, _stable_, _alpha_, _beta_ branches, and every build tagged with a version number
- the step that builds the haddock documentation checks that ALL projects in the repo build, including pro, but the deploy only deploys the graphql-engine documentation, as it pushes it to a publicly-accessible place
## Required work
**DO NOT MERGE THIS PR IT IS NOT READY**. Some work needs to go into this PR before it is ready.
First of all: the `gh-pages` branch of the OSS repo does NOT yet contain the documentation scaffolding that this new process assumes. At the bare minimum, it should be a orphan branch that contains a top-level README.md file, and a _server_ folder. An example of the bare minimum required can be previewed [on my fork](https://nicuveo.github.io/graphql-engine/server/).
The content of the `server/documentation` folder needs to be adjusted to reflect this; at the very least, a `README.md` file needs to be added to do the indexing (again, see the placeholder [on my fork](https://nicuveo.github.io/graphql-engine/server/) for an example).
This way of publishing documentation must be validated against [proposed changes to the documentation](https://github.com/hasura/graphql-engine-mono/pull/3294). @marionschleifer what do you think?
~~The buildkite code in this branch is currently untested, and I am not sure how to test it.~~
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3380
GitOrigin-RevId: b24f6759c64ae29886c1f1b481b172febc512032
2022-01-31 16:15:31 +03:00
|
|
|
|
5. If for whatever reason the difference between the current time and the
|
2020-05-13 15:33:16 +03:00
|
|
|
|
scheduled time is greater than the tolerance of the scheduled event, it
|
|
|
|
|
will not be processed and its state will be set to 'dead'.
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
processSuccess ::
|
2023-03-30 08:51:18 +03:00
|
|
|
|
(MonadMetadataStorage m, MonadError QErr m, MonadIO m) =>
|
2020-11-25 13:56:44 +03:00
|
|
|
|
ScheduledEventId ->
|
2020-07-03 03:55:07 +03:00
|
|
|
|
[HeaderConf] ->
|
|
|
|
|
ScheduledEventType ->
|
|
|
|
|
J.Value ->
|
|
|
|
|
HTTPResp a ->
|
2023-03-30 08:51:18 +03:00
|
|
|
|
ScheduledTriggerMetrics ->
|
2020-07-03 03:55:07 +03:00
|
|
|
|
m ()
|
2023-03-30 08:51:18 +03:00
|
|
|
|
processSuccess eventId decodedHeaders type' reqBodyJson resp scheduledTriggerMetric = do
|
2020-05-13 15:33:16 +03:00
|
|
|
|
let respBody = hrsBody resp
|
|
|
|
|
respHeaders = hrsHeaders resp
|
|
|
|
|
respStatus = hrsStatus resp
|
2021-09-20 16:14:28 +03:00
|
|
|
|
invocation = mkInvocation eventId (Just respStatus) decodedHeaders respBody respHeaders reqBodyJson
|
2023-02-03 04:03:23 +03:00
|
|
|
|
liftEitherM $ insertScheduledEventInvocation invocation type'
|
|
|
|
|
liftEitherM $ setScheduledEventOp eventId (SEOpStatus SESDelivered) type'
|
2023-03-30 08:51:18 +03:00
|
|
|
|
case type' of
|
|
|
|
|
Cron -> liftIO $ Prometheus.Counter.inc (stmCronEventsProcessedTotalSuccess scheduledTriggerMetric)
|
|
|
|
|
OneOff -> liftIO $ Prometheus.Counter.inc (stmOneOffEventsProcessedTotalSuccess scheduledTriggerMetric)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
|
|
|
|
|
processDead ::
|
2023-02-03 04:03:23 +03:00
|
|
|
|
(MonadMetadataStorage m, MonadError QErr m) =>
|
2020-11-25 13:56:44 +03:00
|
|
|
|
ScheduledEventId ->
|
|
|
|
|
ScheduledEventType ->
|
|
|
|
|
m ()
|
|
|
|
|
processDead eventId type' =
|
2023-02-03 04:03:23 +03:00
|
|
|
|
liftEitherM $ setScheduledEventOp eventId (SEOpStatus SESDead) type'
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
|
|
mkInvocation ::
|
2020-11-25 13:56:44 +03:00
|
|
|
|
ScheduledEventId ->
|
2021-09-20 16:14:28 +03:00
|
|
|
|
Maybe Int ->
|
2020-07-03 03:55:07 +03:00
|
|
|
|
[HeaderConf] ->
|
2022-06-17 12:56:38 +03:00
|
|
|
|
SB.SerializableBlob ->
|
2020-07-03 03:55:07 +03:00
|
|
|
|
[HeaderConf] ->
|
|
|
|
|
J.Value ->
|
2020-11-25 13:56:44 +03:00
|
|
|
|
(Invocation 'ScheduledType)
|
2021-09-20 16:14:28 +03:00
|
|
|
|
mkInvocation eventId status reqHeaders respBody respHeaders reqBodyJson =
|
|
|
|
|
Invocation
|
|
|
|
|
eventId
|
|
|
|
|
status
|
|
|
|
|
(mkWebhookReq reqBodyJson reqHeaders invocationVersionST)
|
|
|
|
|
(mkInvocationResp status respBody respHeaders)
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
-- metadata database transactions
|
|
|
|
|
|
2021-04-27 08:34:14 +03:00
|
|
|
|
-- | Get cron trigger stats for cron jobs with fewer than 100 future reified
|
|
|
|
|
-- events in the database
|
|
|
|
|
--
|
|
|
|
|
-- The point here is to maintain a certain number of future events so the user
|
|
|
|
|
-- can kind of see what's coming up, and obviously to give 'processCronEvents'
|
|
|
|
|
-- something to do.
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
getDeprivedCronTriggerStatsTx :: [TriggerName] -> PG.TxE QErr [CronTriggerStats]
|
2021-05-26 19:19:26 +03:00
|
|
|
|
getDeprivedCronTriggerStatsTx cronTriggerNames =
|
2020-11-25 13:56:44 +03:00
|
|
|
|
map (\(n, count, maxTx) -> CronTriggerStats n count maxTx)
|
2022-10-07 14:55:42 +03:00
|
|
|
|
<$> PG.withQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2021-05-26 19:19:26 +03:00
|
|
|
|
SELECT t.trigger_name, coalesce(q.upcoming_events_count, 0), coalesce(q.max_scheduled_time, now())
|
|
|
|
|
FROM (SELECT UNNEST ($1::text[]) as trigger_name) as t
|
|
|
|
|
LEFT JOIN
|
2020-11-25 13:56:44 +03:00
|
|
|
|
( SELECT
|
|
|
|
|
trigger_name,
|
2021-05-26 19:19:26 +03:00
|
|
|
|
count(1) as upcoming_events_count,
|
2020-11-25 13:56:44 +03:00
|
|
|
|
max(scheduled_time) as max_scheduled_time
|
|
|
|
|
FROM hdb_catalog.hdb_cron_events
|
|
|
|
|
WHERE tries = 0 and status = 'scheduled'
|
|
|
|
|
GROUP BY trigger_name
|
|
|
|
|
) AS q
|
2021-05-26 19:19:26 +03:00
|
|
|
|
ON t.trigger_name = q.trigger_name
|
|
|
|
|
WHERE coalesce(q.upcoming_events_count, 0) < 100
|
|
|
|
|
|]
|
|
|
|
|
(Identity $ PGTextArray $ map triggerNameToTxt cronTriggerNames)
|
|
|
|
|
True
|
2020-11-25 13:56:44 +03:00
|
|
|
|
|
2021-04-27 08:34:14 +03:00
|
|
|
|
-- TODO
|
|
|
|
|
-- - cron events have minute resolution, while one-off events have arbitrary
|
|
|
|
|
-- resolution, so it doesn't make sense to fetch them at the same rate
|
|
|
|
|
-- - if we decide to fetch cron events less frequently we should wake up that
|
|
|
|
|
-- thread at second 0 of every minute, and then pass hasura's now time into
|
|
|
|
|
-- the query (since the DB may disagree about the time)
|
2023-04-10 15:25:44 +03:00
|
|
|
|
getScheduledEventsForDeliveryTx :: [TriggerName] -> PG.TxE QErr ([CronEvent], [OneOffScheduledEvent])
|
|
|
|
|
getScheduledEventsForDeliveryTx cronTriggerNames =
|
2020-11-25 13:56:44 +03:00
|
|
|
|
(,) <$> getCronEventsForDelivery <*> getOneOffEventsForDelivery
|
|
|
|
|
where
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
getCronEventsForDelivery :: PG.TxE QErr [CronEvent]
|
2020-11-25 13:56:44 +03:00
|
|
|
|
getCronEventsForDelivery =
|
2022-09-21 21:40:41 +03:00
|
|
|
|
map (PG.getViaJSON . runIdentity)
|
2022-10-07 14:55:42 +03:00
|
|
|
|
<$> PG.withQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
WITH cte AS
|
|
|
|
|
( UPDATE hdb_catalog.hdb_cron_events
|
|
|
|
|
SET status = 'locked'
|
|
|
|
|
WHERE id IN ( SELECT t.id
|
|
|
|
|
FROM hdb_catalog.hdb_cron_events t
|
|
|
|
|
WHERE ( t.status = 'scheduled'
|
|
|
|
|
and (
|
|
|
|
|
(t.next_retry_at is NULL and t.scheduled_time <= now()) or
|
|
|
|
|
(t.next_retry_at is not NULL and t.next_retry_at <= now())
|
|
|
|
|
)
|
2023-04-10 15:25:44 +03:00
|
|
|
|
) AND trigger_name = ANY($1)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
FOR UPDATE SKIP LOCKED
|
|
|
|
|
)
|
|
|
|
|
RETURNING *
|
|
|
|
|
)
|
|
|
|
|
SELECT row_to_json(t.*) FROM cte AS t
|
|
|
|
|
|]
|
2023-04-10 15:25:44 +03:00
|
|
|
|
(Identity $ PGTextArray $ triggerNameToTxt <$> cronTriggerNames)
|
2020-11-25 13:56:44 +03:00
|
|
|
|
True
|
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
getOneOffEventsForDelivery :: PG.TxE QErr [OneOffScheduledEvent]
|
2020-11-25 13:56:44 +03:00
|
|
|
|
getOneOffEventsForDelivery = do
|
2022-09-21 21:40:41 +03:00
|
|
|
|
map (PG.getViaJSON . runIdentity)
|
2022-10-07 14:55:42 +03:00
|
|
|
|
<$> PG.withQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
WITH cte AS (
|
|
|
|
|
UPDATE hdb_catalog.hdb_scheduled_events
|
|
|
|
|
SET status = 'locked'
|
|
|
|
|
WHERE id IN ( SELECT t.id
|
|
|
|
|
FROM hdb_catalog.hdb_scheduled_events t
|
|
|
|
|
WHERE ( t.status = 'scheduled'
|
|
|
|
|
and (
|
|
|
|
|
(t.next_retry_at is NULL and t.scheduled_time <= now()) or
|
|
|
|
|
(t.next_retry_at is not NULL and t.next_retry_at <= now())
|
|
|
|
|
)
|
|
|
|
|
)
|
|
|
|
|
FOR UPDATE SKIP LOCKED
|
|
|
|
|
)
|
|
|
|
|
RETURNING *
|
|
|
|
|
)
|
|
|
|
|
SELECT row_to_json(t.*) FROM cte AS t
|
|
|
|
|
|]
|
|
|
|
|
()
|
|
|
|
|
False
|
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
insertInvocationTx :: Invocation 'ScheduledType -> ScheduledEventType -> PG.TxE QErr ()
|
2020-11-25 13:56:44 +03:00
|
|
|
|
insertInvocationTx invo type' = do
|
2020-05-13 15:33:16 +03:00
|
|
|
|
case type' of
|
2020-09-09 09:47:34 +03:00
|
|
|
|
Cron -> do
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-05-13 15:33:16 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
INSERT INTO hdb_catalog.hdb_cron_event_invocation_logs
|
|
|
|
|
(event_id, status, request, response)
|
|
|
|
|
VALUES ($1, $2, $3, $4)
|
|
|
|
|
|]
|
|
|
|
|
( iEventId invo,
|
2021-09-20 16:14:28 +03:00
|
|
|
|
fromIntegral <$> iStatus invo :: Maybe Int64,
|
2022-09-21 21:40:41 +03:00
|
|
|
|
PG.ViaJSON $ J.toJSON $ iRequest invo,
|
|
|
|
|
PG.ViaJSON $ J.toJSON $ iResponse invo
|
2020-05-13 15:33:16 +03:00
|
|
|
|
)
|
|
|
|
|
True
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-05-13 15:33:16 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_cron_events
|
|
|
|
|
SET tries = tries + 1
|
|
|
|
|
WHERE id = $1
|
|
|
|
|
|]
|
|
|
|
|
(Identity $ iEventId invo)
|
|
|
|
|
True
|
2020-09-09 09:47:34 +03:00
|
|
|
|
OneOff -> do
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-05-13 15:33:16 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
INSERT INTO hdb_catalog.hdb_scheduled_event_invocation_logs
|
|
|
|
|
(event_id, status, request, response)
|
|
|
|
|
VALUES ($1, $2, $3, $4)
|
|
|
|
|
|]
|
|
|
|
|
( iEventId invo,
|
2021-09-20 16:14:28 +03:00
|
|
|
|
fromIntegral <$> iStatus invo :: Maybe Int64,
|
2022-09-21 21:40:41 +03:00
|
|
|
|
PG.ViaJSON $ J.toJSON $ iRequest invo,
|
|
|
|
|
PG.ViaJSON $ J.toJSON $ iResponse invo
|
2020-05-13 15:33:16 +03:00
|
|
|
|
)
|
|
|
|
|
True
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-05-13 15:33:16 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-05-13 15:33:16 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_scheduled_events
|
|
|
|
|
SET tries = tries + 1
|
|
|
|
|
WHERE id = $1
|
|
|
|
|
|]
|
|
|
|
|
(Identity $ iEventId invo)
|
|
|
|
|
True
|
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
setScheduledEventOpTx ::
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
ScheduledEventId -> ScheduledEventOp -> ScheduledEventType -> PG.TxE QErr ()
|
2020-11-25 13:56:44 +03:00
|
|
|
|
setScheduledEventOpTx eventId op type' = case op of
|
|
|
|
|
SEOpRetry time -> setRetry time
|
|
|
|
|
SEOpStatus status -> setStatus status
|
2020-05-13 15:33:16 +03:00
|
|
|
|
where
|
2020-11-25 13:56:44 +03:00
|
|
|
|
setRetry time =
|
|
|
|
|
case type' of
|
|
|
|
|
Cron ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_cron_events
|
|
|
|
|
SET next_retry_at = $1,
|
|
|
|
|
STATUS = 'scheduled'
|
|
|
|
|
WHERE id = $2
|
|
|
|
|
|]
|
|
|
|
|
(time, eventId)
|
|
|
|
|
True
|
|
|
|
|
OneOff ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_scheduled_events
|
|
|
|
|
SET next_retry_at = $1,
|
|
|
|
|
STATUS = 'scheduled'
|
|
|
|
|
WHERE id = $2
|
|
|
|
|
|]
|
|
|
|
|
(time, eventId)
|
|
|
|
|
True
|
|
|
|
|
setStatus status =
|
|
|
|
|
case type' of
|
|
|
|
|
Cron -> do
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_cron_events
|
|
|
|
|
SET status = $2
|
|
|
|
|
WHERE id = $1
|
|
|
|
|
|]
|
|
|
|
|
(eventId, status)
|
|
|
|
|
True
|
|
|
|
|
OneOff -> do
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_scheduled_events
|
|
|
|
|
SET status = $2
|
|
|
|
|
WHERE id = $1
|
|
|
|
|
|]
|
|
|
|
|
(eventId, status)
|
|
|
|
|
True
|
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
unlockScheduledEventsTx :: ScheduledEventType -> [ScheduledEventId] -> PG.TxE QErr Int
|
2020-11-25 13:56:44 +03:00
|
|
|
|
unlockScheduledEventsTx type' eventIds =
|
2021-05-26 19:19:26 +03:00
|
|
|
|
let eventIdsTextArray = map unEventId eventIds
|
2020-11-25 13:56:44 +03:00
|
|
|
|
in case type' of
|
|
|
|
|
Cron ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
(runIdentity . PG.getRow)
|
|
|
|
|
<$> PG.withQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
WITH "cte" AS
|
|
|
|
|
(UPDATE hdb_catalog.hdb_cron_events
|
|
|
|
|
SET status = 'scheduled'
|
|
|
|
|
WHERE id = ANY($1::text[]) and status = 'locked'
|
|
|
|
|
RETURNING *)
|
|
|
|
|
SELECT count(*) FROM "cte"
|
2021-05-26 19:19:26 +03:00
|
|
|
|
|]
|
|
|
|
|
(Identity $ PGTextArray eventIdsTextArray)
|
|
|
|
|
True
|
2020-11-25 13:56:44 +03:00
|
|
|
|
OneOff ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
(runIdentity . PG.getRow)
|
|
|
|
|
<$> PG.withQE
|
2020-11-25 13:56:44 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
WITH "cte" AS
|
|
|
|
|
(UPDATE hdb_catalog.hdb_scheduled_events
|
|
|
|
|
SET status = 'scheduled'
|
|
|
|
|
WHERE id = ANY($1::text[]) AND status = 'locked'
|
|
|
|
|
RETURNING *)
|
|
|
|
|
SELECT count(*) FROM "cte"
|
2021-05-26 19:19:26 +03:00
|
|
|
|
|]
|
|
|
|
|
(Identity $ PGTextArray eventIdsTextArray)
|
|
|
|
|
True
|
2020-11-25 13:56:44 +03:00
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
unlockAllLockedScheduledEventsTx :: PG.TxE QErr ()
|
2020-11-25 13:56:44 +03:00
|
|
|
|
unlockAllLockedScheduledEventsTx = do
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-07-02 14:57:09 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-07-02 14:57:09 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_cron_events
|
|
|
|
|
SET status = 'scheduled'
|
|
|
|
|
WHERE status = 'locked'
|
|
|
|
|
|]
|
|
|
|
|
()
|
|
|
|
|
True
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2020-07-02 14:57:09 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2020-07-02 14:57:09 +03:00
|
|
|
|
UPDATE hdb_catalog.hdb_scheduled_events
|
|
|
|
|
SET status = 'scheduled'
|
|
|
|
|
WHERE status = 'locked'
|
|
|
|
|
|]
|
|
|
|
|
()
|
|
|
|
|
True
|
2020-11-25 13:56:44 +03:00
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
insertCronEventsTx :: [CronEventSeed] -> PG.TxE QErr ()
|
2021-09-13 21:00:53 +03:00
|
|
|
|
insertCronEventsTx cronSeeds = do
|
|
|
|
|
let insertCronEventsSql =
|
|
|
|
|
TB.run $
|
|
|
|
|
toSQL
|
|
|
|
|
S.SQLInsert
|
|
|
|
|
{ siTable = cronEventsTable,
|
|
|
|
|
siCols = map unsafePGCol ["trigger_name", "scheduled_time"],
|
|
|
|
|
siValues = S.ValuesExp $ map (toTupleExp . toArr) cronSeeds,
|
|
|
|
|
siConflict = Just $ S.DoNothing Nothing,
|
|
|
|
|
siRet = Nothing
|
|
|
|
|
}
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE defaultTxErrorHandler (PG.fromText insertCronEventsSql) () False
|
2021-09-13 21:00:53 +03:00
|
|
|
|
where
|
|
|
|
|
toArr (CronEventSeed n t) = [(triggerNameToTxt n), (formatTime' t)]
|
|
|
|
|
toTupleExp = S.TupleExp . map S.SELit
|
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
insertOneOffScheduledEventTx :: OneOffEvent -> PG.TxE QErr EventId
|
2021-09-13 21:00:53 +03:00
|
|
|
|
insertOneOffScheduledEventTx CreateScheduledEvent {..} =
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
runIdentity . PG.getRow
|
|
|
|
|
<$> PG.withQE
|
2021-09-13 21:00:53 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2021-09-13 21:00:53 +03:00
|
|
|
|
INSERT INTO hdb_catalog.hdb_scheduled_events
|
|
|
|
|
(webhook_conf,scheduled_time,payload,retry_conf,header_conf,comment)
|
|
|
|
|
VALUES
|
|
|
|
|
($1, $2, $3, $4, $5, $6) RETURNING id
|
|
|
|
|
|]
|
2022-09-21 21:40:41 +03:00
|
|
|
|
( PG.ViaJSON cseWebhook,
|
2021-09-13 21:00:53 +03:00
|
|
|
|
cseScheduleAt,
|
2022-09-21 21:40:41 +03:00
|
|
|
|
PG.ViaJSON csePayload,
|
|
|
|
|
PG.ViaJSON cseRetryConf,
|
|
|
|
|
PG.ViaJSON cseHeaders,
|
2021-09-13 21:00:53 +03:00
|
|
|
|
cseComment
|
|
|
|
|
)
|
|
|
|
|
False
|
2020-11-25 13:56:44 +03:00
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
dropFutureCronEventsTx :: ClearCronEvents -> PG.TxE QErr ()
|
2021-05-26 19:19:26 +03:00
|
|
|
|
dropFutureCronEventsTx = \case
|
|
|
|
|
SingleCronTrigger triggerName ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2021-05-26 19:19:26 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2021-05-26 19:19:26 +03:00
|
|
|
|
DELETE FROM hdb_catalog.hdb_cron_events
|
|
|
|
|
WHERE trigger_name = $1 AND scheduled_time > now() AND tries = 0
|
|
|
|
|
|]
|
|
|
|
|
(Identity triggerName)
|
|
|
|
|
True
|
|
|
|
|
MetadataCronTriggers triggerNames ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2021-05-26 19:19:26 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2021-05-26 19:19:26 +03:00
|
|
|
|
DELETE FROM hdb_catalog.hdb_cron_events
|
|
|
|
|
WHERE scheduled_time > now() AND tries = 0 AND trigger_name = ANY($1::text[])
|
|
|
|
|
|]
|
|
|
|
|
(Identity $ PGTextArray $ map triggerNameToTxt triggerNames)
|
|
|
|
|
False
|
2020-12-14 07:30:19 +03:00
|
|
|
|
|
2020-11-25 13:56:44 +03:00
|
|
|
|
cronEventsTable :: QualifiedTable
|
|
|
|
|
cronEventsTable =
|
|
|
|
|
QualifiedObject "hdb_catalog" $ TableName "hdb_cron_events"
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
mkScheduledEventStatusFilter :: [ScheduledEventStatus] -> S.BoolExp
|
|
|
|
|
mkScheduledEventStatusFilter = \case
|
|
|
|
|
[] -> S.BELit True
|
|
|
|
|
v ->
|
|
|
|
|
S.BEIN (S.SEIdentifier $ Identifier "status") $
|
|
|
|
|
map (S.SELit . scheduledEventStatusToText) v
|
|
|
|
|
|
|
|
|
|
scheduledTimeOrderBy :: S.OrderByExp
|
|
|
|
|
scheduledTimeOrderBy =
|
|
|
|
|
let scheduledTimeCol = S.SEIdentifier $ Identifier "scheduled_time"
|
|
|
|
|
in S.OrderByExp $
|
|
|
|
|
flip (NE.:|) [] $
|
|
|
|
|
S.OrderByItem
|
|
|
|
|
scheduledTimeCol
|
|
|
|
|
(Just S.OTAsc)
|
|
|
|
|
Nothing
|
|
|
|
|
|
|
|
|
|
-- | Build a select expression which outputs total count and
|
|
|
|
|
-- list of json rows with pagination limit and offset applied
|
|
|
|
|
mkPaginationSelectExp ::
|
|
|
|
|
S.Select ->
|
|
|
|
|
ScheduledEventPagination ->
|
2022-09-15 22:10:53 +03:00
|
|
|
|
RowsCountOption ->
|
2021-01-07 12:04:22 +03:00
|
|
|
|
S.Select
|
2022-09-15 22:10:53 +03:00
|
|
|
|
mkPaginationSelectExp allRowsSelect ScheduledEventPagination {..} shouldIncludeRowsCount =
|
2021-01-07 12:04:22 +03:00
|
|
|
|
S.mkSelect
|
2023-02-28 14:17:08 +03:00
|
|
|
|
{ S.selCTEs = [(countCteAlias, S.ICTESelect allRowsSelect), (limitCteAlias, limitCteSelect)],
|
2022-09-15 22:10:53 +03:00
|
|
|
|
S.selExtr =
|
|
|
|
|
case shouldIncludeRowsCount of
|
|
|
|
|
IncludeRowsCount -> [countExtractor, rowsExtractor]
|
|
|
|
|
DontIncludeRowsCount -> [rowsExtractor]
|
2021-01-07 12:04:22 +03:00
|
|
|
|
}
|
|
|
|
|
where
|
2022-10-05 13:03:36 +03:00
|
|
|
|
countCteAlias = S.mkTableAlias "count_cte"
|
|
|
|
|
limitCteAlias = S.mkTableAlias "limit_cte"
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
countExtractor =
|
|
|
|
|
let selectExp =
|
|
|
|
|
S.mkSelect
|
|
|
|
|
{ S.selExtr = [S.Extractor S.countStar Nothing],
|
2022-10-05 13:03:36 +03:00
|
|
|
|
S.selFrom = Just $ S.mkIdenFromExp (S.tableAliasToIdentifier countCteAlias)
|
2021-01-07 12:04:22 +03:00
|
|
|
|
}
|
|
|
|
|
in S.Extractor (S.SESelect selectExp) Nothing
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2021-01-07 12:04:22 +03:00
|
|
|
|
limitCteSelect =
|
2023-02-28 14:17:08 +03:00
|
|
|
|
S.ICTESelect
|
|
|
|
|
S.mkSelect
|
|
|
|
|
{ S.selExtr = [S.selectStar],
|
|
|
|
|
S.selFrom = Just $ S.mkIdenFromExp (S.tableAliasToIdentifier countCteAlias),
|
|
|
|
|
S.selLimit = (S.LimitExp . S.intToSQLExp) <$> _sepLimit,
|
|
|
|
|
S.selOffset = (S.OffsetExp . S.intToSQLExp) <$> _sepOffset
|
|
|
|
|
}
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
rowsExtractor =
|
|
|
|
|
let jsonAgg = S.SEUnsafe "json_agg(row_to_json(limit_cte.*))"
|
|
|
|
|
selectExp =
|
|
|
|
|
S.mkSelect
|
|
|
|
|
{ S.selExtr = [S.Extractor jsonAgg Nothing],
|
2022-10-05 13:03:36 +03:00
|
|
|
|
S.selFrom = Just $ S.mkIdenFromExp (S.tableAliasToIdentifier limitCteAlias)
|
2021-01-07 12:04:22 +03:00
|
|
|
|
}
|
|
|
|
|
in S.Extractor (S.handleIfNull (S.SELit "[]") (S.SESelect selectExp)) Nothing
|
|
|
|
|
|
2022-09-21 21:40:41 +03:00
|
|
|
|
withCount :: (Int, PG.ViaJSON a) -> WithOptionalTotalCount a
|
|
|
|
|
withCount (count, PG.ViaJSON a) = WithOptionalTotalCount (Just count) a
|
2022-09-15 22:10:53 +03:00
|
|
|
|
|
2022-09-21 21:40:41 +03:00
|
|
|
|
withoutCount :: PG.ViaJSON a -> WithOptionalTotalCount a
|
|
|
|
|
withoutCount (PG.ViaJSON a) = WithOptionalTotalCount Nothing a
|
2022-09-15 22:10:53 +03:00
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
executeWithOptionalTotalCount :: J.FromJSON a => PG.Query -> RowsCountOption -> PG.TxE QErr (WithOptionalTotalCount a)
|
2022-09-15 22:10:53 +03:00
|
|
|
|
executeWithOptionalTotalCount sql getRowsCount =
|
|
|
|
|
case getRowsCount of
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
IncludeRowsCount -> (withCount . PG.getRow) <$> PG.withQE defaultTxErrorHandler sql () False
|
|
|
|
|
DontIncludeRowsCount -> (withoutCount . runIdentity . PG.getRow) <$> PG.withQE defaultTxErrorHandler sql () False
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
getOneOffScheduledEventsTx ::
|
|
|
|
|
ScheduledEventPagination ->
|
|
|
|
|
[ScheduledEventStatus] ->
|
2022-09-15 22:10:53 +03:00
|
|
|
|
RowsCountOption ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.TxE QErr (WithOptionalTotalCount [OneOffScheduledEvent])
|
2022-09-15 22:10:53 +03:00
|
|
|
|
getOneOffScheduledEventsTx pagination statuses getRowsCount = do
|
2021-01-07 12:04:22 +03:00
|
|
|
|
let table = QualifiedObject "hdb_catalog" $ TableName "hdb_scheduled_events"
|
|
|
|
|
statusFilter = mkScheduledEventStatusFilter statuses
|
|
|
|
|
select =
|
|
|
|
|
S.mkSelect
|
|
|
|
|
{ S.selExtr = [S.selectStar],
|
|
|
|
|
S.selFrom = Just $ S.mkSimpleFromExp table,
|
|
|
|
|
S.selWhere = Just $ S.WhereFrag statusFilter,
|
|
|
|
|
S.selOrderBy = Just scheduledTimeOrderBy
|
|
|
|
|
}
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
sql = PG.fromBuilder $ toSQL $ mkPaginationSelectExp select pagination getRowsCount
|
2022-09-15 22:10:53 +03:00
|
|
|
|
executeWithOptionalTotalCount sql getRowsCount
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
getCronEventsTx ::
|
|
|
|
|
TriggerName ->
|
|
|
|
|
ScheduledEventPagination ->
|
|
|
|
|
[ScheduledEventStatus] ->
|
2022-09-15 22:10:53 +03:00
|
|
|
|
RowsCountOption ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.TxE QErr (WithOptionalTotalCount [CronEvent])
|
2022-09-15 22:10:53 +03:00
|
|
|
|
getCronEventsTx triggerName pagination status getRowsCount = do
|
2021-01-07 12:04:22 +03:00
|
|
|
|
let triggerNameFilter =
|
|
|
|
|
S.BECompare S.SEQ (S.SEIdentifier $ Identifier "trigger_name") (S.SELit $ triggerNameToTxt triggerName)
|
|
|
|
|
statusFilter = mkScheduledEventStatusFilter status
|
|
|
|
|
select =
|
|
|
|
|
S.mkSelect
|
|
|
|
|
{ S.selExtr = [S.selectStar],
|
|
|
|
|
S.selFrom = Just $ S.mkSimpleFromExp cronEventsTable,
|
|
|
|
|
S.selWhere = Just $ S.WhereFrag $ S.BEBin S.AndOp triggerNameFilter statusFilter,
|
|
|
|
|
S.selOrderBy = Just scheduledTimeOrderBy
|
|
|
|
|
}
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
sql = PG.fromBuilder $ toSQL $ mkPaginationSelectExp select pagination getRowsCount
|
2022-09-15 22:10:53 +03:00
|
|
|
|
executeWithOptionalTotalCount sql getRowsCount
|
2021-01-07 12:04:22 +03:00
|
|
|
|
|
|
|
|
|
deleteScheduledEventTx ::
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
ScheduledEventId -> ScheduledEventType -> PG.TxE QErr ()
|
2021-01-07 12:04:22 +03:00
|
|
|
|
deleteScheduledEventTx eventId = \case
|
|
|
|
|
OneOff ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2021-01-07 12:04:22 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2021-01-07 12:04:22 +03:00
|
|
|
|
DELETE FROM hdb_catalog.hdb_scheduled_events
|
|
|
|
|
WHERE id = $1
|
|
|
|
|
|]
|
|
|
|
|
(Identity eventId)
|
|
|
|
|
False
|
|
|
|
|
Cron ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.unitQE
|
2021-01-07 12:04:22 +03:00
|
|
|
|
defaultTxErrorHandler
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
[PG.sql|
|
2021-01-07 12:04:22 +03:00
|
|
|
|
DELETE FROM hdb_catalog.hdb_cron_events
|
|
|
|
|
WHERE id = $1
|
|
|
|
|
|]
|
|
|
|
|
(Identity eventId)
|
|
|
|
|
False
|
|
|
|
|
|
|
|
|
|
invocationFieldExtractors :: QualifiedTable -> [S.Extractor]
|
|
|
|
|
invocationFieldExtractors table =
|
|
|
|
|
[ S.Extractor (seIden "id") Nothing,
|
|
|
|
|
S.Extractor (seIden "event_id") Nothing,
|
|
|
|
|
S.Extractor (seIden "status") Nothing,
|
|
|
|
|
S.Extractor (withJsonTypeAnn $ seIden "request") Nothing,
|
|
|
|
|
S.Extractor (withJsonTypeAnn $ seIden "response") Nothing,
|
|
|
|
|
S.Extractor (seIden "created_at") Nothing
|
|
|
|
|
]
|
|
|
|
|
where
|
|
|
|
|
withJsonTypeAnn e = S.SETyAnn e $ S.TypeAnn "json"
|
|
|
|
|
seIden = S.SEQIdentifier . S.mkQIdentifierTable table . Identifier
|
|
|
|
|
|
|
|
|
|
mkEventIdBoolExp :: QualifiedTable -> EventId -> S.BoolExp
|
|
|
|
|
mkEventIdBoolExp table eventId =
|
|
|
|
|
S.BECompare
|
|
|
|
|
S.SEQ
|
|
|
|
|
(S.SEQIdentifier $ S.mkQIdentifierTable table $ Identifier "event_id")
|
|
|
|
|
(S.SELit $ unEventId eventId)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
2022-11-03 13:21:56 +03:00
|
|
|
|
getScheduledEventInvocationsTx ::
|
|
|
|
|
GetScheduledEventInvocations ->
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
|
PG.TxE QErr (WithOptionalTotalCount [ScheduledEventInvocation])
|
2022-11-03 13:21:56 +03:00
|
|
|
|
getScheduledEventInvocationsTx getEventInvocations = do
|
2021-02-22 19:02:04 +03:00
|
|
|
|
let eventsTables = EventTables oneOffInvocationsTable cronInvocationsTable cronEventsTable
|
2022-11-03 13:21:56 +03:00
|
|
|
|
sql = PG.fromBuilder $ toSQL $ getScheduledEventsInvocationsQuery eventsTables getEventInvocations
|
2022-09-15 22:10:53 +03:00
|
|
|
|
executeWithOptionalTotalCount sql (_geiGetRowsCount getEventInvocations)
|
2021-02-22 19:02:04 +03:00
|
|
|
|
where
|
|
|
|
|
oneOffInvocationsTable = QualifiedObject "hdb_catalog" $ TableName "hdb_scheduled_event_invocation_logs"
|
|
|
|
|
cronInvocationsTable = QualifiedObject "hdb_catalog" $ TableName "hdb_cron_event_invocation_logs"
|
|
|
|
|
|
|
|
|
|
data EventTables = EventTables
|
|
|
|
|
{ etOneOffInvocationsTable :: QualifiedTable,
|
|
|
|
|
etCronInvocationsTable :: QualifiedTable,
|
|
|
|
|
etCronEventsTable :: QualifiedTable
|
|
|
|
|
}
|
2021-02-11 20:54:25 +03:00
|
|
|
|
|
2022-11-03 13:21:56 +03:00
|
|
|
|
getScheduledEventsInvocationsQueryNoPagination :: EventTables -> GetScheduledEventInvocationsBy -> S.Select
|
|
|
|
|
getScheduledEventsInvocationsQueryNoPagination (EventTables oneOffInvocationsTable cronInvocationsTable cronEventsTable') invocationsBy =
|
2021-04-14 04:23:45 +03:00
|
|
|
|
allRowsSelect
|
2021-01-07 12:04:22 +03:00
|
|
|
|
where
|
|
|
|
|
createdAtOrderBy table =
|
|
|
|
|
let createdAtCol = S.SEQIdentifier $ S.mkQIdentifierTable table $ Identifier "created_at"
|
|
|
|
|
in S.OrderByExp $ flip (NE.:|) [] $ S.OrderByItem createdAtCol (Just S.OTDesc) Nothing
|
|
|
|
|
|
|
|
|
|
allRowsSelect = case invocationsBy of
|
|
|
|
|
GIBEventId eventId eventType ->
|
|
|
|
|
let table = case eventType of
|
|
|
|
|
OneOff -> oneOffInvocationsTable
|
|
|
|
|
Cron -> cronInvocationsTable
|
|
|
|
|
in S.mkSelect
|
|
|
|
|
{ S.selExtr = invocationFieldExtractors table,
|
|
|
|
|
S.selFrom = Just $ S.mkSimpleFromExp table,
|
|
|
|
|
S.selOrderBy = Just $ createdAtOrderBy table,
|
|
|
|
|
S.selWhere = Just $ S.WhereFrag $ mkEventIdBoolExp table eventId
|
|
|
|
|
}
|
|
|
|
|
GIBEvent event -> case event of
|
|
|
|
|
SEOneOff ->
|
|
|
|
|
let table = oneOffInvocationsTable
|
|
|
|
|
in S.mkSelect
|
|
|
|
|
{ S.selExtr = invocationFieldExtractors table,
|
|
|
|
|
S.selFrom = Just $ S.mkSimpleFromExp table,
|
|
|
|
|
S.selOrderBy = Just $ createdAtOrderBy table
|
|
|
|
|
}
|
|
|
|
|
SECron triggerName ->
|
|
|
|
|
let invocationTable = cronInvocationsTable
|
2021-02-22 19:02:04 +03:00
|
|
|
|
eventTable = cronEventsTable'
|
2021-01-07 12:04:22 +03:00
|
|
|
|
joinCondition =
|
|
|
|
|
S.JoinOn $
|
|
|
|
|
S.BECompare
|
|
|
|
|
S.SEQ
|
|
|
|
|
(S.SEQIdentifier $ S.mkQIdentifierTable eventTable $ Identifier "id")
|
|
|
|
|
(S.SEQIdentifier $ S.mkQIdentifierTable invocationTable $ Identifier "event_id")
|
|
|
|
|
joinTables =
|
|
|
|
|
S.JoinExpr
|
|
|
|
|
(S.FISimple invocationTable Nothing)
|
|
|
|
|
S.Inner
|
|
|
|
|
(S.FISimple eventTable Nothing)
|
|
|
|
|
joinCondition
|
|
|
|
|
triggerBoolExp =
|
|
|
|
|
S.BECompare
|
|
|
|
|
S.SEQ
|
|
|
|
|
(S.SEQIdentifier $ S.mkQIdentifierTable eventTable (Identifier "trigger_name"))
|
|
|
|
|
(S.SELit $ triggerNameToTxt triggerName)
|
|
|
|
|
in S.mkSelect
|
|
|
|
|
{ S.selExtr = invocationFieldExtractors invocationTable,
|
|
|
|
|
S.selFrom = Just $ S.FromExp [S.FIJoin joinTables],
|
|
|
|
|
S.selWhere = Just $ S.WhereFrag triggerBoolExp,
|
|
|
|
|
S.selOrderBy = Just $ createdAtOrderBy invocationTable
|
|
|
|
|
}
|
2021-04-14 04:23:45 +03:00
|
|
|
|
|
2022-11-03 13:21:56 +03:00
|
|
|
|
getScheduledEventsInvocationsQuery :: EventTables -> GetScheduledEventInvocations -> S.Select
|
|
|
|
|
getScheduledEventsInvocationsQuery eventTables (GetScheduledEventInvocations invocationsBy pagination shouldIncludeRowsCount) =
|
|
|
|
|
let invocationsSelect = getScheduledEventsInvocationsQueryNoPagination eventTables invocationsBy
|
2022-09-15 22:10:53 +03:00
|
|
|
|
in mkPaginationSelectExp invocationsSelect pagination shouldIncludeRowsCount
|
2023-01-30 09:06:45 +03:00
|
|
|
|
|
|
|
|
|
-- | Logger to accumulate stats of fetched scheduled events over a period of time and log once using @'L.Logger L.Hasura'.
|
|
|
|
|
-- See @'createStatsLogger' for more details.
|
|
|
|
|
createFetchedScheduledEventsStatsLogger :: (MonadIO m) => L.Logger L.Hasura -> m FetchedScheduledEventsStatsLogger
|
2023-03-14 07:38:09 +03:00
|
|
|
|
createFetchedScheduledEventsStatsLogger = L.createStatsLogger
|
2023-01-30 09:06:45 +03:00
|
|
|
|
|
|
|
|
|
-- | Close the fetched scheduled events stats logger.
|
|
|
|
|
closeFetchedScheduledEventsStatsLogger ::
|
|
|
|
|
(MonadIO m) => L.Logger L.Hasura -> FetchedScheduledEventsStatsLogger -> m ()
|
2023-03-14 07:38:09 +03:00
|
|
|
|
closeFetchedScheduledEventsStatsLogger = L.closeStatsLogger L.scheduledTriggerProcessLogType
|
2023-01-30 09:06:45 +03:00
|
|
|
|
|
|
|
|
|
-- | Log statistics of fetched scheduled events. See @'logStats' for more details.
|
|
|
|
|
logFetchedScheduledEventsStats ::
|
|
|
|
|
(MonadIO m) =>
|
|
|
|
|
FetchedScheduledEventsStatsLogger ->
|
|
|
|
|
CronEventsCount ->
|
|
|
|
|
OneOffScheduledEventsCount ->
|
|
|
|
|
m ()
|
|
|
|
|
logFetchedScheduledEventsStats logger cron oneOff =
|
2023-03-14 07:38:09 +03:00
|
|
|
|
L.logStats logger (FetchedScheduledEventsStats cron oneOff 1)
|
2023-02-07 15:22:08 +03:00
|
|
|
|
|
|
|
|
|
-- | Logger to accumulate stats of fetched cron triggers, for generating cron events, over a period of time and
|
|
|
|
|
-- log once using @'L.Logger L.Hasura'.
|
|
|
|
|
-- See @'createStatsLogger' for more details.
|
|
|
|
|
createFetchedCronTriggerStatsLogger :: (MonadIO m) => L.Logger L.Hasura -> m FetchedCronTriggerStatsLogger
|
2023-03-14 07:38:09 +03:00
|
|
|
|
createFetchedCronTriggerStatsLogger = L.createStatsLogger
|
2023-02-07 15:22:08 +03:00
|
|
|
|
|
|
|
|
|
-- | Close the fetched cron trigger stats logger.
|
|
|
|
|
closeFetchedCronTriggersStatsLogger ::
|
|
|
|
|
(MonadIO m) => L.Logger L.Hasura -> FetchedCronTriggerStatsLogger -> m ()
|
2023-03-14 07:38:09 +03:00
|
|
|
|
closeFetchedCronTriggersStatsLogger = L.closeStatsLogger L.cronEventGeneratorProcessType
|
2023-02-07 15:22:08 +03:00
|
|
|
|
|
|
|
|
|
-- | Log statistics of fetched cron triggers. See @'logStats' for more details.
|
|
|
|
|
logFetchedCronTriggersStats ::
|
|
|
|
|
(MonadIO m) =>
|
|
|
|
|
FetchedCronTriggerStatsLogger ->
|
|
|
|
|
[CronTriggerStats] ->
|
|
|
|
|
m ()
|
|
|
|
|
logFetchedCronTriggersStats logger cronTriggerStats =
|
2023-03-14 07:38:09 +03:00
|
|
|
|
L.logStats logger (FetchedCronTriggerStats cronTriggerStats 1)
|