graphql-engine/server/src-lib/Hasura/GraphQL/Parser/Column.hs
Auke Booij 3c3ed55914 server: schema that grows (#105)
This PR makes a bunch of schema generation code in Hasura.GraphQL.Schema backend-agnostic, by moving the backend-specific parts into a new BackendSchema type class. This way, the schema generation code can be reused for other backends, simply by implementing new instances of the BackendSchema type class.

This work is now in a state where the schema generators are sufficiently generic to accept the implementation of a new backend. That means that we can start exposing MS SQL schema. Execution is not implemented yet, of course.
The branch currently does not support computed fields or Relay. This is, in a sense, intentional: computed field support is normally baked into the schema generation (through the fieldSelection schema generator), and so this branch shows a programming technique that allows us to expose certain GraphQL schema depending on backend support. We can write support for computed fields and Relay at a later stage.

Co-authored-by: Antoine Leblanc <antoine@hasura.io>
GitOrigin-RevId: df369fc3d189cbda1b931d31678e9450a6601314
2020-12-01 15:51:13 +00:00

84 lines
3.0 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE StrictData #-}
module Hasura.GraphQL.Parser.Column
( ColumnValue(..)
, mkScalarTypeName
, UnpreparedValue(..)
, Opaque
, mkOpaque
, openOpaque
, mkParameter
) where
import Hasura.Prelude
import Data.Text.Extended
import Language.GraphQL.Draft.Syntax (Name (..),
mkName)
import qualified Hasura.RQL.Types.CustomTypes as RQL
import Hasura.Backends.Postgres.SQL.Types
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Schema
import Hasura.RQL.Types.Column hiding (EnumValue (..), EnumValueInfo (..))
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Error
import Hasura.SQL.Backend
import Hasura.SQL.Types
import Hasura.Session (SessionVariable)
-- -------------------------------------------------------------------------------------------------
data Opaque a = Opaque
{ _opVariable :: Maybe VariableInfo
-- ^ The variable this value came from, if any.
, _opValue :: a
} -- Note: we intentionally dont derive any instances here, since that would
-- defeat the opaqueness!
mkOpaque :: Maybe VariableInfo -> a -> Opaque a
mkOpaque = Opaque
openOpaque :: MonadParse m => Opaque a -> m a
openOpaque (Opaque Nothing value) = pure value
openOpaque (Opaque (Just _) value) = markNotReusable $> value
data UnpreparedValue (b :: BackendType)
-- | A SQL value that can be parameterized over.
= UVParameter
(ColumnValue b)
(Maybe VariableInfo)
-- ^ The GraphQL variable this value came from, if any.
-- | A literal SQL expression that /cannot/ be parameterized over.
| UVLiteral (SQLExpression b)
-- | The entire session variables JSON object.
| UVSession
-- | A single session variable.
| UVSessionVar (SessionVarType b) SessionVariable
data ColumnValue (b :: BackendType) = ColumnValue
{ cvType :: ColumnType b
, cvValue :: ColumnValueType b
}
-- FIXME exporting this method means doing away with the opaqueness of the
-- 'Opaque' data type, since the constructors of 'UnpreparedValue' are exported
-- globally.
mkParameter :: Opaque (ColumnValue b) -> UnpreparedValue b
mkParameter (Opaque variable value) = UVParameter value variable
-- -------------------------------------------------------------------------------------------------
mkScalarTypeName :: MonadError QErr m => PGScalarType -> m Name
mkScalarTypeName PGInteger = pure RQL.intScalar
mkScalarTypeName PGBoolean = pure RQL.boolScalar
mkScalarTypeName PGFloat = pure RQL.floatScalar
mkScalarTypeName PGText = pure RQL.stringScalar
mkScalarTypeName PGVarchar = pure RQL.stringScalar
mkScalarTypeName scalarType = mkName (toSQLTxt scalarType) `onNothing` throw400 ValidationFailed
("cannot use SQL type " <> scalarType <<> " in the GraphQL schema because its name is not a "
<> "valid GraphQL identifier")