graphql-engine/server/src-lib/Hasura/Backends/Postgres/Execute/Prepare.hs
Auke Booij 8ccf7724ce server: Metadata origin for definitions (type parameter version v2)
The code that builds the GraphQL schema, and `buildGQLContext` in particular, is partial: not every value of `(ServerConfigCtx, GraphQLQueryType, SourceCache, HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject), ActionCache, AnnotatedCustomTypes)` results in a valid GraphQL schema. When it fails, we want to be able to return better error messages than we currently do.

The key thing that is missing is a way to trace back GraphQL type information to their origin from the Hasura metadata. Currently, we have a number of correctness checks of our GraphQL schema. But these correctness checks only have access to pure GraphQL type information, and hence can only report errors in terms of that. Possibly the worst is the "conflicting definitions" error, which, in practice, can only be debugged by Hasura engineers. This is terrible DX for customers.

This PR allows us to print better error messages, by adding a field to the `Definition` type that traces the GraphQL type to its origin in the metadata. So the idea is simple: just add `MetadataObjId`, or `Maybe` that, or some other sum type of that, to `Definition`.

However, we want to avoid having to import a `Hasura.RQL` module from `Hasura.GraphQL.Parser`. So we instead define this additional field of `Definition` through a new type parameter, which is threaded through in `Hasura.GraphQL.Parser`. We then define type synonyms in `Hasura.GraphQL.Schema.Parser` that fill in this type parameter, so that it is not visible for the majority of the codebase.

The idea of associating metadata information to `Definition`s really comes to fruition when combined with hasura/graphql-engine-mono#4517. Their combination would allow us to use the API of fatal errors (just like the current `MonadError QErr`) to report _inconsistencies_ in the metadata. Such inconsistencies are then _automatically_ ignored. So no ad-hoc decisions need to be made on how to cut out inconsistent metadata from the GraphQL schema. This will allow us to report much better errors, as well as improve the likelihood of a successful HGE startup.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4770
Co-authored-by: Samir Talwar <47582+SamirTalwar@users.noreply.github.com>
GitOrigin-RevId: 728402b0cae83ae8e83463a826ceeb609001acae
2022-06-28 15:53:44 +00:00

133 lines
4.3 KiB
Haskell

-- | Postgres Execute Prepare
--
-- Deals with translating (session) variables to SQL expressions. Uses a state
-- monad to keep track of things like variables and generating fresh variable
-- names.
--
-- See 'Hasura.Backends.Postgres.Instances.Execute'.
module Hasura.Backends.Postgres.Execute.Prepare
( PlanVariables,
PrepArgMap,
PlanningSt (..),
ExecutionPlan,
ExecutionStep (..),
initPlanningSt,
prepareWithPlan,
prepareWithoutPlan,
withUserVars,
)
where
import Data.Aeson qualified as J
import Data.HashMap.Strict qualified as Map
import Data.IntMap qualified as IntMap
import Data.Text.Extended
import Database.PG.Query qualified as Q
import Hasura.Backends.Postgres.Connection.MonadTx
import Hasura.Backends.Postgres.SQL.DML qualified as S
import Hasura.Backends.Postgres.SQL.Value
import Hasura.Backends.Postgres.Translate.Column
import Hasura.Backends.Postgres.Types.Column
import Hasura.Base.Error
import Hasura.GraphQL.Execute.Backend
import Hasura.GraphQL.Parser.Names
import Hasura.Prelude
import Hasura.RQL.IR.Value
import Hasura.RQL.Types.Column
import Hasura.SQL.Backend
import Hasura.Session
import Language.GraphQL.Draft.Syntax qualified as G
type PlanVariables = Map.HashMap G.Name Int
-- | The value is (Q.PrepArg, PGScalarValue) because we want to log the human-readable value of the
-- prepared argument and not the binary encoding in PG format
type PrepArgMap = IntMap.IntMap (Q.PrepArg, PGScalarValue)
data PlanningSt = PlanningSt
{ _psArgNumber :: !Int,
_psVariables :: !PlanVariables,
_psPrepped :: !PrepArgMap
}
initPlanningSt :: PlanningSt
initPlanningSt = PlanningSt 2 Map.empty IntMap.empty
prepareWithPlan ::
( MonadState PlanningSt m,
MonadError QErr m
) =>
UserInfo ->
UnpreparedValue ('Postgres pgKind) ->
m S.SQLExp
prepareWithPlan userInfo = \case
UVParameter varInfoM ColumnValue {..} -> do
argNum <- maybe getNextArgNum (getVarArgNum . getName) varInfoM
addPrepArg argNum (binEncoder cvValue, cvValue)
return $ toPrepParam argNum (unsafePGColumnToBackend cvType)
UVSessionVar ty sessVar -> do
-- For queries, we need to make sure the session variables are passed. However,
-- we want to keep them as variables in the resulting SQL in order to keep
-- hitting query caching for similar queries.
_ <-
getSessionVariableValue sessVar (_uiSession userInfo)
`onNothing` throw400
NotFound
("missing session variable: " <>> sessionVariableToText sessVar)
let sessVarVal =
S.SEOpApp
(S.SQLOp "->>")
[currentSessionExp, S.SELit $ sessionVariableToText sessVar]
pure $ withTypeAnn ty sessVarVal
UVLiteral sqlExp -> pure sqlExp
UVSession -> pure currentSessionExp
where
currentSessionExp = S.SEPrep 1
prepareWithoutPlan ::
(MonadError QErr m) =>
UserInfo ->
UnpreparedValue ('Postgres pgKind) ->
m S.SQLExp
prepareWithoutPlan userInfo = \case
UVParameter _ cv -> pure $ toTxtValue cv
UVLiteral sqlExp -> pure sqlExp
UVSession -> pure $ sessionInfoJsonExp $ _uiSession userInfo
UVSessionVar ty sessVar -> do
let maybeSessionVariableValue =
getSessionVariableValue sessVar (_uiSession userInfo)
sessionVariableValue <-
fmap S.SELit
<$> onNothing maybeSessionVariableValue
$ throw400 NotFound $
"missing session variable: " <>> sessionVariableToText sessVar
pure $ withTypeAnn ty sessionVariableValue
withUserVars :: SessionVariables -> PrepArgMap -> PrepArgMap
withUserVars usrVars list =
let usrVarsAsPgScalar = PGValJSON $ Q.JSON $ J.toJSON usrVars
prepArg = Q.toPrepVal (Q.AltJ usrVars)
in IntMap.insert 1 (prepArg, usrVarsAsPgScalar) list
getVarArgNum :: (MonadState PlanningSt m) => G.Name -> m Int
getVarArgNum var = do
PlanningSt curArgNum vars prepped <- get
Map.lookup var vars `onNothing` do
put $ PlanningSt (curArgNum + 1) (Map.insert var curArgNum vars) prepped
pure curArgNum
addPrepArg ::
(MonadState PlanningSt m) =>
Int ->
(Q.PrepArg, PGScalarValue) ->
m ()
addPrepArg argNum arg = do
prepped <- gets _psPrepped
modify \x -> x {_psPrepped = IntMap.insert argNum arg prepped}
getNextArgNum :: (MonadState PlanningSt m) => m Int
getNextArgNum = do
curArgNum <- gets _psArgNumber
modify \x -> x {_psArgNumber = curArgNum + 1}
return curArgNum