2020-05-13 15:33:16 +03:00
|
|
|
{-|
|
|
|
|
= Event Triggers
|
|
|
|
|
|
|
|
Event triggers are like ordinary SQL triggers, except instead of calling a SQL
|
|
|
|
procedure, they call a webhook. The event delivery mechanism involves coordination
|
|
|
|
between both the database and graphql-engine: only the SQL database knows
|
|
|
|
when the events should fire, but only graphql-engine know how to actually
|
|
|
|
deliver them.
|
|
|
|
|
|
|
|
Therefore, event triggers are implemented in two parts:
|
|
|
|
|
|
|
|
1. Every event trigger is backed by a bona fide SQL trigger. When the SQL trigger
|
|
|
|
fires, it creates a new record in the hdb_catalog.event_log table.
|
|
|
|
|
|
|
|
2. Concurrently, a thread in graphql-engine monitors the hdb_catalog.event_log
|
|
|
|
table for new events. When new event(s) are found, it uses the information
|
|
|
|
(URL,payload and headers) stored in the event to deliver the event
|
|
|
|
to the webhook.
|
|
|
|
|
|
|
|
The creation and deletion of SQL trigger itself is managed by the metadata DDL
|
|
|
|
APIs (see Hasura.RQL.DDL.EventTrigger), so this module focuses on event delivery.
|
|
|
|
|
|
|
|
Most of the subtleties involve guaranteeing reliable delivery of events:
|
|
|
|
we guarantee that every event will be delivered at least once,
|
|
|
|
even if graphql-engine crashes. This means we have to record the state
|
|
|
|
of each event in the database, and we have to retry
|
|
|
|
failed requests at a regular (user-configurable) interval.
|
|
|
|
|
|
|
|
-}
|
2020-03-11 09:27:31 +03:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2020-04-24 10:55:51 +03:00
|
|
|
{-# LANGUAGE StrictData #-}
|
2020-05-13 15:33:16 +03:00
|
|
|
module Hasura.Eventing.EventTrigger
|
2018-09-05 14:26:46 +03:00
|
|
|
( initEventEngineCtx
|
2020-03-11 09:27:31 +03:00
|
|
|
, processEventQueue
|
2018-09-05 14:26:46 +03:00
|
|
|
, unlockAllEvents
|
|
|
|
, defaultMaxEventThreads
|
2020-05-13 15:33:16 +03:00
|
|
|
, defaultFetchInterval
|
2018-09-07 14:51:01 +03:00
|
|
|
, Event(..)
|
2020-04-14 09:01:50 +03:00
|
|
|
, unlockEvents
|
|
|
|
, EventEngineCtx(..)
|
2018-09-05 14:26:46 +03:00
|
|
|
) where
|
|
|
|
|
2020-07-14 22:00:58 +03:00
|
|
|
import Control.Concurrent.Extended (sleep)
|
2018-09-05 14:26:46 +03:00
|
|
|
import Control.Concurrent.STM.TVar
|
2020-07-14 22:00:58 +03:00
|
|
|
import Control.Monad.Catch (MonadMask, bracket_)
|
2020-03-05 20:59:26 +03:00
|
|
|
import Control.Monad.STM
|
2020-07-14 22:00:58 +03:00
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
2018-09-05 14:26:46 +03:00
|
|
|
import Data.Aeson
|
|
|
|
import Data.Aeson.Casing
|
|
|
|
import Data.Aeson.TH
|
|
|
|
import Data.Has
|
2020-07-14 22:00:58 +03:00
|
|
|
import Data.Int (Int64)
|
2020-03-05 20:59:26 +03:00
|
|
|
import Data.String
|
2018-09-24 14:50:11 +03:00
|
|
|
import Data.Time.Clock
|
2020-03-11 09:27:31 +03:00
|
|
|
import Data.Word
|
2020-07-02 14:57:09 +03:00
|
|
|
import Hasura.Eventing.Common
|
2020-07-14 22:00:58 +03:00
|
|
|
import Hasura.Eventing.HTTP
|
2019-08-23 11:57:19 +03:00
|
|
|
import Hasura.HTTP
|
2018-09-05 14:26:46 +03:00
|
|
|
import Hasura.Prelude
|
2018-11-23 16:02:46 +03:00
|
|
|
import Hasura.RQL.DDL.Headers
|
2018-09-05 14:26:46 +03:00
|
|
|
import Hasura.RQL.Types
|
2020-07-14 22:00:58 +03:00
|
|
|
import Hasura.Server.Version (HasVersion)
|
2018-09-05 14:26:46 +03:00
|
|
|
import Hasura.SQL.Types
|
2020-07-15 13:40:48 +03:00
|
|
|
import qualified Hasura.Tracing as Tracing
|
2018-09-05 14:26:46 +03:00
|
|
|
|
2020-07-14 22:00:58 +03:00
|
|
|
import qualified Control.Concurrent.Async.Lifted.Safe as LA
|
2020-07-28 20:52:44 +03:00
|
|
|
import qualified Data.ByteString.Lazy as LBS
|
2020-07-14 22:00:58 +03:00
|
|
|
import qualified Data.HashMap.Strict as M
|
|
|
|
import qualified Data.TByteString as TBS
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import qualified Data.Time.Clock as Time
|
|
|
|
import qualified Database.PG.Query as Q
|
|
|
|
import qualified Database.PG.Query.PTI as PTI
|
|
|
|
import qualified Hasura.Logging as L
|
|
|
|
import qualified Network.HTTP.Client as HTTP
|
|
|
|
import qualified PostgreSQL.Binary.Encoding as PE
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
data TriggerMetadata
|
|
|
|
= TriggerMetadata { tmName :: TriggerName }
|
|
|
|
deriving (Show, Eq)
|
2018-10-26 19:28:03 +03:00
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
$(deriveJSON (aesonDrop 2 snakeCase){omitNothingFields=True} ''TriggerMetadata)
|
2018-09-05 14:26:46 +03:00
|
|
|
|
|
|
|
newtype EventInternalErr
|
|
|
|
= EventInternalErr QErr
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
2019-11-26 15:14:21 +03:00
|
|
|
instance L.ToEngineLog EventInternalErr L.Hasura where
|
|
|
|
toEngineLog (EventInternalErr qerr) = (L.LevelError, L.eventTriggerLogType, toJSON qerr)
|
2018-09-05 14:26:46 +03:00
|
|
|
|
2020-03-11 09:27:31 +03:00
|
|
|
-- | Change data for a particular row
|
|
|
|
--
|
2020-04-14 09:01:50 +03:00
|
|
|
-- https://docs.hasura.io/1.0/graphql/manual/event-triggers/payload.html
|
2018-09-05 14:26:46 +03:00
|
|
|
data Event
|
|
|
|
= Event
|
2018-09-07 14:51:01 +03:00
|
|
|
{ eId :: EventId
|
2018-09-05 14:26:46 +03:00
|
|
|
, eTable :: QualifiedTable
|
2020-05-13 15:33:16 +03:00
|
|
|
, eTrigger :: TriggerMetadata
|
2018-09-05 14:26:46 +03:00
|
|
|
, eEvent :: Value
|
2018-09-07 14:51:01 +03:00
|
|
|
, eTries :: Int
|
2018-09-05 14:26:46 +03:00
|
|
|
, eCreatedAt :: Time.UTCTime
|
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
2019-02-07 15:37:28 +03:00
|
|
|
$(deriveFromJSON (aesonDrop 1 snakeCase){omitNothingFields=True} ''Event)
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
data EventEngineCtx
|
|
|
|
= EventEngineCtx
|
|
|
|
{ _eeCtxEventThreadsCapacity :: TVar Int
|
|
|
|
, _eeCtxFetchInterval :: DiffTime
|
|
|
|
}
|
|
|
|
|
|
|
|
data DeliveryInfo
|
|
|
|
= DeliveryInfo
|
|
|
|
{ diCurrentRetry :: Int
|
|
|
|
, diMaxRetries :: Int
|
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
|
|
|
$(deriveJSON (aesonDrop 2 snakeCase){omitNothingFields=True} ''DeliveryInfo)
|
|
|
|
|
2019-02-07 15:37:28 +03:00
|
|
|
newtype QualifiedTableStrict = QualifiedTableStrict
|
|
|
|
{ getQualifiedTable :: QualifiedTable
|
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
|
|
|
instance ToJSON QualifiedTableStrict where
|
|
|
|
toJSON (QualifiedTableStrict (QualifiedObject sn tn)) =
|
|
|
|
object [ "schema" .= sn
|
|
|
|
, "name" .= tn
|
2018-09-05 14:26:46 +03:00
|
|
|
]
|
|
|
|
|
2019-02-07 15:37:28 +03:00
|
|
|
data EventPayload
|
|
|
|
= EventPayload
|
|
|
|
{ epId :: EventId
|
|
|
|
, epTable :: QualifiedTableStrict
|
2020-05-13 15:33:16 +03:00
|
|
|
, epTrigger :: TriggerMetadata
|
2019-02-07 15:37:28 +03:00
|
|
|
, epEvent :: Value
|
|
|
|
, epDeliveryInfo :: DeliveryInfo
|
|
|
|
, epCreatedAt :: Time.UTCTime
|
|
|
|
} deriving (Show, Eq)
|
|
|
|
|
|
|
|
$(deriveToJSON (aesonDrop 2 snakeCase){omitNothingFields=True} ''EventPayload)
|
2018-09-05 14:26:46 +03:00
|
|
|
|
|
|
|
defaultMaxEventThreads :: Int
|
|
|
|
defaultMaxEventThreads = 100
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
defaultFetchInterval :: DiffTime
|
|
|
|
defaultFetchInterval = seconds 1
|
2018-10-26 19:28:03 +03:00
|
|
|
|
2020-01-16 04:56:57 +03:00
|
|
|
initEventEngineCtx :: Int -> DiffTime -> STM EventEngineCtx
|
2020-03-11 09:27:31 +03:00
|
|
|
initEventEngineCtx maxT _eeCtxFetchInterval = do
|
|
|
|
_eeCtxEventThreadsCapacity <- newTVar maxT
|
|
|
|
return $ EventEngineCtx{..}
|
|
|
|
|
|
|
|
-- | Service events from our in-DB queue.
|
|
|
|
--
|
|
|
|
-- There are a few competing concerns and constraints here; we want to...
|
|
|
|
-- - fetch events in batches for lower DB pressure
|
|
|
|
-- - don't fetch more than N at a time (since that can mean: space leak, less
|
2020-04-14 09:01:50 +03:00
|
|
|
-- effective scale out, possible double sends for events we've checked out
|
2020-03-11 09:27:31 +03:00
|
|
|
-- on exit (TODO clean shutdown procedure))
|
|
|
|
-- - try not to cause webhook workers to stall waiting on DB fetch
|
|
|
|
-- - limit webhook HTTP concurrency per HASURA_GRAPHQL_EVENTS_HTTP_POOL_SIZE
|
|
|
|
processEventQueue
|
2020-07-14 22:00:58 +03:00
|
|
|
:: forall m void
|
|
|
|
. ( HasVersion
|
|
|
|
, MonadIO m
|
2020-07-15 13:40:48 +03:00
|
|
|
, Tracing.HasReporter m
|
2020-07-14 22:00:58 +03:00
|
|
|
, MonadBaseControl IO m
|
|
|
|
, LA.Forall (LA.Pure m)
|
|
|
|
, MonadMask m
|
|
|
|
)
|
|
|
|
=> L.Logger L.Hasura
|
|
|
|
-> LogEnvHeaders
|
|
|
|
-> HTTP.Manager
|
|
|
|
-> Q.PGPool
|
|
|
|
-> IO SchemaCache
|
|
|
|
-> EventEngineCtx
|
|
|
|
-> LockedEventsCtx
|
|
|
|
-> m void
|
|
|
|
processEventQueue logger logenv httpMgr pool getSchemaCache eeCtx@EventEngineCtx{..} LockedEventsCtx{leEvents} = do
|
2020-03-11 09:27:31 +03:00
|
|
|
events0 <- popEventsBatch
|
|
|
|
go events0 0 False
|
2018-09-05 14:26:46 +03:00
|
|
|
where
|
2020-03-11 09:27:31 +03:00
|
|
|
fetchBatchSize = 100
|
|
|
|
popEventsBatch = do
|
2020-07-14 22:00:58 +03:00
|
|
|
let run = liftIO . runExceptT . Q.runTx pool (Q.RepeatableRead, Just Q.ReadWrite)
|
2020-03-11 09:27:31 +03:00
|
|
|
run (fetchEvents fetchBatchSize) >>= \case
|
2020-04-14 09:01:50 +03:00
|
|
|
Left err -> do
|
2020-07-14 22:00:58 +03:00
|
|
|
liftIO $ L.unLogger logger $ EventInternalErr err
|
2020-03-11 09:27:31 +03:00
|
|
|
return []
|
2020-04-14 09:01:50 +03:00
|
|
|
Right events -> do
|
2020-07-02 14:57:09 +03:00
|
|
|
saveLockedEvents (map eId events) leEvents
|
2020-03-11 09:27:31 +03:00
|
|
|
return events
|
|
|
|
|
|
|
|
-- work on this batch of events while prefetching the next. Recurse after we've forked workers
|
|
|
|
-- for each in the batch, minding the requested pool size.
|
2020-07-14 22:00:58 +03:00
|
|
|
go :: [Event] -> Int -> Bool -> m void
|
2020-03-11 09:27:31 +03:00
|
|
|
go events !fullFetchCount !alreadyWarned = do
|
|
|
|
-- process events ASAP until we've caught up; only then can we sleep
|
2020-07-14 22:00:58 +03:00
|
|
|
when (null events) . liftIO $ sleep _eeCtxFetchInterval
|
2020-03-11 09:27:31 +03:00
|
|
|
|
|
|
|
-- Prefetch next events payload while concurrently working through our current batch.
|
|
|
|
-- NOTE: we probably don't need to prefetch so early, but probably not
|
|
|
|
-- worth the effort for something more fine-tuned
|
2020-07-14 22:00:58 +03:00
|
|
|
eventsNext <- LA.withAsync popEventsBatch $ \eventsNextA -> do
|
2020-03-11 09:27:31 +03:00
|
|
|
-- process approximately in order, minding HASURA_GRAPHQL_EVENTS_HTTP_POOL_SIZE:
|
2020-06-02 20:17:58 +03:00
|
|
|
forM_ events $ \event -> do
|
2020-07-23 23:39:26 +03:00
|
|
|
tracingCtx <- liftIO (Tracing.extractEventContext (eEvent event))
|
|
|
|
let runTraceT = maybe
|
|
|
|
Tracing.runTraceT
|
|
|
|
Tracing.runTraceTInContext
|
|
|
|
tracingCtx
|
2020-07-14 22:00:58 +03:00
|
|
|
t <- processEvent event
|
2020-07-28 23:45:20 +03:00
|
|
|
& runTraceT "Event trigger"
|
2020-07-14 22:00:58 +03:00
|
|
|
& withEventEngineCtx eeCtx
|
|
|
|
& flip runReaderT (logger, httpMgr)
|
|
|
|
& LA.async
|
|
|
|
-- removing an event from the _eeCtxLockedEvents after the event has
|
|
|
|
-- been processed
|
|
|
|
removeEventFromLockedEvents (eId event) leEvents
|
|
|
|
LA.link t
|
|
|
|
LA.wait eventsNextA
|
2020-03-11 09:27:31 +03:00
|
|
|
|
|
|
|
let lenEvents = length events
|
|
|
|
if | lenEvents == fetchBatchSize -> do
|
2020-04-14 09:01:50 +03:00
|
|
|
-- If we've seen N fetches in a row from the DB come back full (i.e. only limited
|
2020-03-11 09:27:31 +03:00
|
|
|
-- by our LIMIT clause), then we say we're clearly falling behind:
|
|
|
|
let clearlyBehind = fullFetchCount >= 3
|
|
|
|
unless alreadyWarned $
|
|
|
|
when clearlyBehind $
|
|
|
|
L.unLogger logger $ L.UnstructuredLog L.LevelWarn $ fromString $
|
|
|
|
"Events processor may not be keeping up with events generated in postgres, " <>
|
|
|
|
"or we're working on a backlog of events. Consider increasing " <>
|
|
|
|
"HASURA_GRAPHQL_EVENTS_HTTP_POOL_SIZE"
|
|
|
|
go eventsNext (fullFetchCount+1) (alreadyWarned || clearlyBehind)
|
|
|
|
|
|
|
|
| otherwise -> do
|
|
|
|
when (lenEvents /= fetchBatchSize && alreadyWarned) $
|
|
|
|
-- emit as warning in case users are only logging warning severity and saw above
|
|
|
|
L.unLogger logger $ L.UnstructuredLog L.LevelWarn $ fromString $
|
|
|
|
"It looks like the events processor is keeping up again."
|
|
|
|
go eventsNext 0 False
|
|
|
|
|
2020-03-05 20:59:26 +03:00
|
|
|
processEvent
|
2020-07-14 22:00:58 +03:00
|
|
|
:: forall io r
|
|
|
|
. ( HasVersion
|
|
|
|
, MonadIO io
|
|
|
|
, MonadReader r io
|
2020-03-05 20:59:26 +03:00
|
|
|
, Has HTTP.Manager r
|
|
|
|
, Has (L.Logger L.Hasura) r
|
2020-07-15 13:40:48 +03:00
|
|
|
, Tracing.MonadTrace io
|
2020-03-05 20:59:26 +03:00
|
|
|
)
|
2020-07-14 22:00:58 +03:00
|
|
|
=> Event -> io ()
|
2020-03-05 20:59:26 +03:00
|
|
|
processEvent e = do
|
|
|
|
cache <- liftIO getSchemaCache
|
|
|
|
let meti = getEventTriggerInfoFromEvent cache e
|
|
|
|
case meti of
|
|
|
|
Nothing -> do
|
2020-04-09 09:33:33 +03:00
|
|
|
-- This rare error can happen in the following known cases:
|
|
|
|
-- i) schema cache is not up-to-date (due to some bug, say during schema syncing across multiple instances)
|
|
|
|
-- ii) the event trigger is dropped when this event was just fetched
|
2020-03-05 20:59:26 +03:00
|
|
|
logQErr $ err500 Unexpected "table or event-trigger not found in schema cache"
|
2020-04-09 09:33:33 +03:00
|
|
|
liftIO . runExceptT $ Q.runTx pool (Q.RepeatableRead, Just Q.ReadWrite) $ do
|
|
|
|
currentTime <- liftIO getCurrentTime
|
|
|
|
-- For such an event, we unlock the event and retry after a minute
|
|
|
|
setRetry e (addUTCTime 60 currentTime)
|
|
|
|
>>= flip onLeft logQErr
|
2020-03-05 20:59:26 +03:00
|
|
|
Just eti -> do
|
|
|
|
let webhook = T.unpack $ wciCachedValue $ etiWebhookInfo eti
|
|
|
|
retryConf = etiRetryConf eti
|
|
|
|
timeoutSeconds = fromMaybe defaultTimeoutSeconds (rcTimeoutSec retryConf)
|
|
|
|
responseTimeout = HTTP.responseTimeoutMicro (timeoutSeconds * 1000000)
|
|
|
|
headerInfos = etiHeaders eti
|
|
|
|
etHeaders = map encodeHeader headerInfos
|
|
|
|
headers = addDefaultHeaders etHeaders
|
|
|
|
ep = createEventPayload retryConf e
|
2020-07-28 20:52:44 +03:00
|
|
|
payload = encode $ toJSON ep
|
2020-05-13 15:33:16 +03:00
|
|
|
extraLogCtx = ExtraLogContext Nothing (epId ep) -- avoiding getting current time here to avoid another IO call with each event call
|
2020-07-28 20:52:44 +03:00
|
|
|
requestDetails = RequestDetails $ LBS.length payload
|
|
|
|
res <- runExceptT $ tryWebhook headers responseTimeout payload webhook
|
|
|
|
logHTTPForET res extraLogCtx requestDetails
|
2020-03-05 20:59:26 +03:00
|
|
|
let decodedHeaders = map (decodeHeader logenv headerInfos) headers
|
2020-03-11 09:27:31 +03:00
|
|
|
either
|
2020-03-05 20:59:26 +03:00
|
|
|
(processError pool e retryConf decodedHeaders ep)
|
|
|
|
(processSuccess pool e decodedHeaders ep) res
|
2020-03-11 09:27:31 +03:00
|
|
|
>>= flip onLeft logQErr
|
2019-02-22 15:25:36 +03:00
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
withEventEngineCtx ::
|
|
|
|
( MonadIO m
|
|
|
|
, MonadMask m
|
|
|
|
)
|
|
|
|
=> EventEngineCtx -> m () -> m ()
|
|
|
|
withEventEngineCtx eeCtx = bracket_ (decrementThreadCount eeCtx) (incrementThreadCount eeCtx)
|
|
|
|
|
|
|
|
incrementThreadCount :: MonadIO m => EventEngineCtx -> m ()
|
2020-07-02 14:57:09 +03:00
|
|
|
incrementThreadCount (EventEngineCtx c _) = liftIO $ atomically $ modifyTVar' c (+1)
|
2020-05-13 15:33:16 +03:00
|
|
|
|
|
|
|
decrementThreadCount :: MonadIO m => EventEngineCtx -> m ()
|
2020-07-02 14:57:09 +03:00
|
|
|
decrementThreadCount (EventEngineCtx c _) = liftIO $ atomically $ do
|
2020-05-13 15:33:16 +03:00
|
|
|
countThreads <- readTVar c
|
|
|
|
if countThreads > 0
|
|
|
|
then modifyTVar' c (\v -> v - 1)
|
|
|
|
else retry
|
|
|
|
|
2019-02-22 15:25:36 +03:00
|
|
|
createEventPayload :: RetryConf -> Event -> EventPayload
|
|
|
|
createEventPayload retryConf e = EventPayload
|
|
|
|
{ epId = eId e
|
|
|
|
, epTable = QualifiedTableStrict { getQualifiedTable = eTable e}
|
|
|
|
, epTrigger = eTrigger e
|
|
|
|
, epEvent = eEvent e
|
|
|
|
, epDeliveryInfo = DeliveryInfo
|
|
|
|
{ diCurrentRetry = eTries e
|
|
|
|
, diMaxRetries = rcNumRetries retryConf
|
|
|
|
}
|
|
|
|
, epCreatedAt = eCreatedAt e
|
|
|
|
}
|
|
|
|
|
|
|
|
processSuccess
|
|
|
|
:: ( MonadIO m )
|
2020-05-13 15:33:16 +03:00
|
|
|
=> Q.PGPool -> Event -> [HeaderConf] -> EventPayload -> HTTPResp a
|
2019-02-22 15:25:36 +03:00
|
|
|
-> m (Either QErr ())
|
|
|
|
processSuccess pool e decodedHeaders ep resp = do
|
|
|
|
let respBody = hrsBody resp
|
|
|
|
respHeaders = hrsHeaders resp
|
|
|
|
respStatus = hrsStatus resp
|
2020-05-13 15:33:16 +03:00
|
|
|
invocation = mkInvocation ep respStatus decodedHeaders respBody respHeaders
|
2019-02-22 15:25:36 +03:00
|
|
|
liftIO $ runExceptT $ Q.runTx pool (Q.RepeatableRead, Just Q.ReadWrite) $ do
|
|
|
|
insertInvocation invocation
|
|
|
|
setSuccess e
|
|
|
|
|
|
|
|
processError
|
2020-05-13 15:33:16 +03:00
|
|
|
:: ( MonadIO m )
|
|
|
|
=> Q.PGPool -> Event -> RetryConf -> [HeaderConf] -> EventPayload -> HTTPErr a
|
2019-02-22 15:25:36 +03:00
|
|
|
-> m (Either QErr ())
|
|
|
|
processError pool e retryConf decodedHeaders ep err = do
|
|
|
|
let invocation = case err of
|
|
|
|
HClient excp -> do
|
|
|
|
let errMsg = TBS.fromLBS $ encode $ show excp
|
2020-05-13 15:33:16 +03:00
|
|
|
mkInvocation ep 1000 decodedHeaders errMsg []
|
2019-02-22 15:25:36 +03:00
|
|
|
HParse _ detail -> do
|
|
|
|
let errMsg = TBS.fromLBS $ encode detail
|
2020-05-13 15:33:16 +03:00
|
|
|
mkInvocation ep 1001 decodedHeaders errMsg []
|
2019-02-22 15:25:36 +03:00
|
|
|
HStatus errResp -> do
|
|
|
|
let respPayload = hrsBody errResp
|
|
|
|
respHeaders = hrsHeaders errResp
|
|
|
|
respStatus = hrsStatus errResp
|
2020-05-13 15:33:16 +03:00
|
|
|
mkInvocation ep respStatus decodedHeaders respPayload respHeaders
|
2019-02-22 15:25:36 +03:00
|
|
|
HOther detail -> do
|
|
|
|
let errMsg = (TBS.fromLBS $ encode detail)
|
2020-05-13 15:33:16 +03:00
|
|
|
mkInvocation ep 500 decodedHeaders errMsg []
|
2019-02-22 15:25:36 +03:00
|
|
|
liftIO $ runExceptT $ Q.runTx pool (Q.RepeatableRead, Just Q.ReadWrite) $ do
|
|
|
|
insertInvocation invocation
|
|
|
|
retryOrSetError e retryConf err
|
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
retryOrSetError :: Event -> RetryConf -> HTTPErr a -> Q.TxE QErr ()
|
2019-02-22 15:25:36 +03:00
|
|
|
retryOrSetError e retryConf err = do
|
|
|
|
let mretryHeader = getRetryAfterHeaderFromError err
|
|
|
|
tries = eTries e
|
2020-01-16 04:56:57 +03:00
|
|
|
mretryHeaderSeconds = mretryHeader >>= parseRetryHeader
|
2019-02-22 15:25:36 +03:00
|
|
|
triesExhausted = tries >= rcNumRetries retryConf
|
|
|
|
noRetryHeader = isNothing mretryHeaderSeconds
|
|
|
|
-- current_try = tries + 1 , allowed_total_tries = rcNumRetries retryConf + 1
|
|
|
|
if triesExhausted && noRetryHeader
|
|
|
|
then do
|
|
|
|
setError e
|
|
|
|
else do
|
|
|
|
currentTime <- liftIO getCurrentTime
|
|
|
|
let delay = fromMaybe (rcIntervalSec retryConf) mretryHeaderSeconds
|
|
|
|
diff = fromIntegral delay
|
|
|
|
retryTime = addUTCTime diff currentTime
|
|
|
|
setRetry e retryTime
|
2018-09-05 14:26:46 +03:00
|
|
|
where
|
2018-10-26 19:28:03 +03:00
|
|
|
getRetryAfterHeaderFromError (HStatus resp) = getRetryAfterHeaderFromResp resp
|
2019-02-22 15:25:36 +03:00
|
|
|
getRetryAfterHeaderFromError _ = Nothing
|
2018-10-26 19:28:03 +03:00
|
|
|
|
2020-01-16 04:56:57 +03:00
|
|
|
parseRetryHeader = mfilter (> 0) . readMaybe . T.unpack
|
2018-10-26 19:28:03 +03:00
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
mkInvocation
|
2019-02-22 15:25:36 +03:00
|
|
|
:: EventPayload -> Int -> [HeaderConf] -> TBS.TByteString -> [HeaderConf]
|
2020-05-13 15:33:16 +03:00
|
|
|
-> (Invocation 'EventType)
|
|
|
|
mkInvocation ep status reqHeaders respBody respHeaders
|
2019-02-22 15:25:36 +03:00
|
|
|
= let resp = if isClientError status
|
|
|
|
then mkClientErr respBody
|
|
|
|
else mkResp status respBody respHeaders
|
|
|
|
in
|
|
|
|
Invocation
|
|
|
|
(epId ep)
|
|
|
|
status
|
2020-05-13 15:33:16 +03:00
|
|
|
(mkWebhookReq (toJSON ep) reqHeaders invocationVersionET)
|
2019-02-22 15:25:36 +03:00
|
|
|
resp
|
|
|
|
|
2019-11-26 15:14:21 +03:00
|
|
|
logQErr :: ( MonadReader r m, Has (L.Logger L.Hasura) r, MonadIO m) => QErr -> m ()
|
2019-02-22 15:25:36 +03:00
|
|
|
logQErr err = do
|
2019-11-26 15:14:21 +03:00
|
|
|
logger :: L.Logger L.Hasura <- asks getter
|
|
|
|
L.unLogger logger $ EventInternalErr err
|
2019-02-22 15:25:36 +03:00
|
|
|
|
2018-09-05 14:26:46 +03:00
|
|
|
getEventTriggerInfoFromEvent :: SchemaCache -> Event -> Maybe EventTriggerInfo
|
|
|
|
getEventTriggerInfoFromEvent sc e = let table = eTable e
|
|
|
|
tableInfo = M.lookup table $ scTables sc
|
2019-07-22 15:47:13 +03:00
|
|
|
in M.lookup ( tmName $ eTrigger e) =<< (_tiEventTriggerInfoMap <$> tableInfo)
|
2018-09-05 14:26:46 +03:00
|
|
|
|
2020-03-11 09:27:31 +03:00
|
|
|
---- DATABASE QUERIES ---------------------
|
|
|
|
--
|
|
|
|
-- The API for our in-database work queue:
|
|
|
|
-------------------------------------------
|
|
|
|
|
|
|
|
-- | Lock and return events not yet being processed or completed, up to some
|
|
|
|
-- limit. Process events approximately in created_at order, but we make no
|
|
|
|
-- ordering guarentees; events can and will race. Nevertheless we want to
|
|
|
|
-- ensure newer change events don't starve older ones.
|
|
|
|
fetchEvents :: Int -> Q.TxE QErr [Event]
|
|
|
|
fetchEvents limitI =
|
2018-09-05 14:26:46 +03:00
|
|
|
map uncurryEvent <$> Q.listQE defaultTxErrorHandler [Q.sql|
|
|
|
|
UPDATE hdb_catalog.event_log
|
2020-07-28 23:45:20 +03:00
|
|
|
SET locked = NOW()
|
2018-09-07 11:23:56 +03:00
|
|
|
WHERE id IN ( SELECT l.id
|
|
|
|
FROM hdb_catalog.event_log l
|
2020-07-28 23:45:20 +03:00
|
|
|
WHERE l.delivered = 'f' and l.error = 'f'
|
2020-07-29 02:11:51 +03:00
|
|
|
and (l.locked IS NULL or l.locked < (NOW() - interval '30 minute'))
|
2019-02-22 15:25:36 +03:00
|
|
|
and (l.next_retry_at is NULL or l.next_retry_at <= now())
|
2019-11-13 10:29:19 +03:00
|
|
|
and l.archived = 'f'
|
2020-03-11 09:27:31 +03:00
|
|
|
ORDER BY created_at
|
|
|
|
LIMIT $1
|
|
|
|
FOR UPDATE SKIP LOCKED )
|
2019-03-25 20:10:52 +03:00
|
|
|
RETURNING id, schema_name, table_name, trigger_name, payload::json, tries, created_at
|
2020-03-11 09:27:31 +03:00
|
|
|
|] (Identity limit) True
|
2019-03-25 20:10:52 +03:00
|
|
|
where uncurryEvent (id', sn, tn, trn, Q.AltJ payload, tries, created) =
|
2019-02-22 15:25:36 +03:00
|
|
|
Event
|
|
|
|
{ eId = id'
|
|
|
|
, eTable = QualifiedObject sn tn
|
2020-05-13 15:33:16 +03:00
|
|
|
, eTrigger = TriggerMetadata trn
|
2019-02-22 15:25:36 +03:00
|
|
|
, eEvent = payload
|
|
|
|
, eTries = tries
|
|
|
|
, eCreatedAt = created
|
|
|
|
}
|
2020-03-11 09:27:31 +03:00
|
|
|
limit = fromIntegral limitI :: Word64
|
2018-09-05 14:26:46 +03:00
|
|
|
|
2020-05-13 15:33:16 +03:00
|
|
|
insertInvocation :: Invocation 'EventType -> Q.TxE QErr ()
|
2018-09-05 14:26:46 +03:00
|
|
|
insertInvocation invo = do
|
|
|
|
Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
INSERT INTO hdb_catalog.event_invocation_logs (event_id, status, request, response)
|
|
|
|
VALUES ($1, $2, $3, $4)
|
2019-02-22 15:25:36 +03:00
|
|
|
|] ( iEventId invo
|
2020-05-13 15:33:16 +03:00
|
|
|
, toInt64 $ iStatus invo :: Int64
|
2019-02-22 15:25:36 +03:00
|
|
|
, Q.AltJ $ toJSON $ iRequest invo
|
|
|
|
, Q.AltJ $ toJSON $ iResponse invo) True
|
2018-09-05 14:26:46 +03:00
|
|
|
Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
UPDATE hdb_catalog.event_log
|
|
|
|
SET tries = tries + 1
|
|
|
|
WHERE id = $1
|
|
|
|
|] (Identity $ iEventId invo) True
|
|
|
|
|
2019-02-22 15:25:36 +03:00
|
|
|
setSuccess :: Event -> Q.TxE QErr ()
|
|
|
|
setSuccess e = Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
UPDATE hdb_catalog.event_log
|
2020-07-28 23:45:20 +03:00
|
|
|
SET delivered = 't', next_retry_at = NULL, locked = NULL
|
2019-02-22 15:25:36 +03:00
|
|
|
WHERE id = $1
|
|
|
|
|] (Identity $ eId e) True
|
|
|
|
|
|
|
|
setError :: Event -> Q.TxE QErr ()
|
|
|
|
setError e = Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
UPDATE hdb_catalog.event_log
|
2020-07-28 23:45:20 +03:00
|
|
|
SET error = 't', next_retry_at = NULL, locked = NULL
|
2019-02-22 15:25:36 +03:00
|
|
|
WHERE id = $1
|
|
|
|
|] (Identity $ eId e) True
|
|
|
|
|
|
|
|
setRetry :: Event -> UTCTime -> Q.TxE QErr ()
|
|
|
|
setRetry e time =
|
2018-09-05 14:26:46 +03:00
|
|
|
Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
UPDATE hdb_catalog.event_log
|
2020-07-28 23:45:20 +03:00
|
|
|
SET next_retry_at = $1, locked = NULL
|
2019-02-22 15:25:36 +03:00
|
|
|
WHERE id = $2
|
|
|
|
|] (time, eId e) True
|
2018-09-05 14:26:46 +03:00
|
|
|
|
|
|
|
unlockAllEvents :: Q.TxE QErr ()
|
|
|
|
unlockAllEvents =
|
|
|
|
Q.unitQE defaultTxErrorHandler [Q.sql|
|
|
|
|
UPDATE hdb_catalog.event_log
|
2020-07-28 23:45:20 +03:00
|
|
|
SET locked = NULL
|
|
|
|
WHERE locked IS NOT NULL
|
2020-04-14 09:01:50 +03:00
|
|
|
|] () True
|
2018-09-05 14:26:46 +03:00
|
|
|
|
2018-10-26 19:28:03 +03:00
|
|
|
toInt64 :: (Integral a) => a -> Int64
|
|
|
|
toInt64 = fromIntegral
|
2020-04-14 09:01:50 +03:00
|
|
|
|
|
|
|
-- EventIdArray is only used for PG array encoding
|
|
|
|
newtype EventIdArray = EventIdArray { unEventIdArray :: [EventId]} deriving (Show, Eq)
|
|
|
|
|
|
|
|
instance Q.ToPrepArg EventIdArray where
|
|
|
|
toPrepVal (EventIdArray l) = Q.toPrepValHelper PTI.unknown encoder $ l
|
|
|
|
where
|
|
|
|
-- 25 is the OID value of TEXT, https://jdbc.postgresql.org/development/privateapi/constant-values.html
|
|
|
|
encoder = PE.array 25 . PE.dimensionArray foldl' (PE.encodingArray . PE.text_strict)
|
|
|
|
|
2020-06-02 20:17:58 +03:00
|
|
|
-- | unlockEvents takes an array of 'EventId' and unlocks them. This function is called
|
|
|
|
-- when a graceful shutdown is initiated.
|
2020-04-14 09:01:50 +03:00
|
|
|
unlockEvents :: [EventId] -> Q.TxE QErr Int
|
|
|
|
unlockEvents eventIds =
|
|
|
|
(runIdentity . Q.getRow) <$> Q.withQE defaultTxErrorHandler
|
|
|
|
[Q.sql|
|
|
|
|
WITH "cte" AS
|
|
|
|
(UPDATE hdb_catalog.event_log
|
2020-07-28 23:45:20 +03:00
|
|
|
SET locked = NULL
|
2020-06-02 20:17:58 +03:00
|
|
|
WHERE id = ANY($1::text[])
|
|
|
|
-- only unlock those events that have been locked, it's possible
|
|
|
|
-- that an event has been processed but not yet been removed from
|
|
|
|
-- the saved locked events, which will lead to a double send
|
2020-07-28 23:45:20 +03:00
|
|
|
AND locked IS NOT NULL
|
2020-06-02 20:17:58 +03:00
|
|
|
RETURNING *)
|
2020-04-14 09:01:50 +03:00
|
|
|
SELECT count(*) FROM "cte"
|
|
|
|
|] (Identity $ EventIdArray eventIds) True
|