2023-01-17 03:33:56 +03:00
module Hasura.Backends.DataConnector.Plan.QueryPlan
2023-03-07 04:31:50 +03:00
( -- Main external interface
mkQueryPlan ,
-- Internals reused by other plan modules
translateAnnSimpleSelectToQueryRequest ,
translateAnnAggregateSelectToQueryRequest ,
2023-01-17 03:33:56 +03:00
translateAnnFields ,
2023-03-07 04:31:50 +03:00
reshapeSimpleSelectRows ,
reshapeTableAggregateFields ,
2023-01-17 03:33:56 +03:00
reshapeAnnFields ,
)
where
--------------------------------------------------------------------------------
import Control.Monad.Trans.Writer.CPS qualified as CPS
import Data.Aeson qualified as J
import Data.Aeson.Encoding qualified as JE
import Data.Bifunctor ( Bifunctor ( bimap ) )
import Data.Has ( Has )
import Data.HashMap.Strict qualified as HashMap
import Data.List.NonEmpty qualified as NE
import Data.Semigroup ( Min ( .. ) )
2023-05-09 19:49:23 +03:00
import Data.Set qualified as Set
2023-05-19 07:47:12 +03:00
import Data.Text.Extended ( toTxt )
2023-01-17 03:33:56 +03:00
import Hasura.Backends.DataConnector.API qualified as API
import Hasura.Backends.DataConnector.Adapter.Backend
import Hasura.Backends.DataConnector.Adapter.Types
import Hasura.Backends.DataConnector.Plan.Common
import Hasura.Base.Error
2023-05-19 07:47:12 +03:00
import Hasura.Function.Cache qualified as Function
2023-01-17 03:33:56 +03:00
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.OrderBy
import Hasura.RQL.IR.Select
import Hasura.RQL.IR.Value
2023-04-24 21:35:48 +03:00
import Hasura.RQL.Types.BackendType
2023-01-17 03:33:56 +03:00
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.Session
import Language.GraphQL.Draft.Syntax qualified as G
import Witch qualified
--------------------------------------------------------------------------------
data FieldsAndAggregates = FieldsAndAggregates
2023-03-15 08:15:11 +03:00
{ _faaFields :: Maybe ( HashMap FieldName API . Field ) ,
_faaAggregates :: Maybe ( HashMap FieldName API . Aggregate )
2023-01-17 03:33:56 +03:00
}
deriving stock ( Show , Eq )
instance Semigroup FieldsAndAggregates where
left <> right =
FieldsAndAggregates
( _faaFields left <> _faaFields right )
( _faaAggregates left <> _faaAggregates right )
instance Monoid FieldsAndAggregates where
2023-03-15 08:15:11 +03:00
mempty = FieldsAndAggregates Nothing Nothing
2023-01-17 03:33:56 +03:00
--------------------------------------------------------------------------------
-- | Map a 'QueryDB 'DataConnector' term into a 'Plan'
mkQueryPlan ::
2023-06-21 09:48:46 +03:00
forall m r .
( MonadError QErr m , MonadReader r m , Has API . ScalarTypesCapabilities r ) =>
2023-01-17 03:33:56 +03:00
SessionVariables ->
QueryDB 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
m ( Plan API . QueryRequest API . QueryResponse )
2023-06-21 09:48:46 +03:00
mkQueryPlan sessionVariables ir = do
2023-01-17 03:33:56 +03:00
queryRequest <- translateQueryDB ir
pure $ Plan queryRequest ( reshapeResponseToQueryShape ir )
where
translateQueryDB ::
QueryDB 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
m API . QueryRequest
translateQueryDB =
\ case
2023-03-07 04:31:50 +03:00
QDBMultipleRows simpleSelect -> translateAnnSimpleSelectToQueryRequest sessionVariables simpleSelect
QDBSingleRow simpleSelect -> translateAnnSimpleSelectToQueryRequest sessionVariables simpleSelect
QDBAggregation aggregateSelect -> translateAnnAggregateSelectToQueryRequest sessionVariables aggregateSelect
2023-01-17 03:33:56 +03:00
2023-03-07 04:31:50 +03:00
translateAnnSimpleSelectToQueryRequest ::
2023-06-21 09:48:46 +03:00
forall m r .
( MonadError QErr m , MonadReader r m , Has API . ScalarTypesCapabilities r ) =>
2023-03-07 04:31:50 +03:00
SessionVariables ->
AnnSimpleSelectG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
m API . QueryRequest
translateAnnSimpleSelectToQueryRequest sessionVariables simpleSelect =
translateAnnSelectToQueryRequest sessionVariables ( translateAnnFieldsWithNoAggregates sessionVariables noPrefix ) simpleSelect
translateAnnAggregateSelectToQueryRequest ::
2023-06-21 09:48:46 +03:00
forall m r .
( MonadError QErr m , MonadReader r m , Has API . ScalarTypesCapabilities r ) =>
2023-03-07 04:31:50 +03:00
SessionVariables ->
AnnAggregateSelectG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
m API . QueryRequest
translateAnnAggregateSelectToQueryRequest sessionVariables aggregateSelect =
translateAnnSelectToQueryRequest sessionVariables ( translateTableAggregateFields sessionVariables ) aggregateSelect
translateAnnSelectToQueryRequest ::
2023-06-21 09:48:46 +03:00
forall m r fieldType .
( MonadError QErr m , MonadReader r m , Has API . ScalarTypesCapabilities r ) =>
2023-03-07 04:31:50 +03:00
SessionVariables ->
2023-05-19 07:47:12 +03:00
( TableRelationshipsKey -> Fields ( fieldType ( UnpreparedValue 'DataConnector ) ) -> CPS . WriterT TableRelationships m FieldsAndAggregates ) ->
2023-03-07 04:31:50 +03:00
AnnSelectG 'DataConnector fieldType ( UnpreparedValue 'DataConnector ) ->
m API . QueryRequest
translateAnnSelectToQueryRequest sessionVariables translateFieldsAndAggregates selectG = do
2023-01-17 03:33:56 +03:00
case _asnFrom selectG of
FromIdentifier _ -> throw400 NotSupported " AnnSelectG: FromIdentifier not supported "
2023-04-13 19:10:38 +03:00
FromNativeQuery { } -> throw400 NotSupported " AnnSelectG: FromNativeQuery not supported "
2023-04-27 17:02:55 +03:00
FromStoredProcedure { } -> throw400 NotSupported " AnnSelectG: FromStoredProcedure not supported "
2023-05-19 07:47:12 +03:00
FromTable tableName -> do
( query , TableRelationships tableRelationships ) <-
CPS . runWriterT ( translateAnnSelect sessionVariables translateFieldsAndAggregates ( TableNameKey ( Witch . into tableName ) ) selectG )
let relationships = mkRelationships <$> HashMap . toList tableRelationships
2023-05-24 16:51:56 +03:00
pure
$ API . QRTable
2023-05-19 07:47:12 +03:00
API . TableRequest
{ _trTable = Witch . into tableName ,
_trRelationships = Set . fromList relationships ,
_trQuery = query ,
_trForeach = Nothing
}
FromFunction fn @ ( FunctionName functionName ) argsExp _dListM -> do
args <- mkArgs sessionVariables argsExp fn
( query , TableRelationships tableRelationships ) <-
CPS . runWriterT ( translateAnnSelect sessionVariables translateFieldsAndAggregates ( FunctionNameKey ( Witch . into functionName ) ) selectG )
let relationships = mkRelationships <$> HashMap . toList tableRelationships
2023-05-24 16:51:56 +03:00
pure
$ API . QRFunction
2023-05-19 07:47:12 +03:00
API . FunctionRequest
{ _frFunction = Witch . into functionName ,
_frRelationships = Set . fromList relationships ,
_frQuery = query ,
_frFunctionArguments = args
}
mkRelationships :: ( TableRelationshipsKey , ( HashMap API . RelationshipName API . Relationship ) ) -> API . Relationships
mkRelationships ( FunctionNameKey functionName , relationships ) = API . RFunction ( API . FunctionRelationships functionName relationships )
mkRelationships ( TableNameKey tableName , relationships ) = API . RTable ( API . TableRelationships tableName relationships )
mkArgs ::
( MonadError QErr m
) =>
SessionVariables ->
Function . FunctionArgsExpG ( ArgumentExp ( UnpreparedValue 'DataConnector ) ) ->
FunctionName ->
m [ API . FunctionArgument ]
mkArgs sessionVariables ( Function . FunctionArgsExp ps ns ) functionName = do
unless ( null ps ) $ throw400 NotSupported $ " Positional arguments not supported in function " <> toTxt functionName
getNamed
where
getNamed = mapM mkArg ( HashMap . toList ns )
mkArg ( n , input ) = ( API . NamedArgument n . API . ScalarArgumentValue ) <$> getValue input
getValue ( AEInput x ) = case x of
UVLiteral _ -> throw400 NotSupported " Literal not supported in Data Connector function args. "
UVSessionVar _ _ -> throw400 NotSupported " SessionVar not supported in Data Connector function args. "
UVParameter _ ( ColumnValue t v ) -> pure ( API . ScalarValue v ( coerce ( toTxt t ) ) )
UVSession -> pure ( API . ScalarValue ( J . toJSON sessionVariables ) ( API . ScalarType " json " ) )
2023-01-17 03:33:56 +03:00
translateAnnSelect ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
( TableRelationshipsKey -> Fields ( fieldType ( UnpreparedValue 'DataConnector ) ) -> CPS . WriterT writerOutput m FieldsAndAggregates ) ->
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
AnnSelectG 'DataConnector fieldType ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m API . Query
2023-05-19 07:47:12 +03:00
translateAnnSelect sessionVariables translateFieldsAndAggregates entityName selectG = do
FieldsAndAggregates { .. } <- translateFieldsAndAggregates entityName ( _asnFields selectG )
2023-01-17 03:33:56 +03:00
let whereClauseWithPermissions =
case _saWhere ( _asnArgs selectG ) of
Just expr -> BoolAnd [ expr , _tpFilter ( _asnPerm selectG ) ]
Nothing -> _tpFilter ( _asnPerm selectG )
2023-05-19 07:47:12 +03:00
whereClause <- translateBoolExpToExpression sessionVariables entityName whereClauseWithPermissions
orderBy <- traverse ( translateOrderBy sessionVariables entityName ) ( _saOrderBy $ _asnArgs selectG )
2023-01-17 03:33:56 +03:00
pure
API . Query
2023-03-15 08:15:11 +03:00
{ _qFields = mapFieldNameHashMap <$> _faaFields ,
_qAggregates = mapFieldNameHashMap <$> _faaAggregates ,
2023-03-20 07:00:34 +03:00
_qAggregatesLimit = _saLimit ( _asnArgs selectG ) <* _faaAggregates , -- Only include the aggregates limit if we actually have aggregrates
2023-01-17 03:33:56 +03:00
_qLimit =
2023-05-24 16:51:56 +03:00
fmap getMin
$ foldMap
2023-01-17 03:33:56 +03:00
( fmap Min )
[ _saLimit ( _asnArgs selectG ) ,
_tpLimit ( _asnPerm selectG )
] ,
_qOffset = fmap fromIntegral ( _saOffset ( _asnArgs selectG ) ) ,
_qWhere = whereClause ,
_qOrderBy = orderBy
}
translateOrderBy ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
NE . NonEmpty ( AnnotatedOrderByItemG 'DataConnector ( UnpreparedValue 'DataConnector ) ) ->
CPS . WriterT writerOutput m API . OrderBy
2023-05-19 07:47:12 +03:00
translateOrderBy sessionVariables sourceName orderByItems = do
2023-01-17 03:33:56 +03:00
orderByElementsAndRelations <- for orderByItems \ OrderByItemG { .. } -> do
let orderDirection = maybe API . Ascending Witch . from obiType
2023-05-19 07:47:12 +03:00
translateOrderByElement sessionVariables sourceName orderDirection [] obiColumn
2023-01-17 03:33:56 +03:00
relations <- lift . mergeOrderByRelations $ snd <$> orderByElementsAndRelations
pure
API . OrderBy
{ _obRelations = relations ,
_obElements = fst <$> orderByElementsAndRelations
}
translateOrderByElement ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
API . OrderDirection ->
[ API . RelationshipName ] ->
AnnotatedOrderByElement 'DataConnector ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m ( API . OrderByElement , HashMap API . RelationshipName API . OrderByRelation )
2023-05-19 07:47:12 +03:00
translateOrderByElement sessionVariables sourceName orderDirection targetReversePath = \ case
2023-01-17 03:33:56 +03:00
AOCColumn ( ColumnInfo { .. } ) ->
pure
( API . OrderByElement
{ _obeTargetPath = reverse targetReversePath ,
_obeTarget = API . OrderByColumn $ Witch . from ciColumn ,
_obeOrderDirection = orderDirection
} ,
mempty
)
AOCObjectRelation relationshipInfo filterExp orderByElement -> do
2023-05-19 07:47:12 +03:00
( relationshipName , API . Relationship { .. } ) <- recordTableRelationshipFromRelInfo sourceName relationshipInfo
( translatedOrderByElement , subOrderByRelations ) <- translateOrderByElement sessionVariables ( TableNameKey _rTargetTable ) orderDirection ( relationshipName : targetReversePath ) orderByElement
2023-01-17 03:33:56 +03:00
2023-05-19 07:47:12 +03:00
targetTableWhereExp <- translateBoolExpToExpression sessionVariables ( TableNameKey _rTargetTable ) filterExp
2023-01-17 03:33:56 +03:00
let orderByRelations = HashMap . fromList [ ( relationshipName , API . OrderByRelation targetTableWhereExp subOrderByRelations ) ]
pure ( translatedOrderByElement , orderByRelations )
AOCArrayAggregation relationshipInfo filterExp aggregateOrderByElement -> do
2023-05-19 07:47:12 +03:00
( relationshipName , API . Relationship { .. } ) <- recordTableRelationshipFromRelInfo sourceName relationshipInfo
2023-01-17 03:33:56 +03:00
orderByTarget <- case aggregateOrderByElement of
AAOCount ->
pure API . OrderByStarCountAggregate
2023-02-06 07:18:54 +03:00
AAOOp aggFunctionTxt resultType ColumnInfo { .. } -> do
2023-01-17 03:33:56 +03:00
aggFunction <- lift $ translateSingleColumnAggregateFunction aggFunctionTxt
2023-02-06 07:18:54 +03:00
let resultScalarType = Witch . from $ columnTypeToScalarType resultType
pure . API . OrderBySingleColumnAggregate $ API . SingleColumnAggregate aggFunction ( Witch . from ciColumn ) resultScalarType
2023-01-17 03:33:56 +03:00
let translatedOrderByElement =
API . OrderByElement
{ _obeTargetPath = reverse ( relationshipName : targetReversePath ) ,
_obeTarget = orderByTarget ,
_obeOrderDirection = orderDirection
}
2023-05-19 07:47:12 +03:00
targetTableWhereExp <- translateBoolExpToExpression sessionVariables ( TableNameKey _rTargetTable ) filterExp
2023-01-17 03:33:56 +03:00
let orderByRelations = HashMap . fromList [ ( relationshipName , API . OrderByRelation targetTableWhereExp mempty ) ]
pure ( translatedOrderByElement , orderByRelations )
mergeOrderByRelations ::
forall m f .
( MonadError QErr m , Foldable f ) =>
f ( HashMap API . RelationshipName API . OrderByRelation ) ->
m ( HashMap API . RelationshipName API . OrderByRelation )
mergeOrderByRelations orderByRelationsList =
foldM mergeMap mempty orderByRelationsList
where
mergeMap :: HashMap API . RelationshipName API . OrderByRelation -> HashMap API . RelationshipName API . OrderByRelation -> m ( HashMap API . RelationshipName API . OrderByRelation )
mergeMap left right = foldM ( \ targetMap ( relName , orderByRel ) -> HashMap . alterF ( maybe ( pure $ Just orderByRel ) ( fmap Just . mergeOrderByRelation orderByRel ) ) relName targetMap ) left $ HashMap . toList right
mergeOrderByRelation :: API . OrderByRelation -> API . OrderByRelation -> m API . OrderByRelation
mergeOrderByRelation right left =
if API . _obrWhere left == API . _obrWhere right
then do
mergedSubrelations <- mergeMap ( API . _obrSubrelations left ) ( API . _obrSubrelations right )
pure $ API . OrderByRelation ( API . _obrWhere left ) mergedSubrelations
else throw500 " mergeOrderByRelations: Differing filter expressions found for the same table "
translateAnnFieldsWithNoAggregates ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
FieldPrefix ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
AnnFieldsG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m FieldsAndAggregates
2023-05-19 07:47:12 +03:00
translateAnnFieldsWithNoAggregates sessionVariables fieldNamePrefix sourceName fields =
( \ fields' -> FieldsAndAggregates ( Just fields' ) Nothing ) <$> translateAnnFields sessionVariables fieldNamePrefix sourceName fields
2023-01-17 03:33:56 +03:00
translateAnnFields ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
FieldPrefix ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
AnnFieldsG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m ( HashMap FieldName API . Field )
2023-05-19 07:47:12 +03:00
translateAnnFields sessionVariables fieldNamePrefix sourceName fields = do
translatedFields <- traverse ( traverse ( translateAnnField sessionVariables sourceName ) ) fields
2023-01-17 03:33:56 +03:00
pure $ HashMap . fromList ( mapMaybe ( \ ( fieldName , field ) -> ( applyPrefix fieldNamePrefix fieldName , ) <$> field ) translatedFields )
translateAnnField ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
AnnFieldG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m ( Maybe API . Field )
translateAnnField sessionVariables sourceTableName = \ case
2023-05-19 07:47:12 +03:00
AFNestedObject nestedObj ->
2023-05-24 16:51:56 +03:00
Just
. API . NestedObjField ( Witch . from $ _anosColumn nestedObj )
2023-05-19 07:47:12 +03:00
<$> translateNestedObjectSelect sessionVariables sourceTableName nestedObj
Nested array support for Data Connectors Backend and MongoDB
## Description
This change adds support for querying into nested arrays in Data Connector agents that support such a concept (currently MongoDB).
### DC API changes
- New API type `ColumnType` which allows representing the type of a "column" as either a scalar type, an object reference or an array of `ColumnType`s. This recursive definition allows arbitrary nesting of arrays of types.
- The `type` fields in the API types `ColumnInfo` and `ColumnInsertSchema` now take a `ColumnType` instead of a `ScalarType`.
- To ensure backwards compatibility, a `ColumnType` representing a scalar serialises and deserialises to the same representation as `ScalarType`.
- In queries, the `Field` type now has a new constructor `NestedArrayField`. This contains a nested `Field` along with optional `limit`, `offset`, `where` and `order_by` arguments. (These optional arguments are not yet used by either HGE or the MongoDB agent.)
### MongoDB Haskell agent changes
- The `/schema` endpoint will now recognise arrays within the JSON validation schema and generate corresponding arrays in the DC schema.
- The `/query` endpoint will now handle `NestedArrayField`s within queries (although it does not yet handle `limit`, `offset`, `where` and `order_by`).
### HGE server changes
- The `Backend` type class adds a new type family `XNestedArrays b` to enable nested arrays on a per-backend basis (currently enabled only for the `DataConnector` backend.
- Within `RawColumnInfo` the column type is now represented by a new type `RawColumnType b` which mirrors the shape of the DC API `ColumnType`, but uses `XNestedObjects b` and `XNestedArrays b` type families to allow turning nested object and array supports on or off for a particular backend. In the `DataConnector` backend `API.CustomType` is converted into `RawColumnInfo 'DataConnector` while building the schema.
- In the next stage of schema building, the `RawColumnInfo` is converted into a `StructuredColumnInfo` which allows us to represent the three different types of columns: scalar, object and array. TODO: the `StructuredColumnInfo` looks very similar to the Logical Model types. The main difference is that it uses the `XNestedObjects` and `XNestedArrays` type families. We should be able to combine these two representations.
- The `StructuredColumnInfo` is then placed into a `FIColumn` `FieldInfo`. This involved some refactoring of `FieldInfo` as I had previously split out `FINestedObject` into a separate constructor. However it works out better to represent all "column" fields (i.e. scalar, object and array) using `FIColumn` as this make it easier to implement permission checking correctly. This is the reason the `StructuredColumnInfo` was needed.
- Next, the `FieldInfo` are used to generate `FieldParser`s. We add a new constructor to `AnnFieldG` for `AFNestedArray`. An `AFNestedArray` field parser can contain either a simple array selection or an array aggregate. Simple array `FieldParsers` are currently limited to subfield selection. We will add support for limit, offset, where and order_by in a future PR. We also don't yet generate array aggregate `FieldParsers.
- The new `AFNestedArray` field is handled by the `QueryPlan` module in the `DataConnector` backend. There we generate an `API.NestedArrayField` from the AFNestedArray. We also handle nested arrays when reshaping the response from the DC agent.
## Limitations
- Support for limit, offset, filter (where) and order_by is not yet fully implemented, although it should not be hard to add this
- Support for aggregations on nested arrays is not yet fully implemented
- Permissions involving nested arrays (and objects) not yet implemented
- This should be integrated with Logical Model types, but that will happen in a separate PR
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/9149
GitOrigin-RevId: 0e7b71a994fc1d2ca1ef73bfe7b96e95b5328531
2023-05-24 11:00:59 +03:00
AFNestedArray _ ( ANASSimple field ) ->
fmap mkArrayField <$> translateAnnField sessionVariables sourceTableName field
where
mkArrayField nestedField =
API . NestedArrayField ( API . ArrayField nestedField Nothing Nothing Nothing Nothing )
-- TODO(dmoverton): support limit, offset, where and order_by in ArrayField
AFNestedArray _ ( ANASAggregate _ ) ->
pure Nothing -- TODO(dmoverton): support nested array aggregates
2023-01-17 03:33:56 +03:00
AFColumn colField ->
2023-05-19 07:47:12 +03:00
-- TODO: make sure certain fields in colField are not in use, since we don't support them
2023-01-17 03:33:56 +03:00
pure . Just $ API . ColumnField ( Witch . from $ _acfColumn colField ) ( Witch . from . columnTypeToScalarType $ _acfType colField )
2023-05-10 18:13:56 +03:00
AFObjectRelation objRel ->
case _aosTarget ( _aarAnnSelect objRel ) of
FromTable tableName -> do
let targetTable = Witch . from tableName
let relationshipName = mkRelationshipName $ _aarRelationshipName objRel
2023-05-19 07:47:12 +03:00
fields <- translateAnnFields sessionVariables noPrefix ( TableNameKey targetTable ) ( _aosFields ( _aarAnnSelect objRel ) )
whereClause <- translateBoolExpToExpression sessionVariables ( TableNameKey targetTable ) ( _aosTargetFilter ( _aarAnnSelect objRel ) )
2023-01-17 03:33:56 +03:00
2023-05-10 18:13:56 +03:00
recordTableRelationship
sourceTableName
relationshipName
API . Relationship
{ _rTargetTable = targetTable ,
_rRelationshipType = API . ObjectRelationship ,
_rColumnMapping = HashMap . fromList $ bimap Witch . from Witch . from <$> HashMap . toList ( _aarColumnMapping objRel )
2023-01-17 03:33:56 +03:00
}
2023-05-10 18:13:56 +03:00
2023-05-24 16:51:56 +03:00
pure
. Just
. API . RelField
$ API . RelationshipField
2023-05-10 18:13:56 +03:00
relationshipName
( API . Query
{ _qFields = Just $ mapFieldNameHashMap fields ,
_qAggregates = mempty ,
_qWhere = whereClause ,
_qAggregatesLimit = Nothing ,
_qLimit = Nothing ,
_qOffset = Nothing ,
_qOrderBy = Nothing
}
)
other -> error $ " translateAnnField: " <> show other
2023-01-17 03:33:56 +03:00
AFArrayRelation ( ASSimple arrayRelationSelect ) -> do
Just <$> translateArrayRelationSelect sessionVariables sourceTableName ( translateAnnFieldsWithNoAggregates sessionVariables noPrefix ) arrayRelationSelect
AFArrayRelation ( ASAggregate arrayRelationSelect ) ->
Just <$> translateArrayRelationSelect sessionVariables sourceTableName ( translateTableAggregateFields sessionVariables ) arrayRelationSelect
AFExpression _literal ->
-- We ignore literal text fields (we don't send them to the data connector agent)
-- and add them back to the response JSON when we reshape what the agent returns
-- to us
pure Nothing
translateArrayRelationSelect ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
( TableRelationshipsKey -> Fields ( fieldType ( UnpreparedValue 'DataConnector ) ) -> CPS . WriterT writerOutput m FieldsAndAggregates ) ->
2023-01-17 03:33:56 +03:00
AnnRelationSelectG 'DataConnector ( AnnSelectG 'DataConnector fieldType ( UnpreparedValue 'DataConnector ) ) ->
CPS . WriterT writerOutput m API . Field
2023-05-19 07:47:12 +03:00
translateArrayRelationSelect sessionVariables sourceName translateFieldsAndAggregates arrRel = do
case _asnFrom ( _aarAnnSelect arrRel ) of
FromIdentifier _ -> lift $ throw400 NotSupported " AnnSelectG: FromIdentifier not supported "
FromNativeQuery { } -> lift $ throw400 NotSupported " AnnSelectG: FromNativeQuery not supported "
FromStoredProcedure { } -> lift $ throw400 NotSupported " AnnSelectG: FromStoredProcedure not supported "
FromFunction { } -> lift $ throw400 NotSupported " translateArrayRelationSelect: FromFunction not currently supported "
FromTable targetTable -> do
query <- translateAnnSelect sessionVariables translateFieldsAndAggregates ( TableNameKey ( Witch . into targetTable ) ) ( _aarAnnSelect arrRel )
let relationshipName = mkRelationshipName $ _aarRelationshipName arrRel
recordTableRelationship
sourceName
relationshipName
API . Relationship
{ _rTargetTable = Witch . into targetTable ,
_rRelationshipType = API . ArrayRelationship ,
_rColumnMapping = HashMap . fromList $ bimap Witch . from Witch . from <$> HashMap . toList ( _aarColumnMapping arrRel )
}
2023-05-24 16:51:56 +03:00
pure
. API . RelField
$ API . RelationshipField
2023-05-19 07:47:12 +03:00
relationshipName
query
2023-01-17 03:33:56 +03:00
translateTableAggregateFields ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
TableAggregateFieldsG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m FieldsAndAggregates
2023-05-19 07:47:12 +03:00
translateTableAggregateFields sessionVariables sourceName fields = do
mconcat <$> traverse ( uncurry ( translateTableAggregateField sessionVariables sourceName ) ) fields
2023-01-17 03:33:56 +03:00
translateTableAggregateField ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-01-17 03:33:56 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-01-17 03:33:56 +03:00
FieldName ->
TableAggregateFieldG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m FieldsAndAggregates
2023-05-19 07:47:12 +03:00
translateTableAggregateField sessionVariables sourceName fieldName = \ case
2023-01-17 03:33:56 +03:00
TAFAgg aggregateFields -> do
let fieldNamePrefix = prefixWith fieldName
translatedAggregateFields <- lift $ mconcat <$> traverse ( uncurry ( translateAggregateField fieldNamePrefix ) ) aggregateFields
2023-05-24 16:51:56 +03:00
pure
$ FieldsAndAggregates
2023-03-15 08:15:11 +03:00
Nothing
( Just translatedAggregateFields )
2023-01-17 03:33:56 +03:00
TAFNodes _ fields ->
2023-05-19 07:47:12 +03:00
translateAnnFieldsWithNoAggregates sessionVariables ( prefixWith fieldName ) sourceName fields
2023-01-17 03:33:56 +03:00
TAFExp _txt ->
-- We ignore literal text fields (we don't send them to the data connector agent)
-- and add them back to the response JSON when we reshape what the agent returns
-- to us
pure mempty
translateAggregateField ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
FieldPrefix ->
FieldName ->
2023-05-23 17:46:27 +03:00
AggregateField 'DataConnector ( UnpreparedValue 'DataConnector ) ->
2023-01-17 03:33:56 +03:00
m ( HashMap FieldName API . Aggregate )
translateAggregateField fieldPrefix fieldName = \ case
AFCount countAggregate ->
let aggregate =
case countAggregate of
StarCount -> API . StarCount
ColumnCount column -> API . ColumnCount $ API . ColumnCountAggregate { _ccaColumn = Witch . from column , _ccaDistinct = False }
ColumnDistinctCount column -> API . ColumnCount $ API . ColumnCountAggregate { _ccaColumn = Witch . from column , _ccaDistinct = True }
in pure $ HashMap . singleton ( applyPrefix fieldPrefix fieldName ) aggregate
AFOp AggregateOp { .. } -> do
let fieldPrefix' = fieldPrefix <> prefixWith fieldName
aggFunction <- translateSingleColumnAggregateFunction _aoOp
fmap ( HashMap . fromList . catMaybes ) . forM _aoFields $ \ ( columnFieldName , columnField ) ->
case columnField of
2023-05-23 17:46:27 +03:00
SFCol column resultType ->
2023-02-06 07:18:54 +03:00
let resultScalarType = Witch . from $ columnTypeToScalarType resultType
in pure . Just $ ( applyPrefix fieldPrefix' columnFieldName , API . SingleColumn $ API . SingleColumnAggregate aggFunction ( Witch . from column ) resultScalarType )
2023-05-23 17:46:27 +03:00
SFExp _txt ->
2023-01-17 03:33:56 +03:00
-- We ignore literal text fields (we don't send them to the data connector agent)
-- and add them back to the response JSON when we reshape what the agent returns
-- to us
pure Nothing
2023-05-23 17:46:27 +03:00
-- See Hasura.RQL.Types.Backend.supportsAggregateComputedFields
SFComputedField _ _ -> error " Aggregate computed fields aren't currently supported for Data Connectors! "
2023-01-17 03:33:56 +03:00
AFExp _txt ->
-- We ignore literal text fields (we don't send them to the data connector agent)
-- and add them back to the response JSON when we reshape what the agent returns
-- to us
pure mempty
2023-05-24 16:51:56 +03:00
translateSingleColumnAggregateFunction :: ( MonadError QErr m ) => Text -> m API . SingleColumnAggregateFunction
2023-01-17 03:33:56 +03:00
translateSingleColumnAggregateFunction functionName =
fmap API . SingleColumnAggregateFunction ( G . mkName functionName )
` onNothing ` throw500 ( " translateSingleColumnAggregateFunction: Invalid aggregate function encountered: " <> functionName )
2023-04-11 04:29:05 +03:00
translateNestedObjectSelect ::
( Has TableRelationships writerOutput ,
Monoid writerOutput ,
2023-06-21 09:48:46 +03:00
MonadError QErr m ,
MonadReader r m ,
Has API . ScalarTypesCapabilities r
2023-04-11 04:29:05 +03:00
) =>
SessionVariables ->
2023-05-19 07:47:12 +03:00
TableRelationshipsKey ->
2023-04-11 04:29:05 +03:00
AnnNestedObjectSelectG 'DataConnector Void ( UnpreparedValue 'DataConnector ) ->
CPS . WriterT writerOutput m API . Query
2023-05-19 07:47:12 +03:00
translateNestedObjectSelect sessionVariables relationshipKey selectG = do
FieldsAndAggregates { .. } <- translateAnnFieldsWithNoAggregates sessionVariables noPrefix relationshipKey $ _anosFields selectG
2023-04-11 04:29:05 +03:00
pure
API . Query
{ _qFields = mapFieldNameHashMap <$> _faaFields ,
_qAggregates = Nothing ,
_qAggregatesLimit = Nothing ,
_qLimit = Nothing ,
_qOffset = Nothing ,
_qWhere = Nothing ,
_qOrderBy = Nothing
}
2023-01-17 03:33:56 +03:00
--------------------------------------------------------------------------------
reshapeResponseToQueryShape ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
QueryDB 'DataConnector Void v ->
API . QueryResponse ->
m J . Encoding
reshapeResponseToQueryShape queryDb response =
case queryDb of
QDBMultipleRows simpleSelect -> reshapeSimpleSelectRows Many ( _asnFields simpleSelect ) response
QDBSingleRow simpleSelect -> reshapeSimpleSelectRows Single ( _asnFields simpleSelect ) response
QDBAggregation aggregateSelect -> reshapeTableAggregateFields ( _asnFields aggregateSelect ) response
reshapeSimpleSelectRows ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
Cardinality ->
AnnFieldsG 'DataConnector Void v ->
API . QueryResponse ->
m J . Encoding
reshapeSimpleSelectRows cardinality fields API . QueryResponse { .. } =
case cardinality of
Single ->
case rows of
[] -> pure $ J . toEncoding J . Null
[ singleRow ] -> reshapeAnnFields noPrefix fields singleRow
_multipleRows ->
throw500 " Data Connector agent returned multiple rows when only one was expected " -- TODO(dchambers): Add pathing information for error clarity
Many -> do
reshapedRows <- traverse ( reshapeAnnFields noPrefix fields ) rows
pure $ JE . list id reshapedRows
where
rows = fromMaybe mempty _qrRows
reshapeTableAggregateFields ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
TableAggregateFieldsG 'DataConnector Void v ->
API . QueryResponse ->
m J . Encoding
reshapeTableAggregateFields tableAggregateFields API . QueryResponse { .. } = do
reshapedFields <- forM tableAggregateFields $ \ ( fieldName @ ( FieldName fieldNameText ) , tableAggregateField ) -> do
case tableAggregateField of
TAFAgg aggregateFields -> do
reshapedAggregateFields <- reshapeAggregateFields ( prefixWith fieldName ) aggregateFields responseAggregates
pure $ ( fieldNameText , reshapedAggregateFields )
TAFNodes _ annFields -> do
reshapedRows <- traverse ( reshapeAnnFields ( prefixWith fieldName ) annFields ) responseRows
pure $ ( fieldNameText , JE . list id reshapedRows )
TAFExp txt ->
pure $ ( fieldNameText , JE . text txt )
pure $ encodeAssocListAsObject reshapedFields
where
responseRows = fromMaybe mempty _qrRows
responseAggregates = fromMaybe mempty _qrAggregates
reshapeAggregateFields ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
FieldPrefix ->
2023-05-23 17:46:27 +03:00
AggregateFields 'DataConnector v ->
2023-01-17 03:33:56 +03:00
HashMap API . FieldName J . Value ->
m J . Encoding
reshapeAggregateFields fieldPrefix aggregateFields responseAggregates = do
reshapedFields <- forM aggregateFields $ \ ( fieldName @ ( FieldName fieldNameText ) , aggregateField ) ->
case aggregateField of
AFCount _countAggregate -> do
let fieldNameKey = API . FieldName . getFieldNameTxt $ applyPrefix fieldPrefix fieldName
responseAggregateValue <-
HashMap . lookup fieldNameKey responseAggregates
` onNothing ` throw500 ( " Unable to find expected aggregate " <> API . unFieldName fieldNameKey <> " in aggregates returned by Data Connector agent " ) -- TODO(dchambers): Add pathing information for error clarity
pure ( fieldNameText , J . toEncoding responseAggregateValue )
AFOp AggregateOp { .. } -> do
reshapedColumnFields <- forM _aoFields $ \ ( columnFieldName @ ( FieldName columnFieldNameText ) , columnField ) ->
case columnField of
2023-05-23 17:46:27 +03:00
SFCol _column _columnType -> do
2023-01-17 03:33:56 +03:00
let fieldPrefix' = fieldPrefix <> prefixWith fieldName
let columnFieldNameKey = API . FieldName . getFieldNameTxt $ applyPrefix fieldPrefix' columnFieldName
responseAggregateValue <-
HashMap . lookup columnFieldNameKey responseAggregates
` onNothing ` throw500 ( " Unable to find expected aggregate " <> API . unFieldName columnFieldNameKey <> " in aggregates returned by Data Connector agent " ) -- TODO(dchambers): Add pathing information for error clarity
pure ( columnFieldNameText , J . toEncoding responseAggregateValue )
2023-05-23 17:46:27 +03:00
SFExp txt ->
2023-01-17 03:33:56 +03:00
pure ( columnFieldNameText , JE . text txt )
2023-05-23 17:46:27 +03:00
-- See Hasura.RQL.Types.Backend.supportsAggregateComputedFields
SFComputedField _ _ -> error " Aggregate computed fields aren't currently supported for Data Connectors! "
2023-01-17 03:33:56 +03:00
pure ( fieldNameText , encodeAssocListAsObject reshapedColumnFields )
AFExp txt ->
pure ( fieldNameText , JE . text txt )
pure $ encodeAssocListAsObject reshapedFields
reshapeAnnFields ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
FieldPrefix ->
AnnFieldsG 'DataConnector Void v ->
HashMap API . FieldName API . FieldValue ->
m J . Encoding
reshapeAnnFields fieldNamePrefix fields responseRow = do
reshapedFields <- forM fields $ \ ( fieldName @ ( FieldName fieldNameText ) , field ) -> do
let fieldNameKey = API . FieldName . getFieldNameTxt $ applyPrefix fieldNamePrefix fieldName
2023-06-15 04:31:43 +03:00
let responseField = fromMaybe API . nullFieldValue $ HashMap . lookup fieldNameKey responseRow
2023-01-17 03:33:56 +03:00
reshapedField <- reshapeField field responseField
pure ( fieldNameText , reshapedField )
pure $ encodeAssocListAsObject reshapedFields
reshapeField ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
AnnFieldG 'DataConnector Void v ->
2023-06-15 04:31:43 +03:00
API . FieldValue ->
2023-01-17 03:33:56 +03:00
m J . Encoding
reshapeField field responseFieldValue =
case field of
2023-06-15 04:31:43 +03:00
AFNestedObject nestedObj ->
handleNull responseFieldValue
$ case API . deserializeAsNestedObjFieldValue responseFieldValue of
Left err -> throw500 $ " Expected object in field returned by Data Connector agent: " <> err -- TODO(dmoverton): Add pathing information for error clarity
Right nestedResponse ->
reshapeAnnFields noPrefix ( _anosFields nestedObj ) nestedResponse
AFNestedArray _ ( ANASSimple arrayField ) ->
handleNull responseFieldValue
$ case API . deserializeAsNestedArrayFieldValue responseFieldValue of
Left err -> throw500 $ " Expected array in field returned by Data Connector agent: " <> err -- TODO(dmoverton): Add pathing information for error clarity
Right arrayResponse ->
JE . list id <$> traverse ( reshapeField arrayField ) arrayResponse
Nested array support for Data Connectors Backend and MongoDB
## Description
This change adds support for querying into nested arrays in Data Connector agents that support such a concept (currently MongoDB).
### DC API changes
- New API type `ColumnType` which allows representing the type of a "column" as either a scalar type, an object reference or an array of `ColumnType`s. This recursive definition allows arbitrary nesting of arrays of types.
- The `type` fields in the API types `ColumnInfo` and `ColumnInsertSchema` now take a `ColumnType` instead of a `ScalarType`.
- To ensure backwards compatibility, a `ColumnType` representing a scalar serialises and deserialises to the same representation as `ScalarType`.
- In queries, the `Field` type now has a new constructor `NestedArrayField`. This contains a nested `Field` along with optional `limit`, `offset`, `where` and `order_by` arguments. (These optional arguments are not yet used by either HGE or the MongoDB agent.)
### MongoDB Haskell agent changes
- The `/schema` endpoint will now recognise arrays within the JSON validation schema and generate corresponding arrays in the DC schema.
- The `/query` endpoint will now handle `NestedArrayField`s within queries (although it does not yet handle `limit`, `offset`, `where` and `order_by`).
### HGE server changes
- The `Backend` type class adds a new type family `XNestedArrays b` to enable nested arrays on a per-backend basis (currently enabled only for the `DataConnector` backend.
- Within `RawColumnInfo` the column type is now represented by a new type `RawColumnType b` which mirrors the shape of the DC API `ColumnType`, but uses `XNestedObjects b` and `XNestedArrays b` type families to allow turning nested object and array supports on or off for a particular backend. In the `DataConnector` backend `API.CustomType` is converted into `RawColumnInfo 'DataConnector` while building the schema.
- In the next stage of schema building, the `RawColumnInfo` is converted into a `StructuredColumnInfo` which allows us to represent the three different types of columns: scalar, object and array. TODO: the `StructuredColumnInfo` looks very similar to the Logical Model types. The main difference is that it uses the `XNestedObjects` and `XNestedArrays` type families. We should be able to combine these two representations.
- The `StructuredColumnInfo` is then placed into a `FIColumn` `FieldInfo`. This involved some refactoring of `FieldInfo` as I had previously split out `FINestedObject` into a separate constructor. However it works out better to represent all "column" fields (i.e. scalar, object and array) using `FIColumn` as this make it easier to implement permission checking correctly. This is the reason the `StructuredColumnInfo` was needed.
- Next, the `FieldInfo` are used to generate `FieldParser`s. We add a new constructor to `AnnFieldG` for `AFNestedArray`. An `AFNestedArray` field parser can contain either a simple array selection or an array aggregate. Simple array `FieldParsers` are currently limited to subfield selection. We will add support for limit, offset, where and order_by in a future PR. We also don't yet generate array aggregate `FieldParsers.
- The new `AFNestedArray` field is handled by the `QueryPlan` module in the `DataConnector` backend. There we generate an `API.NestedArrayField` from the AFNestedArray. We also handle nested arrays when reshaping the response from the DC agent.
## Limitations
- Support for limit, offset, filter (where) and order_by is not yet fully implemented, although it should not be hard to add this
- Support for aggregations on nested arrays is not yet fully implemented
- Permissions involving nested arrays (and objects) not yet implemented
- This should be integrated with Logical Model types, but that will happen in a separate PR
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/9149
GitOrigin-RevId: 0e7b71a994fc1d2ca1ef73bfe7b96e95b5328531
2023-05-24 11:00:59 +03:00
AFNestedArray _ ( ANASAggregate _ ) ->
throw400 NotSupported " Nested array aggregate not supported "
2023-01-17 03:33:56 +03:00
AFColumn _columnField -> do
2023-06-15 04:31:43 +03:00
let columnFieldValue = API . deserializeAsColumnFieldValue responseFieldValue
2023-01-17 03:33:56 +03:00
pure $ J . toEncoding columnFieldValue
AFObjectRelation objectRelationField -> do
2023-06-15 04:31:43 +03:00
case API . deserializeAsRelationshipFieldValue responseFieldValue of
2023-01-17 03:33:56 +03:00
Left err -> throw500 $ " Found column field value where relationship field value was expected in field returned by Data Connector agent: " <> err -- TODO(dchambers): Add pathing information for error clarity
Right subqueryResponse ->
let fields = _aosFields $ _aarAnnSelect objectRelationField
in reshapeSimpleSelectRows Single fields subqueryResponse
AFArrayRelation ( ASSimple simpleArrayRelationField ) ->
2023-06-15 04:31:43 +03:00
reshapeAnnRelationSelect ( reshapeSimpleSelectRows Many ) simpleArrayRelationField responseFieldValue
2023-01-17 03:33:56 +03:00
AFArrayRelation ( ASAggregate aggregateArrayRelationField ) ->
2023-06-15 04:31:43 +03:00
reshapeAnnRelationSelect reshapeTableAggregateFields aggregateArrayRelationField responseFieldValue
2023-01-17 03:33:56 +03:00
AFExpression txt -> pure $ JE . text txt
2023-06-15 04:31:43 +03:00
where
handleNull v a =
if API . isNullFieldValue v
then pure JE . null_
else a
2023-01-17 03:33:56 +03:00
reshapeAnnRelationSelect ::
2023-05-24 16:51:56 +03:00
( MonadError QErr m ) =>
2023-01-17 03:33:56 +03:00
( Fields ( fieldType v ) -> API . QueryResponse -> m J . Encoding ) ->
AnnRelationSelectG 'DataConnector ( AnnSelectG 'DataConnector fieldType v ) ->
API . FieldValue ->
m J . Encoding
reshapeAnnRelationSelect reshapeFields annRelationSelect fieldValue =
case API . deserializeAsRelationshipFieldValue fieldValue of
Left err -> throw500 $ " Found column field value where relationship field value was expected in field returned by Data Connector agent: " <> err -- TODO(dchambers): Add pathing information for error clarity
Right subqueryResponse ->
let annSimpleSelect = _aarAnnSelect annRelationSelect
in reshapeFields ( _asnFields annSimpleSelect ) subqueryResponse