2022-05-02 08:03:12 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
|
2022-07-15 06:27:31 +03:00
|
|
|
module Hasura.Backends.DataConnector.Adapter.Backend (CustomBooleanOperator (..)) where
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2022-07-15 06:27:31 +03:00
|
|
|
import Data.Aeson qualified as J (ToJSON (..), Value)
|
|
|
|
import Data.Aeson.Extended (ToJSONKeyValue (..))
|
|
|
|
import Data.Aeson.Key (fromText)
|
2022-08-04 11:34:45 +03:00
|
|
|
import Data.List.NonEmpty qualified as NonEmpty
|
|
|
|
import Data.Text qualified as Text
|
2022-05-26 14:54:30 +03:00
|
|
|
import Data.Text.Casing qualified as C
|
2022-08-04 11:34:45 +03:00
|
|
|
import Data.Text.Extended ((<<>))
|
2022-05-02 08:03:12 +03:00
|
|
|
import Hasura.Backends.DataConnector.Adapter.Types qualified as Adapter
|
2022-07-20 08:20:49 +03:00
|
|
|
import Hasura.Backends.DataConnector.IR.Aggregate qualified as IR.A
|
2022-05-02 08:03:12 +03:00
|
|
|
import Hasura.Backends.DataConnector.IR.Column qualified as IR.C
|
|
|
|
import Hasura.Backends.DataConnector.IR.Function qualified as IR.F
|
|
|
|
import Hasura.Backends.DataConnector.IR.OrderBy qualified as IR.O
|
|
|
|
import Hasura.Backends.DataConnector.IR.Scalar.Type qualified as IR.S.T
|
|
|
|
import Hasura.Backends.DataConnector.IR.Scalar.Value qualified as IR.S.V
|
|
|
|
import Hasura.Backends.DataConnector.IR.Table as IR.T
|
2022-06-02 05:06:45 +03:00
|
|
|
import Hasura.Base.Error (Code (ValidationFailed), QErr, runAesonParser, throw400)
|
2022-07-15 06:27:31 +03:00
|
|
|
import Hasura.Incremental
|
2022-05-02 08:03:12 +03:00
|
|
|
import Hasura.Prelude
|
2022-07-15 06:27:31 +03:00
|
|
|
import Hasura.RQL.IR.BoolExp
|
2022-07-20 08:20:49 +03:00
|
|
|
import Hasura.RQL.Types.Backend (Backend (..), ComputedFieldReturnType, SupportedNamingCase (..), XDisable, XEnable)
|
2022-05-02 08:03:12 +03:00
|
|
|
import Hasura.SQL.Backend (BackendType (DataConnector))
|
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
|
|
|
|
-- | An alias for '()' indicating that a particular associated type has not yet
|
|
|
|
-- been implemented for the 'DataConnector' backend.
|
|
|
|
--
|
|
|
|
-- '()' is used (rather than a type with an empty data constructor) because it
|
|
|
|
-- comes with many of the instances that these associated types require.
|
|
|
|
--
|
|
|
|
-- This alias should /not/ be exported from this module, and it's only defined
|
|
|
|
-- for clarity.
|
|
|
|
type Unimplemented = ()
|
|
|
|
|
|
|
|
instance Backend 'DataConnector where
|
2022-08-18 01:13:32 +03:00
|
|
|
type BackendConfig 'DataConnector = InsOrdHashMap Adapter.DataConnectorName Adapter.DataConnectorOptions
|
2022-09-05 05:42:59 +03:00
|
|
|
type BackendInfo 'DataConnector = HashMap Adapter.DataConnectorName Adapter.DataConnectorInfo
|
2022-05-02 08:03:12 +03:00
|
|
|
type SourceConfig 'DataConnector = Adapter.SourceConfig
|
|
|
|
type SourceConnConfiguration 'DataConnector = Adapter.ConnSourceConfig
|
|
|
|
|
|
|
|
type TableName 'DataConnector = IR.T.Name
|
|
|
|
type FunctionName 'DataConnector = IR.F.Name
|
|
|
|
type RawFunctionInfo 'DataConnector = XDisable
|
2022-05-25 13:24:41 +03:00
|
|
|
type FunctionArgument 'DataConnector = XDisable
|
2022-08-24 00:46:10 +03:00
|
|
|
type ConstraintName 'DataConnector = IR.T.ConstraintName
|
2022-08-19 10:00:46 +03:00
|
|
|
type BasicOrderType 'DataConnector = IR.O.OrderDirection
|
2022-05-02 08:03:12 +03:00
|
|
|
type NullsOrderType 'DataConnector = Unimplemented
|
2022-07-20 08:20:49 +03:00
|
|
|
type CountType 'DataConnector = IR.A.CountAggregate
|
2022-05-02 08:03:12 +03:00
|
|
|
type Column 'DataConnector = IR.C.Name
|
2022-09-06 07:24:46 +03:00
|
|
|
type ScalarValue 'DataConnector = J.Value
|
2022-05-02 08:03:12 +03:00
|
|
|
type ScalarType 'DataConnector = IR.S.T.Type
|
2022-06-02 05:06:45 +03:00
|
|
|
|
|
|
|
-- This does not actually have to be the full IR Expression, in fact it is only
|
|
|
|
-- required to represent literals, so we use a special type for that.
|
|
|
|
-- The 'SQLExpression' type family should be removed in a future refactor
|
|
|
|
type SQLExpression 'DataConnector = IR.S.V.Literal
|
2022-05-03 11:58:56 +03:00
|
|
|
type ScalarSelectionArguments 'DataConnector = Void
|
2022-07-15 06:27:31 +03:00
|
|
|
type BooleanOperators 'DataConnector = CustomBooleanOperator
|
2022-05-02 08:03:12 +03:00
|
|
|
type ExtraTableMetadata 'DataConnector = Unimplemented
|
2022-05-04 17:52:29 +03:00
|
|
|
type ComputedFieldDefinition 'DataConnector = Unimplemented
|
2022-05-25 13:24:41 +03:00
|
|
|
type FunctionArgumentExp 'DataConnector = Const Unimplemented
|
|
|
|
type ComputedFieldImplicitArguments 'DataConnector = Unimplemented
|
|
|
|
type ComputedFieldReturn 'DataConnector = Unimplemented
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
type XComputedField 'DataConnector = XDisable
|
|
|
|
type XRelay 'DataConnector = XDisable
|
2022-07-20 08:20:49 +03:00
|
|
|
type XNodesAgg 'DataConnector = XEnable
|
2022-05-02 08:03:12 +03:00
|
|
|
type XNestedInserts 'DataConnector = XDisable
|
|
|
|
type XStreamingSubscription 'DataConnector = XDisable
|
|
|
|
|
2022-09-02 09:33:21 +03:00
|
|
|
type HealthCheckTest 'DataConnector = Void
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
isComparableType :: ScalarType 'DataConnector -> Bool
|
2022-08-02 03:22:05 +03:00
|
|
|
isComparableType = \case
|
|
|
|
IR.S.T.Number -> True
|
|
|
|
IR.S.T.String -> True
|
|
|
|
IR.S.T.Bool -> False
|
2022-09-06 07:24:46 +03:00
|
|
|
IR.S.T.Custom _ -> False -- TODO: extend Capabilities for custom types
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
isNumType :: ScalarType 'DataConnector -> Bool
|
|
|
|
isNumType IR.S.T.Number = True
|
|
|
|
isNumType _ = False
|
|
|
|
|
|
|
|
textToScalarValue :: Maybe Text -> ScalarValue 'DataConnector
|
|
|
|
textToScalarValue = error "textToScalarValue: not implemented for the Data Connector backend."
|
|
|
|
|
|
|
|
parseScalarValue :: ScalarType 'DataConnector -> J.Value -> Either QErr (ScalarValue 'DataConnector)
|
2022-06-02 05:06:45 +03:00
|
|
|
parseScalarValue type' value = runAesonParser (IR.S.V.parseValue type') value
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
scalarValueToJSON :: ScalarValue 'DataConnector -> J.Value
|
|
|
|
scalarValueToJSON = error "scalarValueToJSON: not implemented for the Data Connector backend."
|
|
|
|
|
|
|
|
functionToTable :: FunctionName 'DataConnector -> TableName 'DataConnector
|
|
|
|
functionToTable = error "functionToTable: not implemented for the Data Connector backend."
|
|
|
|
|
2022-05-04 17:52:29 +03:00
|
|
|
computedFieldFunction :: ComputedFieldDefinition 'DataConnector -> FunctionName 'DataConnector
|
|
|
|
computedFieldFunction = error "computedFieldFunction: not implemented for the Data Connector backend"
|
|
|
|
|
2022-05-25 13:24:41 +03:00
|
|
|
computedFieldReturnType :: ComputedFieldReturn 'DataConnector -> ComputedFieldReturnType 'DataConnector
|
|
|
|
computedFieldReturnType = error "computedFieldReturnType: not implemented for the Data Connector backend"
|
|
|
|
|
|
|
|
fromComputedFieldImplicitArguments :: v -> ComputedFieldImplicitArguments 'DataConnector -> [FunctionArgumentExp 'DataConnector v]
|
|
|
|
fromComputedFieldImplicitArguments = error "fromComputedFieldImplicitArguments: not implemented for the Data Connector backend"
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
-- phil said this was cursed
|
|
|
|
tableToFunction :: TableName 'DataConnector -> FunctionName 'DataConnector
|
|
|
|
tableToFunction = coerce
|
|
|
|
|
|
|
|
tableGraphQLName :: TableName 'DataConnector -> Either QErr G.Name
|
2022-08-04 11:34:45 +03:00
|
|
|
tableGraphQLName name = do
|
|
|
|
let snakedName = snakeCaseTableName @'DataConnector name
|
|
|
|
G.mkName snakedName
|
|
|
|
`onNothing` throw400 ValidationFailed ("TableName " <> snakedName <> " is not a valid GraphQL identifier")
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
functionGraphQLName :: FunctionName 'DataConnector -> Either QErr G.Name
|
|
|
|
functionGraphQLName = error "functionGraphQLName: not implemented for the Data Connector backend."
|
|
|
|
|
|
|
|
snakeCaseTableName :: TableName 'DataConnector -> Text
|
2022-08-04 11:34:45 +03:00
|
|
|
snakeCaseTableName = Text.intercalate "_" . NonEmpty.toList . IR.T.unName
|
2022-05-26 14:54:30 +03:00
|
|
|
|
|
|
|
getTableIdentifier :: TableName 'DataConnector -> Either QErr C.GQLNameIdentifier
|
2022-08-17 15:46:36 +03:00
|
|
|
getTableIdentifier name@(IR.T.Name (prefix :| suffixes)) =
|
|
|
|
let identifier = do
|
|
|
|
namePrefix <- G.mkName prefix
|
|
|
|
nameSuffixes <- traverse G.mkNameSuffix suffixes
|
|
|
|
pure $ C.fromAutogeneratedTuple (namePrefix, nameSuffixes)
|
|
|
|
in identifier
|
|
|
|
`onNothing` throw400 ValidationFailed ("TableName " <> name <<> " is not a valid GraphQL identifier")
|
2022-05-26 14:54:30 +03:00
|
|
|
|
|
|
|
namingConventionSupport :: SupportedNamingCase
|
|
|
|
namingConventionSupport = OnlyHasuraCase
|
2022-07-15 06:27:31 +03:00
|
|
|
|
|
|
|
data CustomBooleanOperator a = CustomBooleanOperator
|
|
|
|
{ _cboName :: Text,
|
|
|
|
_cboRHS :: Maybe (Either (RootOrCurrentColumn 'DataConnector) a) -- TODO turn Either into a specific type
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Generic, Foldable, Functor, Traversable, Show)
|
|
|
|
|
|
|
|
instance NFData a => NFData (CustomBooleanOperator a)
|
|
|
|
|
|
|
|
instance Hashable a => Hashable (CustomBooleanOperator a)
|
|
|
|
|
|
|
|
instance Cacheable a => Cacheable (CustomBooleanOperator a)
|
|
|
|
|
|
|
|
instance J.ToJSON a => ToJSONKeyValue (CustomBooleanOperator a) where
|
|
|
|
toJSONKeyValue CustomBooleanOperator {..} = (fromText _cboName, J.toJSON _cboRHS)
|