2022-09-05 05:42:59 +03:00
{- # LANGUAGE Arrows # -}
2022-02-25 19:08:18 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
2022-09-05 05:42:59 +03:00
module Hasura.Backends.DataConnector.Adapter.Metadata ( ) where
2022-02-25 19:08:18 +03:00
2022-09-05 05:42:59 +03:00
import Control.Arrow.Extended
2022-04-14 05:06:07 +03:00
import Data.Aeson qualified as J
2022-06-08 18:31:28 +03:00
import Data.Aeson.Key qualified as K
import Data.Aeson.KeyMap qualified as KM
2022-04-14 05:06:07 +03:00
import Data.Environment ( Environment )
import Data.HashMap.Strict qualified as Map
2022-09-05 05:42:59 +03:00
import Data.HashMap.Strict.Extended qualified as HashMap
2022-04-29 05:13:13 +03:00
import Data.HashMap.Strict.InsOrd qualified as OMap
2022-08-24 00:46:10 +03:00
import Data.HashMap.Strict.NonEmpty qualified as NEHashMap
import Data.HashSet qualified as HashSet
2022-07-01 15:20:07 +03:00
import Data.Sequence qualified as Seq
2022-07-19 11:41:27 +03:00
import Data.Sequence.NonEmpty qualified as NESeq
2022-05-05 08:18:43 +03:00
import Data.Text qualified as Text
2022-06-02 05:06:45 +03:00
import Data.Text.Extended ( toTxt , ( <<> ) , ( <>> ) )
2022-10-11 03:25:07 +03:00
import Hasura.Backends.DataConnector.API ( capabilitiesCase , errorResponseSummary , schemaCase )
2022-05-02 08:03:12 +03:00
import Hasura.Backends.DataConnector.API qualified as API
2022-10-11 03:25:07 +03:00
import Hasura.Backends.DataConnector.API.V0.ErrorResponse ( _crDetails )
2022-07-19 04:51:42 +03:00
import Hasura.Backends.DataConnector.Adapter.ConfigTransform ( transformConnSourceConfig )
2022-05-02 08:03:12 +03:00
import Hasura.Backends.DataConnector.Adapter.Types qualified as DC
2022-07-11 11:04:30 +03:00
import Hasura.Backends.DataConnector.Agent.Client ( AgentClientContext ( .. ) , runAgentClientT )
2022-04-14 05:06:07 +03:00
import Hasura.Backends.Postgres.SQL.Types ( PGDescription ( .. ) )
2022-10-11 03:25:07 +03:00
import Hasura.Base.Error ( Code ( .. ) , QErr , decodeValue , throw400 , throw400WithDetail , throw500 , withPathK )
2022-09-05 05:42:59 +03:00
import Hasura.Incremental qualified as Inc
2022-07-11 11:04:30 +03:00
import Hasura.Logging ( Hasura , Logger )
2022-02-25 19:08:18 +03:00
import Hasura.Prelude
2022-06-02 05:06:45 +03:00
import Hasura.RQL.IR.BoolExp ( OpExpG ( .. ) , PartialSQLExp ( .. ) , RootOrCurrent ( .. ) , RootOrCurrentColumn ( .. ) )
2022-04-28 04:51:58 +03:00
import Hasura.RQL.Types.Column qualified as RQL . T . C
2022-09-05 05:42:59 +03:00
import Hasura.RQL.Types.Common ( OID ( .. ) , SourceName )
2022-05-05 16:43:50 +03:00
import Hasura.RQL.Types.EventTrigger ( RecreateEventTriggers ( RETDoNothing ) )
2022-04-14 05:06:07 +03:00
import Hasura.RQL.Types.Metadata ( SourceMetadata ( .. ) )
2022-02-25 19:08:18 +03:00
import Hasura.RQL.Types.Metadata.Backend ( BackendMetadata ( .. ) )
2022-09-05 05:42:59 +03:00
import Hasura.RQL.Types.Metadata.Object
2022-06-02 05:06:45 +03:00
import Hasura.RQL.Types.SchemaCache qualified as SchemaCache
2022-09-05 05:42:59 +03:00
import Hasura.RQL.Types.SchemaCache.Build
2022-04-14 05:06:07 +03:00
import Hasura.RQL.Types.Source ( ResolvedSource ( .. ) )
import Hasura.RQL.Types.SourceCustomization ( SourceTypeCustomization )
2022-08-24 00:46:10 +03:00
import Hasura.RQL.Types.Table ( ForeignKey ( _fkConstraint ) )
2022-04-28 04:51:58 +03:00
import Hasura.RQL.Types.Table qualified as RQL . T . T
2022-04-29 05:13:13 +03:00
import Hasura.SQL.Backend ( BackendSourceKind ( .. ) , BackendType ( .. ) )
2022-04-14 05:06:07 +03:00
import Hasura.SQL.Types ( CollectableType ( .. ) )
2022-04-28 04:51:58 +03:00
import Hasura.Server.Utils qualified as HSU
2022-04-14 05:06:07 +03:00
import Hasura.Session ( SessionVariable , mkSessionVariable )
2022-07-11 11:04:30 +03:00
import Hasura.Tracing ( noReporter , runTraceTWithReporter )
2022-04-14 05:06:07 +03:00
import Language.GraphQL.Draft.Syntax qualified as GQL
import Network.HTTP.Client qualified as HTTP
2022-09-05 05:42:59 +03:00
import Network.HTTP.Client.Manager
2022-07-11 11:04:30 +03:00
import Servant.Client.Core.HasClient ( ( // ) )
import Servant.Client.Generic ( genericClient )
2022-04-14 05:06:07 +03:00
import Witch qualified
2022-02-25 19:08:18 +03:00
2022-05-02 08:03:12 +03:00
instance BackendMetadata 'DataConnector where
2022-08-10 12:40:57 +03:00
prepareCatalog _ = pure RETDoNothing
2022-09-14 15:59:37 +03:00
type BackendInvalidationKeys 'DataConnector = HashMap DC . DataConnectorName Inc . InvalidationKey
2022-09-05 05:42:59 +03:00
resolveBackendInfo = resolveBackendInfo'
2022-04-14 05:06:07 +03:00
resolveSourceConfig = resolveSourceConfig'
resolveDatabaseMetadata = resolveDatabaseMetadata'
parseBoolExpOperations = parseBoolExpOperations'
parseCollectableType = parseCollectableType'
2022-05-02 08:03:12 +03:00
buildComputedFieldInfo = error " buildComputedFieldInfo: not implemented for the Data Connector backend. "
fetchAndValidateEnumValues = error " fetchAndValidateEnumValues: not implemented for the Data Connector backend. "
buildFunctionInfo = error " buildFunctionInfo: not implemented for the Data Connector backend. "
updateColumnInEventTrigger = error " updateColumnInEventTrigger: not implemented for the Data Connector backend. "
2022-07-19 14:39:44 +03:00
postDropSourceHook _sourceConfig _tableTriggerMap = pure ()
2022-05-25 13:24:41 +03:00
buildComputedFieldBooleanExp _ _ _ _ _ _ =
error " buildComputedFieldBooleanExp: not implemented for the Data Connector backend. "
2022-04-14 05:06:07 +03:00
2022-09-05 05:42:59 +03:00
resolveBackendInfo' ::
( ArrowChoice arr ,
Inc . ArrowCache m arr ,
Inc . ArrowDistribute arr ,
ArrowWriter ( Seq CollectedInfo ) arr ,
MonadIO m ,
HasHttpManagerM m
) =>
2022-09-01 08:27:57 +03:00
Logger Hasura ->
2022-09-14 15:59:37 +03:00
( Inc . Dependency ( HashMap DC . DataConnectorName Inc . InvalidationKey ) , InsOrdHashMap DC . DataConnectorName DC . DataConnectorOptions ) ` arr ` HashMap DC . DataConnectorName DC . DataConnectorInfo
resolveBackendInfo' logger = proc ( invalidationKeys , optionsMap ) -> do
2022-09-05 05:42:59 +03:00
maybeDataConnectorCapabilities <-
( |
Inc . keyed
( \ dataConnectorName dataConnectorOptions -> do
2022-09-14 15:59:37 +03:00
getDataConnectorCapabilitiesIfNeeded -< ( invalidationKeys , dataConnectorName , dataConnectorOptions )
2022-09-05 05:42:59 +03:00
)
| ) ( OMap . toHashMap optionsMap )
returnA -< HashMap . catMaybes maybeDataConnectorCapabilities
where
getDataConnectorCapabilitiesIfNeeded ::
forall arr m .
( ArrowChoice arr ,
Inc . ArrowCache m arr ,
ArrowWriter ( Seq CollectedInfo ) arr ,
MonadIO m ,
HasHttpManagerM m
) =>
2022-09-14 15:59:37 +03:00
( Inc . Dependency ( HashMap DC . DataConnectorName Inc . InvalidationKey ) , DC . DataConnectorName , DC . DataConnectorOptions ) ` arr ` Maybe DC . DataConnectorInfo
getDataConnectorCapabilitiesIfNeeded = Inc . cache proc ( invalidationKeys , dataConnectorName , dataConnectorOptions ) -> do
2022-09-05 05:42:59 +03:00
let metadataObj = MetadataObject ( MODataConnectorAgent dataConnectorName ) $ J . toJSON dataConnectorName
httpMgr <- bindA -< askHttpManager
2022-09-14 15:59:37 +03:00
Inc . dependOn -< Inc . selectKeyD dataConnectorName invalidationKeys
2022-09-05 05:42:59 +03:00
( |
withRecordInconsistency
( liftEitherA <<< bindA -< getDataConnectorCapabilities dataConnectorOptions httpMgr
)
| ) metadataObj
getDataConnectorCapabilities ::
MonadIO m =>
DC . DataConnectorOptions ->
HTTP . Manager ->
m ( Either QErr DC . DataConnectorInfo )
getDataConnectorCapabilities options @ DC . DataConnectorOptions { .. } manager = runExceptT do
2022-10-11 03:25:07 +03:00
capabilitiesU <-
2022-09-05 05:42:59 +03:00
runTraceTWithReporter noReporter " capabilities "
. flip runAgentClientT ( AgentClientContext logger _dcoUri manager Nothing )
$ genericClient // API . _capabilities
2022-10-11 03:25:07 +03:00
let defaultAction = throw400 DataConnectorError " Unexpected data connector capabilities response - Unexpected Type "
capabilitiesAction API . CapabilitiesResponse { .. } = pure $ DC . DataConnectorInfo options _crCapabilities _crConfigSchemaResponse
capabilitiesCase defaultAction capabilitiesAction errorAction capabilitiesU
2022-09-01 08:27:57 +03:00
2022-04-14 05:06:07 +03:00
resolveSourceConfig' ::
MonadIO m =>
2022-07-11 11:04:30 +03:00
Logger Hasura ->
2022-04-14 05:06:07 +03:00
SourceName ->
2022-05-02 08:03:12 +03:00
DC . ConnSourceConfig ->
BackendSourceKind 'DataConnector ->
2022-09-05 05:42:59 +03:00
HashMap DC . DataConnectorName DC . DataConnectorInfo ->
2022-04-14 05:06:07 +03:00
Environment ->
2022-07-27 10:18:36 +03:00
HTTP . Manager ->
2022-05-02 08:03:12 +03:00
m ( Either QErr DC . SourceConfig )
2022-09-01 08:27:57 +03:00
resolveSourceConfig'
logger
sourceName
2022-09-14 15:59:37 +03:00
csc @ DC . ConnSourceConfig { template , timeout , value = originalConfig }
2022-09-01 08:27:57 +03:00
( DataConnectorKind dataConnectorName )
2022-09-05 05:42:59 +03:00
backendInfo
2022-09-01 08:27:57 +03:00
env
manager = runExceptT do
2022-09-05 05:42:59 +03:00
DC . DataConnectorInfo { DC . _dciOptions = DC . DataConnectorOptions { .. } , .. } <-
Map . lookup dataConnectorName backendInfo
` onNothing ` throw400 DataConnectorError ( " Data connector named " <> toTxt dataConnectorName <<> " was not found in the data connector backend info " )
2022-07-19 04:51:42 +03:00
2022-09-01 08:27:57 +03:00
transformedConfig <- transformConnSourceConfig csc [ ( " $session " , J . object [] ) , ( " $env " , J . toJSON env ) ] env
2022-06-03 11:06:31 +03:00
2022-09-05 05:42:59 +03:00
validateConfiguration sourceName dataConnectorName _dciConfigSchemaResponse transformedConfig
2022-07-11 11:04:30 +03:00
2022-10-11 03:25:07 +03:00
schemaResponseU <-
2022-09-01 08:27:57 +03:00
runTraceTWithReporter noReporter " resolve source "
. flip runAgentClientT ( AgentClientContext logger _dcoUri manager ( DC . sourceTimeoutMicroseconds <$> timeout ) )
$ ( genericClient // API . _schema ) ( toTxt sourceName ) transformedConfig
2022-06-03 11:06:31 +03:00
2022-10-11 03:25:07 +03:00
let defaultAction = throw400 DataConnectorError " Unexpected data connector schema response - Unexpected Type "
schemaResponse <- schemaCase defaultAction pure errorAction schemaResponseU
2022-09-01 08:27:57 +03:00
pure
DC . SourceConfig
{ _scEndpoint = _dcoUri ,
_scConfig = originalConfig ,
_scTemplate = template ,
2022-09-05 05:42:59 +03:00
_scCapabilities = _dciCapabilities ,
2022-09-01 08:27:57 +03:00
_scSchema = schemaResponse ,
_scManager = manager ,
_scTimeoutMicroseconds = ( DC . sourceTimeoutMicroseconds <$> timeout ) ,
_scDataConnectorName = dataConnectorName
}
2022-04-14 05:06:07 +03:00
2022-05-05 08:18:43 +03:00
validateConfiguration ::
2022-07-11 11:04:30 +03:00
MonadError QErr m =>
2022-05-05 08:18:43 +03:00
SourceName ->
DC . DataConnectorName ->
2022-07-11 11:04:30 +03:00
API . ConfigSchemaResponse ->
2022-05-05 08:18:43 +03:00
API . Config ->
2022-07-11 11:04:30 +03:00
m ()
validateConfiguration sourceName dataConnectorName configSchema config = do
let errors = API . validateConfigAgainstConfigSchema configSchema config
2022-05-27 16:33:38 +03:00
unless ( null errors ) $
let errorsText = Text . unlines ( ( " - " <> ) . Text . pack <$> errors )
in throw400
DataConnectorError
( " Configuration for source " <> sourceName <<> " is not valid based on the configuration schema declared by the " <> dataConnectorName <<> " data connector agent. Errors: \ n " <> errorsText )
2022-05-05 08:18:43 +03:00
2022-04-14 05:06:07 +03:00
resolveDatabaseMetadata' ::
Applicative m =>
2022-05-02 08:03:12 +03:00
SourceMetadata 'DataConnector ->
DC . SourceConfig ->
2022-04-14 05:06:07 +03:00
SourceTypeCustomization ->
2022-05-02 08:03:12 +03:00
m ( Either QErr ( ResolvedSource 'DataConnector ) )
resolveDatabaseMetadata' _ sc @ ( DC . SourceConfig { _scSchema = API . SchemaResponse { .. } } ) customization =
2022-08-24 00:46:10 +03:00
-- We need agents to provide the foreign key contraints inside 'API.SchemaResponse'
2022-09-21 08:11:53 +03:00
let foreignKeys = fmap API . _tiForeignKeys _srTables
2022-08-24 00:46:10 +03:00
tables = Map . fromList $ do
2022-09-21 08:11:53 +03:00
API . TableInfo { .. } <- _srTables
2022-10-10 05:23:43 +03:00
let primaryKeyColumns = Seq . fromList $ coerce <$> _tiPrimaryKey
2022-04-14 05:06:07 +03:00
let meta =
2022-04-28 04:51:58 +03:00
RQL . T . T . DBTableMetadata
2022-04-14 05:06:07 +03:00
{ _ptmiOid = OID 0 ,
_ptmiColumns = do
2022-09-21 08:11:53 +03:00
API . ColumnInfo { .. } <- _tiColumns
2022-04-14 05:06:07 +03:00
pure $
2022-04-28 04:51:58 +03:00
RQL . T . C . RawColumnInfo
2022-09-21 08:11:53 +03:00
{ rciName = Witch . from _ciName ,
2022-04-14 05:06:07 +03:00
rciPosition = 1 ,
2022-09-21 08:11:53 +03:00
rciType = Witch . from _ciType ,
rciIsNullable = _ciNullable ,
rciDescription = fmap GQL . Description _ciDescription ,
2022-04-14 05:06:07 +03:00
-- TODO: Add Column Mutability to the 'TableInfo'
2022-04-28 04:51:58 +03:00
rciMutability = RQL . T . C . ColumnMutability False False
2022-04-14 05:06:07 +03:00
} ,
2022-09-20 09:18:46 +03:00
_ptmiPrimaryKey = RQL . T . T . PrimaryKey ( RQL . T . T . Constraint ( DC . ConstraintName " " ) ( OID 0 ) ) <$> NESeq . nonEmptySeq primaryKeyColumns ,
2022-04-14 05:06:07 +03:00
_ptmiUniqueConstraints = mempty ,
2022-08-24 00:46:10 +03:00
_ptmiForeignKeys = buildForeignKeySet foreignKeys ,
2022-04-28 04:51:58 +03:00
_ptmiViewInfo = Just $ RQL . T . T . ViewInfo False False False ,
2022-09-21 08:11:53 +03:00
_ptmiDescription = fmap PGDescription _tiDescription ,
2022-04-14 05:06:07 +03:00
_ptmiExtraTableMetadata = ()
}
2022-09-21 08:11:53 +03:00
pure ( coerce _tiName , meta )
2022-04-14 05:06:07 +03:00
in pure $
pure $
ResolvedSource
{ _rsConfig = sc ,
_rsCustomization = customization ,
_rsTables = tables ,
_rsFunctions = mempty ,
Move, document, and prune action types and custom types types.
### Description
This PR is a first step in a series of cleanups of action relationships. This first step does not contain any behavioral change, and it simply reorganizes / prunes / rearranges / documents the code. Mainly:
- it divides some files in RQL.Types between metadata types, schema cache types, execution types;
- it renames some types for consistency;
- it minimizes exports and prunes unnecessary types;
- it moves some types in places where they make more sense;
- it replaces uses of `DMap BackendTag` with `BackendMap`.
Most of the "movement" within files re-organizes declarations in a "top-down" fashion, by moving all TH splices to the end of the file, which avoids order or declarations mattering.
### Optional list types
One main type change this PR makes is a replacement of variant list types in `CustomTypes.hs`; we had `Maybe [a]`, or sometimes `Maybe (NonEmpty a)`. This PR harmonizes all of them to `[a]`, as most of the code would use them as such, by doing `fromMaybe []` or `maybe [] toList`.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4613
GitOrigin-RevId: bc624e10df587eba862ff27a5e8021b32d0d78a2
2022-06-07 18:43:34 +03:00
_rsScalars = mempty
2022-04-14 05:06:07 +03:00
}
2022-08-24 00:46:10 +03:00
-- | Construct a 'HashSet' 'RQL.T.T.ForeignKeyMetadata'
-- 'DataConnector' to build the foreign key constraints in the table
-- metadata.
2022-10-10 05:23:43 +03:00
buildForeignKeySet :: [ API . ForeignKeys ] -> HashSet ( RQL . T . T . ForeignKeyMetadata 'DataConnector )
buildForeignKeySet foreignKeys =
2022-08-24 00:46:10 +03:00
HashSet . fromList $
join $
foreignKeys <&> \ ( API . ForeignKeys constraints ) ->
constraints & HashMap . foldMapWithKey @ [ RQL . T . T . ForeignKeyMetadata 'DataConnector ]
\ constraintName API . Constraint { .. } -> maybeToList do
2022-10-06 02:23:49 +03:00
let columnMapAssocList = HashMap . foldrWithKey' ( \ ( API . ColumnName k ) ( API . ColumnName v ) acc -> ( DC . ColumnName k , DC . ColumnName v ) : acc ) [] _cColumnMapping
2022-08-24 00:46:10 +03:00
columnMapping <- NEHashMap . fromList columnMapAssocList
let foreignKey =
RQL . T . T . ForeignKey
{ _fkConstraint = RQL . T . T . Constraint ( Witch . from constraintName ) ( OID 1 ) ,
2022-09-21 08:11:53 +03:00
_fkForeignTable = Witch . from _cForeignTable ,
2022-08-24 00:46:10 +03:00
_fkColumnMapping = columnMapping
}
pure $ RQL . T . T . ForeignKeyMetadata foreignKey
2022-04-14 05:06:07 +03:00
-- | This is needed to get permissions to work
parseBoolExpOperations' ::
forall m v .
2022-06-02 05:06:45 +03:00
( MonadError QErr m , SchemaCache . TableCoreInfoRM 'DataConnector m ) =>
2022-05-02 08:03:12 +03:00
RQL . T . C . ValueParser 'DataConnector m v ->
2022-09-20 09:18:46 +03:00
DC . TableName ->
2022-05-02 08:03:12 +03:00
RQL . T . T . FieldInfoMap ( RQL . T . T . FieldInfo 'DataConnector ) ->
RQL . T . C . ColumnReference 'DataConnector ->
2022-04-14 05:06:07 +03:00
J . Value ->
2022-05-02 08:03:12 +03:00
m [ OpExpG 'DataConnector v ]
2022-06-02 05:06:45 +03:00
parseBoolExpOperations' rhsParser rootTable fieldInfoMap columnRef value =
withPathK ( toTxt columnRef ) $ parseOperations value
2022-04-14 05:06:07 +03:00
where
2022-06-02 05:06:45 +03:00
columnType :: RQL . T . C . ColumnType 'DataConnector
columnType = RQL . T . C . columnReferenceType columnRef
2022-04-14 05:06:07 +03:00
parseWithTy ty = rhsParser ( CollectableTypeScalar ty )
2022-06-02 05:06:45 +03:00
parseOperations :: J . Value -> m [ OpExpG 'DataConnector v ]
parseOperations = \ case
2022-06-08 18:31:28 +03:00
J . Object o -> traverse ( parseOperation . first K . toText ) $ KM . toList o
2022-04-14 05:06:07 +03:00
v -> pure . AEQ False <$> parseWithTy columnType v
2022-06-02 05:06:45 +03:00
parseOperation :: ( Text , J . Value ) -> m ( OpExpG 'DataConnector v )
parseOperation ( opStr , val ) = withPathK opStr $
2022-04-14 05:06:07 +03:00
case opStr of
" _eq " -> parseEq
" $eq " -> parseEq
" _neq " -> parseNeq
" $neq " -> parseNeq
" _gt " -> parseGt
" $gt " -> parseGt
" _lt " -> parseLt
" $lt " -> parseLt
" _gte " -> parseGte
" $gte " -> parseGte
" _lte " -> parseLte
" $lte " -> parseLte
2022-04-28 04:51:58 +03:00
" _in " -> parseIn
2022-06-02 05:06:45 +03:00
" $in " -> parseIn
2022-04-28 04:51:58 +03:00
" _nin " -> parseNin
2022-06-02 05:06:45 +03:00
" $nin " -> parseNin
" _is_null " -> parseIsNull
" $is_null " -> parseIsNull
" _ceq " -> parseCeq
" $ceq " -> parseCeq
" _cneq " -> parseCne
" $cneq " -> parseCne
" _cgt " -> parseCgt
" $cgt " -> parseCgt
" _clt " -> parseClt
" $clt " -> parseClt
" _cgte " -> parseCgte
" $cgte " -> parseCgte
" _clte " -> parseClte
" $clte " -> parseClte
2022-04-14 05:06:07 +03:00
-- "_like" -> parseLike
2022-06-02 05:06:45 +03:00
-- "$like" -> parseLike
2022-04-14 05:06:07 +03:00
--
-- "_nlike" -> parseNlike
2022-06-02 05:06:45 +03:00
-- "$nlike" -> parseNlike
--
-- "_cast" -> parseCast
-- "$cast" -> parseCast
2022-04-14 05:06:07 +03:00
2022-10-01 17:47:12 +03:00
x -> throw400 UnexpectedPayload $ " Unknown operator: " <> x
2022-04-14 05:06:07 +03:00
where
parseOne = parseWithTy columnType val
2022-04-28 04:51:58 +03:00
parseManyWithType ty = rhsParser ( CollectableTypeArray ty ) val
2022-04-14 05:06:07 +03:00
parseEq = AEQ False <$> parseOne
parseNeq = ANE False <$> parseOne
2022-06-02 05:06:45 +03:00
parseIn = AIN <$> parseManyWithType columnType
parseNin = ANIN <$> parseManyWithType columnType
2022-04-14 05:06:07 +03:00
parseGt = AGT <$> parseOne
parseLt = ALT <$> parseOne
parseGte = AGTE <$> parseOne
parseLte = ALTE <$> parseOne
2022-06-02 05:06:45 +03:00
parseIsNull = bool ANISNOTNULL ANISNULL <$> decodeValue val
parseCeq = CEQ <$> decodeAndValidateRhsCol val
parseCne = CNE <$> decodeAndValidateRhsCol val
parseCgt = CGT <$> decodeAndValidateRhsCol val
parseClt = CLT <$> decodeAndValidateRhsCol val
parseCgte = CGTE <$> decodeAndValidateRhsCol val
parseClte = CLTE <$> decodeAndValidateRhsCol val
decodeAndValidateRhsCol :: J . Value -> m ( RootOrCurrentColumn 'DataConnector )
decodeAndValidateRhsCol v = case v of
J . String _ -> go IsCurrent fieldInfoMap v
J . Array path -> case toList path of
[] -> throw400 Unexpected " path cannot be empty "
[ col ] -> go IsCurrent fieldInfoMap col
[ J . String " $ " , col ] -> do
rootTableInfo <-
SchemaCache . lookupTableCoreInfo rootTable
>>= flip onNothing ( throw500 $ " unexpected: " <> rootTable <<> " doesn't exist " )
go IsRoot ( RQL . T . T . _tciFieldInfoMap rootTableInfo ) col
_ -> throw400 NotSupported " Relationship references are not supported in column comparison RHS "
_ -> throw400 Unexpected " a boolean expression JSON must be either a string or an array "
where
go rootInfo fieldInfoMap' columnValue = do
colName <- decodeValue columnValue
colInfo <- validateRhsColumn fieldInfoMap' colName
pure $ RootOrCurrentColumn rootInfo colInfo
2022-09-20 09:18:46 +03:00
validateRhsColumn :: RQL . T . T . FieldInfoMap ( RQL . T . T . FieldInfo 'DataConnector ) -> DC . ColumnName -> m DC . ColumnName
2022-06-02 05:06:45 +03:00
validateRhsColumn fieldInfoMap' rhsCol = do
rhsType <- RQL . T . T . askColumnType fieldInfoMap' rhsCol " column operators can only compare table columns "
when ( columnType /= rhsType ) $
throw400 UnexpectedPayload $
" incompatible column types: "
<> columnRef <<> " has type "
<> columnType <<> " , but "
<> rhsCol <<> " has type " <>> rhsType
pure rhsCol
2022-04-14 05:06:07 +03:00
parseCollectableType' ::
MonadError QErr m =>
2022-05-02 08:03:12 +03:00
CollectableType ( RQL . T . C . ColumnType 'DataConnector ) ->
2022-04-14 05:06:07 +03:00
J . Value ->
2022-05-02 08:03:12 +03:00
m ( PartialSQLExp 'DataConnector )
2022-04-14 05:06:07 +03:00
parseCollectableType' collectableType = \ case
J . String t
2022-04-28 04:51:58 +03:00
| HSU . isSessionVariable t -> pure $ mkTypedSessionVar collectableType $ mkSessionVariable t
| HSU . isReqUserId t -> pure $ mkTypedSessionVar collectableType HSU . userIdHeader
2022-04-14 05:06:07 +03:00
val -> case collectableType of
CollectableTypeScalar scalarType ->
2022-09-20 09:18:46 +03:00
PSESQLExp . DC . ValueLiteral <$> RQL . T . C . parseScalarValueColumnType scalarType val
2022-04-14 05:06:07 +03:00
CollectableTypeArray _ ->
2022-05-02 08:03:12 +03:00
throw400 NotSupported " Array types are not supported by the Data Connector backend "
2022-04-14 05:06:07 +03:00
mkTypedSessionVar ::
2022-05-02 08:03:12 +03:00
CollectableType ( RQL . T . C . ColumnType 'DataConnector ) ->
2022-04-14 05:06:07 +03:00
SessionVariable ->
2022-05-02 08:03:12 +03:00
PartialSQLExp 'DataConnector
2022-04-14 05:06:07 +03:00
mkTypedSessionVar columnType =
PSESessVar ( columnTypeToScalarType <$> columnType )
2022-09-20 09:18:46 +03:00
columnTypeToScalarType :: RQL . T . C . ColumnType 'DataConnector -> DC . ScalarType
2022-04-14 05:06:07 +03:00
columnTypeToScalarType = \ case
2022-04-28 04:51:58 +03:00
RQL . T . C . ColumnScalar scalarType -> scalarType
-- NOTE: This should be unreachable:
2022-09-20 09:18:46 +03:00
RQL . T . C . ColumnEnumReference _ -> DC . StringTy
2022-10-11 03:25:07 +03:00
errorAction :: MonadError QErr m => API . ErrorResponse -> m a
errorAction e = throw400WithDetail DataConnectorError ( errorResponseSummary e ) ( _crDetails e )