2021-02-12 06:04:09 +03:00
|
|
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
|
|
|
|
|
|
|
module Hasura.GraphQL.Execute.Backend where
|
|
|
|
|
2021-03-10 10:26:22 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
|
|
import qualified Data.Aeson as J
|
|
|
|
import qualified Data.Environment as Env
|
|
|
|
import qualified Language.GraphQL.Draft.Syntax as G
|
|
|
|
import qualified Network.HTTP.Client as HTTP
|
|
|
|
import qualified Network.HTTP.Types as HTTP
|
|
|
|
|
|
|
|
import Data.Kind (Type)
|
|
|
|
import Data.Text.Extended
|
|
|
|
|
|
|
|
import qualified Hasura.GraphQL.Transport.HTTP.Protocol as GH
|
|
|
|
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.GraphQL.Context
|
|
|
|
import Hasura.GraphQL.Execute.Action.Types
|
|
|
|
import Hasura.GraphQL.Execute.LiveQuery.Plan
|
|
|
|
import Hasura.GraphQL.Parser hiding (Type)
|
|
|
|
import Hasura.RQL.IR.RemoteJoin
|
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
import Hasura.RQL.Types.Error
|
|
|
|
import Hasura.RQL.Types.RemoteSchema
|
|
|
|
import Hasura.SQL.Backend
|
|
|
|
import Hasura.Server.Version (HasVersion)
|
|
|
|
import Hasura.Session
|
2021-02-12 06:04:09 +03:00
|
|
|
|
|
|
|
|
|
|
|
-- | This typeclass enacapsulates how a given backend translates a root field into an execution
|
|
|
|
-- plan. For now, each root field maps to one execution step, but in the future, when we have
|
|
|
|
-- a client-side dataloader, each root field might translate into a multi-step plan.
|
2021-02-20 16:45:49 +03:00
|
|
|
class ( Backend b
|
|
|
|
, ToTxt (MultiplexedQuery b)
|
|
|
|
, Monad (ExecutionMonad b)
|
|
|
|
) => BackendExecute (b :: BackendType) where
|
2021-02-12 06:04:09 +03:00
|
|
|
-- generated query information
|
2021-02-20 16:45:49 +03:00
|
|
|
type PreparedQuery b :: Type
|
|
|
|
type MultiplexedQuery b :: Type
|
|
|
|
type ExecutionMonad b :: Type -> Type
|
2021-02-12 06:04:09 +03:00
|
|
|
getRemoteJoins :: PreparedQuery b -> [RemoteJoin b]
|
|
|
|
|
|
|
|
-- execution plan generation
|
|
|
|
mkDBQueryPlan
|
|
|
|
:: forall m
|
|
|
|
. ( MonadError QErr m
|
|
|
|
, HasVersion
|
|
|
|
)
|
|
|
|
=> Env.Environment
|
|
|
|
-> HTTP.Manager
|
|
|
|
-> [HTTP.Header]
|
|
|
|
-> UserInfo
|
|
|
|
-> [G.Directive G.Name]
|
|
|
|
-> SourceConfig b
|
|
|
|
-> QueryDB b (UnpreparedValue b)
|
2021-02-20 16:45:49 +03:00
|
|
|
-> m ExecutionStep
|
2021-02-12 06:04:09 +03:00
|
|
|
mkDBMutationPlan
|
|
|
|
:: forall m
|
|
|
|
. ( MonadError QErr m
|
|
|
|
, HasVersion
|
|
|
|
)
|
|
|
|
=> Env.Environment
|
|
|
|
-> HTTP.Manager
|
|
|
|
-> [HTTP.Header]
|
|
|
|
-> UserInfo
|
|
|
|
-> Bool
|
|
|
|
-> SourceConfig b
|
|
|
|
-> MutationDB b (UnpreparedValue b)
|
2021-02-20 16:45:49 +03:00
|
|
|
-> m ExecutionStep
|
|
|
|
mkDBSubscriptionPlan
|
|
|
|
:: forall m
|
|
|
|
. ( MonadError QErr m
|
|
|
|
, MonadIO m
|
|
|
|
)
|
|
|
|
=> UserInfo
|
|
|
|
-> SourceConfig b
|
|
|
|
-> InsOrdHashMap G.Name (QueryDB b (UnpreparedValue b))
|
|
|
|
-> m (LiveQueryPlan b (MultiplexedQuery b))
|
2021-02-12 06:04:09 +03:00
|
|
|
|
|
|
|
|
|
|
|
-- | One execution step to processing a GraphQL query (e.g. one root field).
|
2021-02-20 16:45:49 +03:00
|
|
|
data ExecutionStep where
|
2021-02-12 06:04:09 +03:00
|
|
|
ExecStepDB
|
2021-02-20 16:45:49 +03:00
|
|
|
:: forall (b :: BackendType)
|
|
|
|
. BackendExecute b
|
2021-02-12 06:04:09 +03:00
|
|
|
=> SourceConfig b
|
|
|
|
-> Maybe (PreparedQuery b)
|
|
|
|
-> HTTP.ResponseHeaders
|
2021-02-20 16:45:49 +03:00
|
|
|
-> ExecutionMonad b EncJSON
|
|
|
|
-> ExecutionStep
|
2021-02-12 06:04:09 +03:00
|
|
|
-- ^ A query to execute against the database
|
|
|
|
ExecStepAction
|
|
|
|
:: ActionExecutionPlan
|
|
|
|
-> HTTP.ResponseHeaders
|
2021-02-20 16:45:49 +03:00
|
|
|
-> ExecutionStep
|
2021-02-12 06:04:09 +03:00
|
|
|
-- ^ Execute an action
|
|
|
|
ExecStepRemote
|
|
|
|
:: !RemoteSchemaInfo
|
|
|
|
-> !GH.GQLReqOutgoing
|
2021-02-20 16:45:49 +03:00
|
|
|
-> ExecutionStep
|
2021-02-12 06:04:09 +03:00
|
|
|
-- ^ A graphql query to execute against a remote schema
|
|
|
|
ExecStepRaw
|
|
|
|
:: J.Value
|
2021-02-20 16:45:49 +03:00
|
|
|
-> ExecutionStep
|
2021-02-12 06:04:09 +03:00
|
|
|
-- ^ Output a plain JSON object
|
|
|
|
|
|
|
|
-- | The series of steps that need to be executed for a given query. For now, those steps are all
|
|
|
|
-- independent. In the future, when we implement a client-side dataloader and generalized joins,
|
|
|
|
-- this will need to be changed into an annotated tree.
|
2021-02-20 16:45:49 +03:00
|
|
|
type ExecutionPlan = InsOrdHashMap G.Name ExecutionStep
|