Experimental backend adapter

This commit introduces an "experimental" backend adapter to the GraphQL Engine.

It defines a high-level interface which will eventually be used as the basis for implementing separate data source query generation & marshaling services that communicate with the GraphQL Engine Server via some protocol.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2684
Co-authored-by: awjchen <13142944+awjchen@users.noreply.github.com>
Co-authored-by: Chris Parks <592078+cdparks@users.noreply.github.com>
GitOrigin-RevId: 4463b682142ad6e069e223b88b14db511f634768
This commit is contained in:
jkachmar 2021-12-21 19:10:28 -05:00 committed by hasura-bot
parent cca3831180
commit 63cff8b731
27 changed files with 835 additions and 1 deletions

View File

@ -449,6 +449,7 @@ constraints: any.Cabal ==3.2.0.0,
wcwidth -cli +split-base,
any.websockets ==0.12.7.2,
websockets -example,
any.witch ==0.3.4.1,
any.wl-pprint-annotated ==0.1.0.1,
any.word8 ==0.1.3,
any.wreq ==0.5.3.3,

View File

@ -313,6 +313,11 @@ library
, mysql
, mysql-simple
-- TODO(jkachmar): re-organize this before merging
-- dynamic backends stuff
, uri-bytestring
, witch
if !flag(profiling)
-- ghc-heap-view can't be built with profiling
build-depends: ghc-heap-view
@ -452,6 +457,27 @@ library
, Hasura.Backends.MySQL.ToQuery
, Hasura.Backends.MySQL.Instances.API
-- XXX(jkachmar): This needs to be renamed before we
-- stabilize it.
, Hasura.Experimental.Adapter.API
, Hasura.Experimental.Adapter.Backend
, Hasura.Experimental.Adapter.Execute
, Hasura.Experimental.Adapter.Metadata
, Hasura.Experimental.Adapter.Schema
, Hasura.Experimental.Adapter.Transport
, Hasura.Experimental.IR.Column
, Hasura.Experimental.IR.Expression
, Hasura.Experimental.IR.Function
, Hasura.Experimental.IR.Name
, Hasura.Experimental.IR.OrderBy
, Hasura.Experimental.IR.Query
, Hasura.Experimental.IR.Scalar.Type
, Hasura.Experimental.IR.Scalar.Value
, Hasura.Experimental.IR.Table
, Hasura.Experimental.Schema.Column
, Hasura.Experimental.Schema.Table
-- Exposed for benchmark:
, Hasura.Cache.Bounded
, Hasura.Logging
, Hasura.HTTP

View File

@ -0,0 +1,13 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Experimental.Adapter.API () where
--------------------------------------------------------------------------------
import Hasura.SQL.Backend (BackendType (Experimental))
import Hasura.Server.API.Backend (BackendAPI (..))
--------------------------------------------------------------------------------
instance BackendAPI 'Experimental where
metadataV1CommandParsers = []

View File

