{-# LANGUAGE DuplicateRecordFields #-}
module Hasura.Backends.BigQuery.DDL.Source
( resolveSource,
postDropSourceHook,
resolveSourceConfig,
restTypeToScalarType,
)
where
import Data.Aeson qualified as J
import Data.ByteString.Lazy qualified as L
import Data.Environment qualified as Env
import Data.HashMap.Strict.Extended qualified as HM
import Data.Int qualified as Int
import Data.Text qualified as T
import Data.Text.Encoding qualified as T
import Data.Time.Clock.System
import Hasura.Backends.BigQuery.Connection
import Hasura.Backends.BigQuery.Meta
import Hasura.Backends.BigQuery.Source
import Hasura.Backends.BigQuery.Types
import Hasura.Base.Error
import Hasura.Logging (Hasura, Logger)
import Hasura.Prelude
import Hasura.RQL.Types.Backend (BackendConfig)
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.Backend
defaultGlobalSelectLimit :: Int.Int64
defaultGlobalSelectLimit :: Int64
defaultGlobalSelectLimit = Int64
1000
defaultRetryLimit :: Int
defaultRetryLimit :: Int
defaultRetryLimit = Int
5
defaultRetryBaseDelay :: Microseconds
defaultRetryBaseDelay :: Microseconds
defaultRetryBaseDelay = Microseconds
500000
resolveSourceConfig ::
MonadIO m =>
Logger Hasura ->
SourceName ->
BigQueryConnSourceConfig ->
BackendSourceKind 'BigQuery ->
BackendConfig 'BigQuery ->
Env.Environment ->
manager ->
m (Either QErr BigQuerySourceConfig)
resolveSourceConfig :: Logger Hasura
-> SourceName
-> BigQueryConnSourceConfig
-> BackendSourceKind 'BigQuery
-> BackendConfig 'BigQuery
-> Environment
-> manager
-> m (Either QErr BigQuerySourceConfig)
resolveSourceConfig Logger Hasura
_logger SourceName
_name BigQueryConnSourceConfig {Maybe ConfigurationInput
ConfigurationInput
ConfigurationInputs
ConfigurationJSON ServiceAccount
_cscRetryLimit :: BigQueryConnSourceConfig -> Maybe ConfigurationInput
_cscRetryBaseDelay :: BigQueryConnSourceConfig -> Maybe ConfigurationInput
_cscGlobalSelectLimit :: BigQueryConnSourceConfig -> Maybe ConfigurationInput
_cscProjectId :: BigQueryConnSourceConfig -> ConfigurationInput
_cscDatasets :: BigQueryConnSourceConfig -> ConfigurationInputs
_cscServiceAccount :: BigQueryConnSourceConfig -> ConfigurationJSON ServiceAccount
_cscRetryLimit :: Maybe ConfigurationInput
_cscRetryBaseDelay :: Maybe ConfigurationInput
_cscGlobalSelectLimit :: Maybe ConfigurationInput
_cscProjectId :: ConfigurationInput
_cscDatasets :: ConfigurationInputs
_cscServiceAccount :: ConfigurationJSON ServiceAccount
..} BackendSourceKind 'BigQuery
_backendKind BackendConfig 'BigQuery
_backendConfig Environment
env manager
_manager = ExceptT QErr m BigQuerySourceConfig
-> m (Either QErr BigQuerySourceConfig)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT QErr m BigQuerySourceConfig
-> m (Either QErr BigQuerySourceConfig))
-> ExceptT QErr m BigQuerySourceConfig
-> m (Either QErr BigQuerySourceConfig)
forall a b. (a -> b) -> a -> b
$ do
Either String ServiceAccount
eSA <- Environment
-> ConfigurationJSON ServiceAccount
-> ExceptT QErr m (Either String ServiceAccount)
forall (m :: * -> *) a.
(QErrM m, FromJSON a) =>
Environment -> ConfigurationJSON a -> m (Either String a)
resolveConfigurationJson Environment
env ConfigurationJSON ServiceAccount
_cscServiceAccount
case Either String ServiceAccount
eSA of
Left String
e -> Code -> Text -> ExceptT QErr m BigQuerySourceConfig
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected (Text -> ExceptT QErr m BigQuerySourceConfig)
-> Text -> ExceptT QErr m BigQuerySourceConfig
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
e
Right ServiceAccount
serviceAccount -> do
Text
projectId <- Environment -> ConfigurationInput -> ExceptT QErr m Text
forall (m :: * -> *).
QErrM m =>
Environment -> ConfigurationInput -> m Text
resolveConfigurationInput Environment
env ConfigurationInput
_cscProjectId
Maybe RetryOptions
retryOptions <- do
Int
numRetries <-
Environment -> ConfigurationInput -> ExceptT QErr m Text
forall (m :: * -> *).
QErrM m =>
Environment -> ConfigurationInput -> m Text
resolveConfigurationInput Environment
env (ConfigurationInput -> ExceptT QErr m Text)
-> Maybe ConfigurationInput -> ExceptT QErr m (Maybe Text)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
`mapM` Maybe ConfigurationInput
_cscRetryLimit ExceptT QErr m (Maybe Text)
-> (Maybe Text -> ExceptT QErr m Int) -> ExceptT QErr m Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> Int -> ExceptT QErr m Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
defaultRetryLimit
Just Text
v -> Text -> Text -> ExceptT QErr m Int
forall (m :: * -> *) a.
(MonadError QErr m, Num a, Ord a, FromJSON a, Read a) =>
Text -> Text -> m a
readNonNegative Text
v Text
"retry limit"
if Int
numRetries Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then Maybe RetryOptions -> ExceptT QErr m (Maybe RetryOptions)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe RetryOptions
forall a. Maybe a
Nothing
else do
let _retryNumRetries :: Int
_retryNumRetries = Int
numRetries
Microseconds
_retryBaseDelay <-
Environment -> ConfigurationInput -> ExceptT QErr m Text
forall (m :: * -> *).
QErrM m =>
Environment -> ConfigurationInput -> m Text
resolveConfigurationInput Environment
env (ConfigurationInput -> ExceptT QErr m Text)
-> Maybe ConfigurationInput -> ExceptT QErr m (Maybe Text)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
`mapM` Maybe ConfigurationInput
_cscRetryBaseDelay ExceptT QErr m (Maybe Text)
-> (Maybe Text -> ExceptT QErr m Microseconds)
-> ExceptT QErr m Microseconds
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> Microseconds -> ExceptT QErr m Microseconds
forall (f :: * -> *) a. Applicative f => a -> f a
pure Microseconds
defaultRetryBaseDelay
Just Text
v -> Integer -> Microseconds
forall a. Num a => Integer -> a
fromInteger (Integer -> Microseconds)
-> ExceptT QErr m Integer -> ExceptT QErr m Microseconds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ExceptT QErr m Integer
forall (m :: * -> *) a.
(MonadError QErr m, Num a, Ord a, FromJSON a, Read a) =>
Text -> Text -> m a
readNonNegative Text
v Text
"retry base delay"
Maybe RetryOptions -> ExceptT QErr m (Maybe RetryOptions)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe RetryOptions -> ExceptT QErr m (Maybe RetryOptions))
-> Maybe RetryOptions -> ExceptT QErr m (Maybe RetryOptions)
forall a b. (a -> b) -> a -> b
$ RetryOptions -> Maybe RetryOptions
forall a. a -> Maybe a
Just RetryOptions :: Microseconds -> Int -> RetryOptions
RetryOptions {Int
Microseconds
_retryNumRetries :: Int
_retryBaseDelay :: Microseconds
_retryBaseDelay :: Microseconds
_retryNumRetries :: Int
..}
BigQueryConnection
_scConnection <- ServiceAccount
-> Text -> Maybe RetryOptions -> ExceptT QErr m BigQueryConnection
forall (m :: * -> *).
MonadIO m =>
ServiceAccount
-> Text -> Maybe RetryOptions -> m BigQueryConnection
initConnection ServiceAccount
serviceAccount Text
projectId Maybe RetryOptions
retryOptions
[Text]
_scDatasets <- Environment -> ConfigurationInputs -> ExceptT QErr m [Text]
forall (m :: * -> *).
QErrM m =>
Environment -> ConfigurationInputs -> m [Text]
resolveConfigurationInputs Environment
env ConfigurationInputs
_cscDatasets
Int64
_scGlobalSelectLimit <-
Environment -> ConfigurationInput -> ExceptT QErr m Text
forall (m :: * -> *).
QErrM m =>
Environment -> ConfigurationInput -> m Text
resolveConfigurationInput Environment
env (ConfigurationInput -> ExceptT QErr m Text)
-> Maybe ConfigurationInput -> ExceptT QErr m (Maybe Text)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
`mapM` Maybe ConfigurationInput
_cscGlobalSelectLimit ExceptT QErr m (Maybe Text)
-> (Maybe Text -> ExceptT QErr m Int64) -> ExceptT QErr m Int64
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> Int64 -> ExceptT QErr m Int64
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int64
defaultGlobalSelectLimit
Just Text
v -> Text -> Text -> ExceptT QErr m Int64
forall (m :: * -> *) a.
(MonadError QErr m, Num a, Ord a, FromJSON a, Read a) =>
Text -> Text -> m a
readNonNegative Text
v Text
"global select limit"
BigQuerySourceConfig -> ExceptT QErr m BigQuerySourceConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure BigQuerySourceConfig :: BigQueryConnection -> [Text] -> Int64 -> BigQuerySourceConfig
BigQuerySourceConfig {Int64
[Text]
BigQueryConnection
_scGlobalSelectLimit :: Int64
_scDatasets :: [Text]
_scConnection :: BigQueryConnection
_scGlobalSelectLimit :: Int64
_scDatasets :: [Text]
_scConnection :: BigQueryConnection
..}
readNonNegative :: (MonadError QErr m, Num a, Ord a, J.FromJSON a, Read a) => Text -> Text -> m a
readNonNegative :: Text -> Text -> m a
readNonNegative Text
i Text
paramName =
case String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe (Text -> String
T.unpack Text
i) Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ByteString -> Maybe a
forall a. FromJSON a => ByteString -> Maybe a
J.decode (ByteString -> ByteString
L.fromStrict (Text -> ByteString
T.encodeUtf8 Text
i)) of
Maybe a
Nothing -> Code -> Text -> m a
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected (Text -> m a) -> Text -> m a
forall a b. (a -> b) -> a -> b
$ Text
"Need a non-negative integer for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
paramName
Just a
i' -> do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (a
i' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Need the integer for the " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
paramName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" to be non-negative"
a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
i'
resolveSource ::
(MonadIO m) =>
BigQuerySourceConfig ->
SourceTypeCustomization ->
m (Either QErr (ResolvedSource 'BigQuery))
resolveSource :: BigQuerySourceConfig
-> SourceTypeCustomization
-> m (Either QErr (ResolvedSource 'BigQuery))
resolveSource BigQuerySourceConfig
sourceConfig SourceTypeCustomization
customization =
ExceptT QErr m (ResolvedSource 'BigQuery)
-> m (Either QErr (ResolvedSource 'BigQuery))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT QErr m (ResolvedSource 'BigQuery)
-> m (Either QErr (ResolvedSource 'BigQuery)))
-> ExceptT QErr m (ResolvedSource 'BigQuery)
-> m (Either QErr (ResolvedSource 'BigQuery))
forall a b. (a -> b) -> a -> b
$ do
Either RestProblem [RestTable]
tables <- BigQuerySourceConfig
-> ExceptT QErr m (Either RestProblem [RestTable])
forall (m :: * -> *).
MonadIO m =>
BigQuerySourceConfig -> m (Either RestProblem [RestTable])
getTables BigQuerySourceConfig
sourceConfig
Either RestProblem [RestRoutine]
routines <- BigQuerySourceConfig
-> ExceptT QErr m (Either RestProblem [RestRoutine])
forall (m :: * -> *).
MonadIO m =>
BigQuerySourceConfig -> m (Either RestProblem [RestRoutine])
getRoutines BigQuerySourceConfig
sourceConfig
let result :: Either RestProblem ([RestTable], [RestRoutine])
result = (,) ([RestTable] -> [RestRoutine] -> ([RestTable], [RestRoutine]))
-> Either RestProblem [RestTable]
-> Either
RestProblem ([RestRoutine] -> ([RestTable], [RestRoutine]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either RestProblem [RestTable]
tables Either RestProblem ([RestRoutine] -> ([RestTable], [RestRoutine]))
-> Either RestProblem [RestRoutine]
-> Either RestProblem ([RestTable], [RestRoutine])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Either RestProblem [RestRoutine]
routines
case Either RestProblem ([RestTable], [RestRoutine])
result of
Left RestProblem
err ->
Code -> Text -> ExceptT QErr m (ResolvedSource 'BigQuery)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected (Text -> ExceptT QErr m (ResolvedSource 'BigQuery))
-> Text -> ExceptT QErr m (ResolvedSource 'BigQuery)
forall a b. (a -> b) -> a -> b
$
Text
"unexpected exception while connecting to database: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RestProblem -> Text
forall a. Show a => a -> Text
tshow RestProblem
err
Right ([RestTable]
restTables, [RestRoutine]
restRoutines) -> do
Int64
seconds <- IO Int64 -> ExceptT QErr m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> ExceptT QErr m Int64)
-> IO Int64 -> ExceptT QErr m Int64
forall a b. (a -> b) -> a -> b
$ (SystemTime -> Int64) -> IO SystemTime -> IO Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SystemTime -> Int64
systemSeconds IO SystemTime
getSystemTime
let functions :: HashMap FunctionName [RestRoutine]
functions = (RestRoutine -> FunctionName)
-> [RestRoutine] -> HashMap FunctionName [RestRoutine]
forall k (t :: * -> *) v.
(Eq k, Hashable k, Foldable t) =>
(v -> k) -> t v -> HashMap k [v]
HM.groupOn (RestRoutineReference -> FunctionName
routineReferenceToFunctionName (RestRoutineReference -> FunctionName)
-> (RestRoutine -> RestRoutineReference)
-> RestRoutine
-> FunctionName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RestRoutine -> RestRoutineReference
routineReference) [RestRoutine]
restRoutines
ResolvedSource 'BigQuery
-> ExceptT QErr m (ResolvedSource 'BigQuery)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( ResolvedSource :: forall (b :: BackendType).
SourceConfig b
-> SourceTypeCustomization
-> DBTablesMetadata b
-> DBFunctionsMetadata b
-> ScalarMap b
-> ResolvedSource b
ResolvedSource
{ _rsConfig :: SourceConfig 'BigQuery
_rsConfig = SourceConfig 'BigQuery
BigQuerySourceConfig
sourceConfig,
_rsCustomization :: SourceTypeCustomization
_rsCustomization = SourceTypeCustomization
customization,
_rsTables :: DBTablesMetadata 'BigQuery
_rsTables =
[(TableName, DBTableMetadata 'BigQuery)]
-> HashMap TableName (DBTableMetadata 'BigQuery)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList
[ ( RestTableReference -> TableName
restTableReferenceToTableName RestTableReference
tableReference,
DBTableMetadata :: forall (b :: BackendType).
OID
-> [RawColumnInfo b]
-> Maybe (PrimaryKey b (Column b))
-> HashSet (UniqueConstraint b)
-> HashSet (ForeignKeyMetadata b)
-> Maybe ViewInfo
-> Maybe PGDescription
-> ExtraTableMetadata b
-> DBTableMetadata b
DBTableMetadata
{ _ptmiOid :: OID
_ptmiOid = Int -> OID
OID (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
seconds Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
index :: Int),
_ptmiColumns :: [RawColumnInfo 'BigQuery]
_ptmiColumns =
[ RawColumnInfo :: forall (b :: BackendType).
Column b
-> Int
-> ScalarType b
-> Bool
-> Maybe Description
-> ColumnMutability
-> RawColumnInfo b
RawColumnInfo
{ rciName :: Column 'BigQuery
rciName = Text -> ColumnName
ColumnName Text
name,
rciPosition :: Int
rciPosition = Int
position,
rciType :: ScalarType 'BigQuery
rciType = RestType -> ScalarType
restTypeToScalarType RestType
type',
rciIsNullable :: Bool
rciIsNullable =
case Mode
mode of
Mode
Nullable -> Bool
True
Mode
_ -> Bool
False,
rciDescription :: Maybe Description
rciDescription = Maybe Description
forall a. Maybe a
Nothing,
rciMutability :: ColumnMutability
rciMutability = ColumnMutability :: Bool -> Bool -> ColumnMutability
ColumnMutability {_cmIsInsertable :: Bool
_cmIsInsertable = Bool
True, _cmIsUpdatable :: Bool
_cmIsUpdatable = Bool
True}
}
| (Int
position, RestFieldSchema {Text
$sel:name:RestFieldSchema :: RestFieldSchema -> Text
name :: Text
name, RestType
$sel:type':RestFieldSchema :: RestFieldSchema -> RestType
type' :: RestType
type', Mode
$sel:mode:RestFieldSchema :: RestFieldSchema -> Mode
mode :: Mode
mode}) <-
[Int] -> [RestFieldSchema] -> [(Int, RestFieldSchema)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1 ..] [RestFieldSchema]
fields
],
_ptmiPrimaryKey :: Maybe (PrimaryKey 'BigQuery (Column 'BigQuery))
_ptmiPrimaryKey = Maybe (PrimaryKey 'BigQuery (Column 'BigQuery))
forall a. Maybe a
Nothing,
_ptmiUniqueConstraints :: HashSet (UniqueConstraint 'BigQuery)
_ptmiUniqueConstraints = HashSet (UniqueConstraint 'BigQuery)
forall a. Monoid a => a
mempty,
_ptmiForeignKeys :: HashSet (ForeignKeyMetadata 'BigQuery)
_ptmiForeignKeys = HashSet (ForeignKeyMetadata 'BigQuery)
forall a. Monoid a => a
mempty,
_ptmiViewInfo :: Maybe ViewInfo
_ptmiViewInfo = ViewInfo -> Maybe ViewInfo
forall a. a -> Maybe a
Just (ViewInfo -> Maybe ViewInfo) -> ViewInfo -> Maybe ViewInfo
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool -> ViewInfo
ViewInfo Bool
False Bool
False Bool
False,
_ptmiDescription :: Maybe PGDescription
_ptmiDescription = Maybe PGDescription
forall a. Maybe a
Nothing,
_ptmiExtraTableMetadata :: ExtraTableMetadata 'BigQuery
_ptmiExtraTableMetadata = ()
}
)
| (Int
index, RestTable {RestTableReference
$sel:tableReference:RestTable :: RestTable -> RestTableReference
tableReference :: RestTableReference
tableReference, RestTableSchema
$sel:schema:RestTable :: RestTable -> RestTableSchema
schema :: RestTableSchema
schema}) <-
[Int] -> [RestTable] -> [(Int, RestTable)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0 ..] [RestTable]
restTables,
let RestTableSchema [RestFieldSchema]
fields = RestTableSchema
schema
],
_rsFunctions :: DBFunctionsMetadata 'BigQuery
_rsFunctions = DBFunctionsMetadata 'BigQuery
HashMap FunctionName [RestRoutine]
functions,
_rsScalars :: ScalarMap 'BigQuery
_rsScalars = ScalarMap 'BigQuery
forall a. Monoid a => a
mempty
}
)
restTypeToScalarType :: RestType -> ScalarType
restTypeToScalarType :: RestType -> ScalarType
restTypeToScalarType =
\case
RestType
STRING -> ScalarType
StringScalarType
RestType
BYTES -> ScalarType
BytesScalarType
RestType
INTEGER -> ScalarType
IntegerScalarType
RestType
FLOAT -> ScalarType
FloatScalarType
RestType
BOOL -> ScalarType
BoolScalarType
RestType
TIMESTAMP -> ScalarType
TimestampScalarType
RestType
DATE -> ScalarType
DateScalarType
RestType
TIME -> ScalarType
TimeScalarType
RestType
DATETIME -> ScalarType
DatetimeScalarType
RestType
GEOGRAPHY -> ScalarType
GeographyScalarType
RestType
STRUCT -> ScalarType
StructScalarType
RestType
BIGDECIMAL -> ScalarType
BigDecimalScalarType
RestType
DECIMAL -> ScalarType
DecimalScalarType
restTableReferenceToTableName :: RestTableReference -> TableName
restTableReferenceToTableName :: RestTableReference -> TableName
restTableReferenceToTableName RestTableReference {Text
$sel:tableId:RestTableReference :: RestTableReference -> Text
$sel:projectId:RestTableReference :: RestTableReference -> Text
$sel:datasetId:RestTableReference :: RestTableReference -> Text
tableId :: Text
projectId :: Text
datasetId :: Text
..} =
TableName :: Text -> Text -> TableName
TableName {$sel:tableName:TableName :: Text
tableName = Text
tableId, $sel:tableNameSchema:TableName :: Text
tableNameSchema = Text
datasetId}
postDropSourceHook ::
(MonadIO m) =>
BigQuerySourceConfig ->
TableEventTriggers 'BigQuery ->
m ()
postDropSourceHook :: BigQuerySourceConfig -> TableEventTriggers 'BigQuery -> m ()
postDropSourceHook BigQuerySourceConfig
_ TableEventTriggers 'BigQuery
_ =
() -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()