{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.DDL.Schema.LegacyCatalog
( saveMetadataToHdbTables,
fetchMetadataFromHdbTables,
recreateSystemMetadata,
addCronTriggerForeignKeyConstraint,
parseLegacyRemoteRelationshipDefinition,
)
where
import Control.Lens hiding ((.=))
import Data.Aeson
import Data.FileEmbed (makeRelativeToProject)
import Data.HashMap.Strict qualified as HM
import Data.HashMap.Strict.InsOrd qualified as OMap
import Data.Text.Extended ((<<>))
import Data.Text.NonEmpty
import Data.Time.Clock qualified as C
import Database.PG.Query qualified as Q
import Hasura.Backends.Postgres.Connection
import Hasura.Backends.Postgres.SQL.Types
import Hasura.Base.Error
import Hasura.Eventing.ScheduledTrigger
import Hasura.Prelude
import Hasura.RQL.DDL.Action
import Hasura.RQL.DDL.ComputedField
import Hasura.RQL.DDL.Permission
import Hasura.RQL.DDL.RemoteRelationship
import Hasura.RQL.Types.Action
import Hasura.RQL.Types.Allowlist
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.CustomTypes
import Hasura.RQL.Types.EventTrigger
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.QueryCollection
import Hasura.RQL.Types.Relationships.Local
import Hasura.RQL.Types.Relationships.Remote
import Hasura.RQL.Types.ScheduledTrigger
import Hasura.RQL.Types.SchemaCache
import Hasura.SQL.Backend
saveMetadataToHdbTables ::
(MonadTx m, MonadReader SystemDefined m) => MetadataNoSources -> m ()
saveMetadataToHdbTables :: MetadataNoSources -> m ()
saveMetadataToHdbTables
( MetadataNoSources
Tables ('Postgres 'Vanilla)
tables
Functions ('Postgres 'Vanilla)
functions
RemoteSchemas
schemas
QueryCollections
collections
MetadataAllowlist
allowlist
CustomTypes
customTypes
Actions
actions
CronTriggers
cronTriggers
) = do
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"tables" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
-> (TableMetadata ('Postgres 'Vanilla) -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ Tables ('Postgres 'Vanilla)
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables ((TableMetadata ('Postgres 'Vanilla) -> m ()) -> m ())
-> (TableMetadata ('Postgres 'Vanilla) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \TableMetadata {Bool
Maybe ApolloFederationConfig
Permissions (UpdPermDef ('Postgres 'Vanilla))
Permissions (DelPermDef ('Postgres 'Vanilla))
Permissions (SelPermDef ('Postgres 'Vanilla))
Permissions (InsPermDef ('Postgres 'Vanilla))
Relationships (ObjRelDef ('Postgres 'Vanilla))
Relationships (ArrRelDef ('Postgres 'Vanilla))
RemoteRelationships
EventTriggers ('Postgres 'Vanilla)
ComputedFields ('Postgres 'Vanilla)
TableName ('Postgres 'Vanilla)
TableConfig ('Postgres 'Vanilla)
_tmApolloFederationConfig :: forall (b :: BackendType).
TableMetadata b -> Maybe ApolloFederationConfig
_tmEventTriggers :: forall (b :: BackendType). TableMetadata b -> EventTriggers b
_tmDeletePermissions :: forall (b :: BackendType).
TableMetadata b -> Permissions (DelPermDef b)
_tmUpdatePermissions :: forall (b :: BackendType).
TableMetadata b -> Permissions (UpdPermDef b)
_tmSelectPermissions :: forall (b :: BackendType).
TableMetadata b -> Permissions (SelPermDef b)
_tmInsertPermissions :: forall (b :: BackendType).
TableMetadata b -> Permissions (InsPermDef b)
_tmRemoteRelationships :: forall (b :: BackendType). TableMetadata b -> RemoteRelationships
_tmComputedFields :: forall (b :: BackendType). TableMetadata b -> ComputedFields b
_tmArrayRelationships :: forall (b :: BackendType).
TableMetadata b -> Relationships (ArrRelDef b)
_tmObjectRelationships :: forall (b :: BackendType).
TableMetadata b -> Relationships (ObjRelDef b)
_tmConfiguration :: forall (b :: BackendType). TableMetadata b -> TableConfig b
_tmIsEnum :: forall (b :: BackendType). TableMetadata b -> Bool
_tmTable :: forall (b :: BackendType). TableMetadata b -> TableName b
_tmApolloFederationConfig :: Maybe ApolloFederationConfig
_tmEventTriggers :: EventTriggers ('Postgres 'Vanilla)
_tmDeletePermissions :: Permissions (DelPermDef ('Postgres 'Vanilla))
_tmUpdatePermissions :: Permissions (UpdPermDef ('Postgres 'Vanilla))
_tmSelectPermissions :: Permissions (SelPermDef ('Postgres 'Vanilla))
_tmInsertPermissions :: Permissions (InsPermDef ('Postgres 'Vanilla))
_tmRemoteRelationships :: RemoteRelationships
_tmComputedFields :: ComputedFields ('Postgres 'Vanilla)
_tmArrayRelationships :: Relationships (ArrRelDef ('Postgres 'Vanilla))
_tmObjectRelationships :: Relationships (ObjRelDef ('Postgres 'Vanilla))
_tmConfiguration :: TableConfig ('Postgres 'Vanilla)
_tmIsEnum :: Bool
_tmTable :: TableName ('Postgres 'Vanilla)
..} -> do
QualifiedTable -> Bool -> TableConfig ('Postgres 'Vanilla) -> m ()
forall (m :: * -> *).
(MonadTx m, MonadReader SystemDefined m) =>
QualifiedTable -> Bool -> TableConfig ('Postgres 'Vanilla) -> m ()
saveTableToCatalog TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable Bool
_tmIsEnum TableConfig ('Postgres 'Vanilla)
_tmConfiguration
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"object_relationships" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Relationships (ObjRelDef ('Postgres 'Vanilla))
-> (ObjRelDef ('Postgres 'Vanilla) -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ Relationships (ObjRelDef ('Postgres 'Vanilla))
_tmObjectRelationships ((ObjRelDef ('Postgres 'Vanilla) -> m ()) -> m ())
-> (ObjRelDef ('Postgres 'Vanilla) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \ObjRelDef ('Postgres 'Vanilla)
objRel ->
QualifiedTable -> RelType -> ObjRelDef ('Postgres 'Vanilla) -> m ()
forall (m :: * -> *) a.
(MonadTx m, MonadReader SystemDefined m, ToJSON a) =>
QualifiedTable -> RelType -> RelDef a -> m ()
insertRelationshipToCatalog TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable RelType
ObjRel ObjRelDef ('Postgres 'Vanilla)
objRel
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"array_relationships" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Relationships (ArrRelDef ('Postgres 'Vanilla))
-> (ArrRelDef ('Postgres 'Vanilla) -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ Relationships (ArrRelDef ('Postgres 'Vanilla))
_tmArrayRelationships ((ArrRelDef ('Postgres 'Vanilla) -> m ()) -> m ())
-> (ArrRelDef ('Postgres 'Vanilla) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \ArrRelDef ('Postgres 'Vanilla)
arrRel ->
QualifiedTable -> RelType -> ArrRelDef ('Postgres 'Vanilla) -> m ()
forall (m :: * -> *) a.
(MonadTx m, MonadReader SystemDefined m, ToJSON a) =>
QualifiedTable -> RelType -> RelDef a -> m ()
insertRelationshipToCatalog TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable RelType
ArrRel ArrRelDef ('Postgres 'Vanilla)
arrRel
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"computed_fields" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
ComputedFields ('Postgres 'Vanilla)
-> (ComputedFieldMetadata ('Postgres 'Vanilla) -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ ComputedFields ('Postgres 'Vanilla)
_tmComputedFields ((ComputedFieldMetadata ('Postgres 'Vanilla) -> m ()) -> m ())
-> (ComputedFieldMetadata ('Postgres 'Vanilla) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
\(ComputedFieldMetadata ComputedFieldName
name ComputedFieldDefinition ('Postgres 'Vanilla)
definition Comment
comment) ->
AddComputedField ('Postgres 'Vanilla) -> m ()
forall (m :: * -> *).
MonadTx m =>
AddComputedField ('Postgres 'Vanilla) -> m ()
addComputedFieldToCatalog (AddComputedField ('Postgres 'Vanilla) -> m ())
-> AddComputedField ('Postgres 'Vanilla) -> m ()
forall a b. (a -> b) -> a -> b
$
SourceName
-> TableName ('Postgres 'Vanilla)
-> ComputedFieldName
-> ComputedFieldDefinition ('Postgres 'Vanilla)
-> Comment
-> AddComputedField ('Postgres 'Vanilla)
forall (b :: BackendType).
SourceName
-> TableName b
-> ComputedFieldName
-> ComputedFieldDefinition b
-> Comment
-> AddComputedField b
AddComputedField SourceName
defaultSource TableName ('Postgres 'Vanilla)
_tmTable ComputedFieldName
name ComputedFieldDefinition ('Postgres 'Vanilla)
definition Comment
comment
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"remote_relationships" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
RemoteRelationships -> (RemoteRelationship -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ RemoteRelationships
_tmRemoteRelationships ((RemoteRelationship -> m ()) -> m ())
-> (RemoteRelationship -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
\RemoteRelationship {RelName
RemoteRelationshipDefinition
_rrDefinition :: RemoteRelationship -> RemoteRelationshipDefinition
_rrName :: RemoteRelationship -> RelName
_rrDefinition :: RemoteRelationshipDefinition
_rrName :: RelName
..} -> do
CreateFromSourceRelationship ('Postgres 'Vanilla) -> m ()
forall (m :: * -> *).
MonadTx m =>
CreateFromSourceRelationship ('Postgres 'Vanilla) -> m ()
addRemoteRelationshipToCatalog (CreateFromSourceRelationship ('Postgres 'Vanilla) -> m ())
-> CreateFromSourceRelationship ('Postgres 'Vanilla) -> m ()
forall a b. (a -> b) -> a -> b
$
SourceName
-> TableName ('Postgres 'Vanilla)
-> RelName
-> RemoteRelationshipDefinition
-> CreateFromSourceRelationship ('Postgres 'Vanilla)
forall (b :: BackendType).
SourceName
-> TableName b
-> RelName
-> RemoteRelationshipDefinition
-> CreateFromSourceRelationship b
CreateFromSourceRelationship SourceName
defaultSource TableName ('Postgres 'Vanilla)
_tmTable RelName
_rrName RemoteRelationshipDefinition
_rrDefinition
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"insert_permissions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ QualifiedTable
-> Permissions (InsPermDef ('Postgres 'Vanilla)) -> m ()
forall (m :: * -> *) (b :: BackendType) (t :: * -> *)
(a :: BackendType -> *).
(MonadReader SystemDefined m, MonadTx m, Backend b, Foldable t) =>
QualifiedTable -> t (PermDef b a) -> m ()
processPerms TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable Permissions (InsPermDef ('Postgres 'Vanilla))
_tmInsertPermissions
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"select_permissions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ QualifiedTable
-> Permissions (SelPermDef ('Postgres 'Vanilla)) -> m ()
forall (m :: * -> *) (b :: BackendType) (t :: * -> *)
(a :: BackendType -> *).
(MonadReader SystemDefined m, MonadTx m, Backend b, Foldable t) =>
QualifiedTable -> t (PermDef b a) -> m ()
processPerms TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable Permissions (SelPermDef ('Postgres 'Vanilla))
_tmSelectPermissions
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"update_permissions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ QualifiedTable
-> Permissions (UpdPermDef ('Postgres 'Vanilla)) -> m ()
forall (m :: * -> *) (b :: BackendType) (t :: * -> *)
(a :: BackendType -> *).
(MonadReader SystemDefined m, MonadTx m, Backend b, Foldable t) =>
QualifiedTable -> t (PermDef b a) -> m ()
processPerms TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable Permissions (UpdPermDef ('Postgres 'Vanilla))
_tmUpdatePermissions
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"delete_permissions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ QualifiedTable
-> Permissions (DelPermDef ('Postgres 'Vanilla)) -> m ()
forall (m :: * -> *) (b :: BackendType) (t :: * -> *)
(a :: BackendType -> *).
(MonadReader SystemDefined m, MonadTx m, Backend b, Foldable t) =>
QualifiedTable -> t (PermDef b a) -> m ()
processPerms TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable Permissions (DelPermDef ('Postgres 'Vanilla))
_tmDeletePermissions
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"event_triggers" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
EventTriggers ('Postgres 'Vanilla)
-> (EventTriggerConf ('Postgres 'Vanilla) -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ EventTriggers ('Postgres 'Vanilla)
_tmEventTriggers ((EventTriggerConf ('Postgres 'Vanilla) -> m ()) -> m ())
-> (EventTriggerConf ('Postgres 'Vanilla) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \EventTriggerConf ('Postgres 'Vanilla)
etc -> QualifiedTable -> EventTriggerConf ('Postgres 'Vanilla) -> m ()
forall (m :: * -> *) (pgKind :: PostgresKind).
(MonadTx m, Backend ('Postgres pgKind)) =>
QualifiedTable -> EventTriggerConf ('Postgres pgKind) -> m ()
addEventTriggerToCatalog TableName ('Postgres 'Vanilla)
QualifiedTable
_tmTable EventTriggerConf ('Postgres 'Vanilla)
etc
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"functions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
-> (FunctionMetadata ('Postgres 'Vanilla) -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ Functions ('Postgres 'Vanilla)
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions ((FunctionMetadata ('Postgres 'Vanilla) -> m ()) -> m ())
-> (FunctionMetadata ('Postgres 'Vanilla) -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$
\(FunctionMetadata FunctionName ('Postgres 'Vanilla)
function FunctionConfig
config [FunctionPermissionInfo]
_ Maybe Text
_) -> QualifiedFunction -> FunctionConfig -> m ()
forall (m :: * -> *).
(MonadTx m, MonadReader SystemDefined m) =>
QualifiedFunction -> FunctionConfig -> m ()
addFunctionToCatalog FunctionName ('Postgres 'Vanilla)
QualifiedFunction
function FunctionConfig
config
SystemDefined
systemDefined <- m SystemDefined
forall r (m :: * -> *). MonadReader r m => m r
ask
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"query_collections" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
QueryCollections -> (CreateCollection -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ QueryCollections
collections ((CreateCollection -> m ()) -> m ())
-> (CreateCollection -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \CreateCollection
c -> TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ CreateCollection -> SystemDefined -> TxE QErr ()
forall (m :: * -> *).
MonadTx m =>
CreateCollection -> SystemDefined -> m ()
addCollectionToCatalog CreateCollection
c SystemDefined
systemDefined
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"allowlist" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
MetadataAllowlist -> (AllowlistEntry -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ MetadataAllowlist
allowlist ((AllowlistEntry -> m ()) -> m ())
-> (AllowlistEntry -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \(AllowlistEntry CollectionName
collectionName AllowlistScope
scope) -> do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (AllowlistScope
scope AllowlistScope -> AllowlistScope -> Bool
forall a. Eq a => a -> a -> Bool
== AllowlistScope
AllowlistScopeGlobal) (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
NotSupported (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$
Text
"cannot downgrade to v1 because the "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CollectionName
collectionName
CollectionName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" added to the allowlist is a role based allowlist"
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ CollectionName -> TxE QErr ()
forall (m :: * -> *). MonadTx m => CollectionName -> m ()
addCollectionToAllowlistCatalog CollectionName
collectionName
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"remote_schemas" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
(RemoteSchemaMetadata -> m ()) -> RemoteSchemas -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
(a -> m b) -> t a -> m ()
indexedMapM_ (TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ())
-> (RemoteSchemaMetadata -> TxE QErr ())
-> RemoteSchemaMetadata
-> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RemoteSchemaMetadata -> TxE QErr ()
addRemoteSchemaToCatalog) RemoteSchemas
schemas
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"custom_types" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ CustomTypes -> m ()
forall (m :: * -> *). MonadTx m => CustomTypes -> m ()
setCustomTypesInCatalog CustomTypes
customTypes
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"cron_triggers" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
CronTriggers -> (CronTriggerMetadata -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ CronTriggers
cronTriggers ((CronTriggerMetadata -> m ()) -> m ())
-> (CronTriggerMetadata -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \CronTriggerMetadata
ct -> TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ do
CronTriggerMetadata -> TxE QErr ()
forall (m :: * -> *). MonadTx m => CronTriggerMetadata -> m ()
addCronTriggerToCatalog CronTriggerMetadata
ct
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"actions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Actions -> (ActionMetadata -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ Actions
actions ((ActionMetadata -> m ()) -> m ())
-> (ActionMetadata -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \ActionMetadata
action -> do
let createAction :: CreateAction
createAction =
ActionName -> ActionDefinitionInput -> Maybe Text -> CreateAction
CreateAction (ActionMetadata -> ActionName
_amName ActionMetadata
action) (ActionMetadata -> ActionDefinitionInput
_amDefinition ActionMetadata
action) (ActionMetadata -> Maybe Text
_amComment ActionMetadata
action)
CreateAction -> m ()
forall (m :: * -> *). MonadTx m => CreateAction -> m ()
addActionToCatalog CreateAction
createAction
Text -> m () -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"permissions" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
[ActionPermissionMetadata]
-> (ActionPermissionMetadata -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ (ActionMetadata -> [ActionPermissionMetadata]
_amPermissions ActionMetadata
action) ((ActionPermissionMetadata -> m ()) -> m ())
-> (ActionPermissionMetadata -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \ActionPermissionMetadata
permission -> do
let createActionPermission :: CreateActionPermission
createActionPermission =
ActionName
-> RoleName -> Maybe Value -> Maybe Text -> CreateActionPermission
CreateActionPermission
(ActionMetadata -> ActionName
_amName ActionMetadata
action)
(ActionPermissionMetadata -> RoleName
_apmRole ActionPermissionMetadata
permission)
Maybe Value
forall a. Maybe a
Nothing
(ActionPermissionMetadata -> Maybe Text
_apmComment ActionPermissionMetadata
permission)
CreateActionPermission -> m ()
forall (m :: * -> *). MonadTx m => CreateActionPermission -> m ()
addActionPermissionToCatalog CreateActionPermission
createActionPermission
where
processPerms :: QualifiedTable -> t (PermDef b a) -> m ()
processPerms QualifiedTable
tableName t (PermDef b a)
perms = t (PermDef b a) -> (PermDef b a -> m ()) -> m ()
forall (m :: * -> *) (t :: * -> *) a b.
(QErrM m, Foldable t) =>
t a -> (a -> m b) -> m ()
indexedForM_ t (PermDef b a)
perms ((PermDef b a -> m ()) -> m ()) -> (PermDef b a -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \PermDef b a
perm -> do
SystemDefined
systemDefined <- m SystemDefined
forall r (m :: * -> *). MonadReader r m => m r
ask
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ QualifiedTable -> PermDef b a -> SystemDefined -> TxE QErr ()
forall (m :: * -> *) (b :: BackendType) (a :: BackendType -> *).
(MonadTx m, Backend b) =>
QualifiedTable -> PermDef b a -> SystemDefined -> m ()
addPermissionToCatalog QualifiedTable
tableName PermDef b a
perm SystemDefined
systemDefined
saveTableToCatalog ::
(MonadTx m, MonadReader SystemDefined m) => QualifiedTable -> Bool -> TableConfig ('Postgres 'Vanilla) -> m ()
saveTableToCatalog :: QualifiedTable -> Bool -> TableConfig ('Postgres 'Vanilla) -> m ()
saveTableToCatalog (QualifiedObject SchemaName
sn TableName
tn) Bool
isEnum TableConfig ('Postgres 'Vanilla)
config = do
SystemDefined
systemDefined <- m SystemDefined
forall r (m :: * -> *). MonadReader r m => m r
ask
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (SchemaName, TableName, SystemDefined, Bool, AltJ Value)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO "hdb_catalog"."hdb_table"
(table_schema, table_name, is_system_defined, is_enum, configuration)
VALUES ($1, $2, $3, $4, $5)
|]
(SchemaName
sn, TableName
tn, SystemDefined
systemDefined, Bool
isEnum, AltJ Value
configVal)
Bool
False
where
configVal :: AltJ Value
configVal = Value -> AltJ Value
forall a. a -> AltJ a
Q.AltJ (Value -> AltJ Value) -> Value -> AltJ Value
forall a b. (a -> b) -> a -> b
$ TableConfig ('Postgres 'Vanilla) -> Value
forall a. ToJSON a => a -> Value
toJSON TableConfig ('Postgres 'Vanilla)
config
insertRelationshipToCatalog ::
(MonadTx m, MonadReader SystemDefined m, ToJSON a) =>
QualifiedTable ->
RelType ->
RelDef a ->
m ()
insertRelationshipToCatalog :: QualifiedTable -> RelType -> RelDef a -> m ()
insertRelationshipToCatalog (QualifiedObject SchemaName
schema TableName
table) RelType
relType (RelDef RelName
name a
using Maybe Text
comment) = do
SystemDefined
systemDefined <- m SystemDefined
forall r (m :: * -> *). MonadReader r m => m r
ask
let args :: (SchemaName, TableName, RelName, Text, AltJ a, Maybe Text,
SystemDefined)
args = (SchemaName
schema, TableName
table, RelName
name, RelType -> Text
relTypeToTxt RelType
relType, a -> AltJ a
forall a. a -> AltJ a
Q.AltJ a
using, Maybe Text
comment, SystemDefined
systemDefined)
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ (PGTxErr -> QErr)
-> Query
-> (SchemaName, TableName, RelName, Text, AltJ a, Maybe Text,
SystemDefined)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE PGTxErr -> QErr
defaultTxErrorHandler Query
query (SchemaName, TableName, RelName, Text, AltJ a, Maybe Text,
SystemDefined)
args Bool
True
where
query :: Query
query =
[Q.sql|
INSERT INTO
hdb_catalog.hdb_relationship
(table_schema, table_name, rel_name, rel_type, rel_def, comment, is_system_defined)
VALUES ($1, $2, $3, $4, $5 :: jsonb, $6, $7) |]
addEventTriggerToCatalog ::
(MonadTx m, Backend ('Postgres pgKind)) =>
QualifiedTable ->
EventTriggerConf ('Postgres pgKind) ->
m ()
addEventTriggerToCatalog :: QualifiedTable -> EventTriggerConf ('Postgres pgKind) -> m ()
addEventTriggerToCatalog QualifiedTable
qt EventTriggerConf ('Postgres pgKind)
etc = TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx do
(PGTxErr -> QErr)
-> Query
-> (TriggerName, SchemaName, TableName, AltJ Value)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT into hdb_catalog.event_triggers
(name, type, schema_name, table_name, configuration)
VALUES ($1, 'table', $2, $3, $4)
|]
(TriggerName
name, SchemaName
sn, TableName
tn, Value -> AltJ Value
forall a. a -> AltJ a
Q.AltJ (Value -> AltJ Value) -> Value -> AltJ Value
forall a b. (a -> b) -> a -> b
$ EventTriggerConf ('Postgres pgKind) -> Value
forall a. ToJSON a => a -> Value
toJSON EventTriggerConf ('Postgres pgKind)
etc)
Bool
False
where
QualifiedObject SchemaName
sn TableName
tn = QualifiedTable
qt
(EventTriggerConf TriggerName
name TriggerOpsDef ('Postgres pgKind)
_ Maybe InputWebhook
_ Maybe Text
_ RetryConf
_ Maybe [HeaderConf]
_ Maybe RequestTransform
_ Maybe MetadataResponseTransform
_) = EventTriggerConf ('Postgres pgKind)
etc
addComputedFieldToCatalog ::
MonadTx m =>
AddComputedField ('Postgres 'Vanilla) ->
m ()
addComputedFieldToCatalog :: AddComputedField ('Postgres 'Vanilla) -> m ()
addComputedFieldToCatalog AddComputedField ('Postgres 'Vanilla)
q =
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (SchemaName, TableName, ComputedFieldName,
AltJ ComputedFieldDefinition, Maybe Text)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) a r e.
(MonadIO m, FromRes a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m a
Q.withQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO hdb_catalog.hdb_computed_field
(table_schema, table_name, computed_field_name, definition, commentText)
VALUES ($1, $2, $3, $4, $5)
|]
(SchemaName
schemaName, TableName
tableName, ComputedFieldName
computedField, ComputedFieldDefinition -> AltJ ComputedFieldDefinition
forall a. a -> AltJ a
Q.AltJ ComputedFieldDefinition ('Postgres 'Vanilla)
ComputedFieldDefinition
definition, Maybe Text
commentText)
Bool
True
where
commentText :: Maybe Text
commentText = Comment -> Maybe Text
commentToMaybeText Comment
comment
QualifiedObject SchemaName
schemaName TableName
tableName = TableName ('Postgres 'Vanilla)
QualifiedTable
table
AddComputedField SourceName
_ TableName ('Postgres 'Vanilla)
table ComputedFieldName
computedField ComputedFieldDefinition ('Postgres 'Vanilla)
definition Comment
comment = AddComputedField ('Postgres 'Vanilla)
q
addRemoteRelationshipToCatalog :: MonadTx m => CreateFromSourceRelationship ('Postgres 'Vanilla) -> m ()
addRemoteRelationshipToCatalog :: CreateFromSourceRelationship ('Postgres 'Vanilla) -> m ()
addRemoteRelationshipToCatalog CreateFromSourceRelationship {SourceName
RelName
TableName ('Postgres 'Vanilla)
RemoteRelationshipDefinition
_crrDefinition :: forall (b :: BackendType).
CreateFromSourceRelationship b -> RemoteRelationshipDefinition
_crrName :: forall (b :: BackendType).
CreateFromSourceRelationship b -> RelName
_crrTable :: forall (b :: BackendType).
CreateFromSourceRelationship b -> TableName b
_crrSource :: forall (b :: BackendType).
CreateFromSourceRelationship b -> SourceName
_crrDefinition :: RemoteRelationshipDefinition
_crrName :: RelName
_crrTable :: TableName ('Postgres 'Vanilla)
_crrSource :: SourceName
..} =
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (RelName, SchemaName, TableName,
AltJ RemoteRelationshipDefinition)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO hdb_catalog.hdb_remote_relationship
(remote_relationship_name, table_schema, table_name, definition)
VALUES ($1, $2, $3, $4::jsonb)
|]
(RelName
_crrName, SchemaName
schemaName, TableName
tableName, RemoteRelationshipDefinition -> AltJ RemoteRelationshipDefinition
forall a. a -> AltJ a
Q.AltJ RemoteRelationshipDefinition
_crrDefinition)
Bool
True
where
QualifiedObject SchemaName
schemaName TableName
tableName = TableName ('Postgres 'Vanilla)
QualifiedTable
_crrTable
addFunctionToCatalog ::
(MonadTx m, MonadReader SystemDefined m) =>
QualifiedFunction ->
FunctionConfig ->
m ()
addFunctionToCatalog :: QualifiedFunction -> FunctionConfig -> m ()
addFunctionToCatalog (QualifiedObject SchemaName
sn FunctionName
fn) FunctionConfig
config = do
SystemDefined
systemDefined <- m SystemDefined
forall r (m :: * -> *). MonadReader r m => m r
ask
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (SchemaName, FunctionName, AltJ FunctionConfig, SystemDefined)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO "hdb_catalog"."hdb_function"
(function_schema, function_name, configuration, is_system_defined)
VALUES ($1, $2, $3, $4)
|]
(SchemaName
sn, FunctionName
fn, FunctionConfig -> AltJ FunctionConfig
forall a. a -> AltJ a
Q.AltJ FunctionConfig
config, SystemDefined
systemDefined)
Bool
False
addRemoteSchemaToCatalog ::
RemoteSchemaMetadata ->
Q.TxE QErr ()
addRemoteSchemaToCatalog :: RemoteSchemaMetadata -> TxE QErr ()
addRemoteSchemaToCatalog (RemoteSchemaMetadata RemoteSchemaName
name RemoteSchemaDef
def Maybe Text
comment [RemoteSchemaPermissionMetadata]
_ SchemaRemoteRelationships
_) =
(PGTxErr -> QErr)
-> Query
-> (RemoteSchemaName, AltJ Value, Maybe Text)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT into hdb_catalog.remote_schemas
(name, definition, comment)
VALUES ($1, $2, $3)
|]
(RemoteSchemaName
name, Value -> AltJ Value
forall a. a -> AltJ a
Q.AltJ (Value -> AltJ Value) -> Value -> AltJ Value
forall a b. (a -> b) -> a -> b
$ RemoteSchemaDef -> Value
forall a. ToJSON a => a -> Value
toJSON RemoteSchemaDef
def, Maybe Text
comment)
Bool
True
addCollectionToCatalog ::
MonadTx m => CreateCollection -> SystemDefined -> m ()
addCollectionToCatalog :: CreateCollection -> SystemDefined -> m ()
addCollectionToCatalog (CreateCollection CollectionName
name CollectionDef
defn Maybe Text
mComment) SystemDefined
systemDefined =
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (CollectionName, AltJ CollectionDef, Maybe Text, SystemDefined)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO hdb_catalog.hdb_query_collection
(collection_name, collection_defn, comment, is_system_defined)
VALUES ($1, $2, $3, $4)
|]
(CollectionName
name, CollectionDef -> AltJ CollectionDef
forall a. a -> AltJ a
Q.AltJ CollectionDef
defn, Maybe Text
mComment, SystemDefined
systemDefined)
Bool
True
addCollectionToAllowlistCatalog :: MonadTx m => CollectionName -> m ()
addCollectionToAllowlistCatalog :: CollectionName -> m ()
addCollectionToAllowlistCatalog CollectionName
collName =
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query -> Identity CollectionName -> Bool -> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO hdb_catalog.hdb_allowlist
(collection_name)
VALUES ($1)
|]
(CollectionName -> Identity CollectionName
forall a. a -> Identity a
Identity CollectionName
collName)
Bool
True
setCustomTypesInCatalog :: MonadTx m => CustomTypes -> m ()
setCustomTypesInCatalog :: CustomTypes -> m ()
setCustomTypesInCatalog CustomTypes
customTypes = TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx do
TxE QErr ()
clearCustomTypes
(PGTxErr -> QErr)
-> Query -> Identity (AltJ CustomTypes) -> Bool -> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT into hdb_catalog.hdb_custom_types
(custom_types)
VALUES ($1)
|]
(AltJ CustomTypes -> Identity (AltJ CustomTypes)
forall a. a -> Identity a
Identity (AltJ CustomTypes -> Identity (AltJ CustomTypes))
-> AltJ CustomTypes -> Identity (AltJ CustomTypes)
forall a b. (a -> b) -> a -> b
$ CustomTypes -> AltJ CustomTypes
forall a. a -> AltJ a
Q.AltJ CustomTypes
customTypes)
Bool
False
where
clearCustomTypes :: TxE QErr ()
clearCustomTypes = do
(PGTxErr -> QErr) -> Query -> () -> Bool -> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
DELETE FROM hdb_catalog.hdb_custom_types
|]
()
Bool
False
addActionToCatalog :: (MonadTx m) => CreateAction -> m ()
addActionToCatalog :: CreateAction -> m ()
addActionToCatalog (CreateAction ActionName
actionName ActionDefinitionInput
actionDefinition Maybe Text
comment) = do
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (ActionName, AltJ ActionDefinitionInput, Maybe Text)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT into hdb_catalog.hdb_action
(action_name, action_defn, comment)
VALUES ($1, $2, $3)
|]
(ActionName
actionName, ActionDefinitionInput -> AltJ ActionDefinitionInput
forall a. a -> AltJ a
Q.AltJ ActionDefinitionInput
actionDefinition, Maybe Text
comment)
Bool
True
addActionPermissionToCatalog :: (MonadTx m) => CreateActionPermission -> m ()
addActionPermissionToCatalog :: CreateActionPermission -> m ()
addActionPermissionToCatalog CreateActionPermission {Maybe Value
Maybe Text
RoleName
ActionName
_capComment :: CreateActionPermission -> Maybe Text
_capDefinition :: CreateActionPermission -> Maybe Value
_capRole :: CreateActionPermission -> RoleName
_capAction :: CreateActionPermission -> ActionName
_capComment :: Maybe Text
_capDefinition :: Maybe Value
_capRole :: RoleName
_capAction :: ActionName
..} = do
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (ActionName, RoleName, Maybe Text)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT into hdb_catalog.hdb_action_permission
(action_name, role_name, comment)
VALUES ($1, $2, $3)
|]
(ActionName
_capAction, RoleName
_capRole, Maybe Text
_capComment)
Bool
True
addPermissionToCatalog ::
(MonadTx m, Backend b) =>
QualifiedTable ->
PermDef b a ->
SystemDefined ->
m ()
addPermissionToCatalog :: QualifiedTable -> PermDef b a -> SystemDefined -> m ()
addPermissionToCatalog (QualifiedObject SchemaName
sn TableName
tn) (PermDef RoleName
rn PermDefPermission b a
qdef Maybe Text
mComment) SystemDefined
systemDefined =
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr)
-> Query
-> (SchemaName, TableName, RoleName, Text,
AltJ (PermDefPermission b a), Maybe Text, SystemDefined)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT INTO
hdb_catalog.hdb_permission
(table_schema, table_name, role_name, perm_type, perm_def, comment, is_system_defined)
VALUES ($1, $2, $3, $4, $5 :: jsonb, $6, $7)
|]
(SchemaName
sn, TableName
tn, RoleName
rn, PermType -> Text
permTypeToCode (PermDefPermission b a -> PermType
forall (b :: BackendType) (a :: BackendType -> *).
PermDefPermission b a -> PermType
reflectPermDefPermission PermDefPermission b a
qdef), PermDefPermission b a -> AltJ (PermDefPermission b a)
forall a. a -> AltJ a
Q.AltJ PermDefPermission b a
qdef, Maybe Text
mComment, SystemDefined
systemDefined)
Bool
True
addCronTriggerToCatalog :: (MonadTx m) => CronTriggerMetadata -> m ()
addCronTriggerToCatalog :: CronTriggerMetadata -> m ()
addCronTriggerToCatalog CronTriggerMetadata {Bool
[HeaderConf]
Maybe Value
Maybe Text
Maybe MetadataResponseTransform
Maybe RequestTransform
CronSchedule
InputWebhook
TriggerName
STRetryConf
ctResponseTransform :: CronTriggerMetadata -> Maybe MetadataResponseTransform
ctRequestTransform :: CronTriggerMetadata -> Maybe RequestTransform
ctComment :: CronTriggerMetadata -> Maybe Text
ctIncludeInMetadata :: CronTriggerMetadata -> Bool
ctHeaders :: CronTriggerMetadata -> [HeaderConf]
ctRetryConf :: CronTriggerMetadata -> STRetryConf
ctPayload :: CronTriggerMetadata -> Maybe Value
ctSchedule :: CronTriggerMetadata -> CronSchedule
ctWebhook :: CronTriggerMetadata -> InputWebhook
ctName :: CronTriggerMetadata -> TriggerName
ctResponseTransform :: Maybe MetadataResponseTransform
ctRequestTransform :: Maybe RequestTransform
ctComment :: Maybe Text
ctIncludeInMetadata :: Bool
ctHeaders :: [HeaderConf]
ctRetryConf :: STRetryConf
ctPayload :: Maybe Value
ctSchedule :: CronSchedule
ctWebhook :: InputWebhook
ctName :: TriggerName
..} = TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ do
(PGTxErr -> QErr)
-> Query
-> (TriggerName, AltJ InputWebhook, CronSchedule,
Maybe (AltJ Value), AltJ STRetryConf, AltJ [HeaderConf], Bool,
Maybe Text)
-> Bool
-> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
INSERT into hdb_catalog.hdb_cron_triggers
(name, webhook_conf, cron_schedule, payload, retry_conf, header_conf, include_in_metadata, comment)
VALUES ($1, $2, $3, $4, $5, $6, $7, $8)
|]
( TriggerName
ctName,
InputWebhook -> AltJ InputWebhook
forall a. a -> AltJ a
Q.AltJ InputWebhook
ctWebhook,
CronSchedule
ctSchedule,
Value -> AltJ Value
forall a. a -> AltJ a
Q.AltJ (Value -> AltJ Value) -> Maybe Value -> Maybe (AltJ Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Value
ctPayload,
STRetryConf -> AltJ STRetryConf
forall a. a -> AltJ a
Q.AltJ STRetryConf
ctRetryConf,
[HeaderConf] -> AltJ [HeaderConf]
forall a. a -> AltJ a
Q.AltJ [HeaderConf]
ctHeaders,
Bool
ctIncludeInMetadata,
Maybe Text
ctComment
)
Bool
False
UTCTime
currentTime <- IO UTCTime -> TxET QErr IO UTCTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UTCTime
C.getCurrentTime
let scheduleTimes :: [UTCTime]
scheduleTimes = UTCTime -> Int -> CronSchedule -> [UTCTime]
generateScheduleTimes UTCTime
currentTime Int
100 CronSchedule
ctSchedule
[CronEventSeed] -> TxE QErr ()
insertCronEventsTx ([CronEventSeed] -> TxE QErr ()) -> [CronEventSeed] -> TxE QErr ()
forall a b. (a -> b) -> a -> b
$ (UTCTime -> CronEventSeed) -> [UTCTime] -> [CronEventSeed]
forall a b. (a -> b) -> [a] -> [b]
map (TriggerName -> UTCTime -> CronEventSeed
CronEventSeed TriggerName
ctName) [UTCTime]
scheduleTimes
parseLegacyRemoteRelationshipDefinition ::
(MonadError QErr m) =>
Value ->
m RemoteRelationshipDefinition
parseLegacyRemoteRelationshipDefinition :: Value -> m RemoteRelationshipDefinition
parseLegacyRemoteRelationshipDefinition =
(Value -> Parser RemoteRelationshipDefinition)
-> Value -> m RemoteRelationshipDefinition
forall (m :: * -> *) v a. QErrM m => (v -> Parser a) -> v -> m a
runAesonParser (RRParseMode -> Value -> Parser RemoteRelationshipDefinition
parseRemoteRelationshipDefinition RRParseMode
RRPLegacy)
fetchMetadataFromHdbTables :: MonadTx m => m MetadataNoSources
fetchMetadataFromHdbTables :: m MetadataNoSources
fetchMetadataFromHdbTables = TxE QErr MetadataNoSources -> m MetadataNoSources
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx do
[(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
tables <- (PGTxErr -> QErr)
-> TxET
PGTxErr
IO
[(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
-> TxET
QErr
IO
[(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> TxET e m a -> TxET e' m a
Q.catchE PGTxErr -> QErr
defaultTxErrorHandler TxET
PGTxErr
IO
[(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
fetchTables
let tableMetaMap :: InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tableMetaMap = [(QualifiedTable, TableMetadata ('Postgres 'Vanilla))]
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
forall k v. (Eq k, Hashable k) => [(k, v)] -> InsOrdHashMap k v
OMap.fromList ([(QualifiedTable, TableMetadata ('Postgres 'Vanilla))]
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> (((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> [(QualifiedTable, TableMetadata ('Postgres 'Vanilla))])
-> ((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> [(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
-> [(QualifiedTable, TableMetadata ('Postgres 'Vanilla))])
-> [(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
-> ((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> [(QualifiedTable, TableMetadata ('Postgres 'Vanilla))]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> [(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
-> [(QualifiedTable, TableMetadata ('Postgres 'Vanilla))]
forall a b. (a -> b) -> [a] -> [b]
map [(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
tables (((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> ((SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))
-> (QualifiedTable, TableMetadata ('Postgres 'Vanilla)))
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
\(SchemaName
schema, TableName
name, Bool
isEnum, Maybe (AltJ (TableConfig ('Postgres 'Vanilla)))
maybeConfig) ->
let qualifiedName :: QualifiedTable
qualifiedName = SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
schema TableName
name
configuration :: TableConfig ('Postgres 'Vanilla)
configuration = TableConfig ('Postgres 'Vanilla)
-> (AltJ (TableConfig ('Postgres 'Vanilla))
-> TableConfig ('Postgres 'Vanilla))
-> Maybe (AltJ (TableConfig ('Postgres 'Vanilla)))
-> TableConfig ('Postgres 'Vanilla)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TableConfig ('Postgres 'Vanilla)
forall (b :: BackendType). TableConfig b
emptyTableConfig AltJ (TableConfig ('Postgres 'Vanilla))
-> TableConfig ('Postgres 'Vanilla)
forall a. AltJ a -> a
Q.getAltJ Maybe (AltJ (TableConfig ('Postgres 'Vanilla)))
maybeConfig
in (QualifiedTable
qualifiedName, TableName ('Postgres 'Vanilla)
-> Bool
-> TableConfig ('Postgres 'Vanilla)
-> TableMetadata ('Postgres 'Vanilla)
forall (b :: BackendType).
TableName b -> Bool -> TableConfig b -> TableMetadata b
mkTableMeta TableName ('Postgres 'Vanilla)
QualifiedTable
qualifiedName Bool
isEnum TableConfig ('Postgres 'Vanilla)
configuration)
[(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
relationships <- (PGTxErr -> QErr)
-> TxET
PGTxErr
IO
[(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
-> TxET
QErr
IO
[(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> TxET e m a -> TxET e' m a
Q.catchE PGTxErr -> QErr
defaultTxErrorHandler TxET
PGTxErr
IO
[(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
fetchRelationships
[(QualifiedTable, ObjRelDef ('Postgres 'Vanilla))]
objRelDefs <- RelType
-> [(SchemaName, TableName, RelName, RelType, AltJ Value,
Maybe Text)]
-> TxET QErr IO [(QualifiedTable, ObjRelDef ('Postgres 'Vanilla))]
forall (m :: * -> *) a d a.
(MonadError QErr m, FromJSON a, Eq d) =>
d
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, RelDef a)]
mkRelDefs RelType
ObjRel [(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
relationships
[(QualifiedTable, ArrRelDef ('Postgres 'Vanilla))]
arrRelDefs <- RelType
-> [(SchemaName, TableName, RelName, RelType, AltJ Value,
Maybe Text)]
-> TxET QErr IO [(QualifiedTable, ArrRelDef ('Postgres 'Vanilla))]
forall (m :: * -> *) a d a.
(MonadError QErr m, FromJSON a, Eq d) =>
d
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, RelDef a)]
mkRelDefs RelType
ArrRel [(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
relationships
[(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
permissions <- (PGTxErr -> QErr)
-> TxET
PGTxErr
IO
[(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
-> TxET
QErr
IO
[(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> TxET e m a -> TxET e' m a
Q.catchE PGTxErr -> QErr
defaultTxErrorHandler TxET
PGTxErr
IO
[(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
fetchPermissions
[(QualifiedTable, InsPermDef ('Postgres 'Vanilla))]
insPermDefs <- PermType
-> [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
-> TxET QErr IO [(QualifiedTable, InsPermDef ('Postgres 'Vanilla))]
forall (m :: * -> *) (b :: BackendType) (perm :: BackendType -> *)
d a.
(MonadError QErr m, FromJSON (PermDefPermission b perm), Eq d) =>
d
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
mkPermDefs PermType
PTInsert [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
permissions
[(QualifiedTable, SelPermDef ('Postgres 'Vanilla))]
selPermDefs <- PermType
-> [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
-> TxET QErr IO [(QualifiedTable, SelPermDef ('Postgres 'Vanilla))]
forall (m :: * -> *) (b :: BackendType) (perm :: BackendType -> *)
d a.
(MonadError QErr m, FromJSON (PermDefPermission b perm), Eq d) =>
d
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
mkPermDefs PermType
PTSelect [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
permissions
[(QualifiedTable, UpdPermDef ('Postgres 'Vanilla))]
updPermDefs <- PermType
-> [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
-> TxET QErr IO [(QualifiedTable, UpdPermDef ('Postgres 'Vanilla))]
forall (m :: * -> *) (b :: BackendType) (perm :: BackendType -> *)
d a.
(MonadError QErr m, FromJSON (PermDefPermission b perm), Eq d) =>
d
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
mkPermDefs PermType
PTUpdate [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
permissions
[(QualifiedTable, DelPermDef ('Postgres 'Vanilla))]
delPermDefs <- PermType
-> [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
-> TxET QErr IO [(QualifiedTable, DelPermDef ('Postgres 'Vanilla))]
forall (m :: * -> *) (b :: BackendType) (perm :: BackendType -> *)
d a.
(MonadError QErr m, FromJSON (PermDefPermission b perm), Eq d) =>
d
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
mkPermDefs PermType
PTDelete [(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
permissions
[(SchemaName, TableName, AltJ Value)]
eventTriggers <- (PGTxErr -> QErr)
-> TxET PGTxErr IO [(SchemaName, TableName, AltJ Value)]
-> TxET QErr IO [(SchemaName, TableName, AltJ Value)]
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> TxET e m a -> TxET e' m a
Q.catchE PGTxErr -> QErr
defaultTxErrorHandler TxET PGTxErr IO [(SchemaName, TableName, AltJ Value)]
fetchEventTriggers
[(QualifiedTable, EventTriggerConf ('Postgres 'Vanilla))]
triggerMetaDefs <- [(SchemaName, TableName, AltJ Value)]
-> TxET
QErr IO [(QualifiedTable, EventTriggerConf ('Postgres 'Vanilla))]
forall a.
[(SchemaName, a, AltJ Value)]
-> TxET
QErr
IO
[(QualifiedObject a, EventTriggerConf ('Postgres 'Vanilla))]
mkTriggerMetaDefs [(SchemaName, TableName, AltJ Value)]
eventTriggers
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
computedFields <- TxET
QErr
IO
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
fetchComputedFields
[(QualifiedTable, RelName, Value)]
remoteRelationshipsRaw <- (PGTxErr -> QErr)
-> TxET PGTxErr IO [(QualifiedTable, RelName, Value)]
-> TxET QErr IO [(QualifiedTable, RelName, Value)]
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> TxET e m a -> TxET e' m a
Q.catchE PGTxErr -> QErr
defaultTxErrorHandler TxET PGTxErr IO [(QualifiedTable, RelName, Value)]
fetchRemoteRelationships
[(QualifiedTable, RemoteRelationship)]
remoteRelationships <- [(QualifiedTable, RelName, Value)]
-> ((QualifiedTable, RelName, Value)
-> TxET QErr IO (QualifiedTable, RemoteRelationship))
-> TxET QErr IO [(QualifiedTable, RemoteRelationship)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [(QualifiedTable, RelName, Value)]
remoteRelationshipsRaw (((QualifiedTable, RelName, Value)
-> TxET QErr IO (QualifiedTable, RemoteRelationship))
-> TxET QErr IO [(QualifiedTable, RemoteRelationship)])
-> ((QualifiedTable, RelName, Value)
-> TxET QErr IO (QualifiedTable, RemoteRelationship))
-> TxET QErr IO [(QualifiedTable, RemoteRelationship)]
forall a b. (a -> b) -> a -> b
$ \(QualifiedTable
table, RelName
relationshipName, Value
definitionValue) -> do
RemoteRelationshipDefinition
definition <- Value -> TxET QErr IO RemoteRelationshipDefinition
forall (m :: * -> *).
MonadError QErr m =>
Value -> m RemoteRelationshipDefinition
parseLegacyRemoteRelationshipDefinition Value
definitionValue
(QualifiedTable, RemoteRelationship)
-> TxET QErr IO (QualifiedTable, RemoteRelationship)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((QualifiedTable, RemoteRelationship)
-> TxET QErr IO (QualifiedTable, RemoteRelationship))
-> (QualifiedTable, RemoteRelationship)
-> TxET QErr IO (QualifiedTable, RemoteRelationship)
forall a b. (a -> b) -> a -> b
$ (QualifiedTable
table, RelName -> RemoteRelationshipDefinition -> RemoteRelationship
RemoteRelationship RelName
relationshipName RemoteRelationshipDefinition
definition)
let (()
_, InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
fullTableMetaMap) = (State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
-> ((),
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
-> ((),
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
forall a b c. (a -> b -> c) -> b -> a -> c
flip State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
-> ((),
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
forall s a. State s a -> s -> (a, s)
runState InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tableMetaMap (State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
-> ((),
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
-> ((),
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
forall a b. (a -> b) -> a -> b
$ do
((Relationships (ObjRelDef ('Postgres 'Vanilla))
-> Identity (Relationships (ObjRelDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (ObjRelDef ('Postgres 'Vanilla) -> RelName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
ObjRelDef ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (Relationships (ObjRelDef ('Postgres 'Vanilla))
-> Identity (Relationships (ObjRelDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (Relationships (ObjRelDef b))
tmObjectRelationships ObjRelDef ('Postgres 'Vanilla) -> RelName
forall a. RelDef a -> RelName
_rdName [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
ObjRelDef ('Postgres 'Vanilla))]
[(QualifiedTable, ObjRelDef ('Postgres 'Vanilla))]
objRelDefs
((Relationships (ArrRelDef ('Postgres 'Vanilla))
-> Identity (Relationships (ArrRelDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (ArrRelDef ('Postgres 'Vanilla) -> RelName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
ArrRelDef ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (Relationships (ArrRelDef ('Postgres 'Vanilla))
-> Identity (Relationships (ArrRelDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (Relationships (ArrRelDef b))
tmArrayRelationships ArrRelDef ('Postgres 'Vanilla) -> RelName
forall a. RelDef a -> RelName
_rdName [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
ArrRelDef ('Postgres 'Vanilla))]
[(QualifiedTable, ArrRelDef ('Postgres 'Vanilla))]
arrRelDefs
((Permissions (InsPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (InsPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (InsPermDef ('Postgres 'Vanilla) -> RoleName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
InsPermDef ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (Permissions (InsPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (InsPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (InsPermDef b))
tmInsertPermissions InsPermDef ('Postgres 'Vanilla) -> RoleName
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
InsPermDef ('Postgres 'Vanilla))]
[(QualifiedTable, InsPermDef ('Postgres 'Vanilla))]
insPermDefs
((Permissions (SelPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (SelPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (SelPermDef ('Postgres 'Vanilla) -> RoleName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
SelPermDef ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (Permissions (SelPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (SelPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (SelPermDef b))
tmSelectPermissions SelPermDef ('Postgres 'Vanilla) -> RoleName
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
SelPermDef ('Postgres 'Vanilla))]
[(QualifiedTable, SelPermDef ('Postgres 'Vanilla))]
selPermDefs
((Permissions (UpdPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (UpdPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (UpdPermDef ('Postgres 'Vanilla) -> RoleName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
UpdPermDef ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (Permissions (UpdPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (UpdPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (UpdPermDef b))
tmUpdatePermissions UpdPermDef ('Postgres 'Vanilla) -> RoleName
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
UpdPermDef ('Postgres 'Vanilla))]
[(QualifiedTable, UpdPermDef ('Postgres 'Vanilla))]
updPermDefs
((Permissions (DelPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (DelPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (DelPermDef ('Postgres 'Vanilla) -> RoleName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
DelPermDef ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (Permissions (DelPermDef ('Postgres 'Vanilla))
-> Identity (Permissions (DelPermDef ('Postgres 'Vanilla))))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (DelPermDef b))
tmDeletePermissions DelPermDef ('Postgres 'Vanilla) -> RoleName
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
DelPermDef ('Postgres 'Vanilla))]
[(QualifiedTable, DelPermDef ('Postgres 'Vanilla))]
delPermDefs
((EventTriggers ('Postgres 'Vanilla)
-> Identity (EventTriggers ('Postgres 'Vanilla)))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (EventTriggerConf ('Postgres 'Vanilla) -> TriggerName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
EventTriggerConf ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (EventTriggers ('Postgres 'Vanilla)
-> Identity (EventTriggers ('Postgres 'Vanilla)))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (EventTriggers b)
tmEventTriggers EventTriggerConf ('Postgres 'Vanilla) -> TriggerName
forall (b :: BackendType). EventTriggerConf b -> TriggerName
etcName [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
EventTriggerConf ('Postgres 'Vanilla))]
[(QualifiedTable, EventTriggerConf ('Postgres 'Vanilla))]
triggerMetaDefs
((ComputedFields ('Postgres 'Vanilla)
-> Identity (ComputedFields ('Postgres 'Vanilla)))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (ComputedFieldMetadata ('Postgres 'Vanilla)
-> ComputedFieldName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
ComputedFieldMetadata ('Postgres 'Vanilla))]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (ComputedFields ('Postgres 'Vanilla)
-> Identity (ComputedFields ('Postgres 'Vanilla)))
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) (ComputedFields b)
tmComputedFields ComputedFieldMetadata ('Postgres 'Vanilla) -> ComputedFieldName
forall (b :: BackendType).
ComputedFieldMetadata b -> ComputedFieldName
_cfmName [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
ComputedFieldMetadata ('Postgres 'Vanilla))]
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
computedFields
((RemoteRelationships -> Identity RemoteRelationships)
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))))
-> (RemoteRelationship -> RelName)
-> [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
RemoteRelationship)]
-> State
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
()
forall (m :: * -> *) s (t :: * -> *) k v.
(MonadState s m, Foldable t, At s, Eq k, Hashable k) =>
((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (RemoteRelationships -> Identity RemoteRelationships)
-> IxValue
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Identity
(IxValue
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))))
forall (b :: BackendType).
Lens' (TableMetadata b) RemoteRelationships
tmRemoteRelationships RemoteRelationship -> RelName
_rrName [(Index
(InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))),
RemoteRelationship)]
[(QualifiedTable, RemoteRelationship)]
remoteRelationships
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions <- (PGTxErr -> QErr)
-> TxET
PGTxErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
-> TxET
QErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> TxET e m a -> TxET e' m a
Q.catchE PGTxErr -> QErr
defaultTxErrorHandler TxET
PGTxErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
fetchFunctions
RemoteSchemas
remoteSchemas <- (RemoteSchemaMetadata -> RemoteSchemaName)
-> [RemoteSchemaMetadata] -> RemoteSchemas
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL RemoteSchemaMetadata -> RemoteSchemaName
_rsmName ([RemoteSchemaMetadata] -> RemoteSchemas)
-> TxET QErr IO [RemoteSchemaMetadata]
-> TxET QErr IO RemoteSchemas
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TxET QErr IO [RemoteSchemaMetadata]
fetchRemoteSchemas
QueryCollections
collections <- (CreateCollection -> CollectionName)
-> [CreateCollection] -> QueryCollections
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL CreateCollection -> CollectionName
_ccName ([CreateCollection] -> QueryCollections)
-> TxET QErr IO [CreateCollection] -> TxET QErr IO QueryCollections
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TxET QErr IO [CreateCollection]
fetchCollections
MetadataAllowlist
allowlist <- (AllowlistEntry -> CollectionName)
-> [AllowlistEntry] -> MetadataAllowlist
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL AllowlistEntry -> CollectionName
aeCollection ([AllowlistEntry] -> MetadataAllowlist)
-> TxET QErr IO [AllowlistEntry] -> TxET QErr IO MetadataAllowlist
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TxET QErr IO [AllowlistEntry]
fetchAllowlist
CustomTypes
customTypes <- TxE QErr CustomTypes
fetchCustomTypes
Actions
actions <- (ActionMetadata -> ActionName) -> [ActionMetadata] -> Actions
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL ActionMetadata -> ActionName
_amName ([ActionMetadata] -> Actions)
-> TxET QErr IO [ActionMetadata] -> TxET QErr IO Actions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TxET QErr IO [ActionMetadata]
fetchActions
CronTriggers
cronTriggers <- TxET QErr IO CronTriggers
fetchCronTriggers
MetadataNoSources -> TxE QErr MetadataNoSources
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MetadataNoSources -> TxE QErr MetadataNoSources)
-> MetadataNoSources -> TxE QErr MetadataNoSources
forall a b. (a -> b) -> a -> b
$
Tables ('Postgres 'Vanilla)
-> Functions ('Postgres 'Vanilla)
-> RemoteSchemas
-> QueryCollections
-> MetadataAllowlist
-> CustomTypes
-> Actions
-> CronTriggers
-> MetadataNoSources
MetadataNoSources
Tables ('Postgres 'Vanilla)
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
fullTableMetaMap
Functions ('Postgres 'Vanilla)
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions
RemoteSchemas
remoteSchemas
QueryCollections
collections
MetadataAllowlist
allowlist
CustomTypes
customTypes
Actions
actions
CronTriggers
cronTriggers
where
modMetaMap :: ((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (v -> k) -> t (Index s, v) -> m ()
modMetaMap (InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s)
l v -> k
f t (Index s, v)
xs = do
s
st <- m s
forall s (m :: * -> *). MonadState s m => m s
get
s -> m ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (s -> m ()) -> s -> m ()
forall a b. (a -> b) -> a -> b
$ (s -> (Index s, v) -> s) -> s -> t (Index s, v) -> s
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\s
b (Index s
qt, v
dfn) -> s
b s -> (s -> s) -> s
forall a b. a -> (a -> b) -> b
& Index s -> Lens' s (Maybe (IxValue s))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index s
qt ((Maybe (IxValue s) -> Identity (Maybe (IxValue s)))
-> s -> Identity s)
-> ((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> Maybe (IxValue s) -> Identity (Maybe (IxValue s)))
-> (InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> s
-> Identity s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IxValue s -> Identity (IxValue s))
-> Maybe (IxValue s) -> Identity (Maybe (IxValue s))
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((IxValue s -> Identity (IxValue s))
-> Maybe (IxValue s) -> Identity (Maybe (IxValue s)))
-> ((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s))
-> (InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> Maybe (IxValue s)
-> Identity (Maybe (IxValue s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> IxValue s -> Identity (IxValue s)
l ((InsOrdHashMap k v -> Identity (InsOrdHashMap k v))
-> s -> Identity s)
-> (InsOrdHashMap k v -> InsOrdHashMap k v) -> s -> s
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.insert (v -> k
f v
dfn) v
dfn) s
st t (Index s, v)
xs
mkPermDefs :: d
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
mkPermDefs d
pt = ((SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, PermDef b perm))
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, PermDef b perm)
forall (m :: * -> *) (b :: BackendType) (perm :: BackendType -> *)
a d.
(FromJSON (PermDefPermission b perm), MonadError QErr m) =>
(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, PermDef b perm)
permRowToDef ([(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)])
-> ([(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)])
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, PermDef b perm)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((SchemaName, a, RoleName, d, AltJ Value, Maybe Text) -> Bool)
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
-> [(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
pr -> (SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
pr (SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
-> Getting d (SchemaName, a, RoleName, d, AltJ Value, Maybe Text) d
-> d
forall s a. s -> Getting a s a -> a
^. Getting d (SchemaName, a, RoleName, d, AltJ Value, Maybe Text) d
forall s t a b. Field4 s t a b => Lens s t a b
_4 d -> d -> Bool
forall a. Eq a => a -> a -> Bool
== d
pt)
permRowToDef :: (SchemaName, a, RoleName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, PermDef b perm)
permRowToDef (SchemaName
sn, a
tn, RoleName
rn, d
_, Q.AltJ Value
pDef, Maybe Text
mComment) = do
PermDefPermission b perm
perm <- Value -> m (PermDefPermission b perm)
forall a (m :: * -> *). (FromJSON a, QErrM m) => Value -> m a
decodeValue Value
pDef
(QualifiedObject a, PermDef b perm)
-> m (QualifiedObject a, PermDef b perm)
forall (m :: * -> *) a. Monad m => a -> m a
return (SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
sn a
tn, RoleName
-> PermDefPermission b perm -> Maybe Text -> PermDef b perm
forall (b :: BackendType) (perm :: BackendType -> *).
RoleName
-> PermDefPermission b perm -> Maybe Text -> PermDef b perm
PermDef RoleName
rn PermDefPermission b perm
perm Maybe Text
mComment)
mkRelDefs :: d
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, RelDef a)]
mkRelDefs d
rt = ((SchemaName, a, RelName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, RelDef a))
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, RelDef a)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (SchemaName, a, RelName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, RelDef a)
forall (m :: * -> *) a a d.
(FromJSON a, MonadError QErr m) =>
(SchemaName, a, RelName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, RelDef a)
relRowToDef ([(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, RelDef a)])
-> ([(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)])
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> m [(QualifiedObject a, RelDef a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((SchemaName, a, RelName, d, AltJ Value, Maybe Text) -> Bool)
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
-> [(SchemaName, a, RelName, d, AltJ Value, Maybe Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(SchemaName, a, RelName, d, AltJ Value, Maybe Text)
rr -> (SchemaName, a, RelName, d, AltJ Value, Maybe Text)
rr (SchemaName, a, RelName, d, AltJ Value, Maybe Text)
-> Getting d (SchemaName, a, RelName, d, AltJ Value, Maybe Text) d
-> d
forall s a. s -> Getting a s a -> a
^. Getting d (SchemaName, a, RelName, d, AltJ Value, Maybe Text) d
forall s t a b. Field4 s t a b => Lens s t a b
_4 d -> d -> Bool
forall a. Eq a => a -> a -> Bool
== d
rt)
relRowToDef :: (SchemaName, a, RelName, d, AltJ Value, Maybe Text)
-> m (QualifiedObject a, RelDef a)
relRowToDef (SchemaName
sn, a
tn, RelName
rn, d
_, Q.AltJ Value
rDef, Maybe Text
mComment) = do
a
using <- Value -> m a
forall a (m :: * -> *). (FromJSON a, QErrM m) => Value -> m a
decodeValue Value
rDef
(QualifiedObject a, RelDef a) -> m (QualifiedObject a, RelDef a)
forall (m :: * -> *) a. Monad m => a -> m a
return (SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
sn a
tn, RelName -> a -> Maybe Text -> RelDef a
forall a. RelName -> a -> Maybe Text -> RelDef a
RelDef RelName
rn a
using Maybe Text
mComment)
mkTriggerMetaDefs :: [(SchemaName, a, AltJ Value)]
-> TxET
QErr
IO
[(QualifiedObject a, EventTriggerConf ('Postgres 'Vanilla))]
mkTriggerMetaDefs = ((SchemaName, a, AltJ Value)
-> TxET
QErr IO (QualifiedObject a, EventTriggerConf ('Postgres 'Vanilla)))
-> [(SchemaName, a, AltJ Value)]
-> TxET
QErr
IO
[(QualifiedObject a, EventTriggerConf ('Postgres 'Vanilla))]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (SchemaName, a, AltJ Value)
-> TxET
QErr IO (QualifiedObject a, EventTriggerConf ('Postgres 'Vanilla))
forall (m :: * -> *) (pgKind :: PostgresKind) a.
(HasTag ('Postgres pgKind), Typeable pgKind,
PostgresBackend pgKind,
HasCodec (BackendSourceKind ('Postgres pgKind)), MonadError QErr m,
FromJSON (BackendSourceKind ('Postgres pgKind))) =>
(SchemaName, a, AltJ Value)
-> m (QualifiedObject a, EventTriggerConf ('Postgres pgKind))
trigRowToDef
trigRowToDef :: (SchemaName, a, AltJ Value)
-> m (QualifiedObject a, EventTriggerConf ('Postgres pgKind))
trigRowToDef (SchemaName
sn, a
tn, Q.AltJ Value
configuration) = do
EventTriggerConf ('Postgres pgKind)
conf :: EventTriggerConf ('Postgres pgKind) <- Value -> m (EventTriggerConf ('Postgres pgKind))
forall a (m :: * -> *). (FromJSON a, QErrM m) => Value -> m a
decodeValue Value
configuration
(QualifiedObject a, EventTriggerConf ('Postgres pgKind))
-> m (QualifiedObject a, EventTriggerConf ('Postgres pgKind))
forall (m :: * -> *) a. Monad m => a -> m a
return (SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
sn a
tn, EventTriggerConf ('Postgres pgKind)
conf)
fetchTables :: TxET
PGTxErr
IO
[(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
fetchTables =
Query
-> ()
-> Bool
-> TxET
PGTxErr
IO
[(SchemaName, TableName, Bool,
Maybe (AltJ (TableConfig ('Postgres 'Vanilla))))]
forall (m :: * -> *) a r.
(MonadIO m, FromRow a, ToPrepArgs r) =>
Query -> r -> Bool -> TxT m [a]
Q.listQ
[Q.sql|
SELECT table_schema, table_name, is_enum, configuration::json
FROM hdb_catalog.hdb_table
WHERE is_system_defined = 'false'
ORDER BY table_schema ASC, table_name ASC
|]
()
Bool
False
fetchRelationships :: TxET
PGTxErr
IO
[(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
fetchRelationships =
Query
-> ()
-> Bool
-> TxET
PGTxErr
IO
[(SchemaName, TableName, RelName, RelType, AltJ Value, Maybe Text)]
forall (m :: * -> *) a r.
(MonadIO m, FromRow a, ToPrepArgs r) =>
Query -> r -> Bool -> TxT m [a]
Q.listQ
[Q.sql|
SELECT table_schema, table_name, rel_name, rel_type, rel_def::json, comment
FROM hdb_catalog.hdb_relationship
WHERE is_system_defined = 'false'
ORDER BY table_schema ASC, table_name ASC, rel_name ASC
|]
()
Bool
False
fetchPermissions :: TxET
PGTxErr
IO
[(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
fetchPermissions =
Query
-> ()
-> Bool
-> TxET
PGTxErr
IO
[(SchemaName, TableName, RoleName, PermType, AltJ Value,
Maybe Text)]
forall (m :: * -> *) a r.
(MonadIO m, FromRow a, ToPrepArgs r) =>
Query -> r -> Bool -> TxT m [a]
Q.listQ
[Q.sql|
SELECT table_schema, table_name, role_name, perm_type, perm_def::json, comment
FROM hdb_catalog.hdb_permission
WHERE is_system_defined = 'false'
ORDER BY table_schema ASC, table_name ASC, role_name ASC, perm_type ASC
|]
()
Bool
False
fetchEventTriggers :: TxET PGTxErr IO [(SchemaName, TableName, AltJ Value)]
fetchEventTriggers =
Query
-> ()
-> Bool
-> TxET PGTxErr IO [(SchemaName, TableName, AltJ Value)]
forall (m :: * -> *) a r.
(MonadIO m, FromRow a, ToPrepArgs r) =>
Query -> r -> Bool -> TxT m [a]
Q.listQ
[Q.sql|
SELECT e.schema_name, e.table_name, e.configuration::json
FROM hdb_catalog.event_triggers e
ORDER BY e.schema_name ASC, e.table_name ASC, e.name ASC
|]
()
Bool
False
fetchFunctions :: TxET
PGTxErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
fetchFunctions = do
[(SchemaName, FunctionName, AltJ FunctionConfig)]
l <-
Query
-> ()
-> Bool
-> TxT IO [(SchemaName, FunctionName, AltJ FunctionConfig)]
forall (m :: * -> *) a r.
(MonadIO m, FromRow a, ToPrepArgs r) =>
Query -> r -> Bool -> TxT m [a]
Q.listQ
[Q.sql|
SELECT function_schema, function_name, configuration::json
FROM hdb_catalog.hdb_function
WHERE is_system_defined = 'false'
ORDER BY function_schema ASC, function_name ASC
|]
()
Bool
False
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
-> TxET
PGTxErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
-> TxET
PGTxErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))))
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
-> TxET
PGTxErr
IO
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall a b. (a -> b) -> a -> b
$
(FunctionMetadata ('Postgres 'Vanilla) -> QualifiedFunction)
-> [FunctionMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL FunctionMetadata ('Postgres 'Vanilla) -> QualifiedFunction
forall (b :: BackendType). FunctionMetadata b -> FunctionName b
_fmFunction ([FunctionMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
-> [FunctionMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
(((SchemaName, FunctionName, AltJ FunctionConfig)
-> FunctionMetadata ('Postgres 'Vanilla))
-> [(SchemaName, FunctionName, AltJ FunctionConfig)]
-> [FunctionMetadata ('Postgres 'Vanilla)])
-> [(SchemaName, FunctionName, AltJ FunctionConfig)]
-> ((SchemaName, FunctionName, AltJ FunctionConfig)
-> FunctionMetadata ('Postgres 'Vanilla))
-> [FunctionMetadata ('Postgres 'Vanilla)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((SchemaName, FunctionName, AltJ FunctionConfig)
-> FunctionMetadata ('Postgres 'Vanilla))
-> [(SchemaName, FunctionName, AltJ FunctionConfig)]
-> [FunctionMetadata ('Postgres 'Vanilla)]
forall a b. (a -> b) -> [a] -> [b]
map [(SchemaName, FunctionName, AltJ FunctionConfig)]
l (((SchemaName, FunctionName, AltJ FunctionConfig)
-> FunctionMetadata ('Postgres 'Vanilla))
-> [FunctionMetadata ('Postgres 'Vanilla)])
-> ((SchemaName, FunctionName, AltJ FunctionConfig)
-> FunctionMetadata ('Postgres 'Vanilla))
-> [FunctionMetadata ('Postgres 'Vanilla)]
forall a b. (a -> b) -> a -> b
$ \(SchemaName
sn, FunctionName
fn, Q.AltJ FunctionConfig
config) ->
FunctionName ('Postgres 'Vanilla)
-> FunctionConfig
-> [FunctionPermissionInfo]
-> Maybe Text
-> FunctionMetadata ('Postgres 'Vanilla)
forall (b :: BackendType).
FunctionName b
-> FunctionConfig
-> [FunctionPermissionInfo]
-> Maybe Text
-> FunctionMetadata b
FunctionMetadata (SchemaName -> FunctionName -> QualifiedFunction
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
sn FunctionName
fn) FunctionConfig
config [] Maybe Text
forall a. Maybe a
Nothing
fetchRemoteSchemas :: TxET QErr IO [RemoteSchemaMetadata]
fetchRemoteSchemas =
((RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)
-> RemoteSchemaMetadata)
-> [(RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)]
-> [RemoteSchemaMetadata]
forall a b. (a -> b) -> [a] -> [b]
map (RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)
-> RemoteSchemaMetadata
fromRow
([(RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)]
-> [RemoteSchemaMetadata])
-> TxET
QErr IO [(RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)]
-> TxET QErr IO [RemoteSchemaMetadata]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query
-> ()
-> Bool
-> TxET
QErr IO [(RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)]
forall (m :: * -> *) a r e.
(MonadIO m, FromRow a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m [a]
Q.listQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
SELECT name, definition, comment
FROM hdb_catalog.remote_schemas
ORDER BY name ASC
|]
()
Bool
True
where
fromRow :: (RemoteSchemaName, AltJ RemoteSchemaDef, Maybe Text)
-> RemoteSchemaMetadata
fromRow (RemoteSchemaName
name, Q.AltJ RemoteSchemaDef
def, Maybe Text
comment) =
RemoteSchemaName
-> RemoteSchemaDef
-> Maybe Text
-> [RemoteSchemaPermissionMetadata]
-> SchemaRemoteRelationships
-> RemoteSchemaMetadata
RemoteSchemaMetadata RemoteSchemaName
name RemoteSchemaDef
def Maybe Text
comment [RemoteSchemaPermissionMetadata]
forall a. Monoid a => a
mempty SchemaRemoteRelationships
forall a. Monoid a => a
mempty
fetchCollections :: TxET QErr IO [CreateCollection]
fetchCollections =
((CollectionName, AltJ CollectionDef, Maybe Text)
-> CreateCollection)
-> [(CollectionName, AltJ CollectionDef, Maybe Text)]
-> [CreateCollection]
forall a b. (a -> b) -> [a] -> [b]
map (CollectionName, AltJ CollectionDef, Maybe Text)
-> CreateCollection
fromRow
([(CollectionName, AltJ CollectionDef, Maybe Text)]
-> [CreateCollection])
-> TxET QErr IO [(CollectionName, AltJ CollectionDef, Maybe Text)]
-> TxET QErr IO [CreateCollection]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query
-> ()
-> Bool
-> TxET QErr IO [(CollectionName, AltJ CollectionDef, Maybe Text)]
forall (m :: * -> *) a r e.
(MonadIO m, FromRow a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m [a]
Q.listQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
SELECT collection_name, collection_defn::json, comment
FROM hdb_catalog.hdb_query_collection
WHERE is_system_defined = 'false'
ORDER BY collection_name ASC
|]
()
Bool
False
where
fromRow :: (CollectionName, AltJ CollectionDef, Maybe Text)
-> CreateCollection
fromRow (CollectionName
name, Q.AltJ CollectionDef
defn, Maybe Text
mComment) =
CollectionName -> CollectionDef -> Maybe Text -> CreateCollection
CreateCollection CollectionName
name CollectionDef
defn Maybe Text
mComment
fetchAllowlist :: TxET QErr IO [AllowlistEntry]
fetchAllowlist =
(Identity CollectionName -> AllowlistEntry)
-> [Identity CollectionName] -> [AllowlistEntry]
forall a b. (a -> b) -> [a] -> [b]
map Identity CollectionName -> AllowlistEntry
fromRow
([Identity CollectionName] -> [AllowlistEntry])
-> TxET QErr IO [Identity CollectionName]
-> TxET QErr IO [AllowlistEntry]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query -> () -> Bool -> TxET QErr IO [Identity CollectionName]
forall (m :: * -> *) a r e.
(MonadIO m, FromRow a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m [a]
Q.listQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
SELECT collection_name
FROM hdb_catalog.hdb_allowlist
ORDER BY collection_name ASC
|]
()
Bool
False
where
fromRow :: Identity CollectionName -> AllowlistEntry
fromRow (Identity CollectionName
name) = CollectionName -> AllowlistScope -> AllowlistEntry
AllowlistEntry CollectionName
name AllowlistScope
AllowlistScopeGlobal
fetchComputedFields :: TxET
QErr
IO
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
fetchComputedFields = do
[(SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)]
r <-
(PGTxErr -> QErr)
-> Query
-> ()
-> Bool
-> TxET
QErr
IO
[(SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)]
forall (m :: * -> *) a r e.
(MonadIO m, FromRow a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m [a]
Q.listQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
SELECT table_schema, table_name, computed_field_name,
definition::json, comment
FROM hdb_catalog.hdb_computed_field
|]
()
Bool
False
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
-> TxET
QErr
IO
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
-> TxET
QErr
IO
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))])
-> [(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
-> TxET
QErr
IO
[(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
forall a b. (a -> b) -> a -> b
$
(((SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)
-> (QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla)))
-> [(SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)]
-> [(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))])
-> [(SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)]
-> ((SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)
-> (QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla)))
-> [(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)
-> (QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla)))
-> [(SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)]
-> [(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
forall a b. (a -> b) -> [a] -> [b]
map [(SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)]
r (((SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)
-> (QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla)))
-> [(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))])
-> ((SchemaName, TableName, ComputedFieldName,
AltJ (ComputedFieldDefinition ('Postgres 'Vanilla)), Maybe Text)
-> (QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla)))
-> [(QualifiedTable, ComputedFieldMetadata ('Postgres 'Vanilla))]
forall a b. (a -> b) -> a -> b
$ \(SchemaName
schema, TableName
table, ComputedFieldName
name, Q.AltJ ComputedFieldDefinition ('Postgres 'Vanilla)
definition, Maybe Text
comment) ->
( SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
schema TableName
table,
ComputedFieldName
-> ComputedFieldDefinition ('Postgres 'Vanilla)
-> Comment
-> ComputedFieldMetadata ('Postgres 'Vanilla)
forall (b :: BackendType).
ComputedFieldName
-> ComputedFieldDefinition b -> Comment -> ComputedFieldMetadata b
ComputedFieldMetadata ComputedFieldName
name ComputedFieldDefinition ('Postgres 'Vanilla)
definition (Maybe Text -> Comment
commentFromMaybeText Maybe Text
comment)
)
fetchCronTriggers :: TxET QErr IO CronTriggers
fetchCronTriggers =
(CronTriggerMetadata -> TriggerName)
-> [CronTriggerMetadata] -> CronTriggers
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL CronTriggerMetadata -> TriggerName
ctName ([CronTriggerMetadata] -> CronTriggers)
-> ([(TriggerName, AltJ InputWebhook, CronSchedule,
Maybe (AltJ Value), AltJ STRetryConf, AltJ [HeaderConf], Bool,
Maybe Text)]
-> [CronTriggerMetadata])
-> [(TriggerName, AltJ InputWebhook, CronSchedule,
Maybe (AltJ Value), AltJ STRetryConf, AltJ [HeaderConf], Bool,
Maybe Text)]
-> CronTriggers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TriggerName, AltJ InputWebhook, CronSchedule, Maybe (AltJ Value),
AltJ STRetryConf, AltJ [HeaderConf], Bool, Maybe Text)
-> CronTriggerMetadata)
-> [(TriggerName, AltJ InputWebhook, CronSchedule,
Maybe (AltJ Value), AltJ STRetryConf, AltJ [HeaderConf], Bool,
Maybe Text)]
-> [CronTriggerMetadata]
forall a b. (a -> b) -> [a] -> [b]
map (TriggerName, AltJ InputWebhook, CronSchedule, Maybe (AltJ Value),
AltJ STRetryConf, AltJ [HeaderConf], Bool, Maybe Text)
-> CronTriggerMetadata
uncurryCronTrigger
([(TriggerName, AltJ InputWebhook, CronSchedule,
Maybe (AltJ Value), AltJ STRetryConf, AltJ [HeaderConf], Bool,
Maybe Text)]
-> CronTriggers)
-> TxET
QErr
IO
[(TriggerName, AltJ InputWebhook, CronSchedule, Maybe (AltJ Value),
AltJ STRetryConf, AltJ [HeaderConf], Bool, Maybe Text)]
-> TxET QErr IO CronTriggers
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query
-> ()
-> Bool
-> TxET
QErr
IO
[(TriggerName, AltJ InputWebhook, CronSchedule, Maybe (AltJ Value),
AltJ STRetryConf, AltJ [HeaderConf], Bool, Maybe Text)]
forall (m :: * -> *) a r e.
(MonadIO m, FromRow a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m [a]
Q.listQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
SELECT ct.name, ct.webhook_conf, ct.cron_schedule, ct.payload,
ct.retry_conf, ct.header_conf, ct.include_in_metadata, ct.comment
FROM hdb_catalog.hdb_cron_triggers ct
WHERE include_in_metadata
|]
()
Bool
False
where
uncurryCronTrigger :: (TriggerName, AltJ InputWebhook, CronSchedule, Maybe (AltJ Value),
AltJ STRetryConf, AltJ [HeaderConf], Bool, Maybe Text)
-> CronTriggerMetadata
uncurryCronTrigger
(TriggerName
name, AltJ InputWebhook
webhook, CronSchedule
schedule, Maybe (AltJ Value)
payload, AltJ STRetryConf
retryConfig, AltJ [HeaderConf]
headerConfig, Bool
includeMetadata, Maybe Text
comment) =
CronTriggerMetadata :: TriggerName
-> InputWebhook
-> CronSchedule
-> Maybe Value
-> STRetryConf
-> [HeaderConf]
-> Bool
-> Maybe Text
-> Maybe RequestTransform
-> Maybe MetadataResponseTransform
-> CronTriggerMetadata
CronTriggerMetadata
{ ctName :: TriggerName
ctName = TriggerName
name,
ctWebhook :: InputWebhook
ctWebhook = AltJ InputWebhook -> InputWebhook
forall a. AltJ a -> a
Q.getAltJ AltJ InputWebhook
webhook,
ctSchedule :: CronSchedule
ctSchedule = CronSchedule
schedule,
ctPayload :: Maybe Value
ctPayload = AltJ Value -> Value
forall a. AltJ a -> a
Q.getAltJ (AltJ Value -> Value) -> Maybe (AltJ Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (AltJ Value)
payload,
ctRetryConf :: STRetryConf
ctRetryConf = AltJ STRetryConf -> STRetryConf
forall a. AltJ a -> a
Q.getAltJ AltJ STRetryConf
retryConfig,
ctHeaders :: [HeaderConf]
ctHeaders = AltJ [HeaderConf] -> [HeaderConf]
forall a. AltJ a -> a
Q.getAltJ AltJ [HeaderConf]
headerConfig,
ctIncludeInMetadata :: Bool
ctIncludeInMetadata = Bool
includeMetadata,
ctComment :: Maybe Text
ctComment = Maybe Text
comment,
ctRequestTransform :: Maybe RequestTransform
ctRequestTransform = Maybe RequestTransform
forall a. Maybe a
Nothing,
ctResponseTransform :: Maybe MetadataResponseTransform
ctResponseTransform = Maybe MetadataResponseTransform
forall a. Maybe a
Nothing
}
fetchCustomTypes :: Q.TxE QErr CustomTypes
fetchCustomTypes :: TxE QErr CustomTypes
fetchCustomTypes =
AltJ CustomTypes -> CustomTypes
forall a. AltJ a -> a
Q.getAltJ (AltJ CustomTypes -> CustomTypes)
-> (SingleRow (Identity (AltJ CustomTypes)) -> AltJ CustomTypes)
-> SingleRow (Identity (AltJ CustomTypes))
-> CustomTypes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity (AltJ CustomTypes) -> AltJ CustomTypes
forall a. Identity a -> a
runIdentity (Identity (AltJ CustomTypes) -> AltJ CustomTypes)
-> (SingleRow (Identity (AltJ CustomTypes))
-> Identity (AltJ CustomTypes))
-> SingleRow (Identity (AltJ CustomTypes))
-> AltJ CustomTypes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SingleRow (Identity (AltJ CustomTypes))
-> Identity (AltJ CustomTypes)
forall a. SingleRow a -> a
Q.getRow
(SingleRow (Identity (AltJ CustomTypes)) -> CustomTypes)
-> TxET QErr IO (SingleRow (Identity (AltJ CustomTypes)))
-> TxE QErr CustomTypes
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query
-> [PrepArg]
-> Bool
-> TxET QErr IO (SingleRow (Identity (AltJ CustomTypes)))
forall (m :: * -> *) a e.
(MonadIO m, FromRes a) =>
(PGTxErr -> e) -> Query -> [PrepArg] -> Bool -> TxET e m a
Q.rawQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
select coalesce((select custom_types::json from hdb_catalog.hdb_custom_types), '{}'::json)
|]
[]
Bool
False
fetchActions :: TxET QErr IO [ActionMetadata]
fetchActions =
AltJ [ActionMetadata] -> [ActionMetadata]
forall a. AltJ a -> a
Q.getAltJ (AltJ [ActionMetadata] -> [ActionMetadata])
-> (SingleRow (Identity (AltJ [ActionMetadata]))
-> AltJ [ActionMetadata])
-> SingleRow (Identity (AltJ [ActionMetadata]))
-> [ActionMetadata]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity (AltJ [ActionMetadata]) -> AltJ [ActionMetadata]
forall a. Identity a -> a
runIdentity (Identity (AltJ [ActionMetadata]) -> AltJ [ActionMetadata])
-> (SingleRow (Identity (AltJ [ActionMetadata]))
-> Identity (AltJ [ActionMetadata]))
-> SingleRow (Identity (AltJ [ActionMetadata]))
-> AltJ [ActionMetadata]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SingleRow (Identity (AltJ [ActionMetadata]))
-> Identity (AltJ [ActionMetadata])
forall a. SingleRow a -> a
Q.getRow
(SingleRow (Identity (AltJ [ActionMetadata])) -> [ActionMetadata])
-> TxET QErr IO (SingleRow (Identity (AltJ [ActionMetadata])))
-> TxET QErr IO [ActionMetadata]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query
-> [PrepArg]
-> Bool
-> TxET QErr IO (SingleRow (Identity (AltJ [ActionMetadata])))
forall (m :: * -> *) a e.
(MonadIO m, FromRes a) =>
(PGTxErr -> e) -> Query -> [PrepArg] -> Bool -> TxET e m a
Q.rawQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
select
coalesce(
json_agg(
json_build_object(
'name', a.action_name,
'definition', a.action_defn,
'comment', a.comment,
'permissions', ap.permissions
) order by a.action_name asc
),
'[]'
)
from
hdb_catalog.hdb_action as a
left outer join lateral (
select
coalesce(
json_agg(
json_build_object(
'role', ap.role_name,
'comment', ap.comment
) order by ap.role_name asc
),
'[]'
) as permissions
from
hdb_catalog.hdb_action_permission ap
where
ap.action_name = a.action_name
) ap on true;
|]
[]
Bool
False
fetchRemoteRelationships :: TxET PGTxErr IO [(QualifiedTable, RelName, Value)]
fetchRemoteRelationships = do
[(SchemaName, TableName, RelName, AltJ Value)]
r <-
Query
-> ()
-> Bool
-> TxT IO [(SchemaName, TableName, RelName, AltJ Value)]
forall (m :: * -> *) a r.
(MonadIO m, FromRow a, ToPrepArgs r) =>
Query -> r -> Bool -> TxT m [a]
Q.listQ
[Q.sql|
SELECT table_schema, table_name,
remote_relationship_name, definition::json
FROM hdb_catalog.hdb_remote_relationship
|]
()
Bool
False
[(QualifiedTable, RelName, Value)]
-> TxET PGTxErr IO [(QualifiedTable, RelName, Value)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([(QualifiedTable, RelName, Value)]
-> TxET PGTxErr IO [(QualifiedTable, RelName, Value)])
-> [(QualifiedTable, RelName, Value)]
-> TxET PGTxErr IO [(QualifiedTable, RelName, Value)]
forall a b. (a -> b) -> a -> b
$
(((SchemaName, TableName, RelName, AltJ Value)
-> (QualifiedTable, RelName, Value))
-> [(SchemaName, TableName, RelName, AltJ Value)]
-> [(QualifiedTable, RelName, Value)])
-> [(SchemaName, TableName, RelName, AltJ Value)]
-> ((SchemaName, TableName, RelName, AltJ Value)
-> (QualifiedTable, RelName, Value))
-> [(QualifiedTable, RelName, Value)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((SchemaName, TableName, RelName, AltJ Value)
-> (QualifiedTable, RelName, Value))
-> [(SchemaName, TableName, RelName, AltJ Value)]
-> [(QualifiedTable, RelName, Value)]
forall a b. (a -> b) -> [a] -> [b]
map [(SchemaName, TableName, RelName, AltJ Value)]
r (((SchemaName, TableName, RelName, AltJ Value)
-> (QualifiedTable, RelName, Value))
-> [(QualifiedTable, RelName, Value)])
-> ((SchemaName, TableName, RelName, AltJ Value)
-> (QualifiedTable, RelName, Value))
-> [(QualifiedTable, RelName, Value)]
forall a b. (a -> b) -> a -> b
$ \(SchemaName
schema, TableName
table, RelName
name, Q.AltJ Value
definition) ->
( SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
schema TableName
table,
RelName
name,
Value
definition
)
addCronTriggerForeignKeyConstraint :: MonadTx m => m ()
addCronTriggerForeignKeyConstraint :: m ()
addCronTriggerForeignKeyConstraint =
TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$
(PGTxErr -> QErr) -> Query -> () -> Bool -> TxE QErr ()
forall (m :: * -> *) r e.
(MonadIO m, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m ()
Q.unitQE
PGTxErr -> QErr
defaultTxErrorHandler
[Q.sql|
ALTER TABLE hdb_catalog.hdb_cron_events ADD CONSTRAINT
hdb_cron_events_trigger_name_fkey FOREIGN KEY (trigger_name)
REFERENCES hdb_catalog.hdb_cron_triggers(name)
ON UPDATE CASCADE ON DELETE CASCADE;
|]
()
Bool
False
recreateSystemMetadata :: (MonadTx m) => m ()
recreateSystemMetadata :: m ()
recreateSystemMetadata = do
() <- TxE QErr () -> m ()
forall (m :: * -> *) a. MonadTx m => TxE QErr a -> m a
liftTx (TxE QErr () -> m ()) -> TxE QErr () -> m ()
forall a b. (a -> b) -> a -> b
$ (PGTxErr -> QErr) -> Query -> TxE QErr ()
forall (m :: * -> *) a e.
(MonadIO m, FromRes a) =>
(PGTxErr -> e) -> Query -> TxET e m a
Q.multiQE PGTxErr -> QErr
defaultTxErrorHandler $(makeRelativeToProject "src-rsr/clear_system_metadata.sql" >>= Q.sqlFromFile)
(ReaderT SystemDefined m () -> SystemDefined -> m ())
-> SystemDefined -> ReaderT SystemDefined m () -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT SystemDefined m () -> SystemDefined -> m ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (Bool -> SystemDefined
SystemDefined Bool
True) (ReaderT SystemDefined m () -> m ())
-> ReaderT SystemDefined m () -> m ()
forall a b. (a -> b) -> a -> b
$ [(QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla))
(ArrRelDef ('Postgres 'Vanilla))])]
-> ((QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
-> ReaderT SystemDefined m ())
-> ReaderT SystemDefined m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [(QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla))
(ArrRelDef ('Postgres 'Vanilla))])]
systemMetadata \(QualifiedTable
tableName, [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
tableRels) -> do
QualifiedTable
-> Bool
-> TableConfig ('Postgres 'Vanilla)
-> ReaderT SystemDefined m ()
forall (m :: * -> *).
(MonadTx m, MonadReader SystemDefined m) =>
QualifiedTable -> Bool -> TableConfig ('Postgres 'Vanilla) -> m ()
saveTableToCatalog QualifiedTable
tableName Bool
False TableConfig ('Postgres 'Vanilla)
forall (b :: BackendType). TableConfig b
emptyTableConfig
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
-> ReaderT SystemDefined m ())
-> ReaderT SystemDefined m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
tableRels \case
Left ObjRelDef ('Postgres 'Vanilla)
relDef -> QualifiedTable
-> RelType
-> ObjRelDef ('Postgres 'Vanilla)
-> ReaderT SystemDefined m ()
forall (m :: * -> *) a.
(MonadTx m, MonadReader SystemDefined m, ToJSON a) =>
QualifiedTable -> RelType -> RelDef a -> m ()
insertRelationshipToCatalog QualifiedTable
tableName RelType
ObjRel ObjRelDef ('Postgres 'Vanilla)
relDef
Right ArrRelDef ('Postgres 'Vanilla)
relDef -> QualifiedTable
-> RelType
-> ArrRelDef ('Postgres 'Vanilla)
-> ReaderT SystemDefined m ()
forall (m :: * -> *) a.
(MonadTx m, MonadReader SystemDefined m, ToJSON a) =>
QualifiedTable -> RelType -> RelDef a -> m ()
insertRelationshipToCatalog QualifiedTable
tableName RelType
ArrRel ArrRelDef ('Postgres 'Vanilla)
relDef
where
systemMetadata :: [(QualifiedTable, [Either (ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])]
systemMetadata :: [(QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla))
(ArrRelDef ('Postgres 'Vanilla))])]
systemMetadata =
[ SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"information_schema" TableName
"tables" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"information_schema" TableName
"schemata" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"information_schema" TableName
"views" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"information_schema" TableName
"columns" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_table"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "detail") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"information_schema" TableName
"tables" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "primary_key") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_primary_key" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "columns") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"information_schema" TableName
"columns" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "foreign_key_constraints") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_foreign_key_constraint" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "relationships") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_relationship" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "permissions") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_permission_agg" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "computed_fields") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_computed_field" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "check_constraints") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_check_constraint" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping,
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "unique_constraints") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"hdb_unique_constraint" [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
[(PGCol, PGCol)]
tableNameMapping
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_primary_key" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_foreign_key_constraint" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_relationship" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_permission_agg" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_computed_field" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_check_constraint" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_unique_constraint" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_remote_relationship" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"event_triggers"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "events") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"event_log" [(Column ('Postgres 'Vanilla)
"name", Column ('Postgres 'Vanilla)
"trigger_name")]
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"event_log"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "trigger") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
"hdb_catalog" TableName
"event_triggers" [(Column ('Postgres 'Vanilla)
"trigger_name", Column ('Postgres 'Vanilla)
"name")],
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "logs") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla)))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
TableName ('Postgres 'Vanilla)
-> NonEmpty (Column ('Postgres 'Vanilla))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
forall (b :: BackendType).
TableName b -> NonEmpty (Column b) -> ArrRelUsingFKeyOn b
ArrRelUsingFKeyOn (SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
"hdb_catalog" TableName
"event_invocation_logs") (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"event_id")
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"event_invocation_logs"
[NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "event") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla)))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ NonEmpty (Column ('Postgres 'Vanilla))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
forall (b :: BackendType).
NonEmpty (Column b) -> ObjRelUsingChoice b
SameTable (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"event_id")],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_function" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_function_agg"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "return_table_info") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig
SchemaName
"hdb_catalog"
TableName
"hdb_table"
[ (Column ('Postgres 'Vanilla)
"return_type_schema", Column ('Postgres 'Vanilla)
"table_schema"),
(Column ('Postgres 'Vanilla)
"return_type_name", Column ('Postgres 'Vanilla)
"table_name")
]
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"remote_schemas" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_version" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_query_collection" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_allowlist" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_custom_types" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_action_permission" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_action"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "permissions") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig
SchemaName
"hdb_catalog"
TableName
"hdb_action_permission"
[(Column ('Postgres 'Vanilla)
"action_name", Column ('Postgres 'Vanilla)
"action_name")]
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
"hdb_catalog" TableName
"hdb_action_log" [],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_role"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "action_permissions") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig
SchemaName
"hdb_catalog"
TableName
"hdb_action_permission"
[(Column ('Postgres 'Vanilla)
"role_name", Column ('Postgres 'Vanilla)
"role_name")],
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "permissions") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
SchemaName
-> TableName
-> [(Column ('Postgres 'Vanilla), Column ('Postgres 'Vanilla))]
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a a.
(Eq (Column b), Hashable (Column b),
TableName b ~ QualifiedObject a) =>
SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig
SchemaName
"hdb_catalog"
TableName
"hdb_permission_agg"
[(Column ('Postgres 'Vanilla)
"role_name", Column ('Postgres 'Vanilla)
"role_name")]
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_cron_triggers"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "cron_events") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla)))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
TableName ('Postgres 'Vanilla)
-> NonEmpty (Column ('Postgres 'Vanilla))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
forall (b :: BackendType).
TableName b -> NonEmpty (Column b) -> ArrRelUsingFKeyOn b
ArrRelUsingFKeyOn (SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
"hdb_catalog" TableName
"hdb_cron_events") (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"trigger_name")
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_cron_events"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "cron_trigger") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla)))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ NonEmpty (Column ('Postgres 'Vanilla))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
forall (b :: BackendType).
NonEmpty (Column b) -> ObjRelUsingChoice b
SameTable (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"trigger_name"),
NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "cron_event_logs") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla)))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
TableName ('Postgres 'Vanilla)
-> NonEmpty (Column ('Postgres 'Vanilla))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
forall (b :: BackendType).
TableName b -> NonEmpty (Column b) -> ArrRelUsingFKeyOn b
ArrRelUsingFKeyOn (SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
"hdb_catalog" TableName
"hdb_cron_event_invocation_logs") (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"event_id")
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_cron_event_invocation_logs"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "cron_event") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla)))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ NonEmpty (Column ('Postgres 'Vanilla))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
forall (b :: BackendType).
NonEmpty (Column b) -> ObjRelUsingChoice b
SameTable (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"event_id")
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_scheduled_events"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a a. NonEmptyText -> a -> Either a (RelDef a)
arrayRel $$(nonEmptyText "scheduled_event_logs") (RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla)))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ArrRelUsingFKeyOn ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
TableName ('Postgres 'Vanilla)
-> NonEmpty (Column ('Postgres 'Vanilla))
-> ArrRelUsingFKeyOn ('Postgres 'Vanilla)
forall (b :: BackendType).
TableName b -> NonEmpty (Column b) -> ArrRelUsingFKeyOn b
ArrRelUsingFKeyOn (SchemaName -> TableName -> QualifiedTable
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
"hdb_catalog" TableName
"hdb_scheduled_event_invocation_logs") (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"event_id")
],
SchemaName
-> TableName
-> [Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))]
-> (QualifiedTable,
[Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))])
forall a b. SchemaName -> a -> b -> (QualifiedObject a, b)
table
SchemaName
"hdb_catalog"
TableName
"hdb_scheduled_event_invocation_logs"
[ NonEmptyText
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. NonEmptyText -> a -> Either (RelDef a) b
objectRel $$(nonEmptyText "scheduled_event") (RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla)))
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
-> Either
(ObjRelDef ('Postgres 'Vanilla)) (ArrRelDef ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall (b :: BackendType) a. a -> RelUsing b a
RUFKeyOn (ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla)))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
-> RelUsing
('Postgres 'Vanilla) (ObjRelUsingChoice ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ NonEmpty (Column ('Postgres 'Vanilla))
-> ObjRelUsingChoice ('Postgres 'Vanilla)
forall (b :: BackendType).
NonEmpty (Column b) -> ObjRelUsingChoice b
SameTable (PGCol -> NonEmpty PGCol
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
"event_id")
]
]
tableNameMapping :: [(PGCol, PGCol)]
tableNameMapping =
[ (PGCol
"table_schema", PGCol
"table_schema"),
(PGCol
"table_name", PGCol
"table_name")
]
table :: SchemaName -> a -> b -> (QualifiedObject a, b)
table SchemaName
schemaName a
tableName b
relationships = (SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
schemaName a
tableName, b
relationships)
objectRel :: NonEmptyText -> a -> Either (RelDef a) b
objectRel NonEmptyText
name a
using = RelDef a -> Either (RelDef a) b
forall a b. a -> Either a b
Left (RelDef a -> Either (RelDef a) b)
-> RelDef a -> Either (RelDef a) b
forall a b. (a -> b) -> a -> b
$ RelName -> a -> Maybe Text -> RelDef a
forall a. RelName -> a -> Maybe Text -> RelDef a
RelDef (NonEmptyText -> RelName
RelName NonEmptyText
name) a
using Maybe Text
forall a. Maybe a
Nothing
arrayRel :: NonEmptyText -> a -> Either a (RelDef a)
arrayRel NonEmptyText
name a
using = RelDef a -> Either a (RelDef a)
forall a b. b -> Either a b
Right (RelDef a -> Either a (RelDef a))
-> RelDef a -> Either a (RelDef a)
forall a b. (a -> b) -> a -> b
$ RelName -> a -> Maybe Text -> RelDef a
forall a. RelName -> a -> Maybe Text -> RelDef a
RelDef (NonEmptyText -> RelName
RelName NonEmptyText
name) a
using Maybe Text
forall a. Maybe a
Nothing
manualConfig :: SchemaName -> a -> [(Column b, Column b)] -> RelUsing b a
manualConfig SchemaName
schemaName a
tableName [(Column b, Column b)]
columns =
RelManualConfig b -> RelUsing b a
forall (b :: BackendType) a. RelManualConfig b -> RelUsing b a
RUManual (RelManualConfig b -> RelUsing b a)
-> RelManualConfig b -> RelUsing b a
forall a b. (a -> b) -> a -> b
$ TableName b
-> HashMap (Column b) (Column b)
-> Maybe InsertOrder
-> RelManualConfig b
forall (b :: BackendType).
TableName b
-> HashMap (Column b) (Column b)
-> Maybe InsertOrder
-> RelManualConfig b
RelManualConfig (SchemaName -> a -> QualifiedObject a
forall a. SchemaName -> a -> QualifiedObject a
QualifiedObject SchemaName
schemaName a
tableName) ([(Column b, Column b)] -> HashMap (Column b) (Column b)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList [(Column b, Column b)]
columns) Maybe InsertOrder
forall a. Maybe a
Nothing