@ -0,0 +1,102 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Experimental.Adapter.Backend () where
--------------------------------------------------------------------------------
import Data.Aeson qualified as J (Value)
import Hasura.Base.Error (Code (ValidationFailed), QErr, throw400)
import Hasura.Experimental.IR.Column qualified as Column (Name)
import Hasura.Experimental.IR.Expression (Expression, Operator)
import Hasura.Experimental.IR.Function qualified as Function (Name)
import Hasura.Experimental.IR.Name as Name (Name (unName))
import Hasura.Experimental.IR.OrderBy (OrderType)
import Hasura.Experimental.IR.Scalar.Type qualified as Scalar (Type)
import Hasura.Experimental.IR.Scalar.Type qualified as Scalar.Type (Type (..))
import Hasura.Experimental.IR.Scalar.Value qualified as Scalar (Value)
import Hasura.Experimental.IR.Table as Table (Name)
import Hasura.Prelude
import Hasura.RQL.Types.Backend (Backend (..), XDisable)
import Hasura.RQL.Types.Common as RQL (boolScalar, floatScalar, stringScalar)
import Hasura.SQL.Backend (BackendType (Experimental))
import Language.GraphQL.Draft.Syntax qualified as G
--------------------------------------------------------------------------------
-- | An alias for '()' indicating that a particular associated type has not yet
-- been implemented for the 'Experimental' 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 'Experimental where
type SourceConfig 'Experimental = Unimplemented
type SourceConnConfiguration 'Experimental = Unimplemented
type TableName 'Experimental = Table.Name
type FunctionName 'Experimental = Function.Name
type RawFunctionInfo 'Experimental = XDisable
type FunctionArgType 'Experimental = XDisable
type ConstraintName 'Experimental = Unimplemented
type BasicOrderType 'Experimental = OrderType
type NullsOrderType 'Experimental = Unimplemented
type CountType 'Experimental = Unimplemented
type Column 'Experimental = Column.Name
type ScalarValue 'Experimental = Scalar.Value
type ScalarType 'Experimental = Scalar.Type
type SQLExpression 'Experimental = Expression
type SQLOperator 'Experimental = Operator
type BooleanOperators 'Experimental = Const XDisable
type ExtraTableMetadata 'Experimental = Unimplemented
type XComputedField 'Experimental = XDisable
type XRelay 'Experimental = XDisable
type XNodesAgg 'Experimental = XDisable
type XNestedInserts 'Experimental = XDisable
functionArgScalarType :: FunctionArgType 'Experimental -> ScalarType 'Experimental
functionArgScalarType = error "functionArgScalarType: not implemented yet"
isComparableType :: ScalarType 'Experimental -> Bool
isComparableType = isNumType @'Experimental
isNumType :: ScalarType 'Experimental -> Bool
isNumType Scalar.Type.Number = True
isNumType _ = False
textToScalarValue :: Maybe Text -> ScalarValue 'Experimental
textToScalarValue = error "textToScalarValue: Experimental backend does not support this operation yet."
parseScalarValue :: ScalarType 'Experimental -> J.Value -> Either QErr (ScalarValue 'Experimental)
parseScalarValue = error "parseScalarValue: Experimental backend does not support this operation yet."
scalarValueToJSON :: ScalarValue 'Experimental -> J.Value
scalarValueToJSON = error "scalarValueToJSON: Experimental backend does not support this operation yet."
functionToTable :: FunctionName 'Experimental -> TableName 'Experimental
functionToTable = error "functionToTable: Experimental backend does not support this operation yet."
-- phil said this was cursed
tableToFunction :: TableName 'Experimental -> FunctionName 'Experimental
tableToFunction = coerce
tableGraphQLName :: TableName 'Experimental -> Either QErr G.Name
tableGraphQLName name =
G.mkName (Name.unName name)
`onNothing` throw400 ValidationFailed ("TableName " <> Name.unName name <> " is not a valid GraphQL identifier")
functionGraphQLName :: FunctionName 'Experimental -> Either QErr G.Name
functionGraphQLName = error "functionGraphQLName: Experimental backend does not support this operation yet."
scalarTypeGraphQLName :: ScalarType 'Experimental -> Either QErr G.Name
scalarTypeGraphQLName = \case
Scalar.Type.String -> pure stringScalar
Scalar.Type.Number -> pure floatScalar
Scalar.Type.Bool -> pure boolScalar
snakeCaseTableName :: TableName 'Experimental -> Text
snakeCaseTableName = Name.unName

View File

@ -0,0 +1,34 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Experimental.Adapter.Execute
(
)
where
--------------------------------------------------------------------------------
import Hasura.Base.Error (Code (NotSupported), QErr, throw400, throw500)
import Hasura.GraphQL.Execute.Backend (BackendExecute (..))
import Hasura.Prelude
import Hasura.SQL.Backend (BackendType (Experimental))
import Hasura.Tracing qualified as Tracing
--------------------------------------------------------------------------------
instance BackendExecute 'Experimental where
type PreparedQuery 'Experimental = ()
type MultiplexedQuery 'Experimental = Void
type ExecutionMonad 'Experimental = Tracing.TraceT (ExceptT QErr IO)
mkDBQueryPlan _ _ _ _ =
throw400 NotSupported "mkDBQueryPlan: not implemented for Experimental"
mkDBQueryExplain _ _ _ _ _ =
throw400 NotSupported "mkDBQueryExplain: not implemented for Experimental"
mkDBMutationPlan _ _ _ _ _ =
throw400 NotSupported "mkDBMutationPlan: Experimental backend does not support this operation yet."
mkDBSubscriptionPlan _ _ _ _ _ =
throw400 NotSupported "mkDBSubscriptionPlan: Experimental backend does not support this operation yet."
mkDBRemoteRelationshipPlan _ _ _ _ _ _ _ =
throw500 "mkDBRemoteRelationshipPlan: Experimental backend does not currently support generalized joins."
mkLiveQueryExplain _ =
throw400 NotSupported "mkLiveQueryExplain: Experimental backend does not support this operation yet."

