mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 04:24:35 +03:00
647231b685
Manually enables: * EmptyCase * ExistentialQuantification * QuantifiedConstraints * QuasiQuotes * TemplateHaskell * TypeFamilyDependencies ...in the following components: * 'graphql-engine' library * 'graphql-engine' 'src-test' * 'graphql-engine' 'tests/integration' * 'graphql-engine' tests-hspec' Additionally, performs some light refactoring and documentation. PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3991 GitOrigin-RevId: 514477d3466b01f60eca8935d0fef60dd0756838
42 lines
1.2 KiB
Haskell
42 lines
1.2 KiB
Haskell
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
module Hasura.GraphQL.Context
|
|
( RoleContext (..),
|
|
GQLContext (..),
|
|
ParserFn,
|
|
)
|
|
where
|
|
|
|
import Data.Aeson qualified as J
|
|
import Data.Aeson.TH
|
|
import Hasura.GraphQL.Namespace
|
|
import Hasura.GraphQL.Parser
|
|
import Hasura.Prelude
|
|
import Hasura.RQL.IR qualified as IR
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
-- | For storing both a normal GQLContext and one for the backend variant.
|
|
-- Currently, this is to enable the backend variant to have certain insert
|
|
-- permissions which the frontend variant does not.
|
|
data RoleContext a = RoleContext
|
|
{ -- | The default context for normal sessions
|
|
_rctxDefault :: !a,
|
|
-- | The context for sessions with backend privilege.
|
|
_rctxBackend :: !(Maybe a)
|
|
}
|
|
deriving (Show, Eq, Functor, Foldable, Traversable)
|
|
|
|
$(deriveToJSON hasuraJSON ''RoleContext)
|
|
|
|
data GQLContext = GQLContext
|
|
{ gqlQueryParser :: ParserFn (RootFieldMap (IR.QueryRootField UnpreparedValue)),
|
|
gqlMutationParser :: Maybe (ParserFn (RootFieldMap (IR.MutationRootField UnpreparedValue)))
|
|
}
|
|
|
|
instance J.ToJSON GQLContext where
|
|
toJSON GQLContext {} = J.String "The GraphQL schema parsers"
|
|
|
|
type ParserFn a =
|
|
G.SelectionSet G.NoFragments Variable ->
|
|
Either (NESeq ParseError) a
|