server: import local Postgres modules as Postgres

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5962
GitOrigin-RevId: 862862c34b6c633c94ee8ae1f075afca2799fd2b
This commit is contained in:
Daniel Harvey 2022-09-21 12:34:39 +01:00 committed by hasura-bot
parent e32bcb183c
commit e2ced4011d
17 changed files with 269 additions and 269 deletions

View File

@ -18,7 +18,7 @@ import Data.Text.Extended
import Database.PG.Query qualified as PG
import Hasura.Backends.Postgres.Connection
import Hasura.Backends.Postgres.Execute.Mutation qualified as PGE
import Hasura.Backends.Postgres.SQL.DML qualified as PG
import Hasura.Backends.Postgres.SQL.DML qualified as Postgres
import Hasura.Backends.Postgres.SQL.Types
import Hasura.Backends.Postgres.SQL.Value
import Hasura.Backends.Postgres.Translate.BoolExp qualified as PGT
@ -53,7 +53,7 @@ convertToSQLTransaction ::
PostgresAnnotatedFieldJSON pgKind,
MonadReader QueryTagsComment m
) =>
IR.AnnotatedInsert ('Postgres pgKind) Void PG.SQLExp ->
IR.AnnotatedInsert ('Postgres pgKind) Void Postgres.SQLExp ->
UserInfo ->
Seq.Seq PG.PrepArg ->
Options.StringifyNumbers ->
@ -78,8 +78,8 @@ insertMultipleObjects ::
PostgresAnnotatedFieldJSON pgKind,
MonadReader QueryTagsComment m
) =>
IR.MultiObjectInsert ('Postgres pgKind) PG.SQLExp ->
Map.HashMap PGCol PG.SQLExp ->
IR.MultiObjectInsert ('Postgres pgKind) Postgres.SQLExp ->
Map.HashMap PGCol Postgres.SQLExp ->
UserInfo ->
IR.MutationOutput ('Postgres pgKind) ->
Seq.Seq PG.PrepArg ->
@ -98,7 +98,7 @@ insertMultipleObjects multiObjIns additionalColumns userInfo mutationOutput plan
indexedForM_ (IR.getInsertColumns <$> insObjs) \column ->
validateInsert (map fst column) [] (Map.keys additionalColumns)
let insObjRows = Map.fromList . IR.getInsertColumns <$> insObjs
(columnNames, insertRows) = Map.homogenise PG.columnDefaultValue $ map ((presetRow <> additionalColumns) <>) insObjRows
(columnNames, insertRows) = Map.homogenise Postgres.columnDefaultValue $ map ((presetRow <> additionalColumns) <>) insObjRows
insertQuery =
IR.InsertQueryP1
table
@ -139,8 +139,8 @@ insertObject ::
PostgresAnnotatedFieldJSON pgKind,
MonadReader QueryTagsComment m
) =>
IR.SingleObjectInsert ('Postgres pgKind) PG.SQLExp ->
HashMap PGCol PG.SQLExp ->
IR.SingleObjectInsert ('Postgres pgKind) Postgres.SQLExp ->
HashMap PGCol Postgres.SQLExp ->
UserInfo ->
Seq.Seq PG.PrepArg ->
Options.StringifyNumbers ->
@ -174,11 +174,11 @@ insertObject singleObjIns additionalColumns userInfo planVars stringifyNum tCase
objectRels = IR.getInsertObjectRelationships annObj
arrayRels = IR.getInsertArrayRelationships annObj
afterInsert, beforeInsert :: [IR.ObjectRelationInsert ('Postgres pgKind) PG.SQLExp]
afterInsert, beforeInsert :: [IR.ObjectRelationInsert ('Postgres pgKind) Postgres.SQLExp]
(afterInsert, beforeInsert) =
L.partition ((== AfterParent) . riInsertOrder . IR._riRelationInfo) objectRels
allAfterInsertRels :: [IR.ArrayRelationInsert ('Postgres pgKind) PG.SQLExp]
allAfterInsertRels :: [IR.ArrayRelationInsert ('Postgres pgKind) Postgres.SQLExp]
allAfterInsertRels = arrayRels <> map objToArr afterInsert
afterInsertDepCols :: [ColumnInfo ('Postgres pgKind)]
@ -229,8 +229,8 @@ insertObjRel ::
UserInfo ->
Options.StringifyNumbers ->
Maybe NamingCase ->
IR.ObjectRelationInsert ('Postgres pgKind) PG.SQLExp ->
m (Int, [(PGCol, PG.SQLExp)])
IR.ObjectRelationInsert ('Postgres pgKind) Postgres.SQLExp ->
m (Int, [(PGCol, Postgres.SQLExp)])
insertObjRel planVars userInfo stringifyNum tCase objRelIns =
withPathK (relNameToTxt relName) $ do
(affRows, colValM) <- withPathK "data" $ insertObject singleObjIns mempty userInfo planVars stringifyNum tCase
@ -261,12 +261,12 @@ insertArrRel ::
PostgresAnnotatedFieldJSON pgKind,
MonadReader QueryTagsComment m
) =>
[(PGCol, PG.SQLExp)] ->
[(PGCol, Postgres.SQLExp)] ->
UserInfo ->
Seq.Seq PG.PrepArg ->
Options.StringifyNumbers ->
Maybe NamingCase ->
IR.ArrayRelationInsert ('Postgres pgKind) PG.SQLExp ->
IR.ArrayRelationInsert ('Postgres pgKind) Postgres.SQLExp ->
m Int
insertArrRel resCols userInfo planVars stringifyNum tCase arrRelIns =
withPathK (relNameToTxt $ riName relInfo) $ do
@ -325,33 +325,33 @@ validateInsert insCols objRels addCols = do
mkInsertQ ::
Backend ('Postgres pgKind) =>
QualifiedTable ->
Maybe (IR.OnConflictClause ('Postgres pgKind) PG.SQLExp) ->
Map.HashMap PGCol PG.SQLExp ->
Maybe (IR.OnConflictClause ('Postgres pgKind) Postgres.SQLExp) ->
Map.HashMap PGCol Postgres.SQLExp ->
(AnnBoolExpSQL ('Postgres pgKind), Maybe (AnnBoolExpSQL ('Postgres pgKind))) ->
PG.TopLevelCTE
Postgres.TopLevelCTE
mkInsertQ table onConflictM insertRow (insCheck, updCheck) =
let sqlConflict = PGT.toSQLConflict table <$> onConflictM
sqlExps = Map.elems insertRow
valueExp = PG.ValuesExp [PG.TupleExp sqlExps]
valueExp = Postgres.ValuesExp [Postgres.TupleExp sqlExps]
tableCols = Map.keys insertRow
sqlInsert =
PG.SQLInsert table tableCols valueExp sqlConflict
Postgres.SQLInsert table tableCols valueExp sqlConflict
. Just
$ PG.RetExp
[ PG.selectStar,
$ Postgres.RetExp
[ Postgres.selectStar,
PGT.insertOrUpdateCheckExpr
table
onConflictM
(PGT.toSQLBoolExp (PG.QualTable table) insCheck)
(fmap (PGT.toSQLBoolExp (PG.QualTable table)) updCheck)
(PGT.toSQLBoolExp (Postgres.QualTable table) insCheck)
(fmap (PGT.toSQLBoolExp (Postgres.QualTable table)) updCheck)
]
in PG.CTEInsert sqlInsert
in Postgres.CTEInsert sqlInsert
fetchFromColVals ::
MonadError QErr m =>
ColumnValues ('Postgres pgKind) TxtEncodedVal ->
[ColumnInfo ('Postgres pgKind)] ->
m [(PGCol, PG.SQLExp)]
m [(PGCol, Postgres.SQLExp)]
fetchFromColVals colVal reqCols =
forM reqCols $ \ci -> do
let valM = Map.lookup (ciColumn ci) colVal
@ -361,8 +361,8 @@ fetchFromColVals colVal reqCols =
"column "
<> ciColumn ci <<> " not found in given colVal"
let pgColVal = case val of
TENull -> PG.SENull
TELit t -> PG.SELit t
TENull -> Postgres.SENull
TELit t -> Postgres.SELit t
return (ciColumn ci, pgColVal)
decodeEncJSON :: (J.FromJSON a, QErrM m) => EncJSON -> m a

View File

@ -35,11 +35,11 @@ import Hasura.Backends.Postgres.Execute.Prepare
import Hasura.Backends.Postgres.Execute.Subscription qualified as PGL
import Hasura.Backends.Postgres.Execute.Types (PGSourceConfig (..), dmlTxErrorHandler)
import Hasura.Backends.Postgres.SQL.DML qualified as S
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Value qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Backends.Postgres.SQL.Value qualified as Postgres
import Hasura.Backends.Postgres.Translate.Select (PostgresAnnotatedFieldJSON)
import Hasura.Backends.Postgres.Translate.Select qualified as DS
import Hasura.Backends.Postgres.Types.Function qualified as PG
import Hasura.Backends.Postgres.Types.Function qualified as Postgres
import Hasura.Backends.Postgres.Types.Update qualified as BackendUpdate
import Hasura.Base.Error (QErr)
import Hasura.EncJSON (EncJSON, encJFromJValue)
@ -473,28 +473,28 @@ pgDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argume
-- a root field name that makes sense to attach to it.
flip runReaderT emptyQueryTagsComment $ pgDBQueryPlan userInfo Env.emptyEnvironment sourceName sourceConfig rootSelection
where
coerceToColumn = PG.unsafePGCol . getFieldNameTxt
coerceToColumn = Postgres.unsafePGCol . getFieldNameTxt
joinColumnMapping = mapKeys coerceToColumn lhsSchema
rowsArgument :: UnpreparedValue ('Postgres pgKind)
rowsArgument =
UVParameter Nothing $
ColumnValue (ColumnScalar PG.PGJSONB) $
PG.PGValJSONB $ PG.JSONB $ J.toJSON lhs
ColumnValue (ColumnScalar Postgres.PGJSONB) $
Postgres.PGValJSONB $ PG.JSONB $ J.toJSON lhs
jsonToRecordSet :: IR.SelectFromG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
recordSetDefinitionList =
(coerceToColumn argumentId, PG.PGBigInt) : Map.toList (fmap snd joinColumnMapping)
(coerceToColumn argumentId, Postgres.PGBigInt) : Map.toList (fmap snd joinColumnMapping)
jsonToRecordSet =
IR.FromFunction
(PG.QualifiedObject "pg_catalog" $ PG.FunctionName "jsonb_to_recordset")
(FunctionArgsExp [PG.AEInput rowsArgument] mempty)
(Postgres.QualifiedObject "pg_catalog" $ Postgres.FunctionName "jsonb_to_recordset")
(FunctionArgsExp [Postgres.AEInput rowsArgument] mempty)
(Just recordSetDefinitionList)
rootSelection =
convertRemoteSourceRelationship
(fst <$> joinColumnMapping)
jsonToRecordSet
(PG.unsafePGCol $ getFieldNameTxt argumentId)
(ColumnScalar PG.PGBigInt)
(Postgres.unsafePGCol $ getFieldNameTxt argumentId)
(ColumnScalar Postgres.PGBigInt)
relationship

View File

@ -8,7 +8,7 @@ module Hasura.Backends.Postgres.Instances.Metadata () where
import Data.HashMap.Strict qualified as Map
import Data.Text.Extended
import Hasura.Backends.Postgres.DDL qualified as PG
import Hasura.Backends.Postgres.DDL qualified as Postgres
import Hasura.Backends.Postgres.SQL.Types (QualifiedTable)
import Hasura.Backends.Postgres.Types.CitusExtraTableMetadata
import Hasura.Base.Error
@ -118,21 +118,21 @@ instance PostgresMetadata 'Cockroach where
instance
( Backend ('Postgres pgKind),
PostgresMetadata pgKind,
PG.FetchTableMetadata pgKind,
PG.FetchFunctionMetadata pgKind,
PG.ToMetadataFetchQuery pgKind
Postgres.FetchTableMetadata pgKind,
Postgres.FetchFunctionMetadata pgKind,
Postgres.ToMetadataFetchQuery pgKind
) =>
BackendMetadata ('Postgres pgKind)
where
prepareCatalog = PG.prepareCatalog
buildComputedFieldInfo = PG.buildComputedFieldInfo
fetchAndValidateEnumValues = PG.fetchAndValidateEnumValues
resolveSourceConfig = PG.resolveSourceConfig
resolveDatabaseMetadata = PG.resolveDatabaseMetadata
parseBoolExpOperations = PG.parseBoolExpOperations
buildFunctionInfo = PG.buildFunctionInfo
updateColumnInEventTrigger = PG.updateColumnInEventTrigger
parseCollectableType = PG.parseCollectableType
postDropSourceHook = PG.postDropSourceHook
prepareCatalog = Postgres.prepareCatalog
buildComputedFieldInfo = Postgres.buildComputedFieldInfo
fetchAndValidateEnumValues = Postgres.fetchAndValidateEnumValues
resolveSourceConfig = Postgres.resolveSourceConfig
resolveDatabaseMetadata = Postgres.resolveDatabaseMetadata
parseBoolExpOperations = Postgres.parseBoolExpOperations
buildFunctionInfo = Postgres.buildFunctionInfo
updateColumnInEventTrigger = Postgres.updateColumnInEventTrigger
parseCollectableType = Postgres.parseCollectableType
postDropSourceHook = Postgres.postDropSourceHook
validateRelationship = validateRel @pgKind
buildComputedFieldBooleanExp = PG.buildComputedFieldBooleanExp
buildComputedFieldBooleanExp = Postgres.buildComputedFieldBooleanExp

View File

@ -22,9 +22,9 @@ import Data.List.NonEmpty qualified as NE
import Data.Parser.JSONPath
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.DML as PG hiding (CountType, incOp)
import Hasura.Backends.Postgres.SQL.Types as PG hiding (FunctionName, TableName)
import Hasura.Backends.Postgres.SQL.Value as PG
import Hasura.Backends.Postgres.SQL.DML as Postgres hiding (CountType, incOp)
import Hasura.Backends.Postgres.SQL.Types as Postgres hiding (FunctionName, TableName)
import Hasura.Backends.Postgres.SQL.Value as Postgres
import Hasura.Backends.Postgres.Schema.OnConflict
import Hasura.Backends.Postgres.Schema.Select
import Hasura.Backends.Postgres.Types.BoolExp
@ -242,7 +242,7 @@ instance
GraphqlCase -> orderByOperatorsGraphqlCase
comparisonExps = const comparisonExps
countTypeInput = countTypeInput
aggregateOrderByCountType = PG.PGInteger
aggregateOrderByCountType = Postgres.PGInteger
computedField = computedFieldPG
backendInsertParser ::
@ -496,7 +496,7 @@ pgScalarSelectionArgumentsParser ::
ColumnType ('Postgres pgKind) ->
InputFieldsParser n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
pgScalarSelectionArgumentsParser columnType
| isScalarColumnWhere PG.isJSONType columnType =
| isScalarColumnWhere Postgres.isJSONType columnType =
P.fieldOptional fieldName description P.string `P.bindFields` fmap join . traverse toColExp
| otherwise = pure Nothing
where
@ -505,9 +505,9 @@ pgScalarSelectionArgumentsParser columnType
toColExp textValue = case parseJSONPath textValue of
Left err -> P.parseError $ "parse json path error: " <> toErrorMessage err
Right [] -> pure Nothing
Right jPaths -> pure $ Just $ PG.ColumnOp PG.jsonbPathOp $ PG.SEArray $ map elToColExp jPaths
elToColExp (Key k) = PG.SELit $ K.toText k
elToColExp (Index i) = PG.SELit $ tshow i
Right jPaths -> pure $ Just $ Postgres.ColumnOp Postgres.jsonbPathOp $ Postgres.SEArray $ map elToColExp jPaths
elToColExp (Key k) = Postgres.SELit $ K.toText k
elToColExp (Index i) = Postgres.SELit $ tshow i
orderByOperatorsHasuraCase ::
(G.Name, NonEmpty (Definition P.EnumValueInfo, (BasicOrderType ('Postgres pgKind), NullsOrderType ('Postgres pgKind))))
@ -526,22 +526,22 @@ orderByOperators tCase =
(Name._order_by,) $
NE.fromList
[ ( define (applyEnumValueCase tCase Name._asc) "in ascending order, nulls last",
(PG.OTAsc, PG.NullsLast)
(Postgres.OTAsc, Postgres.NullsLast)
),
( define (applyEnumValueCase tCase Name._asc_nulls_first) "in ascending order, nulls first",
(PG.OTAsc, PG.NullsFirst)
(Postgres.OTAsc, Postgres.NullsFirst)
),
( define (applyEnumValueCase tCase Name._asc_nulls_last) "in ascending order, nulls last",
(PG.OTAsc, PG.NullsLast)
(Postgres.OTAsc, Postgres.NullsLast)
),
( define (applyEnumValueCase tCase Name._desc) "in descending order, nulls first",
(PG.OTDesc, PG.NullsFirst)
(Postgres.OTDesc, Postgres.NullsFirst)
),
( define (applyEnumValueCase tCase Name._desc_nulls_first) "in descending order, nulls first",
(PG.OTDesc, PG.NullsFirst)
(Postgres.OTDesc, Postgres.NullsFirst)
),
( define (applyEnumValueCase tCase Name._desc_nulls_last) "in descending order, nulls last",
(PG.OTDesc, PG.NullsLast)
(Postgres.OTDesc, Postgres.NullsLast)
)
]
where
@ -852,8 +852,8 @@ comparisonExps = memoize 'comparisonExps \columnType -> do
let scalarType = unsafePGColumnToBackend columnType
IR.UVParameter Nothing $
ColumnValue
(ColumnScalar $ PG.PGArray scalarType)
(PG.PGValArray $ cvValue <$> columnValues)
(ColumnScalar $ Postgres.PGArray scalarType)
(Postgres.PGValArray $ cvValue <$> columnValues)
castExp :: ColumnType ('Postgres pgKind) -> NamingCase -> SchemaT r m (Maybe (Parser 'Input n (CastExp ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind)))))
castExp sourceType tCase = do
@ -939,9 +939,9 @@ countTypeInput = \case
Nothing -> pure $ flip mkCountType Nothing
where
mkCountType :: IR.CountDistinct -> Maybe [Column ('Postgres pgKind)] -> CountType ('Postgres pgKind)
mkCountType _ Nothing = PG.CTStar
mkCountType IR.SelectCountDistinct (Just cols) = PG.CTDistinct cols
mkCountType IR.SelectCountNonDistinct (Just cols) = PG.CTSimple cols
mkCountType _ Nothing = Postgres.CTStar
mkCountType IR.SelectCountDistinct (Just cols) = Postgres.CTDistinct cols
mkCountType IR.SelectCountNonDistinct (Just cols) = Postgres.CTSimple cols
-- | Update operator that prepends a value to a column containing jsonb arrays.
--

View File

@ -14,16 +14,16 @@ import Data.Aeson (FromJSON)
import Data.Aeson qualified as J
import Data.Kind (Type)
import Data.Typeable
import Hasura.Backends.Postgres.Connection qualified as PG
import Hasura.Backends.Postgres.SQL.DML qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Value qualified as PG
import Hasura.Backends.Postgres.Types.BoolExp qualified as PG
import Hasura.Backends.Postgres.Connection qualified as Postgres
import Hasura.Backends.Postgres.SQL.DML qualified as Postgres
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Backends.Postgres.SQL.Value qualified as Postgres
import Hasura.Backends.Postgres.Types.BoolExp qualified as Postgres
import Hasura.Backends.Postgres.Types.CitusExtraTableMetadata qualified as Citus
import Hasura.Backends.Postgres.Types.ComputedField qualified as PG
import Hasura.Backends.Postgres.Types.Function qualified as PG
import Hasura.Backends.Postgres.Types.Insert qualified as PG (BackendInsert)
import Hasura.Backends.Postgres.Types.Update qualified as PG
import Hasura.Backends.Postgres.Types.ComputedField qualified as Postgres
import Hasura.Backends.Postgres.Types.Function qualified as Postgres
import Hasura.Backends.Postgres.Types.Insert qualified as Postgres (BackendInsert)
import Hasura.Backends.Postgres.Types.Update qualified as Postgres
import Hasura.Base.Error
import Hasura.Metadata.DTO.Placeholder (placeholderCodecViaJSON)
import Hasura.Prelude
@ -76,34 +76,34 @@ instance
where
type BackendConfig ('Postgres pgKind) = ()
type BackendInfo ('Postgres pgKind) = ()
type SourceConfig ('Postgres pgKind) = PG.PGSourceConfig
type SourceConnConfiguration ('Postgres pgKind) = PG.PostgresConnConfiguration
type TableName ('Postgres pgKind) = PG.QualifiedTable
type FunctionName ('Postgres pgKind) = PG.QualifiedFunction
type FunctionArgument ('Postgres pgKind) = PG.FunctionArg
type RawFunctionInfo ('Postgres pgKind) = PG.PGRawFunctionInfo
type ConstraintName ('Postgres pgKind) = PG.ConstraintName
type BasicOrderType ('Postgres pgKind) = PG.OrderType
type NullsOrderType ('Postgres pgKind) = PG.NullsOrder
type CountType ('Postgres pgKind) = PG.CountType
type Column ('Postgres pgKind) = PG.PGCol
type ScalarValue ('Postgres pgKind) = PG.PGScalarValue
type ScalarType ('Postgres pgKind) = PG.PGScalarType
type BooleanOperators ('Postgres pgKind) = PG.BooleanOperators
type SQLExpression ('Postgres pgKind) = PG.SQLExp
type ComputedFieldDefinition ('Postgres pgKind) = PG.ComputedFieldDefinition
type ScalarSelectionArguments ('Postgres pgKind) = PG.ColumnOp
type SourceConfig ('Postgres pgKind) = Postgres.PGSourceConfig
type SourceConnConfiguration ('Postgres pgKind) = Postgres.PostgresConnConfiguration
type TableName ('Postgres pgKind) = Postgres.QualifiedTable
type FunctionName ('Postgres pgKind) = Postgres.QualifiedFunction
type FunctionArgument ('Postgres pgKind) = Postgres.FunctionArg
type RawFunctionInfo ('Postgres pgKind) = Postgres.PGRawFunctionInfo
type ConstraintName ('Postgres pgKind) = Postgres.ConstraintName
type BasicOrderType ('Postgres pgKind) = Postgres.OrderType
type NullsOrderType ('Postgres pgKind) = Postgres.NullsOrder
type CountType ('Postgres pgKind) = Postgres.CountType
type Column ('Postgres pgKind) = Postgres.PGCol
type ScalarValue ('Postgres pgKind) = Postgres.PGScalarValue
type ScalarType ('Postgres pgKind) = Postgres.PGScalarType
type BooleanOperators ('Postgres pgKind) = Postgres.BooleanOperators
type SQLExpression ('Postgres pgKind) = Postgres.SQLExp
type ComputedFieldDefinition ('Postgres pgKind) = Postgres.ComputedFieldDefinition
type ScalarSelectionArguments ('Postgres pgKind) = Postgres.ColumnOp
type FunctionArgumentExp ('Postgres pgKind) = PG.ArgumentExp
type ComputedFieldImplicitArguments ('Postgres pgKind) = PG.ComputedFieldImplicitArguments
type ComputedFieldReturn ('Postgres pgKind) = PG.ComputedFieldReturn
type FunctionArgumentExp ('Postgres pgKind) = Postgres.ArgumentExp
type ComputedFieldImplicitArguments ('Postgres pgKind) = Postgres.ComputedFieldImplicitArguments
type ComputedFieldReturn ('Postgres pgKind) = Postgres.ComputedFieldReturn
type BackendUpdate ('Postgres pgKind) = PG.BackendUpdate pgKind
type BackendUpdate ('Postgres pgKind) = Postgres.BackendUpdate pgKind
type AggregationPredicates ('Postgres pgKind) = Agg.AggregationPredicatesImplementation ('Postgres pgKind)
type ExtraTableMetadata ('Postgres pgKind) = PgExtraTableMetadata pgKind
type BackendInsert ('Postgres pgKind) = PG.BackendInsert pgKind
type BackendInsert ('Postgres pgKind) = Postgres.BackendInsert pgKind
type XComputedField ('Postgres pgKind) = XEnable
type XRelay ('Postgres pgKind) = XEnable
@ -119,22 +119,22 @@ instance
_hciTestCodec = placeholderCodecViaJSON
}
isComparableType = PG.isComparableType
isNumType = PG.isNumType
textToScalarValue = PG.textToScalarValue
parseScalarValue ty val = runAesonParser (PG.parsePGValue ty) val
scalarValueToJSON = PG.pgScalarValueToJson
functionToTable = fmap (PG.TableName . PG.getFunctionTxt)
tableToFunction = fmap (PG.FunctionName . PG.getTableTxt)
computedFieldFunction = PG._cfdFunction
isComparableType = Postgres.isComparableType
isNumType = Postgres.isNumType
textToScalarValue = Postgres.textToScalarValue
parseScalarValue ty val = runAesonParser (Postgres.parsePGValue ty) val
scalarValueToJSON = Postgres.pgScalarValueToJson
functionToTable = fmap (Postgres.TableName . Postgres.getFunctionTxt)
tableToFunction = fmap (Postgres.FunctionName . Postgres.getTableTxt)
computedFieldFunction = Postgres._cfdFunction
computedFieldReturnType = \case
PG.CFRScalar scalarType -> ReturnsScalar scalarType
PG.CFRSetofTable table -> ReturnsTable table
fromComputedFieldImplicitArguments = PG.fromComputedFieldImplicitArguments
Postgres.CFRScalar scalarType -> ReturnsScalar scalarType
Postgres.CFRSetofTable table -> ReturnsTable table
fromComputedFieldImplicitArguments = Postgres.fromComputedFieldImplicitArguments
tableGraphQLName = PG.qualifiedObjectToName
functionGraphQLName = PG.qualifiedObjectToName
tableGraphQLName = Postgres.qualifiedObjectToName
functionGraphQLName = Postgres.qualifiedObjectToName
snakeCaseTableName = PG.snakeCaseQualifiedObject
getTableIdentifier = PG.getIdentifierQualifiedObject
namingConventionSupport = PG.namingConventionSupport
snakeCaseTableName = Postgres.snakeCaseQualifiedObject
getTableIdentifier = Postgres.getIdentifierQualifiedObject
namingConventionSupport = Postgres.namingConventionSupport

View File

@ -18,9 +18,9 @@ import Data.Sequence qualified as Seq
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Data.Traversable (mapAccumL)
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.Types.ComputedField qualified as PG
import Hasura.Backends.Postgres.Types.Function qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Backends.Postgres.Types.ComputedField qualified as Postgres
import Hasura.Backends.Postgres.Types.Function qualified as Postgres
import Hasura.Base.Error
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
@ -212,7 +212,7 @@ computedFieldPG sourceInfo ComputedFieldInfo {..} parentTable tableInfo = runMay
fieldName <- lift $ textToName $ computedFieldNameToText _cfiName
functionArgsParser <- lift $ computedFieldFunctionArgs _cfiFunction
case _cfiReturnType of
PG.CFRScalar scalarReturnType -> do
Postgres.CFRScalar scalarReturnType -> do
caseBoolExpMaybe <-
hoistMaybe (Map.lookup _cfiName (spiComputedFields selectPermissions))
let caseBoolExpUnpreparedValue =
@ -236,7 +236,7 @@ computedFieldPG sourceInfo ComputedFieldInfo {..} parentTable tableInfo = runMay
)
dummyParser <- lift $ columnParser @('Postgres pgKind) (ColumnScalar scalarReturnType) (G.Nullability True)
pure $ P.selection fieldName fieldDescription fieldArgsParser dummyParser
PG.CFRSetofTable tableName -> do
Postgres.CFRSetofTable tableName -> do
otherTableInfo <- lift $ askTableInfo sourceInfo tableName
remotePerms <- hoistMaybe $ tableSelectPermissions roleName otherTableInfo
selectionSetParser <- MaybeT (fmap (P.multiple . P.nonNullableParser) <$> tableSelectionSet sourceInfo otherTableInfo)
@ -267,13 +267,13 @@ computedFieldPG sourceInfo ComputedFieldInfo {..} parentTable tableInfo = runMay
<&> fmap addTableAndSessionArgument
where
addTableAndSessionArgument args@(FunctionArgsExp positional named) =
let withTable = case PG._cffaTableArgument _cffComputedFieldImplicitArgs of
PG.FTAFirst -> FunctionArgsExp (PG.AETableRow : positional) named
PG.FTANamed argName index -> IR.insertFunctionArg argName index PG.AETableRow args
sessionArgVal = PG.AESession IR.UVSession
in case PG._cffaSessionArgument _cffComputedFieldImplicitArgs of
let withTable = case Postgres._cffaTableArgument _cffComputedFieldImplicitArgs of
Postgres.FTAFirst -> FunctionArgsExp (Postgres.AETableRow : positional) named
Postgres.FTANamed argName index -> IR.insertFunctionArg argName index Postgres.AETableRow args
sessionArgVal = Postgres.AESession IR.UVSession
in case Postgres._cffaSessionArgument _cffComputedFieldImplicitArgs of
Nothing -> withTable
Just (PG.FunctionSessionArgument argName index) ->
Just (Postgres.FunctionSessionArgument argName index) ->
IR.insertFunctionArg argName index sessionArgVal withTable
-- | The custom SQL functions' input "args" field parser
@ -381,33 +381,33 @@ functionArgs sourceInfo functionTrackedAs (toList -> inputArgs) = do
pure $ P.field fieldName (Just fieldDesc) objectParser
where
sessionPlaceholder :: PG.ArgumentExp (IR.UnpreparedValue b)
sessionPlaceholder = PG.AEInput IR.UVSession
sessionPlaceholder :: Postgres.ArgumentExp (IR.UnpreparedValue b)
sessionPlaceholder = Postgres.AEInput IR.UVSession
splitArguments ::
Int ->
FunctionInputArgument ('Postgres pgKind) ->
( Int,
( [Text], -- graphql names, in order
[(Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))], -- session argument
[SchemaT r m (InputFieldsParser n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))], -- optional argument
[SchemaT r m (InputFieldsParser n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))] -- mandatory argument
[(Text, Postgres.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))], -- session argument
[SchemaT r m (InputFieldsParser n (Maybe (Text, Postgres.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))], -- optional argument
[SchemaT r m (InputFieldsParser n (Maybe (Text, Postgres.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))] -- mandatory argument
)
)
splitArguments positionalIndex (IASessionVariables name) =
let argName = getFuncArgNameTxt name
in (positionalIndex, ([argName], [(argName, sessionPlaceholder)], [], []))
splitArguments positionalIndex (IAUserProvided arg) =
let (argName, newIndex) = case PG.faName arg of
let (argName, newIndex) = case Postgres.faName arg of
Nothing -> ("arg_" <> tshow positionalIndex, positionalIndex + 1)
Just name -> (getFuncArgNameTxt name, positionalIndex)
in if PG.unHasDefault $ PG.faHasDefault arg
in if Postgres.unHasDefault $ Postgres.faHasDefault arg
then (newIndex, ([argName], [], [parseArgument arg argName], []))
else (newIndex, ([argName], [], [], [parseArgument arg argName]))
parseArgument :: FunctionArgument ('Postgres pgKind) -> Text -> SchemaT r m (InputFieldsParser n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))
parseArgument :: FunctionArgument ('Postgres pgKind) -> Text -> SchemaT r m (InputFieldsParser n (Maybe (Text, Postgres.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))
parseArgument arg name = do
typedParser <- columnParser (ColumnScalar $ PG.mkFunctionArgScalarType $ PG.faType arg) (G.Nullability True)
typedParser <- columnParser (ColumnScalar $ Postgres.mkFunctionArgScalarType $ Postgres.faType arg) (G.Nullability True)
fieldName <- textToName name
-- Since all postgres function arguments are nullable, we define the
@ -422,20 +422,20 @@ functionArgs sourceInfo functionTrackedAs (toList -> inputArgs) = do
-- explicit value of `null` is used, as long as we don't set a default
-- value, not even `null`.
let argParser = P.fieldOptional fieldName Nothing typedParser
pure $ argParser `mapField` ((name,) . PG.AEInput . IR.mkParameter)
pure $ argParser `mapField` ((name,) . Postgres.AEInput . IR.mkParameter)
namedArgument ::
HashMap Text (PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind))) ->
HashMap Text (Postgres.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind))) ->
(Text, FunctionInputArgument ('Postgres pgKind)) ->
n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind))))
n (Maybe (Text, Postgres.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind))))
namedArgument dictionary (name, inputArgument) = case inputArgument of
IASessionVariables _ -> pure $ Just (name, sessionPlaceholder)
IAUserProvided arg -> case Map.lookup name dictionary of
Just parsedValue -> case PG.faName arg of
Just parsedValue -> case Postgres.faName arg of
Just _ -> pure $ Just (name, parsedValue)
Nothing -> P.parseErrorWith P.NotSupported "Only last set of positional arguments can be omitted"
Nothing ->
whenMaybe (not $ PG.unHasDefault $ PG.faHasDefault arg) $
whenMaybe (not $ Postgres.unHasDefault $ Postgres.faHasDefault arg) $
P.parseErrorWith P.NotSupported "Non default arguments cannot be omitted"
buildFunctionQueryFieldsPG ::

View File

@ -30,19 +30,19 @@ where
import Data.HashMap.Strict qualified as HM
import Data.Int (Int64)
import Hasura.Backends.Postgres.SQL.DML qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.DML qualified as Postgres
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Prelude
import Hasura.RQL.IR.Select
import Hasura.RQL.Types.Common
data SourcePrefixes = SourcePrefixes
{ -- | Current source prefix
_pfThis :: PG.Identifier,
_pfThis :: Postgres.Identifier,
-- | Base table source row identifier to generate
-- the table's column identifiers for computed field
-- function input parameters
_pfBase :: PG.Identifier
_pfBase :: Postgres.Identifier
}
deriving (Show, Eq, Generic)
@ -58,8 +58,8 @@ data SelectSlicing = SelectSlicing
instance Hashable SelectSlicing
data DistinctAndOrderByExpr = ASorting
{ _sortAtNode :: (PG.OrderByExp, Maybe PG.DistinctExpr),
_sortAtBase :: Maybe (PG.OrderByExp, Maybe PG.DistinctExpr)
{ _sortAtNode :: (Postgres.OrderByExp, Maybe Postgres.DistinctExpr),
_sortAtBase :: Maybe (Postgres.OrderByExp, Maybe Postgres.DistinctExpr)
}
deriving (Show, Eq, Generic)
@ -67,7 +67,7 @@ instance Hashable DistinctAndOrderByExpr
-- | Sorting with -- Note [Optimizing queries using limit/offset])
data SelectSorting
= NoSorting (Maybe PG.DistinctExpr)
= NoSorting (Maybe Postgres.DistinctExpr)
| Sorting DistinctAndOrderByExpr
deriving (Show, Eq, Generic)
@ -82,9 +82,9 @@ data SortingAndSlicing = SortingAndSlicing
instance Hashable SortingAndSlicing
data SelectSource = SelectSource
{ _ssPrefix :: PG.Identifier,
_ssFrom :: PG.FromItem,
_ssWhere :: PG.BoolExp,
{ _ssPrefix :: Postgres.Identifier,
_ssFrom :: Postgres.FromItem,
_ssWhere :: Postgres.BoolExp,
_ssSortingAndSlicing :: SortingAndSlicing
}
deriving (Generic)
@ -102,15 +102,15 @@ noSortingAndSlicing =
noSlicing :: SelectSlicing
noSlicing = SelectSlicing Nothing Nothing
orderByForJsonAgg :: SelectSource -> Maybe PG.OrderByExp
orderByForJsonAgg :: SelectSource -> Maybe Postgres.OrderByExp
orderByForJsonAgg SelectSource {..} =
case _sasSorting _ssSortingAndSlicing of
NoSorting {} -> Nothing
Sorting ASorting {..} -> Just $ fst _sortAtNode
data ApplySortingAndSlicing = ApplySortingAndSlicing
{ _applyAtBase :: (Maybe PG.OrderByExp, SelectSlicing, Maybe PG.DistinctExpr),
_applyAtNode :: (Maybe PG.OrderByExp, SelectSlicing, Maybe PG.DistinctExpr)
{ _applyAtBase :: (Maybe Postgres.OrderByExp, SelectSlicing, Maybe Postgres.DistinctExpr),
_applyAtNode :: (Maybe Postgres.OrderByExp, SelectSlicing, Maybe Postgres.DistinctExpr)
}
applySortingAndSlicing :: SortingAndSlicing -> ApplySortingAndSlicing
@ -130,7 +130,7 @@ applySortingAndSlicing SortingAndSlicing {..} =
ApplySortingAndSlicing (Nothing, noSlicing, Nothing) (Just nodeOrderBy, _sasSlicing, nodeDistinctOn)
data SelectNode = SelectNode
{ _snExtractors :: HM.HashMap PG.ColumnAlias PG.SQLExp,
{ _snExtractors :: HM.HashMap Postgres.ColumnAlias Postgres.SQLExp,
_snJoinTree :: JoinTree
}
deriving stock (Eq)
@ -140,9 +140,9 @@ instance Semigroup SelectNode where
SelectNode (lExtrs <> rExtrs) (lJoinTree <> rJoinTree)
data ObjectSelectSource = ObjectSelectSource
{ _ossPrefix :: PG.Identifier,
_ossFrom :: PG.FromItem,
_ossWhere :: PG.BoolExp
{ _ossPrefix :: Postgres.Identifier,
_ossFrom :: Postgres.FromItem,
_ossWhere :: Postgres.BoolExp
}
deriving (Show, Eq, Generic)
@ -165,7 +165,7 @@ objectSelectSourceToSelectSource ObjectSelectSource {..} =
data ObjectRelationSource = ObjectRelationSource
{ _orsRelationshipName :: RelName,
_orsRelationMapping :: HM.HashMap PG.PGCol PG.PGCol,
_orsRelationMapping :: HM.HashMap Postgres.PGCol Postgres.PGCol,
_orsSelectSource :: ObjectSelectSource
}
deriving (Generic)
@ -175,8 +175,8 @@ instance Hashable ObjectRelationSource
deriving instance Eq ObjectRelationSource
data ArrayRelationSource = ArrayRelationSource
{ _arsAlias :: PG.TableAlias,
_arsRelationMapping :: HM.HashMap PG.PGCol PG.PGCol,
{ _arsAlias :: Postgres.TableAlias,
_arsRelationMapping :: HM.HashMap Postgres.PGCol Postgres.PGCol,
_arsSelectSource :: SelectSource
}
deriving (Generic)
@ -186,7 +186,7 @@ instance Hashable ArrayRelationSource
deriving instance Eq ArrayRelationSource
data MultiRowSelectNode = MultiRowSelectNode
{ _mrsnTopExtractors :: [PG.Extractor],
{ _mrsnTopExtractors :: [Postgres.Extractor],
_mrsnSelectNode :: SelectNode
}
deriving stock (Eq)
@ -208,9 +208,9 @@ deriving instance Show ComputedFieldTableSetSource
deriving instance Eq ComputedFieldTableSetSource
data ArrayConnectionSource = ArrayConnectionSource
{ _acsAlias :: PG.TableAlias,
_acsRelationMapping :: HM.HashMap PG.PGCol PG.PGCol,
_acsSplitFilter :: Maybe PG.BoolExp,
{ _acsAlias :: Postgres.TableAlias,
_acsRelationMapping :: HM.HashMap Postgres.PGCol Postgres.PGCol,
_acsSplitFilter :: Maybe Postgres.BoolExp,
_acsSlice :: Maybe ConnectionSlice,
_acsSource :: SelectSource
}

View File

@ -55,7 +55,7 @@ import Data.HashMap.Strict.InsOrd qualified as OMap
import Data.Text qualified as T
import Data.Text.Casing (GQLNameIdentifier)
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Base.Error
import Hasura.GraphQL.Namespace (NamespacedField)
import Hasura.GraphQL.Parser.Internal.TypeChecking qualified as P
@ -355,10 +355,10 @@ numericAggOperators =
comparisonAggOperators :: [G.Name]
comparisonAggOperators = [$$(G.litName "max"), $$(G.litName "min")]
mkDescriptionWith :: Maybe PG.PGDescription -> Text -> G.Description
mkDescriptionWith :: Maybe Postgres.PGDescription -> Text -> G.Description
mkDescriptionWith descM defaultTxt = G.Description $ case descM of
Nothing -> defaultTxt
Just (PG.PGDescription descTxt) -> T.unlines [descTxt, "\n", defaultTxt]
Just (Postgres.PGDescription descTxt) -> T.unlines [descTxt, "\n", defaultTxt]
-- TODO why do we do these validations at this point? What does it mean to track
-- a function but not add it to the schema...?

View File

@ -24,7 +24,7 @@ import Data.Aeson.Types qualified as J
import Data.HashMap.Strict qualified as Map
import Data.Sequence qualified as Seq
import Data.Sequence.NonEmpty qualified as NESeq
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Prelude
import Hasura.RQL.IR qualified as IR
import Hasura.RQL.Types.Backend
@ -117,7 +117,7 @@ data NodeId
-- This id does NOT uniquely identify the table properly, as it only knows the
-- table's name, but doesn't store a source name.
data V1NodeId = V1NodeId
{ _ni1Table :: PG.QualifiedTable,
{ _ni1Table :: Postgres.QualifiedTable,
_ni1Columns :: NESeq.NESeq J.Value
}
@ -141,7 +141,7 @@ instance J.FromJSON NodeId where
parseNodeIdV1 :: [J.Value] -> J.Parser V1NodeId
parseNodeIdV1 (schemaValue : nameValue : firstColumn : remainingColumns) =
V1NodeId
<$> (PG.QualifiedObject <$> J.parseJSON schemaValue <*> J.parseJSON nameValue)
<$> (Postgres.QualifiedObject <$> J.parseJSON schemaValue <*> J.parseJSON nameValue)
<*> pure (firstColumn NESeq.:<|| Seq.fromList remainingColumns)
parseNodeIdV1 _ = fail "GUID version 1: expecting schema name, table name and at least one column value"

View File

@ -38,7 +38,7 @@ import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Text.Casing (GQLNameIdentifier)
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (toErrorMessage)
import Hasura.GraphQL.Parser.Class
@ -410,7 +410,7 @@ defaultTableSelectionSet sourceInfo tableInfo = runMaybeT do
if isApolloFedV1enabled (_tciApolloFederationConfig tableCoreInfo) && (not . null) pkFields
then [(G.Directive Name._key . Map.singleton Name._fields . G.VString) pkFieldDirective]
else mempty
description = G.Description . PG.getPGDescription <$> _tciDescription tableCoreInfo
description = G.Description . Postgres.getPGDescription <$> _tciDescription tableCoreInfo
fieldParsers <-
concat
<$> for

View File

@ -30,7 +30,7 @@ import Data.Aeson.TH
import Data.Attoparsec.Text qualified as AT
import Data.HashMap.Strict qualified as M
import Hasura.Backends.Postgres.Instances.Types ()
import Hasura.Backends.Postgres.SQL.DML qualified as PG
import Hasura.Backends.Postgres.SQL.DML qualified as Postgres
import Hasura.Backends.Postgres.SQL.Types
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
@ -68,8 +68,8 @@ instance FromJSON OrderByExp where
<*> pure Nothing
orderTypeParser =
choice
[ "+" *> pure (Just PG.OTAsc),
"-" *> pure (Just PG.OTDesc),
[ "+" *> pure (Just Postgres.OTAsc),
"-" *> pure (Just Postgres.OTDesc),
pure Nothing
]
orderColumnParser = AT.takeText >>= orderByColFromTxt

View File

@ -152,7 +152,7 @@ import Data.Int (Int64)
import Data.Kind (Type)
import Data.List.NonEmpty qualified as NE
import Data.Sequence qualified as Seq
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.GraphQL.Schema.NamingCase (NamingCase)
import Hasura.GraphQL.Schema.Options (StringifyNumbers)
import Hasura.Prelude
@ -369,7 +369,7 @@ newtype FIIdentifier = FIIdentifier
deriving newtype (Eq, Show)
deriving anyclass (Hashable)
instance PG.IsIdentifier FIIdentifier where
instance Postgres.IsIdentifier FIIdentifier where
toIdentifier = coerce
{-# INLINE toIdentifier #-}

View File

@ -54,7 +54,7 @@ import Data.HashSet qualified as Set
import Data.Text qualified as T
import Data.Text.Extended (ToTxt (..))
import Hasura.Backends.Postgres.Instances.Types ()
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.GraphQL.Parser.Name qualified as GName
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
@ -248,8 +248,8 @@ data TypeRelationshipDefinition = TypeRelationshipDefinition
-- are performed, then we can replace this PG-specific code with the new and
-- fancy generalized remote relationship code.
_trdSource :: SourceName,
_trdRemoteTable :: PG.QualifiedTable,
_trdFieldMapping :: HashMap ObjectFieldName PG.PGCol
_trdRemoteTable :: Postgres.QualifiedTable,
_trdFieldMapping :: HashMap ObjectFieldName Postgres.PGCol
}
deriving (Show, Eq, Generic)

View File

@ -8,7 +8,7 @@ import Data.Aeson
import Data.Set.NonEmpty qualified as NE
import Data.Time.Clock qualified as Time
import Hasura.Backends.MSSQL.DDL.EventTrigger qualified as MSSQL
import Hasura.Backends.Postgres.DDL.EventTrigger qualified as PG
import Hasura.Backends.Postgres.DDL.EventTrigger qualified as Postgres
import Hasura.Base.Error
import Hasura.Prelude
import Hasura.RQL.Types.Backend
@ -294,27 +294,27 @@ class Backend b => BackendEventTrigger (b :: BackendType) where
-- depending / importing backend-specific files.
instance BackendEventTrigger ('Postgres 'Vanilla) where
insertManualEvent = PG.insertManualEvent
fetchUndeliveredEvents = PG.fetchUndeliveredEvents
setRetry = PG.setRetry
getMaintenanceModeVersion = PG.getMaintenanceModeVersion
recordSuccess = PG.recordSuccess
recordError = PG.recordError
recordError' = PG.recordError'
dropTriggerAndArchiveEvents = PG.dropTriggerAndArchiveEvents
dropDanglingSQLTrigger = PG.dropDanglingSQLTrigger
redeliverEvent = PG.redeliverEvent
unlockEventsInSource = PG.unlockEventsInSource
createTableEventTrigger = PG.createTableEventTrigger
createMissingSQLTriggers = PG.createMissingSQLTriggers
checkIfTriggerExists = PG.checkIfTriggerExists
addCleanupSchedules = PG.addCleanupSchedules
deleteAllScheduledCleanups = PG.deleteAllScheduledCleanups
getCleanupEventsForDeletion = PG.getCleanupEventsForDeletion
updateCleanupEventStatusToDead = PG.updateCleanupEventStatusToDead
updateCleanupEventStatusToPaused = PG.updateCleanupEventStatusToPaused
updateCleanupEventStatusToCompleted = PG.updateCleanupEventStatusToCompleted
deleteEventTriggerLogs = PG.deleteEventTriggerLogs
insertManualEvent = Postgres.insertManualEvent
fetchUndeliveredEvents = Postgres.fetchUndeliveredEvents
setRetry = Postgres.setRetry
getMaintenanceModeVersion = Postgres.getMaintenanceModeVersion
recordSuccess = Postgres.recordSuccess
recordError = Postgres.recordError
recordError' = Postgres.recordError'
dropTriggerAndArchiveEvents = Postgres.dropTriggerAndArchiveEvents
dropDanglingSQLTrigger = Postgres.dropDanglingSQLTrigger
redeliverEvent = Postgres.redeliverEvent
unlockEventsInSource = Postgres.unlockEventsInSource
createTableEventTrigger = Postgres.createTableEventTrigger
createMissingSQLTriggers = Postgres.createMissingSQLTriggers
checkIfTriggerExists = Postgres.checkIfTriggerExists
addCleanupSchedules = Postgres.addCleanupSchedules
deleteAllScheduledCleanups = Postgres.deleteAllScheduledCleanups
getCleanupEventsForDeletion = Postgres.getCleanupEventsForDeletion
updateCleanupEventStatusToDead = Postgres.updateCleanupEventStatusToDead
updateCleanupEventStatusToPaused = Postgres.updateCleanupEventStatusToPaused
updateCleanupEventStatusToCompleted = Postgres.updateCleanupEventStatusToCompleted
deleteEventTriggerLogs = Postgres.deleteEventTriggerLogs
instance BackendEventTrigger ('Postgres 'Citus) where
insertManualEvent _ _ _ _ _ _ = throw400 NotSupported $ "Event triggers are not supported for Citus sources"
@ -340,27 +340,27 @@ instance BackendEventTrigger ('Postgres 'Citus) where
deleteEventTriggerLogs _ _ = throw400 NotSupported $ "Event triggers are not supported for Citus sources"
instance BackendEventTrigger ('Postgres 'Cockroach) where
insertManualEvent = PG.insertManualEvent
fetchUndeliveredEvents = PG.fetchUndeliveredEvents
setRetry = PG.setRetry
getMaintenanceModeVersion = PG.getMaintenanceModeVersion
recordSuccess = PG.recordSuccess
recordError = PG.recordError
recordError' = PG.recordError'
dropTriggerAndArchiveEvents = PG.dropTriggerAndArchiveEvents
dropDanglingSQLTrigger = PG.dropDanglingSQLTrigger
redeliverEvent = PG.redeliverEvent
unlockEventsInSource = PG.unlockEventsInSource
createTableEventTrigger = PG.createTableEventTrigger
createMissingSQLTriggers = PG.createMissingSQLTriggers
checkIfTriggerExists = PG.checkIfTriggerExists
addCleanupSchedules = PG.addCleanupSchedules
deleteAllScheduledCleanups = PG.deleteAllScheduledCleanups
getCleanupEventsForDeletion = PG.getCleanupEventsForDeletion
updateCleanupEventStatusToDead = PG.updateCleanupEventStatusToDead
updateCleanupEventStatusToPaused = PG.updateCleanupEventStatusToPaused
updateCleanupEventStatusToCompleted = PG.updateCleanupEventStatusToCompleted
deleteEventTriggerLogs = PG.deleteEventTriggerLogs
insertManualEvent = Postgres.insertManualEvent
fetchUndeliveredEvents = Postgres.fetchUndeliveredEvents
setRetry = Postgres.setRetry
getMaintenanceModeVersion = Postgres.getMaintenanceModeVersion
recordSuccess = Postgres.recordSuccess
recordError = Postgres.recordError
recordError' = Postgres.recordError'
dropTriggerAndArchiveEvents = Postgres.dropTriggerAndArchiveEvents
dropDanglingSQLTrigger = Postgres.dropDanglingSQLTrigger
redeliverEvent = Postgres.redeliverEvent
unlockEventsInSource = Postgres.unlockEventsInSource
createTableEventTrigger = Postgres.createTableEventTrigger
createMissingSQLTriggers = Postgres.createMissingSQLTriggers
checkIfTriggerExists = Postgres.checkIfTriggerExists
addCleanupSchedules = Postgres.addCleanupSchedules
deleteAllScheduledCleanups = Postgres.deleteAllScheduledCleanups
getCleanupEventsForDeletion = Postgres.getCleanupEventsForDeletion
updateCleanupEventStatusToDead = Postgres.updateCleanupEventStatusToDead
updateCleanupEventStatusToPaused = Postgres.updateCleanupEventStatusToPaused
updateCleanupEventStatusToCompleted = Postgres.updateCleanupEventStatusToCompleted
deleteEventTriggerLogs = Postgres.deleteEventTriggerLogs
instance BackendEventTrigger 'MSSQL where
insertManualEvent = MSSQL.insertManualEvent

View File

@ -129,7 +129,7 @@ import Data.Int (Int64)
import Data.Text.Extended
import Database.MSSQL.Transaction qualified as MSSQL
import Database.PG.Query qualified as PG
import Hasura.Backends.Postgres.Connection qualified as PG
import Hasura.Backends.Postgres.Connection qualified as Postgres
import Hasura.Base.Error
import Hasura.GraphQL.Context (GQLContext, RoleContext)
import Hasura.GraphQL.Schema.Options qualified as Options
@ -574,7 +574,7 @@ instance (SourceM m) => SourceM (TraceT m) where
newtype SourceT m a = SourceT {runSourceT :: SourceName -> m a}
deriving
(Functor, Applicative, Monad, MonadIO, MonadError e, MonadState s, MonadWriter w, PG.MonadTx, TableCoreInfoRM b, CacheRM)
(Functor, Applicative, Monad, MonadIO, MonadError e, MonadState s, MonadWriter w, Postgres.MonadTx, TableCoreInfoRM b, CacheRM)
via (ReaderT SourceName m)
deriving (MonadTrans) via (ReaderT SourceName)
@ -600,7 +600,7 @@ instance (TableCoreInfoRM b m) => TableCoreInfoRM b (TraceT m) where
newtype TableCoreCacheRT b m a = TableCoreCacheRT {runTableCoreCacheRT :: (SourceName, Dependency (TableCoreCache b)) -> m a}
deriving
(Functor, Applicative, Monad, MonadIO, MonadError e, MonadState s, MonadWriter w, PG.MonadTx)
(Functor, Applicative, Monad, MonadIO, MonadError e, MonadState s, MonadWriter w, Postgres.MonadTx)
via (ReaderT (SourceName, Dependency (TableCoreCache b)) m)
deriving (MonadTrans) via (ReaderT (SourceName, Dependency (TableCoreCache b)))
@ -634,7 +634,7 @@ instance (TableInfoRM b m) => TableInfoRM b (TraceT m) where
newtype TableCacheRT b m a = TableCacheRT {runTableCacheRT :: (SourceName, TableCache b) -> m a}
deriving
(Functor, Applicative, Monad, MonadIO, MonadError e, MonadState s, MonadWriter w, PG.MonadTx)
(Functor, Applicative, Monad, MonadIO, MonadError e, MonadState s, MonadWriter w, Postgres.MonadTx)
via (ReaderT (SourceName, TableCache b) m)
deriving (MonadTrans) via (ReaderT (SourceName, TableCache b))

View File

@ -104,7 +104,7 @@ import Data.List.NonEmpty qualified as NE
import Data.Semigroup (Any (..), Max (..))
import Data.Text qualified as T
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as PG (PGDescription)
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres (PGDescription)
import Hasura.Base.Error
import Hasura.Incremental (Cacheable)
import Hasura.Name qualified as Name
@ -864,7 +864,7 @@ instance Backend b => FromJSON (ForeignKey b) where
-- information is accumulated. See also 'TableCoreInfo'.
data TableCoreInfoG (b :: BackendType) field primaryKeyColumn = TableCoreInfo
{ _tciName :: TableName b,
_tciDescription :: Maybe PG.PGDescription, -- TODO make into type family?
_tciDescription :: Maybe Postgres.PGDescription, -- TODO make into type family?
_tciFieldInfoMap :: FieldInfoMap field,
_tciPrimaryKey :: Maybe (PrimaryKey b primaryKeyColumn),
-- | Does /not/ include the primary key; use 'tciUniqueOrPrimaryKeyConstraints' if you need both.
@ -992,7 +992,7 @@ data DBTableMetadata (b :: BackendType) = DBTableMetadata
_ptmiUniqueConstraints :: HashSet (UniqueConstraint b),
_ptmiForeignKeys :: HashSet (ForeignKeyMetadata b),
_ptmiViewInfo :: Maybe ViewInfo,
_ptmiDescription :: Maybe PG.PGDescription,
_ptmiDescription :: Maybe Postgres.PGDescription,
_ptmiExtraTableMetadata :: ExtraTableMetadata b
}
deriving (Generic)

View File

@ -17,8 +17,8 @@ import Data.Int (Int)
import Data.Text (Text)
import Data.Text qualified as T
import Hasura.Backends.Postgres.Instances.Types ()
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.SQL.Types qualified as PGTypes
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Backends.Postgres.Types.BoolExp qualified as B
import Hasura.Backends.Postgres.Types.Function qualified as PGTypes
import Hasura.Generator.Common (defaultRange, genArbitraryUnicodeText)
@ -34,7 +34,7 @@ import Hedgehog.Range qualified as Range
-- Exported
genColumn :: MonadGen m => m (Column ('Postgres 'Vanilla))
genColumn = PG.unsafePGCol <$> genArbitraryUnicodeText defaultRange
genColumn = Postgres.unsafePGCol <$> genArbitraryUnicodeText defaultRange
-- | Generator for a qualified Postgres 'TableName'
genTableName :: MonadGen m => m (TableName ('Postgres 'Vanilla))
@ -43,40 +43,40 @@ genTableName = genQualifiedTable
genScalarType :: MonadGen m => m (ScalarType ('Postgres 'Vanilla))
genScalarType =
Gen.choice
[ pure PG.PGSmallInt,
pure PG.PGInteger,
pure PG.PGBigInt,
pure PG.PGSerial,
pure PG.PGBigSerial,
pure PG.PGFloat,
pure PG.PGDouble,
pure PG.PGNumeric,
pure PG.PGMoney,
pure PG.PGBoolean,
pure PG.PGChar,
pure PG.PGVarchar,
pure PG.PGText,
pure PG.PGCitext,
pure PG.PGDate,
pure PG.PGTimeStamp,
pure PG.PGTimeStampTZ,
pure PG.PGTimeTZ,
pure PG.PGJSON,
pure PG.PGJSONB,
pure PG.PGGeometry,
pure PG.PGGeography,
pure PG.PGRaster,
pure PG.PGUUID,
pure PG.PGLtree,
pure PG.PGLquery,
pure PG.PGLtxtquery,
PG.PGUnknown <$> genArbitraryUnicodeText defaultRange,
PG.PGCompositeScalar <$> genArbitraryUnicodeText defaultRange
[ pure Postgres.PGSmallInt,
pure Postgres.PGInteger,
pure Postgres.PGBigInt,
pure Postgres.PGSerial,
pure Postgres.PGBigSerial,
pure Postgres.PGFloat,
pure Postgres.PGDouble,
pure Postgres.PGNumeric,
pure Postgres.PGMoney,
pure Postgres.PGBoolean,
pure Postgres.PGChar,
pure Postgres.PGVarchar,
pure Postgres.PGText,
pure Postgres.PGCitext,
pure Postgres.PGDate,
pure Postgres.PGTimeStamp,
pure Postgres.PGTimeStampTZ,
pure Postgres.PGTimeTZ,
pure Postgres.PGJSON,
pure Postgres.PGJSONB,
pure Postgres.PGGeometry,
pure Postgres.PGGeography,
pure Postgres.PGRaster,
pure Postgres.PGUUID,
pure Postgres.PGLtree,
pure Postgres.PGLquery,
pure Postgres.PGLtxtquery,
Postgres.PGUnknown <$> genArbitraryUnicodeText defaultRange,
Postgres.PGCompositeScalar <$> genArbitraryUnicodeText defaultRange
]
genFunctionName :: MonadGen m => m (FunctionName ('Postgres 'Vanilla))
genFunctionName =
PG.QualifiedObject <$> genSchemaName defaultRange <*> genPgFunctionName defaultRange
Postgres.QualifiedObject <$> genSchemaName defaultRange <*> genPgFunctionName defaultRange
genXComputedField :: MonadGen m => m (XComputedField ('Postgres 'Vanilla))
genXComputedField = pure ()
@ -177,12 +177,12 @@ genIdentifier = do
-- Construct the arbitrarily generated identifier
pure $ T.cons begin rest
genSchemaName :: MonadGen m => Range Int -> m PG.SchemaName
genSchemaName :: MonadGen m => Range Int -> m Postgres.SchemaName
genSchemaName textRange =
Gen.choice [pure PG.publicSchema, PG.SchemaName <$> genArbitraryUnicodeText textRange]
Gen.choice [pure Postgres.publicSchema, Postgres.SchemaName <$> genArbitraryUnicodeText textRange]
genPgFunctionName :: MonadGen m => Range Int -> m PG.FunctionName
genPgFunctionName textRange = PG.FunctionName <$> genArbitraryUnicodeText textRange
genPgFunctionName :: MonadGen m => Range Int -> m Postgres.FunctionName
genPgFunctionName textRange = Postgres.FunctionName <$> genArbitraryUnicodeText textRange
genDWithinGeomOp :: MonadGen m => m a -> m (DWithinGeomOp a)
genDWithinGeomOp genA = DWithinGeomOp <$> genA <*> genA