View File

@ -0,0 +1,21 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Experimental.Adapter.Metadata () where
--------------------------------------------------------------------------------
import Hasura.Prelude
import Hasura.RQL.Types.Metadata.Backend (BackendMetadata (..))
import Hasura.SQL.Backend (BackendType (Experimental))
--------------------------------------------------------------------------------
instance BackendMetadata 'Experimental where
resolveSourceConfig = error "resolveSourceConfig: Unimplemented for Experimental backend."
resolveDatabaseMetadata = error "resolveDatabaseMetadata: Unimplemented for Experimental backend."
parseBoolExpOperations = error "parseBoolExpOperations: Unimplemented for Experimental backend."
parseCollectableType = error "parseCollectableType: Unimplemented for Experimental backend."
buildComputedFieldInfo = error "buildComputedFieldInfo: Unimplemented for Experimental backend."
fetchAndValidateEnumValues = error "fetchAndValidateEnumValues: Unimplemented for Experimental backend."
buildFunctionInfo = error "buildFunctionInfo: Unimplemented for Experimental backend."
updateColumnInEventTrigger = error "updateColumnInEventTrigger: Unimplemented for Experimental backend."
postDropSourceHook = error "postDropSourceHook: Unimplemented for Experimental backend."

View File

@ -0,0 +1,75 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Experimental.Adapter.Schema () where
--------------------------------------------------------------------------------
import Hasura.GraphQL.Schema.Backend (BackendSchema (..), MonadBuildSchema)
import Hasura.GraphQL.Schema.Build qualified as GSB
import Hasura.Prelude
import Hasura.RQL.Types qualified as RQL
import Hasura.SQL.Backend (BackendType (Experimental))
import Language.GraphQL.Draft.Syntax qualified as GraphQL
--------------------------------------------------------------------------------
instance BackendSchema 'Experimental where
-- top level parsers
buildTableQueryFields = GSB.buildTableQueryFields
buildTableRelayQueryFields = experimentalBuildTableRelayQueryFields
buildFunctionQueryFields =
error "buildFunctionQueryFields: Unimplemented for Experimental backend."
buildFunctionRelayQueryFields =
error "buildFunctionRelayQueryFields: Unimplemented for Experimental backend."
buildFunctionMutationFields =
error "buildFunctionMutationFields: Unimplemented for Experimental backend."
buildTableInsertMutationFields =
error "buildTableInsertMutationFields: Unimplemented for Experimental backend."
buildTableUpdateMutationFields =
error "buildTableUpdateMutationFields: Unimplemented for Experimental backend."
buildTableDeleteMutationFields =
error "buildTableDeleteMutationFields: Unimplemented for Experimental backend."
-- backend extensions
relayExtension = Nothing
nodesAggExtension = Nothing
-- table arguments
tableArguments =
error "tableArguments: Unimplemented for Experimental backend."
-- indivdual components
columnParser =
error "columnParser: Unimplemented for Experimental backend."
jsonPathArg _ = pure Nothing
orderByOperators =
error "orderByOperators: Unimplemented for Experimental backend."
comparisonExps =
error "comparisonExps: Unimplemented for Experimental backend."
mkCountType =
error "mkCountType: Unimplemented for Experimental backend."
aggregateOrderByCountType =
error "aggregateOrderByCountType: Unimplemented for Experimental backend."
computedField =
error "computedField: Unimplemented for Experimental backend."
node =
error "node: Unimplemented for Experimental backend."
columnDefaultValue =
error "columnDefaultValue: Unimplemented for Experimental backend."
--------------------------------------------------------------------------------
experimentalBuildTableRelayQueryFields ::
MonadBuildSchema 'Experimental r m n =>
RQL.SourceName ->
RQL.TableName 'Experimental ->
RQL.TableInfo 'Experimental ->
GraphQL.Name ->
NESeq (RQL.ColumnInfo 'Experimental) ->
RQL.SelPermInfo 'Experimental ->
m [a]
experimentalBuildTableRelayQueryFields _sourceName _tableName _tableInfo _gqlName _pkeyColumns _selPerms =
pure []

View File

@ -0,0 +1,24 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Experimental.Adapter.Transport () where
--------------------------------------------------------------------------------
import Control.Exception (throwIO)
import Hasura.Base.Error (Code (NotSupported), throw400)
import Hasura.Experimental.Adapter.Execute ()
import Hasura.GraphQL.Transport.Backend (BackendTransport (..))
import Hasura.Prelude
import Hasura.SQL.Backend (BackendType (Experimental))
--------------------------------------------------------------------------------
instance BackendTransport 'Experimental where
runDBQuery _ _ _ _ _ _ _ _ =
throw400 NotSupported "runDBQuery: not implemented for Experimental"
runDBQueryExplain _ =
throw400 NotSupported "runDBQueryExplain: not implemented for Experimental"
runDBMutation _ _ _ _ _ _ _ _ =
throw400 NotSupported "runDBMutation: not implemented for Experimental"
runDBSubscription _ _ _ =
liftIO $ throwIO $ userError "runDBSubscription: not implemented for Experimental"

View File

@ -0,0 +1,27 @@
{-# LANGUAGE DeriveAnyClass #-}
module Hasura.Experimental.IR.Column
( Name,
)
where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Name qualified as Name
--------------------------------------------------------------------------------
-- | An alias for 'Name.Column' 'Name.Name's.
--
-- This alias is defined in its own module primarily for the convenience of
-- importing it qualified.
--
-- For example:
-- @
-- import Data.Coerce (coerce)
-- import Hasura.Experimental.IR.Column qualified as Column (Name)
--
-- example :: Table.Name
-- example = coerce @Text @Table.Name "column_name"
-- @
type Name = Name.Name 'Name.Column

View File

@ -0,0 +1,130 @@
{-# LANGUAGE DeriveAnyClass #-}
module Hasura.Experimental.IR.Expression
( Expression (..),
Operator (..),
)
where
--------------------------------------------------------------------------------
import Data.Aeson (FromJSON, ToJSON)
import Hasura.Experimental.IR.Column qualified as Column (Name)
import Hasura.Experimental.IR.Scalar.Value qualified as Scalar (Value)
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | A concrete (i.e. not polymorphic) representation for expressions that make
-- up datasource-agnostic queries.
--
-- This type should be seen as an intermediate phase of the processing pipeline
-- which provides a high-level interface that the GraphQL Engine can use to
-- inspect, manipulate, optimize, etc. before sending off to an agent that will
-- be responsible for performing query generation/execution.
--
-- This type should ascribe clear semantics to its sub-expressions; when this
-- is not possible, it should clearly defer to the semantics of some reference
-- datasource with clearer documentation.
--
-- e.g. https://www.postgresql.org/docs/13/sql-expressions.html
data Expression
= -- | A constant 'Scalar.Value'.
Literal Scalar.Value
| -- | A construct for making multiple comparisons between groups of
-- 'Scalar.Value's.
--
-- The right-hand side is a collection of unique 'Scalar.Value's; the
-- result is "true" if the result of the left-hand 'Expression' is equal to
-- any of these 'Scalar.Value's.
--
-- cf. https://www.postgresql.org/docs/13/functions-comparisons.html#FUNCTIONS-COMPARISONS-IN-SCALAR
--
-- NOTE(jkachmar): It's unclear that there's any benefit from using a
-- 'HashSet' for the RHS collection of 'Scalar.Value's.
--
-- Consider switching this to a 'Set' after the typeclass methods which use
-- this type have been implemented and we have an opportunity to see how
-- its used in practice.
In Expression (HashSet Scalar.Value)
| -- | A logical @AND@ operator.
--
-- cf. https://www.postgresql.org/docs/13/functions-logical.html
And [Expression]
| -- | A logical @OR@ operator.
--
-- cf. https://www.postgresql.org/docs/13/functions-logical.html
Or [Expression]
| -- | A logical @NOT@ operator.
--
-- cf. https://www.postgresql.org/docs/13/functions-logical.html
Not Expression
| -- | A comparison predicate which returns "true" if an expression evaluates
-- to 'Scalar.Null'.
IsNull Expression
| -- | A comparison predicate which returns "true" if an expression does not
-- evaluate to 'Scalar.Null'.
IsNotNull Expression
| -- | The textual name associated with some "column" of data within a
-- datasource.
--
-- XXX(jkachmar): It's unclear whether "column" is the right descriptor for
-- this construct; what we want here seems closer to an "identifier".
--
-- cf. https://www.postgresql.org/docs/current/sql-syntax-lexical.html#SQL-SYNTAX-IDENTIFIERS
Column Column.Name
| -- | An equality operation which returns "true" if two expressions evaluate
-- to equivalent forms.
--
-- cf. https://www.postgresql.org/docs/13/functions-comparison.html
--
-- XXX(jkachmar): Consider making this a part of 'Operator'.
--
-- XXX(jkachmar): Equality of expressions is tricky business!
--
-- We should define the semantics of expression equality in a way that is
-- clear and carefully considered.
Equal Expression Expression
| -- | An inequality operation which returns "true" if two expressions do not
-- evaluate to equivalent forms.
--
-- cf. https://www.postgresql.org/docs/13/functions-comparison.html
--
-- XXX(jkachmar): Consider making this a part of 'Operator', or eliminating
-- 'NotEqual' as an explicit case of 'Expression' and only ever construct
-- it as @Not (Equal x y)@.
--
-- XXX(jkachmar): Inequality of expressions is tricky business!
--
-- We should define the semantics of expression inequality in a way that is
-- clear and carefully considered.
NotEqual Expression Expression
| -- | Apply a comparison 'Operator' to two expressions; the result of this
-- application will return "true" or "false" depending on the 'Operator'
-- that's being applied.
--
-- XXX(jkachmar): Consider renaming 'Operator' to @ComparisonOperator@ and
-- this sub-expression to @ApplyComparisonOperator@ for clarity.
ApplyOperator Operator Expression Expression
deriving stock (Data, Eq, Generic, Ord, Show)
deriving anyclass (Cacheable, FromJSON, Hashable, NFData, ToJSON)
--------------------------------------------------------------------------------
-- | Operators which are typically applied to two 'Expression's (via the
-- 'ApplyOperator' sub-'Expression') to perform a boolean comparison.
--
-- cf. https://www.postgresql.org/docs/13/functions-comparison.html
--
-- XXX(jkachmar): Comparison operations are tricky business!
--
-- We should define the semantics of these comparisons in a way that is clear
-- and carefully considered.
data Operator
= LessThan
| LessThanOrEqual
| GreaterThan
| GreaterThanOrEqual
deriving stock (Data, Eq, Generic, Ord, Show)
deriving anyclass (Cacheable, FromJSON, Hashable, NFData, ToJSON)

View File

@ -0,0 +1,22 @@
module Hasura.Experimental.IR.Function (Name) where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Name qualified as Name
--------------------------------------------------------------------------------
-- | An alias for 'Name.Function' 'Name.Name's.
--
-- This alias is defined in its own module primarily for the convenience of
-- importing it qualified.
--
-- For example:
-- @
-- import Data.Coerce (coerce)
-- import Hasura.Experimental.IR.Function qualified as Function (Name)
--
-- example :: Function.Name
-- example = coerce @Text @Function.Name "function_name"
-- @
type Name = Name.Name 'Name.Function

View File

@ -0,0 +1,47 @@
{-# LANGUAGE StandaloneKindSignatures #-}
module Hasura.Experimental.IR.Name
( Name (..),
NameType (..),
)
where
--------------------------------------------------------------------------------
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
import Data.Kind (Type)
import Data.Text.Extended (ToTxt)
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | A tagged, opaque wrapper around 'Text' that provides a number of derived
-- derived instances (primarily as required by the @Backend@ typeclass).
--
-- This wrapper is indexed by 'NameType' so that different "names" can be
-- represented as semantically distinct types without the boilerplate of
-- actually defining these wrappers separately.
type Name :: NameType -> Type
newtype Name ty = Name {unName :: Text}
deriving stock (Data, Eq, Generic, Ord, Show)
deriving newtype
( Cacheable,
FromJSON,
FromJSONKey,
Hashable,
NFData,
ToJSON,
ToJSONKey,
ToTxt
)
-- | The "type" of "name" that the 'Name' type is meant to provide a textual
-- representation for.
--
-- In other words: an enumeration of all the types for which 'Name' acts as a
-- shared abstraction.
data NameType
= Column
| Function
| Table

View File

@ -0,0 +1,40 @@
{-# LANGUAGE DeriveAnyClass #-}
module Hasura.Experimental.IR.OrderBy
( OrderBy (..),
OrderType (..),
)
where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Column qualified as Column (Name)
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | Indicates a particular sort order that should be applied based on some
-- 'Column.Name' returned within a data source query.
--
-- TODO: We should use a sum type like @Query.Field@ here so that we can handle
-- @order by@ constraints on object/array relationships as well.
--
-- cf. https://www.postgresql.org/docs/13/queries-order.html
data OrderBy = OrderBy
{ column :: Column.Name,
ordering :: OrderType
}
deriving stock (Data, Eq, Generic, Ord, Show)
deriving anyclass (Cacheable, Hashable, NFData)
--------------------------------------------------------------------------------
-- | 'Column.Name's may be sorted in either ascending or descending order.
--
-- cf. https://www.postgresql.org/docs/13/queries-order.html
data OrderType
= Ascending
| Descending
deriving stock (Data, Eq, Generic, Ord, Show)
deriving anyclass (Cacheable, Hashable, NFData)

View File

@ -0,0 +1,75 @@
module Hasura.Experimental.IR.Query
( Query (..),
Field (..),
ColumnContents (..),
RelationshipContents (..),
)
where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Column qualified as Column (Name)
import Hasura.Experimental.IR.Expression (Expression)
import Hasura.Experimental.IR.OrderBy (OrderBy)
import Hasura.Experimental.IR.Table qualified as Table (Name)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | An abstract request to retrieve structured data from some source
data Query = Query
{ -- NOTE: We should clarify what the 'Text' key is supposed to indicate.
fields :: HashMap Text Field,
-- | Reference to the table these fields are in
from :: Table.Name,
-- | Optionally limit to N results
limit :: Maybe Int,
-- | Optionally offset from the Nth result
offset :: Maybe Int,
-- | Optionally constrain the results to satisfy some predicate
where_ :: Maybe Expression,
-- | Optionally order the results by the value of one or more fields
orderBy :: [OrderBy]
}
deriving stock (Data, Eq, Generic, Ord, Show)
--------------------------------------------------------------------------------
-- | The specific fields that are targeted by a 'Query'.
--
-- A field conceptually falls under one of the two following categories:
-- 1. a "column" within the data store that the query is being issued against
-- 2. a "relationship", which indicates that the field is the result of
-- another query that must be executed on its own
data Field
= Column ColumnContents
| Relationship RelationshipContents
deriving stock (Data, Eq, Generic, Ord, Show)
newtype ColumnContents = ColumnContents
{ column :: Column.Name
}
deriving stock (Data, Eq, Generic, Ord, Show)
-- | A relationship consists of the following components:
-- - a sub-query, from the perspective that a relationship field will occur
-- within a broader 'Query'
-- - a join condition relating the data returned by the sub-query with that
-- of the broader 'Query'
--
-- cf. https://en.wikipedia.org/wiki/Join_(SQL)
-- https://www.postgresql.org/docs/13/tutorial-join.html
-- https://www.postgresql.org/docs/13/queries-table-expressions.html#QUERIES-FROM
data RelationshipContents = RelationshipContents
{ joinCondition :: HashMap PrimaryKey ForeignKey,
query :: Query
}
deriving stock (Data, Eq, Generic, Ord, Show)
newtype PrimaryKey = PrimaryKey Column.Name
deriving stock (Data, Generic)
deriving newtype (Eq, Hashable, Ord, Show)
newtype ForeignKey = ForeignKey Column.Name
deriving stock (Data, Generic)
deriving newtype (Eq, Hashable, Ord, Show)

View File

@ -0,0 +1,42 @@
{-# LANGUAGE DeriveAnyClass #-}
module Hasura.Experimental.IR.Scalar.Type
( Type (..),
)
where
--------------------------------------------------------------------------------
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
import Data.Text.Extended (ToTxt (..))
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | Types of scalar values
--
-- Used to specify the domain of legal values for a @Column@.
--
-- NOTE(jkachmar): This type shouldn't _need_ ser/de instances, but they're
-- imposed by the 'Backend' class.
--
-- NOTE(cdparks): Should we add a Nullable _ :: Type constructor
-- instead of using a isNullable flag in @Column@?
data Type
= String
| Number
| Bool
deriving stock (Data, Eq, Generic, Ord, Show)
deriving anyclass
( Cacheable,
FromJSON,
FromJSONKey,
Hashable,
NFData,
ToJSON,
ToJSONKey
)
instance ToTxt Type where
toTxt = tshow

View File

@ -0,0 +1,26 @@
{-# LANGUAGE DeriveAnyClass #-}
module Hasura.Experimental.IR.Scalar.Value
( Value (..),
)
where
--------------------------------------------------------------------------------
import Data.Aeson (FromJSON, ToJSON)
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | Literal scalar values that can appear as leaf nodes in expressions
--
-- NOTE(jkachmar): This type shouldn't _need_ ser/de instances, but they're
-- imposed by the 'Backend' class.
data Value
= String Text
| Number Double
| Boolean Bool
| Null
deriving stock (Data, Eq, Generic, Ord, Show)
deriving anyclass (Cacheable, FromJSON, Hashable, NFData, ToJSON)

View File

@ -0,0 +1,25 @@
module Hasura.Experimental.IR.Table
( Name,
)
where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Name qualified as Name
--------------------------------------------------------------------------------
-- | An alias for 'Name.Table' 'Name.Name's.
--
-- This alias is defined in its own module primarily for the convenience of
-- importing it qualified.
--
-- For example:
-- @
-- import Data.Coerce (coerce)
-- import Hasura.Experimental.IR.Table qualified as Table (Name)
--
-- example :: Table.Name
-- example = coerce @Text @Table.Name "table_name"
-- @
type Name = Name.Name 'Name.Table

View File

@ -0,0 +1,31 @@
module Hasura.Experimental.Schema.Column
( Column (..),
)
where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Column qualified as Column (Name)
import Hasura.Experimental.IR.Scalar.Type qualified as Scalar (Type)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | A schematic representation which captures common attributes associated
-- with a piece of data that is stored in a given backend.
--
-- These attributes ascribe meaningful semantics to the data that they are
-- associated with.
--
-- cf. https://en.wikipedia.org/wiki/Column_(database)
-- https://www.postgresql.org/docs/13/ddl-basics.html
--
-- NOTE(cdparks): Instead of an isNullable flag, should we instead
-- add a Nullable constructor to Scalar.Type?
data Column = Column
{ name :: Column.Name,
type_ :: Scalar.Type,
isNullable :: Bool,
description :: Maybe Text
}
deriving stock (Data, Eq, Generic, Ord, Show)

View File

@ -0,0 +1,34 @@
module Hasura.Experimental.Schema.Table
( Table (..),
)
where
--------------------------------------------------------------------------------
import Hasura.Experimental.IR.Table qualified as Table (Name)
import Hasura.Experimental.Schema.Column (Column)
import Hasura.Prelude
--------------------------------------------------------------------------------
-- | A schematic representation which captures a named collection of columns
--
-- TODO(cdparks): schematic in the sense of "relating to a schema" or symbolic?
-- This language is also used in the @Column@ documentation
--
-- An element of a table is known as a row, record, tuple, or object,
-- and conforms to the shape specified by the list of @Column@s below.
--
-- cf. https://en.wikipedia.org/wiki/Table_(database)
-- https://www.postgresql.org/docs/13/ddl-basics.html
--
-- NOTE(jkachmar): This type shouldn't _need_ ser/de instances, but they're
-- imposed by the 'Backend' class.
data Table = Table
{ name :: Table.Name,
columns :: [Column],
-- TODO(cdparks): Composite primary keys
primaryKey :: Maybe Text,
description :: Maybe Text
}
deriving stock (Data, Eq, Generic, Ord, Show)

View File

@ -6,3 +6,4 @@ import Hasura.Backends.BigQuery.Instances.Execute as B ()
import Hasura.Backends.MSSQL.Instances.Execute as B ()
import Hasura.Backends.MySQL.Instances.Execute as B ()
import Hasura.Backends.Postgres.Instances.Execute as B ()
import Hasura.Experimental.Adapter.Execute as B ()

View File

@ -6,3 +6,4 @@ import Hasura.Backends.BigQuery.Instances.Schema as B ()
import Hasura.Backends.MSSQL.Instances.Schema as B ()
import Hasura.Backends.MySQL.Instances.Schema as B ()
import Hasura.Backends.Postgres.Instances.Schema as B ()
import Hasura.Experimental.Adapter.Schema as B ()

View File

@ -6,3 +6,4 @@ import Hasura.Backends.BigQuery.Instances.Transport as B ()
import Hasura.Backends.MSSQL.Instances.Transport as B ()
import Hasura.Backends.MySQL.Instances.Transport as B ()
import Hasura.Backends.Postgres.Instances.Transport as B ()
import Hasura.Experimental.Adapter.Transport as B ()

View File

@ -231,3 +231,33 @@ instance BackendEventTrigger 'MySQL where
redeliverEvent _ _ = throw400 NotSupported "Event triggers are not supported for MySQL sources"
unlockEventsInSource _ _ = runExceptT $ throw400 NotSupported "Event triggers are not supported for MySQL sources"
createTableEventTrigger _ _ _ _ _ _ = runExceptT $ throw400 NotSupported "Event triggers are not supported for MySQL sources"
--------------------------------------------------------------------------------
-- TODO(jkachmar): See if there isn't a way to define the function that
-- implement these methods in the 'Hasura.Experimental.Adapters' module
-- hierarchy just to keep everything as tidy as possible for that section of
-- code.
instance BackendEventTrigger 'Experimental where
insertManualEvent _ _ _ _ _ _ =
throw400 NotSupported "Event triggers are not supported for Experimental sources"
fetchUndeliveredEvents _ _ _ _ =
throw400 NotSupported "Event triggers are not supported for Experimental sources"
setRetry _ _ _ _ =
throw400 NotSupported "Event triggers are not supported for Experimental sources"
recordSuccess _ _ _ _ =
runExceptT $ throw400 NotSupported "Event triggers are not supported for Experimental sources"
getMaintenanceModeVersion _ =
throw400 NotSupported "Event triggers are not supported for Experimental sources"
recordError _ _ _ _ _ =
runExceptT $ throw400 NotSupported "Event triggers are not supported for Experimental sources"
recordError' _ _ _ _ _ =
runExceptT $ throw400 NotSupported "Event triggers are not supported for Experimental sources"
dropTriggerAndArchiveEvents _ _ =
throw400 NotSupported "Event triggers are not supported for Experimental sources"
redeliverEvent _ _ =
throw400 NotSupported "Event triggers are not supported for Experimental sources"
unlockEventsInSource _ _ =
runExceptT $ throw400 NotSupported "Event triggers are not supported for Experimental sources"
createTableEventTrigger _ _ _ _ _ _ =
runExceptT $ throw400 NotSupported "Event triggers are not supported for Experimental sources"

View File

@ -6,3 +6,4 @@ import Hasura.Backends.BigQuery.Instances.Types as B ()
import Hasura.Backends.MSSQL.Instances.Types as B ()
import Hasura.Backends.MySQL.Instances.Types as B ()
import Hasura.Backends.Postgres.Instances.Types as B ()
import Hasura.Experimental.Adapter.Backend as B ()

View File

@ -6,3 +6,4 @@ import Hasura.Backends.BigQuery.Instances.Metadata as B ()
import Hasura.Backends.MSSQL.Instances.Metadata as B ()
import Hasura.Backends.MySQL.Instances.Metadata as B ()
import Hasura.Backends.Postgres.Instances.Metadata as B ()
import Hasura.Experimental.Adapter.Metadata as B ()

View File

@ -27,6 +27,7 @@ data BackendType
| MSSQL
| BigQuery
| MySQL
| Experimental
deriving (Show, Eq, Ord)
-- | The name of the backend, as we expect it to appear in our metadata and API.
@ -36,6 +37,7 @@ instance ToTxt BackendType where
toTxt MSSQL = "mssql"
toTxt BigQuery = "bigquery"
toTxt MySQL = "mysql"
toTxt Experimental = "experimental"
-- | The FromJSON instance uses this lookup mechanism to avoid having to duplicate and hardcode the
-- backend string. We accept both the short form and the long form of the backend's name.
@ -68,5 +70,6 @@ supportedBackends =
Postgres Citus,
MSSQL,
BigQuery,
MySQL
MySQL,
Experimental
]

View File

@ -6,3 +6,4 @@ import Hasura.Backends.BigQuery.Instances.API as B ()
import Hasura.Backends.MSSQL.Instances.API as B ()
import Hasura.Backends.MySQL.Instances.API as B ()
import Hasura.Backends.Postgres.Instances.API as B ()
import Hasura.Experimental.Adapter.API as B ()