{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Hasura.GraphQL.Schema
( buildGQLContext,
)
where
import Control.Concurrent.Extended (forConcurrentlyEIO)
import Control.Lens
import Control.Monad.Memoize
import Data.Aeson.Ordered qualified as JO
import Data.Has
import Data.HashMap.Strict qualified as Map
import Data.HashMap.Strict.InsOrd qualified as OMap
import Data.HashSet qualified as Set
import Data.List.Extended (duplicates)
import Data.Text.Extended
import Data.Text.NonEmpty qualified as NT
import Hasura.Base.Error
import Hasura.Base.ErrorMessage
import Hasura.Base.ToErrorValue
import Hasura.GraphQL.ApolloFederation
import Hasura.GraphQL.Context
import Hasura.GraphQL.Execute.Types
import Hasura.GraphQL.Namespace
import Hasura.GraphQL.Parser.Schema.Convert (convertToSchemaIntrospection)
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Instances ()
import Hasura.GraphQL.Schema.Introspect
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options (SchemaOptions (..))
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser
( FieldParser,
Kind (..),
MonadParse,
Parser,
Schema,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Postgres
import Hasura.GraphQL.Schema.Relay
import Hasura.GraphQL.Schema.Remote (buildRemoteParser)
import Hasura.GraphQL.Schema.RemoteRelationship
import Hasura.GraphQL.Schema.Table
import Hasura.GraphQL.Schema.Typename (MkTypename (..))
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.Types.Action
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.CustomTypes
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.QueryTags
import Hasura.RQL.Types.RemoteSchema
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.SQL.Tag (HasTag)
import Hasura.Server.Types
import Hasura.Session
import Language.GraphQL.Draft.Syntax qualified as G
buildGQLContext ::
forall m.
( MonadError QErr m,
MonadIO m
) =>
ServerConfigCtx ->
GraphQLQueryType ->
SourceCache ->
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject) ->
ActionCache ->
AnnotatedCustomTypes ->
m
( G.SchemaIntrospection,
HashMap RoleName (RoleContext GQLContext),
GQLContext,
HashSet InconsistentMetadata
)
buildGQLContext :: ServerConfigCtx
-> GraphQLQueryType
-> SourceCache
-> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> ActionCache
-> AnnotatedCustomTypes
-> m (SchemaIntrospection,
HashMap RoleName (RoleContext GQLContext), GQLContext,
HashSet InconsistentMetadata)
buildGQLContext ServerConfigCtx {Maybe NamingCase
HashSet ExperimentalFeature
RemoteSchemaPermissions
InferFunctionPermissions
SQLGenCtx
EventingMode
ReadOnlyMode
MaintenanceMode ()
_sccDefaultNamingConvention :: ServerConfigCtx -> Maybe NamingCase
_sccReadOnlyMode :: ServerConfigCtx -> ReadOnlyMode
_sccEventingMode :: ServerConfigCtx -> EventingMode
_sccExperimentalFeatures :: ServerConfigCtx -> HashSet ExperimentalFeature
_sccMaintenanceMode :: ServerConfigCtx -> MaintenanceMode ()
_sccSQLGenCtx :: ServerConfigCtx -> SQLGenCtx
_sccRemoteSchemaPermsCtx :: ServerConfigCtx -> RemoteSchemaPermissions
_sccFunctionPermsCtx :: ServerConfigCtx -> InferFunctionPermissions
_sccDefaultNamingConvention :: Maybe NamingCase
_sccReadOnlyMode :: ReadOnlyMode
_sccEventingMode :: EventingMode
_sccExperimentalFeatures :: HashSet ExperimentalFeature
_sccMaintenanceMode :: MaintenanceMode ()
_sccSQLGenCtx :: SQLGenCtx
_sccRemoteSchemaPermsCtx :: RemoteSchemaPermissions
_sccFunctionPermsCtx :: InferFunctionPermissions
..} GraphQLQueryType
queryType SourceCache
sources HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
allRemoteSchemas ActionCache
allActions AnnotatedCustomTypes
customTypes = do
let remoteSchemasRoles :: [RoleName]
remoteSchemasRoles = ((RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> [RoleName])
-> [(RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))]
-> [RoleName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (HashMap RoleName IntrospectionResult -> [RoleName]
forall k v. HashMap k v -> [k]
Map.keys (HashMap RoleName IntrospectionResult -> [RoleName])
-> ((RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> HashMap RoleName IntrospectionResult)
-> (RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> [RoleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RemoteSchemaCtx -> HashMap RoleName IntrospectionResult
_rscPermissions (RemoteSchemaCtx -> HashMap RoleName IntrospectionResult)
-> ((RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> RemoteSchemaCtx)
-> (RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> HashMap RoleName IntrospectionResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RemoteSchemaCtx, MetadataObject) -> RemoteSchemaCtx
forall a b. (a, b) -> a
fst ((RemoteSchemaCtx, MetadataObject) -> RemoteSchemaCtx)
-> ((RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> (RemoteSchemaCtx, MetadataObject))
-> (RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> RemoteSchemaCtx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))
-> (RemoteSchemaCtx, MetadataObject)
forall a b. (a, b) -> b
snd) ([(RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))]
-> [RoleName])
-> [(RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))]
-> [RoleName]
forall a b. (a -> b) -> a -> b
$ HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [(RemoteSchemaName, (RemoteSchemaCtx, MetadataObject))]
forall k v. HashMap k v -> [(k, v)]
Map.toList HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
allRemoteSchemas
nonTableRoles :: HashSet RoleName
nonTableRoles =
RoleName -> HashSet RoleName -> HashSet RoleName
forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a
Set.insert RoleName
adminRoleName (HashSet RoleName -> HashSet RoleName)
-> HashSet RoleName -> HashSet RoleName
forall a b. (a -> b) -> a -> b
$
[RoleName] -> HashSet RoleName
forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList ([ActionInfo]
allActionInfos [ActionInfo]
-> Getting (Endo [RoleName]) [ActionInfo] RoleName -> [RoleName]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (ActionInfo -> Const (Endo [RoleName]) ActionInfo)
-> [ActionInfo] -> Const (Endo [RoleName]) [ActionInfo]
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
folded ((ActionInfo -> Const (Endo [RoleName]) ActionInfo)
-> [ActionInfo] -> Const (Endo [RoleName]) [ActionInfo])
-> ((RoleName -> Const (Endo [RoleName]) RoleName)
-> ActionInfo -> Const (Endo [RoleName]) ActionInfo)
-> Getting (Endo [RoleName]) [ActionInfo] RoleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashMap RoleName ActionPermissionInfo
-> Const (Endo [RoleName]) (HashMap RoleName ActionPermissionInfo))
-> ActionInfo -> Const (Endo [RoleName]) ActionInfo
Lens' ActionInfo (HashMap RoleName ActionPermissionInfo)
aiPermissions ((HashMap RoleName ActionPermissionInfo
-> Const (Endo [RoleName]) (HashMap RoleName ActionPermissionInfo))
-> ActionInfo -> Const (Endo [RoleName]) ActionInfo)
-> ((RoleName -> Const (Endo [RoleName]) RoleName)
-> HashMap RoleName ActionPermissionInfo
-> Const (Endo [RoleName]) (HashMap RoleName ActionPermissionInfo))
-> (RoleName -> Const (Endo [RoleName]) RoleName)
-> ActionInfo
-> Const (Endo [RoleName]) ActionInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashMap RoleName ActionPermissionInfo -> [RoleName])
-> Optic'
(->)
(Const (Endo [RoleName]))
(HashMap RoleName ActionPermissionInfo)
[RoleName]
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to HashMap RoleName ActionPermissionInfo -> [RoleName]
forall k v. HashMap k v -> [k]
Map.keys Optic'
(->)
(Const (Endo [RoleName]))
(HashMap RoleName ActionPermissionInfo)
[RoleName]
-> ((RoleName -> Const (Endo [RoleName]) RoleName)
-> [RoleName] -> Const (Endo [RoleName]) [RoleName])
-> (RoleName -> Const (Endo [RoleName]) RoleName)
-> HashMap RoleName ActionPermissionInfo
-> Const (Endo [RoleName]) (HashMap RoleName ActionPermissionInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RoleName -> Const (Endo [RoleName]) RoleName)
-> [RoleName] -> Const (Endo [RoleName]) [RoleName]
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
folded)
HashSet RoleName -> HashSet RoleName -> HashSet RoleName
forall a. Semigroup a => a -> a -> a
<> [RoleName] -> HashSet RoleName
forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList ([RoleName] -> [RoleName] -> Bool -> [RoleName]
forall a. a -> a -> Bool -> a
bool [RoleName]
forall a. Monoid a => a
mempty [RoleName]
remoteSchemasRoles (Bool -> [RoleName]) -> Bool -> [RoleName]
forall a b. (a -> b) -> a -> b
$ RemoteSchemaPermissions
_sccRemoteSchemaPermsCtx RemoteSchemaPermissions -> RemoteSchemaPermissions -> Bool
forall a. Eq a => a -> a -> Bool
== RemoteSchemaPermissions
Options.EnableRemoteSchemaPermissions)
allActionInfos :: [ActionInfo]
allActionInfos = ActionCache -> [ActionInfo]
forall k v. HashMap k v -> [v]
Map.elems ActionCache
allActions
allTableRoles :: HashSet RoleName
allTableRoles = [RoleName] -> HashSet RoleName
forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList ([RoleName] -> HashSet RoleName) -> [RoleName] -> HashSet RoleName
forall a b. (a -> b) -> a -> b
$ BackendSourceInfo -> [RoleName]
getTableRoles (BackendSourceInfo -> [RoleName])
-> [BackendSourceInfo] -> [RoleName]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SourceCache -> [BackendSourceInfo]
forall k v. HashMap k v -> [v]
Map.elems SourceCache
sources
allRoles :: HashSet RoleName
allRoles = HashSet RoleName
nonTableRoles HashSet RoleName -> HashSet RoleName -> HashSet RoleName
forall a. Semigroup a => a -> a -> a
<> HashSet RoleName
allTableRoles
defaultNC :: Maybe NamingCase
defaultNC = Maybe NamingCase -> Maybe NamingCase -> Bool -> Maybe NamingCase
forall a. a -> a -> Bool -> a
bool Maybe NamingCase
forall a. Maybe a
Nothing Maybe NamingCase
_sccDefaultNamingConvention (Bool -> Maybe NamingCase) -> Bool -> Maybe NamingCase
forall a b. (a -> b) -> a -> b
$ ExperimentalFeature
EFNamingConventions ExperimentalFeature -> HashSet ExperimentalFeature -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` HashSet ExperimentalFeature
_sccExperimentalFeatures
HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
roleContexts <-
([(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
-> HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))
-> m [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
-> m (HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
-> HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList (m [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
-> m (HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)))
-> m [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
-> m (HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))
forall a b. (a -> b) -> a -> b
$
Int
-> [RoleName]
-> (RoleName
-> ExceptT
QErr
IO
(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)))
-> m [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
forall (m :: * -> *) e a b.
(MonadIO m, MonadError e m) =>
Int -> [a] -> (a -> ExceptT e IO b) -> m [b]
forConcurrentlyEIO Int
10 (HashSet RoleName -> [RoleName]
forall a. HashSet a -> [a]
Set.toList HashSet RoleName
allRoles) ((RoleName
-> ExceptT
QErr
IO
(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)))
-> m [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))])
-> (RoleName
-> ExceptT
QErr
IO
(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)))
-> m [(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))]
forall a b. (a -> b) -> a -> b
$ \RoleName
role ->
(RoleName
role,)
((RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> (RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)))
-> ExceptT
QErr
IO
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> ExceptT
QErr
IO
(RoleName,
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case GraphQLQueryType
queryType of
GraphQLQueryType
QueryHasura ->
(SQLGenCtx, InferFunctionPermissions)
-> SourceCache
-> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [ActionInfo]
-> AnnotatedCustomTypes
-> RoleName
-> RemoteSchemaPermissions
-> HashSet ExperimentalFeature
-> Maybe NamingCase
-> ExceptT
QErr
IO
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
(SQLGenCtx, InferFunctionPermissions)
-> SourceCache
-> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [ActionInfo]
-> AnnotatedCustomTypes
-> RoleName
-> RemoteSchemaPermissions
-> HashSet ExperimentalFeature
-> Maybe NamingCase
-> m (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
buildRoleContext
(SQLGenCtx
_sccSQLGenCtx, InferFunctionPermissions
_sccFunctionPermsCtx)
SourceCache
sources
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
allRemoteSchemas
[ActionInfo]
allActionInfos
AnnotatedCustomTypes
customTypes
RoleName
role
RemoteSchemaPermissions
_sccRemoteSchemaPermsCtx
HashSet ExperimentalFeature
_sccExperimentalFeatures
Maybe NamingCase
defaultNC
GraphQLQueryType
QueryRelay ->
(,HashSet InconsistentMetadata
forall a. Monoid a => a
mempty,HashMap Name (TypeDefinition [Name] InputValueDefinition)
-> SchemaIntrospection
G.SchemaIntrospection HashMap Name (TypeDefinition [Name] InputValueDefinition)
forall a. Monoid a => a
mempty)
(RoleContext GQLContext
-> (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))
-> ExceptT QErr IO (RoleContext GQLContext)
-> ExceptT
QErr
IO
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SQLGenCtx, InferFunctionPermissions)
-> SourceCache
-> [ActionInfo]
-> AnnotatedCustomTypes
-> RoleName
-> HashSet ExperimentalFeature
-> Maybe NamingCase
-> ExceptT QErr IO (RoleContext GQLContext)
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
(SQLGenCtx, InferFunctionPermissions)
-> SourceCache
-> [ActionInfo]
-> AnnotatedCustomTypes
-> RoleName
-> HashSet ExperimentalFeature
-> Maybe NamingCase
-> m (RoleContext GQLContext)
buildRelayRoleContext
(SQLGenCtx
_sccSQLGenCtx, InferFunctionPermissions
_sccFunctionPermsCtx)
SourceCache
sources
[ActionInfo]
allActionInfos
AnnotatedCustomTypes
customTypes
RoleName
role
HashSet ExperimentalFeature
_sccExperimentalFeatures
Maybe NamingCase
defaultNC
SchemaIntrospection
adminIntrospection <-
case RoleName
-> HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> Maybe
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup RoleName
adminRoleName HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
roleContexts of
Just (RoleContext GQLContext
_context, HashSet InconsistentMetadata
_errors, SchemaIntrospection
introspection) -> SchemaIntrospection -> m SchemaIntrospection
forall (f :: * -> *) a. Applicative f => a -> f a
pure SchemaIntrospection
introspection
Maybe
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
Nothing -> Text -> m SchemaIntrospection
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 Text
"buildGQLContext failed to build for the admin role"
(GQLContext
unauthenticated, HashSet InconsistentMetadata
unauthenticatedRemotesErrors) <- HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> RemoteSchemaPermissions
-> m (GQLContext, HashSet InconsistentMetadata)
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> RemoteSchemaPermissions
-> m (GQLContext, HashSet InconsistentMetadata)
unauthenticatedContext HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
allRemoteSchemas RemoteSchemaPermissions
_sccRemoteSchemaPermsCtx
(SchemaIntrospection, HashMap RoleName (RoleContext GQLContext),
GQLContext, HashSet InconsistentMetadata)
-> m (SchemaIntrospection,
HashMap RoleName (RoleContext GQLContext), GQLContext,
HashSet InconsistentMetadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( SchemaIntrospection
adminIntrospection,
Getting
(RoleContext GQLContext)
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
(RoleContext GQLContext)
-> (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> RoleContext GQLContext
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(RoleContext GQLContext)
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
(RoleContext GQLContext)
forall s t a b. Field1 s t a b => Lens s t a b
_1 ((RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> RoleContext GQLContext)
-> HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> HashMap RoleName (RoleContext GQLContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
roleContexts,
GQLContext
unauthenticated,
[HashSet InconsistentMetadata] -> HashSet InconsistentMetadata
forall a. (Eq a, Hashable a) => [HashSet a] -> HashSet a
Set.unions ([HashSet InconsistentMetadata] -> HashSet InconsistentMetadata)
-> [HashSet InconsistentMetadata] -> HashSet InconsistentMetadata
forall a b. (a -> b) -> a -> b
$ HashSet InconsistentMetadata
unauthenticatedRemotesErrors HashSet InconsistentMetadata
-> [HashSet InconsistentMetadata] -> [HashSet InconsistentMetadata]
forall a. a -> [a] -> [a]
: ((RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> HashSet InconsistentMetadata)
-> [(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)]
-> [HashSet InconsistentMetadata]
forall a b. (a -> b) -> [a] -> [b]
map (Getting
(HashSet InconsistentMetadata)
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
(HashSet InconsistentMetadata)
-> (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> HashSet InconsistentMetadata
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(HashSet InconsistentMetadata)
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
(HashSet InconsistentMetadata)
forall s t a b. Field2 s t a b => Lens s t a b
_2) (HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> [(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)]
forall k v. HashMap k v -> [v]
Map.elems HashMap
RoleName
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
roleContexts)
)
buildRoleContext ::
forall m.
(MonadError QErr m, MonadIO m) =>
(SQLGenCtx, Options.InferFunctionPermissions) ->
SourceCache ->
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject) ->
[ActionInfo] ->
AnnotatedCustomTypes ->
RoleName ->
Options.RemoteSchemaPermissions ->
Set.HashSet ExperimentalFeature ->
Maybe NamingCase ->
m
( RoleContext GQLContext,
HashSet InconsistentMetadata,
G.SchemaIntrospection
)
buildRoleContext :: (SQLGenCtx, InferFunctionPermissions)
-> SourceCache
-> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [ActionInfo]
-> AnnotatedCustomTypes
-> RoleName
-> RemoteSchemaPermissions
-> HashSet ExperimentalFeature
-> Maybe NamingCase
-> m (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
buildRoleContext (SQLGenCtx, InferFunctionPermissions)
options SourceCache
sources HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
remotes [ActionInfo]
actions AnnotatedCustomTypes
customTypes RoleName
role RemoteSchemaPermissions
remoteSchemaPermsCtx HashSet ExperimentalFeature
expFeatures Maybe NamingCase
globalDefaultNC = do
let ( SQLGenCtx StringifyNumbers
stringifyNum DangerouslyCollapseBooleans
dangerousBooleanCollapse OptimizePermissionFilters
optimizePermissionFilters,
InferFunctionPermissions
functionPermsCtx
) = (SQLGenCtx, InferFunctionPermissions)
options
schemaOptions :: SchemaOptions
schemaOptions =
StringifyNumbers
-> DangerouslyCollapseBooleans
-> InferFunctionPermissions
-> OptimizePermissionFilters
-> SchemaOptions
SchemaOptions
StringifyNumbers
stringifyNum
DangerouslyCollapseBooleans
dangerousBooleanCollapse
InferFunctionPermissions
functionPermsCtx
OptimizePermissionFilters
optimizePermissionFilters
schemaContext :: SchemaContext
schemaContext =
SchemaKind
-> RemoteRelationshipParserBuilder -> RoleName -> SchemaContext
SchemaContext
SchemaKind
HasuraSchema
(SourceCache
-> RemoteSchemaMap
-> RemoteSchemaPermissions
-> RemoteRelationshipParserBuilder
remoteRelationshipField SourceCache
sources ((RemoteSchemaCtx, MetadataObject) -> RemoteSchemaCtx
forall a b. (a, b) -> a
fst ((RemoteSchemaCtx, MetadataObject) -> RemoteSchemaCtx)
-> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> RemoteSchemaMap
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
remotes) RemoteSchemaPermissions
remoteSchemaPermsCtx)
RoleName
role
MemoizeT
m
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> m (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall (m :: * -> *) a. Monad m => MemoizeT m a -> m a
runMemoizeT (MemoizeT
m
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> m (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection))
-> MemoizeT
m
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> m (RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall a b. (a -> b) -> a -> b
$ do
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesQueryFields, [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationFrontendFields, [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationBackendFields, [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesSubscriptionFields, [(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]
apolloFedTableParsers) <-
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
-> MemoizeT
m
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall (m :: * -> *) a.
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
m
a
-> m a
runSourceSchema SchemaContext
schemaContext SchemaOptions
schemaOptions (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
-> MemoizeT
m
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
-> MemoizeT
m
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall a b. (a -> b) -> a -> b
$
([([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall a. Monoid a => [a] -> a
mconcat (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall a b. (a -> b) -> a -> b
$ [BackendSourceInfo]
-> (BackendSourceInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (SourceCache -> [BackendSourceInfo]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList SourceCache
sources) \BackendSourceInfo
sourceInfo ->
BackendSourceInfo
-> (forall (b :: BackendType).
BackendSchema b =>
SourceInfo b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendSchema BackendSourceInfo
sourceInfo forall (b :: BackendType).
BackendSchema b =>
SourceInfo b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
buildSource
([RemoteSchemaParser Parse]
remoteSchemaFields, HashSet InconsistentMetadata
remoteSchemaErrors) <-
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
-> MemoizeT
m ([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall (m :: * -> *) a.
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
m
a
-> m a
runRemoteSchema SchemaContext
schemaContext SchemaOptions
schemaOptions (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
-> MemoizeT
m ([RemoteSchemaParser Parse], HashSet InconsistentMetadata))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
-> MemoizeT
m ([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall a b. (a -> b) -> a -> b
$
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> RoleName
-> RemoteSchemaPermissions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> RoleName
-> RemoteSchemaPermissions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
buildAndValidateRemoteSchemas HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
remotes [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesQueryFields [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationBackendFields RoleName
role RemoteSchemaPermissions
remoteSchemaPermsCtx
let remotesQueryFields :: [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesQueryFields = (RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piQuery [RemoteSchemaParser Parse]
remoteSchemaFields
remotesMutationFields :: [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesMutationFields = [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall a b. (a -> b) -> a -> b
$ (RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> Maybe
[FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piMutation [RemoteSchemaParser Parse]
remoteSchemaFields
remotesSubscriptionFields :: [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesSubscriptionFields = [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall a b. (a -> b) -> a -> b
$ (RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> Maybe
[FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piSubscription [RemoteSchemaParser Parse]
remoteSchemaFields
apolloQueryFields :: [FieldParser
Parse (SchemaIntrospection -> QueryRootField UnpreparedValue)]
apolloQueryFields = HashSet ExperimentalFeature
-> [(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]
-> [FieldParser
Parse (SchemaIntrospection -> QueryRootField UnpreparedValue)]
apolloRootFields HashSet ExperimentalFeature
expFeatures [(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]
apolloFedTableParsers
([FieldParser Parse (QueryRootField UnpreparedValue)]
actionsQueryFields, [FieldParser Parse (MutationRootField UnpreparedValue)]
actionsMutationFields, [FieldParser Parse (QueryRootField UnpreparedValue)]
actionsSubscriptionFields) <-
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
-> MemoizeT
m
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall (m :: * -> *) a.
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
m
a
-> m a
runSourceSchema SchemaContext
schemaContext SchemaOptions
schemaOptions (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
-> MemoizeT
m
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
-> MemoizeT
m
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall a b. (a -> b) -> a -> b
$
([([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])]
-> ([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])]
-> ([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall a. Monoid a => [a] -> a
mconcat (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall a b. (a -> b) -> a -> b
$ [ActionInfo]
-> (ActionInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [ActionInfo]
actions \ActionInfo
action -> do
[FieldParser Parse (QueryRootField UnpreparedValue)]
queryFields <- AnnotatedCustomTypes
-> ActionInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres 'Vanilla) r m n =>
AnnotatedCustomTypes
-> ActionInfo -> m [FieldParser n (QueryRootField UnpreparedValue)]
buildActionQueryFields AnnotatedCustomTypes
customTypes ActionInfo
action
[FieldParser Parse (MutationRootField UnpreparedValue)]
mutationFields <- AnnotatedCustomTypes
-> ActionInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres 'Vanilla) r m n =>
AnnotatedCustomTypes
-> ActionInfo
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildActionMutationFields AnnotatedCustomTypes
customTypes ActionInfo
action
[FieldParser Parse (QueryRootField UnpreparedValue)]
subscriptionFields <- AnnotatedCustomTypes
-> ActionInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres 'Vanilla) r m n =>
AnnotatedCustomTypes
-> ActionInfo -> m [FieldParser n (QueryRootField UnpreparedValue)]
buildActionSubscriptionFields AnnotatedCustomTypes
customTypes ActionInfo
action
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (MutationRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser Parse (QueryRootField UnpreparedValue)]
queryFields, [FieldParser Parse (MutationRootField UnpreparedValue)]
mutationFields, [FieldParser Parse (QueryRootField UnpreparedValue)]
subscriptionFields)
Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend <-
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
buildMutationParser [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationFrontendFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesMutationFields [FieldParser Parse (MutationRootField UnpreparedValue)]
actionsMutationFields
Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend <-
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
buildMutationParser [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationBackendFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesMutationFields [FieldParser Parse (MutationRootField UnpreparedValue)]
actionsMutationFields
Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser <-
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (QueryRootField UnpreparedValue)]
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))))
buildSubscriptionParser [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesSubscriptionFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesSubscriptionFields [FieldParser Parse (QueryRootField UnpreparedValue)]
actionsSubscriptionFields
Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserFrontend <-
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (SchemaIntrospection -> QueryRootField UnpreparedValue)]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (QueryRootField UnpreparedValue)]
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
buildQueryParser [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesQueryFields [FieldParser
Parse (SchemaIntrospection -> QueryRootField UnpreparedValue)]
apolloQueryFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesQueryFields [FieldParser Parse (QueryRootField UnpreparedValue)]
actionsQueryFields Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser
Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserBackend <-
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (SchemaIntrospection -> QueryRootField UnpreparedValue)]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (QueryRootField UnpreparedValue)]
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
buildQueryParser [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesQueryFields [FieldParser
Parse (SchemaIntrospection -> QueryRootField UnpreparedValue)]
apolloQueryFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remotesQueryFields [FieldParser Parse (QueryRootField UnpreparedValue)]
actionsQueryFields Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser
SchemaIntrospection
introspectionSchema <- do
SchemaIntrospection
result <-
Either ConflictingDefinitions SchemaIntrospection
-> MemoizeT m SchemaIntrospection
forall (m :: * -> *) a.
QErrM m =>
Either ConflictingDefinitions a -> m a
throwOnConflictingDefinitions (Either ConflictingDefinitions SchemaIntrospection
-> MemoizeT m SchemaIntrospection)
-> Either ConflictingDefinitions SchemaIntrospection
-> MemoizeT m SchemaIntrospection
forall a b. (a -> b) -> a -> b
$
Schema MetadataObjId -> SchemaIntrospection
forall origin. Schema origin -> SchemaIntrospection
convertToSchemaIntrospection
(Schema MetadataObjId -> SchemaIntrospection)
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> Either ConflictingDefinitions SchemaIntrospection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions (Schema MetadataObjId)
buildIntrospectionSchema
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserBackend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
SchemaIntrospection -> MemoizeT m SchemaIntrospection
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SchemaIntrospection -> MemoizeT m SchemaIntrospection)
-> SchemaIntrospection -> MemoizeT m SchemaIntrospection
forall a b. (a -> b) -> a -> b
$
if RoleName
role RoleName -> RoleName -> Bool
forall a. Eq a => a -> a -> Bool
== RoleName
adminRoleName
then SchemaIntrospection
result
else HashMap Name (TypeDefinition [Name] InputValueDefinition)
-> SchemaIntrospection
G.SchemaIntrospection HashMap Name (TypeDefinition [Name] InputValueDefinition)
forall a. Monoid a => a
mempty
MemoizeT m (Schema MetadataObjId) -> MemoizeT m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MemoizeT m (Schema MetadataObjId) -> MemoizeT m ())
-> (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId))
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId)
forall (m :: * -> *) a.
QErrM m =>
Either ConflictingDefinitions a -> m a
throwOnConflictingDefinitions (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ())
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall a b. (a -> b) -> a -> b
$
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions (Schema MetadataObjId)
buildIntrospectionSchema
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserFrontend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
let !frontendContext :: GQLContext
frontendContext =
ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> GQLContext
GQLContext
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserFrontend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
!backendContext :: GQLContext
backendContext =
ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> GQLContext
GQLContext
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserBackend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
-> MemoizeT
m
(RoleContext GQLContext, HashSet InconsistentMetadata,
SchemaIntrospection)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( GQLContext -> Maybe GQLContext -> RoleContext GQLContext
forall a. a -> Maybe a -> RoleContext a
RoleContext GQLContext
frontendContext (Maybe GQLContext -> RoleContext GQLContext)
-> Maybe GQLContext -> RoleContext GQLContext
forall a b. (a -> b) -> a -> b
$ GQLContext -> Maybe GQLContext
forall a. a -> Maybe a
Just GQLContext
backendContext,
HashSet InconsistentMetadata
remoteSchemaErrors,
SchemaIntrospection
introspectionSchema
)
where
buildSource ::
forall b.
BackendSchema b =>
SourceInfo b ->
ReaderT
( SchemaContext,
SchemaOptions,
MkTypename,
CustomizeRemoteFieldName,
NamingCase
)
(MemoizeT m)
( [FieldParser P.Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser P.Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser P.Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser P.Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(G.Name, Parser 'Output P.Parse (ApolloFederationParserFunction P.Parse))]
)
buildSource :: SourceInfo b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
buildSource sourceInfo :: SourceInfo b
sourceInfo@(SourceInfo SourceName
_ TableCache b
tables FunctionCache b
functions SourceConfig b
_ Maybe QueryTagsConfig
_ SourceCustomization
sourceCustomization') =
SourceCustomization
-> SupportedNamingCase
-> Maybe NamingCase
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall (m :: * -> *) r a.
(MonadReader r m, Has MkTypename r, Has NamingCase r,
MonadError QErr m) =>
SourceCustomization
-> SupportedNamingCase -> Maybe NamingCase -> m a -> m a
withSourceCustomization SourceCustomization
sourceCustomization (Backend b => SupportedNamingCase
forall (b :: BackendType). Backend b => SupportedNamingCase
namingConventionSupport @b) Maybe NamingCase
globalDefaultNC do
MkRootFieldName
mkRootFieldName <- SourceCustomization
-> SupportedNamingCase
-> Maybe NamingCase
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
MkRootFieldName
forall (m :: * -> *).
MonadError QErr m =>
SourceCustomization
-> SupportedNamingCase -> Maybe NamingCase -> m MkRootFieldName
getRootFieldsCustomizer SourceCustomization
sourceCustomization (Backend b => SupportedNamingCase
forall (b :: BackendType). Backend b => SupportedNamingCase
namingConventionSupport @b) Maybe NamingCase
globalDefaultNC
let validFunctions :: FunctionCache b
validFunctions = FunctionCache b -> FunctionCache b
forall (b :: BackendType). FunctionCache b -> FunctionCache b
takeValidFunctions FunctionCache b
functions
validTables :: TableCache b
validTables = TableCache b -> TableCache b
forall (b :: BackendType).
Backend b =>
TableCache b -> TableCache b
takeValidTables TableCache b
tables
MkTypename
makeTypename <- ((SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
-> MkTypename)
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
MkTypename
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
-> MkTypename
forall a t. Has a t => t -> a
getter
([FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedQueryRootFields, [FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedSubscriptionRootFields, [(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]
apolloFedTableParsers) <-
MkRootFieldName
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
MkRootFieldName
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)],
[(Name, Parser 'Output n (ApolloFederationParserFunction n))])
buildQueryAndSubscriptionFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo TableCache b
validTables FunctionCache b
validFunctions
(,,,,[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]
apolloFedTableParsers)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__query))
([FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedQueryRootFields)
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__mutation_frontend))
(MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildMutationFields MkRootFieldName
mkRootFieldName Scenario
Frontend SourceInfo b
sourceInfo TableCache b
validTables FunctionCache b
validFunctions)
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__mutation_backend))
(MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildMutationFields MkRootFieldName
mkRootFieldName Scenario
Backend SourceInfo b
sourceInfo TableCache b
validTables FunctionCache b
validFunctions)
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[(Name,
Parser 'Output Parse (ApolloFederationParserFunction Parse))])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__subscription))
([FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedSubscriptionRootFields)
where
sourceCustomization :: SourceCustomization
sourceCustomization =
if ExperimentalFeature
EFNamingConventions ExperimentalFeature -> HashSet ExperimentalFeature -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` HashSet ExperimentalFeature
expFeatures
then SourceCustomization
sourceCustomization'
else SourceCustomization
sourceCustomization' {_scNamingConvention :: Maybe NamingCase
_scNamingConvention = Maybe NamingCase
forall a. Maybe a
Nothing}
buildRelayRoleContext ::
forall m.
(MonadError QErr m, MonadIO m) =>
(SQLGenCtx, Options.InferFunctionPermissions) ->
SourceCache ->
[ActionInfo] ->
AnnotatedCustomTypes ->
RoleName ->
Set.HashSet ExperimentalFeature ->
Maybe NamingCase ->
m (RoleContext GQLContext)
buildRelayRoleContext :: (SQLGenCtx, InferFunctionPermissions)
-> SourceCache
-> [ActionInfo]
-> AnnotatedCustomTypes
-> RoleName
-> HashSet ExperimentalFeature
-> Maybe NamingCase
-> m (RoleContext GQLContext)
buildRelayRoleContext (SQLGenCtx, InferFunctionPermissions)
options SourceCache
sources [ActionInfo]
actions AnnotatedCustomTypes
customTypes RoleName
role HashSet ExperimentalFeature
expFeatures Maybe NamingCase
globalDefaultNC = do
let ( SQLGenCtx StringifyNumbers
stringifyNum DangerouslyCollapseBooleans
dangerousBooleanCollapse OptimizePermissionFilters
optimizePermissionFilters,
InferFunctionPermissions
functionPermsCtx
) = (SQLGenCtx, InferFunctionPermissions)
options
schemaOptions :: SchemaOptions
schemaOptions =
StringifyNumbers
-> DangerouslyCollapseBooleans
-> InferFunctionPermissions
-> OptimizePermissionFilters
-> SchemaOptions
SchemaOptions
StringifyNumbers
stringifyNum
DangerouslyCollapseBooleans
dangerousBooleanCollapse
InferFunctionPermissions
functionPermsCtx
OptimizePermissionFilters
optimizePermissionFilters
schemaContext :: SchemaContext
schemaContext =
SchemaKind
-> RemoteRelationshipParserBuilder -> RoleName -> SchemaContext
SchemaContext
(NodeInterfaceParserBuilder -> SchemaKind
RelaySchema (NodeInterfaceParserBuilder -> SchemaKind)
-> NodeInterfaceParserBuilder -> SchemaKind
forall a b. (a -> b) -> a -> b
$ SourceCache -> NodeInterfaceParserBuilder
nodeInterface SourceCache
sources)
(SourceCache
-> RemoteSchemaMap
-> RemoteSchemaPermissions
-> RemoteRelationshipParserBuilder
remoteRelationshipField SourceCache
sources RemoteSchemaMap
forall a. Monoid a => a
mempty RemoteSchemaPermissions
Options.DisableRemoteSchemaPermissions)
RoleName
role
MemoizeT m (RoleContext GQLContext) -> m (RoleContext GQLContext)
forall (m :: * -> *) a. Monad m => MemoizeT m a -> m a
runMemoizeT do
(FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
node, [([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])]
fieldsList) <-
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)),
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])])
-> MemoizeT
m
(FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)),
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])])
forall (m :: * -> *) a.
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
m
a
-> m a
runSourceSchema SchemaContext
schemaContext SchemaOptions
schemaOptions do
FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
node <- (QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser Parse (QueryRootField UnpreparedValue)
-> FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue)
forall a. a -> NamespacedField a
NotNamespaced (FieldParser Parse (QueryRootField UnpreparedValue)
-> FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(FieldParser Parse (QueryRootField UnpreparedValue))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceCache
-> MonadBuildSchemaBase
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
Parse =>
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(FieldParser Parse (QueryRootField UnpreparedValue))
forall (m :: * -> *) (n :: * -> *) r.
SourceCache
-> MonadBuildSchemaBase r m n =>
m (FieldParser n (QueryRootField UnpreparedValue))
nodeField SourceCache
sources
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])]
fieldsList <-
[BackendSourceInfo]
-> (BackendSourceInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (SourceCache -> [BackendSourceInfo]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList SourceCache
sources) \BackendSourceInfo
sourceInfo ->
BackendSourceInfo
-> (forall (b :: BackendType).
BackendSchema b =>
SourceInfo b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendSchema BackendSourceInfo
sourceInfo forall (b :: BackendType).
BackendSchema b =>
SourceInfo b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
buildSource
(FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)),
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)),
[([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
node, [([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])]
fieldsList)
let ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
queryFields, [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationFrontendFields, [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationBackendFields, [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields) = [([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
forall a. Monoid a => [a] -> a
mconcat [([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])]
fieldsList
allQueryFields :: [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
allQueryFields = FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
node FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall a. a -> [a] -> [a]
: [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
queryFields
allSubscriptionFields :: [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
allSubscriptionFields = FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
node FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall a. a -> [a] -> [a]
: [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields
[FieldParser Parse (MutationRootField UnpreparedValue)]
actionsMutationFields <-
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m [FieldParser Parse (MutationRootField UnpreparedValue)]
forall (m :: * -> *) a.
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
m
a
-> m a
runSourceSchema SchemaContext
schemaContext SchemaOptions
schemaOptions (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m [FieldParser Parse (MutationRootField UnpreparedValue)])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m [FieldParser Parse (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$
([[FieldParser Parse (MutationRootField UnpreparedValue)]]
-> [FieldParser Parse (MutationRootField UnpreparedValue)])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[[FieldParser Parse (MutationRootField UnpreparedValue)]]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FieldParser Parse (MutationRootField UnpreparedValue)]]
-> [FieldParser Parse (MutationRootField UnpreparedValue)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[[FieldParser Parse (MutationRootField UnpreparedValue)]]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[[FieldParser Parse (MutationRootField UnpreparedValue)]]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$
(ActionInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)])
-> [ActionInfo]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[[FieldParser Parse (MutationRootField UnpreparedValue)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (AnnotatedCustomTypes
-> ActionInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres 'Vanilla) r m n =>
AnnotatedCustomTypes
-> ActionInfo
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildActionMutationFields AnnotatedCustomTypes
customTypes) [ActionInfo]
actions
Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend <-
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
buildMutationParser [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationFrontendFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall a. Monoid a => a
mempty [FieldParser Parse (MutationRootField UnpreparedValue)]
actionsMutationFields
Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend <-
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (MutationRootField UnpreparedValue)]
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
buildMutationParser [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationBackendFields [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall a. Monoid a => a
mempty [FieldParser Parse (MutationRootField UnpreparedValue)]
actionsMutationFields
Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser <-
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser Parse (QueryRootField UnpreparedValue)]
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))))
buildSubscriptionParser [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
allSubscriptionFields [] []
Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserFrontend <-
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadParse n, MonadError QErr m) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryWithIntrospectionHelper [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
allQueryFields Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser
Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserBackend <-
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadParse n, MonadError QErr m) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryWithIntrospectionHelper [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
allQueryFields Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser
MemoizeT m (Schema MetadataObjId) -> MemoizeT m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MemoizeT m (Schema MetadataObjId) -> MemoizeT m ())
-> (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId))
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId)
forall (m :: * -> *) a.
QErrM m =>
Either ConflictingDefinitions a -> m a
throwOnConflictingDefinitions (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ())
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall a b. (a -> b) -> a -> b
$
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions (Schema MetadataObjId)
buildIntrospectionSchema
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserBackend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
MemoizeT m (Schema MetadataObjId) -> MemoizeT m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MemoizeT m (Schema MetadataObjId) -> MemoizeT m ())
-> (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId))
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId)
forall (m :: * -> *) a.
QErrM m =>
Either ConflictingDefinitions a -> m a
throwOnConflictingDefinitions (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ())
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall a b. (a -> b) -> a -> b
$
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions (Schema MetadataObjId)
buildIntrospectionSchema
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserFrontend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
let frontendContext :: GQLContext
frontendContext =
ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> GQLContext
GQLContext
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserFrontend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserFrontend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
backendContext :: GQLContext
backendContext =
ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> GQLContext
GQLContext
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParserBackend)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParserBackend)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
RoleContext GQLContext -> MemoizeT m (RoleContext GQLContext)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RoleContext GQLContext -> MemoizeT m (RoleContext GQLContext))
-> RoleContext GQLContext -> MemoizeT m (RoleContext GQLContext)
forall a b. (a -> b) -> a -> b
$ GQLContext -> Maybe GQLContext -> RoleContext GQLContext
forall a. a -> Maybe a -> RoleContext a
RoleContext GQLContext
frontendContext (Maybe GQLContext -> RoleContext GQLContext)
-> Maybe GQLContext -> RoleContext GQLContext
forall a b. (a -> b) -> a -> b
$ GQLContext -> Maybe GQLContext
forall a. a -> Maybe a
Just GQLContext
backendContext
where
buildSource ::
forall b.
BackendSchema b =>
SourceInfo b ->
ReaderT
( SchemaContext,
SchemaOptions,
MkTypename,
CustomizeRemoteFieldName,
NamingCase
)
(MemoizeT m)
( [FieldParser P.Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser P.Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser P.Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser P.Parse (NamespacedField (QueryRootField UnpreparedValue))]
)
buildSource :: SourceInfo b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
buildSource sourceInfo :: SourceInfo b
sourceInfo@(SourceInfo SourceName
_ TableCache b
tables FunctionCache b
functions SourceConfig b
_ Maybe QueryTagsConfig
_ SourceCustomization
sourceCustomization') = do
MkRootFieldName
mkRootFieldName <- SourceCustomization
-> SupportedNamingCase
-> Maybe NamingCase
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
MkRootFieldName
forall (m :: * -> *).
MonadError QErr m =>
SourceCustomization
-> SupportedNamingCase -> Maybe NamingCase -> m MkRootFieldName
getRootFieldsCustomizer SourceCustomization
sourceCustomization (Backend b => SupportedNamingCase
forall (b :: BackendType). Backend b => SupportedNamingCase
namingConventionSupport @b) Maybe NamingCase
globalDefaultNC
SourceCustomization
-> SupportedNamingCase
-> Maybe NamingCase
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
forall (m :: * -> *) r a.
(MonadReader r m, Has MkTypename r, Has NamingCase r,
MonadError QErr m) =>
SourceCustomization
-> SupportedNamingCase -> Maybe NamingCase -> m a -> m a
withSourceCustomization SourceCustomization
sourceCustomization (Backend b => SupportedNamingCase
forall (b :: BackendType). Backend b => SupportedNamingCase
namingConventionSupport @b) Maybe NamingCase
globalDefaultNC do
let validFunctions :: FunctionCache b
validFunctions = FunctionCache b -> FunctionCache b
forall (b :: BackendType). FunctionCache b -> FunctionCache b
takeValidFunctions FunctionCache b
functions
validTables :: TableCache b
validTables = TableCache b -> TableCache b
forall (b :: BackendType).
Backend b =>
TableCache b -> TableCache b
takeValidTables TableCache b
tables
([FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedQueryRootFields, [FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedSubscriptionRootFields) <-
MkRootFieldName
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser Parse (QueryRootField UnpreparedValue)],
[FieldParser Parse (QueryRootField UnpreparedValue)])
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
MkRootFieldName
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
buildRelayQueryAndSubscriptionFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo TableCache b
validTables FunctionCache b
validFunctions
MkTypename
makeTypename <- ((SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
-> MkTypename)
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
MkTypename
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
-> MkTypename
forall a t. Has a t => t -> a
getter
(,,,)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__query))
([FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedQueryRootFields)
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__mutation_frontend))
(MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildMutationFields MkRootFieldName
mkRootFieldName Scenario
Frontend SourceInfo b
sourceInfo TableCache b
validTables FunctionCache b
validFunctions)
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__mutation_backend))
(MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (MutationRootField UnpreparedValue)]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildMutationFields MkRootFieldName
mkRootFieldName Scenario
Backend SourceInfo b
sourceInfo TableCache b
validTables FunctionCache b
validFunctions)
ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SourceCustomization
-> MkTypename
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) (n :: * -> *) (db :: BackendType -> *) remote
action.
(Functor f, MonadParse n) =>
SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields
SourceCustomization
sourceCustomization
(MkTypename
makeTypename MkTypename -> MkTypename -> MkTypename
forall a. Semigroup a => a -> a -> a
<> (Name -> Name) -> MkTypename
MkTypename (Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__subscription))
([FieldParser Parse (QueryRootField UnpreparedValue)]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
[FieldParser Parse (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldParser Parse (QueryRootField UnpreparedValue)]
uncustomizedSubscriptionRootFields)
where
sourceCustomization :: SourceCustomization
sourceCustomization =
if ExperimentalFeature
EFNamingConventions ExperimentalFeature -> HashSet ExperimentalFeature -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` HashSet ExperimentalFeature
expFeatures
then SourceCustomization
sourceCustomization'
else SourceCustomization
sourceCustomization' {_scNamingConvention :: Maybe NamingCase
_scNamingConvention = Maybe NamingCase
forall a. Maybe a
Nothing}
unauthenticatedContext ::
forall m.
( MonadError QErr m,
MonadIO m
) =>
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject) ->
Options.RemoteSchemaPermissions ->
m (GQLContext, HashSet InconsistentMetadata)
unauthenticatedContext :: HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> RemoteSchemaPermissions
-> m (GQLContext, HashSet InconsistentMetadata)
unauthenticatedContext HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
allRemotes RemoteSchemaPermissions
remoteSchemaPermsCtx = do
let fakeSchemaOptions :: SchemaOptions
fakeSchemaOptions =
StringifyNumbers
-> DangerouslyCollapseBooleans
-> InferFunctionPermissions
-> OptimizePermissionFilters
-> SchemaOptions
SchemaOptions
StringifyNumbers
Options.Don'tStringifyNumbers
DangerouslyCollapseBooleans
Options.Don'tDangerouslyCollapseBooleans
InferFunctionPermissions
Options.InferFunctionPermissions
OptimizePermissionFilters
Options.Don'tOptimizePermissionFilters
fakeSchemaContext :: SchemaContext
fakeSchemaContext =
SchemaKind
-> RemoteRelationshipParserBuilder -> RoleName -> SchemaContext
SchemaContext
SchemaKind
HasuraSchema
RemoteRelationshipParserBuilder
ignoreRemoteRelationship
RoleName
fakeRole
fakeRole :: RoleName
fakeRole = NonEmptyText -> RoleName
mkRoleNameSafe [NT.nonEmptyTextQQ|MyNameIsOzymandiasKingOfKingsLookOnMyWorksYeMightyAndDespair|]
alteredRemoteSchemas :: HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
alteredRemoteSchemas =
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
allRemotes HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> ((RemoteSchemaCtx, MetadataObject)
-> (RemoteSchemaCtx, MetadataObject))
-> HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (RemoteSchemaCtx -> RemoteSchemaCtx)
-> (RemoteSchemaCtx, MetadataObject)
-> (RemoteSchemaCtx, MetadataObject)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first \RemoteSchemaCtx
context ->
RemoteSchemaCtx
context {_rscRemoteRelationships :: RemoteSchemaRelationships
_rscRemoteRelationships = RemoteSchemaRelationships
forall a. Monoid a => a
mempty}
MemoizeT m (GQLContext, HashSet InconsistentMetadata)
-> m (GQLContext, HashSet InconsistentMetadata)
forall (m :: * -> *) a. Monad m => MemoizeT m a -> m a
runMemoizeT do
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
queryFields, [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationFields, [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields, HashSet InconsistentMetadata
remoteErrors) <- case RemoteSchemaPermissions
remoteSchemaPermsCtx of
RemoteSchemaPermissions
Options.EnableRemoteSchemaPermissions ->
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
HashSet InconsistentMetadata)
-> MemoizeT
m
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
HashSet InconsistentMetadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([], [], [], HashSet InconsistentMetadata
forall a. Monoid a => a
mempty)
RemoteSchemaPermissions
Options.DisableRemoteSchemaPermissions -> do
([RemoteSchemaParser Parse]
remoteFields, HashSet InconsistentMetadata
remoteSchemaErrors) <-
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
-> MemoizeT
m ([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall (m :: * -> *) a.
SchemaContext
-> SchemaOptions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
m
a
-> m a
runRemoteSchema SchemaContext
fakeSchemaContext SchemaOptions
fakeSchemaOptions (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
-> MemoizeT
m ([RemoteSchemaParser Parse], HashSet InconsistentMetadata))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
-> MemoizeT
m ([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall a b. (a -> b) -> a -> b
$
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> RoleName
-> RemoteSchemaPermissions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> RoleName
-> RemoteSchemaPermissions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
buildAndValidateRemoteSchemas HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
alteredRemoteSchemas [] [] RoleName
fakeRole RemoteSchemaPermissions
remoteSchemaPermsCtx
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
HashSet InconsistentMetadata)
-> MemoizeT
m
([FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))],
[FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))],
HashSet InconsistentMetadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( (NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue)
-> NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue
forall remote (db :: BackendType -> *) action raw.
remote -> RootField db remote action raw
RFRemote) (FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piQuery [RemoteSchemaParser Parse]
remoteFields,
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (MutationRootField UnpreparedValue))
-> FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> MutationRootField UnpreparedValue)
-> NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (MutationRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> MutationRootField UnpreparedValue
forall remote (db :: BackendType -> *) action raw.
remote -> RootField db remote action raw
RFRemote) (FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue)))
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> Maybe
[FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piMutation [RemoteSchemaParser Parse]
remoteFields),
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue)
-> NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue
forall remote (db :: BackendType -> *) action raw.
remote -> RootField db remote action raw
RFRemote) (FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ((RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> Maybe
[FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piSubscription [RemoteSchemaParser Parse]
remoteFields),
HashSet InconsistentMetadata
remoteSchemaErrors
)
Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser <-
Bool
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))))
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
whenMaybe (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationFields) (MemoizeT
m
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> MemoizeT
m
(Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))))
forall (n :: * -> *) (m :: * -> *) a.
(QErrM n, MonadParse m) =>
Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
mutationRoot (Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description Text
"mutation root") [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
mutationFields
MemoizeT
m
(Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))))
-> (Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))))
-> Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> RootFieldMap (MutationRootField UnpreparedValue))
-> Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))))
-> Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NamespacedFieldMap (MutationRootField UnpreparedValue)
-> RootFieldMap (MutationRootField UnpreparedValue)
forall a. NamespacedFieldMap a -> RootFieldMap a
flattenNamespaces (NamespacedFieldMap (MutationRootField UnpreparedValue)
-> RootFieldMap (MutationRootField UnpreparedValue))
-> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> NamespacedFieldMap (MutationRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> RootFieldMap (MutationRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))
-> NamespacedField (MutationRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> NamespacedFieldMap (MutationRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))
-> NamespacedField (MutationRootField UnpreparedValue)
forall (db :: BackendType -> *) remote action.
ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF)
Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser <-
Bool
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))))
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
whenMaybe (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields) (MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> MemoizeT
m
(Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
forall (n :: * -> *) (m :: * -> *) a.
(QErrM n, MonadParse m) =>
Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
subscriptionRoot (Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description Text
"subscription root") [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields
MemoizeT
m
(Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
-> (Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue))
-> Parser
'Output
Parse
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue)
forall a. NamespacedFieldMap a -> RootFieldMap a
flattenNamespaces (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue))
-> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue)
forall (db :: BackendType -> *) remote action.
ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF)
Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParser <- [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> MemoizeT
m
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadParse n, MonadError QErr m) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryWithIntrospectionHelper [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
queryFields Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
forall a. Maybe a
Nothing
MemoizeT m (Schema MetadataObjId) -> MemoizeT m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MemoizeT m (Schema MetadataObjId) -> MemoizeT m ())
-> (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId))
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m (Schema MetadataObjId)
forall (m :: * -> *) a.
QErrM m =>
Either ConflictingDefinitions a -> m a
throwOnConflictingDefinitions (Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ())
-> Either ConflictingDefinitions (Schema MetadataObjId)
-> MemoizeT m ()
forall a b. (a -> b) -> a -> b
$
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions (Schema MetadataObjId)
buildIntrospectionSchema
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParser)
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser)
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
(GQLContext, HashSet InconsistentMetadata)
-> MemoizeT m (GQLContext, HashSet InconsistentMetadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> GQLContext
GQLContext (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
queryParser) (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue))
-> ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(ParserFn (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser) (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
forall a. Parser 'Output Parse a -> ParserFn a
finalizeParser (Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue))
-> ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output Parse (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser), HashSet InconsistentMetadata
remoteErrors)
buildAndValidateRemoteSchemas ::
forall m.
( MonadError QErr m,
MonadIO m
) =>
HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject) ->
[FieldParser P.Parse (NamespacedField (QueryRootField UnpreparedValue))] ->
[FieldParser P.Parse (NamespacedField (MutationRootField UnpreparedValue))] ->
RoleName ->
Options.RemoteSchemaPermissions ->
ReaderT
( SchemaContext,
SchemaOptions,
MkTypename,
CustomizeRemoteFieldName,
NamingCase
)
(MemoizeT m)
([RemoteSchemaParser P.Parse], HashSet InconsistentMetadata)
buildAndValidateRemoteSchemas :: HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> RoleName
-> RemoteSchemaPermissions
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
buildAndValidateRemoteSchemas HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
remotes [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesQueryFields [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationFields RoleName
role RemoteSchemaPermissions
remoteSchemaPermsCtx =
WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata))
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
([RemoteSchemaParser Parse], HashSet InconsistentMetadata)
forall a b. (a -> b) -> a -> b
$ ([RemoteSchemaParser Parse]
-> (RemoteSchemaCtx, MetadataObject)
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse])
-> [RemoteSchemaParser Parse]
-> [(RemoteSchemaCtx, MetadataObject)]
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM [RemoteSchemaParser Parse]
-> (RemoteSchemaCtx, MetadataObject)
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
step [] (HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
-> [(RemoteSchemaCtx, MetadataObject)]
forall k v. HashMap k v -> [v]
Map.elems HashMap RemoteSchemaName (RemoteSchemaCtx, MetadataObject)
remotes)
where
getFieldName :: FieldParser origin m a -> Name
getFieldName = Definition origin (FieldInfo origin) -> Name
forall a. HasName a => a -> Name
P.getName (Definition origin (FieldInfo origin) -> Name)
-> (FieldParser origin m a -> Definition origin (FieldInfo origin))
-> FieldParser origin m a
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldParser origin m a -> Definition origin (FieldInfo origin)
forall origin (m :: * -> *) a.
FieldParser origin m a -> Definition origin (FieldInfo origin)
P.fDefinition
sourcesQueryFieldNames :: [Name]
sourcesQueryFieldNames = FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
-> Name
forall origin (m :: * -> *) a. FieldParser origin m a -> Name
getFieldName (FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))
-> Name)
-> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
-> [Name]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldParser
Parse (NamespacedField (QueryRootField UnpreparedValue))]
sourcesQueryFields
sourcesMutationFieldNames :: [Name]
sourcesMutationFieldNames = FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))
-> Name
forall origin (m :: * -> *) a. FieldParser origin m a -> Name
getFieldName (FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))
-> Name)
-> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
-> [Name]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldParser
Parse (NamespacedField (MutationRootField UnpreparedValue))]
sourcesMutationFields
step :: [RemoteSchemaParser Parse]
-> (RemoteSchemaCtx, MetadataObject)
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
step [RemoteSchemaParser Parse]
validatedSchemas (RemoteSchemaCtx
remoteSchemaContext, MetadataObject
metadataId) = do
let previousSchemasQueryFieldNames :: [Name]
previousSchemasQueryFieldNames = (FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name)
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name
forall origin (m :: * -> *) a. FieldParser origin m a -> Name
getFieldName ([FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name])
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> a -> b
$ (RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piQuery [RemoteSchemaParser Parse]
validatedSchemas
previousSchemasMutationFieldNames :: [Name]
previousSchemasMutationFieldNames = (FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name)
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name
forall origin (m :: * -> *) a. FieldParser origin m a -> Name
getFieldName ([FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name])
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> a -> b
$ [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall a b. (a -> b) -> a -> b
$ (RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))])
-> [RemoteSchemaParser Parse]
-> [[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> Maybe
[FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piMutation [RemoteSchemaParser Parse]
validatedSchemas
reportInconsistency :: Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
reportInconsistency Text
reason = HashSet InconsistentMetadata
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (HashSet InconsistentMetadata
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> HashSet InconsistentMetadata
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$ InconsistentMetadata -> HashSet InconsistentMetadata
forall a. Hashable a => a -> HashSet a
Set.singleton (InconsistentMetadata -> HashSet InconsistentMetadata)
-> InconsistentMetadata -> HashSet InconsistentMetadata
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Value -> MetadataObject -> InconsistentMetadata
InconsistentObject Text
reason Maybe Value
forall a. Maybe a
Nothing MetadataObject
metadataId
Maybe (RemoteSchemaParser Parse)
maybeParser <- ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
(Maybe (RemoteSchemaParser Parse))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
(Maybe (RemoteSchemaParser Parse)))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
(Maybe (RemoteSchemaParser Parse))
forall a b. (a -> b) -> a -> b
$ RemoteSchemaPermissions
-> RoleName
-> RemoteSchemaCtx
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
RemoteSchemaPermissions
-> RoleName
-> RemoteSchemaCtx
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
buildRemoteSchemaParser RemoteSchemaPermissions
remoteSchemaPermsCtx RoleName
role RemoteSchemaCtx
remoteSchemaContext
case Maybe (RemoteSchemaParser Parse)
maybeParser of
Maybe (RemoteSchemaParser Parse)
Nothing -> [RemoteSchemaParser Parse]
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [RemoteSchemaParser Parse]
validatedSchemas
Just RemoteSchemaParser Parse
remoteSchemaParser -> do
(()
_, HashSet InconsistentMetadata
inconsistencies) <- WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
((), HashSet InconsistentMetadata)
forall w (m :: * -> *) a. MonadWriter w m => m a -> m (a, w)
listen (WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
((), HashSet InconsistentMetadata))
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
((), HashSet InconsistentMetadata)
forall a b. (a -> b) -> a -> b
$ do
let newSchemaQueryFieldNames :: [Name]
newSchemaQueryFieldNames = (FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name)
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name
forall origin (m :: * -> *) a. FieldParser origin m a -> Name
getFieldName ([FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name])
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> a -> b
$ RemoteSchemaParser Parse
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piQuery RemoteSchemaParser Parse
remoteSchemaParser
newSchemaMutationFieldNames :: [Name]
newSchemaMutationFieldNames = ([FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name])
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name)
-> [FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> Name
forall origin (m :: * -> *) a. FieldParser origin m a -> Name
getFieldName) (Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name])
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [Name]
forall a b. (a -> b) -> a -> b
$ RemoteSchemaParser Parse
-> Maybe
[FieldParser
Parse
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
forall (n :: * -> *).
RemoteSchemaParser n
-> Maybe
[FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
piMutation RemoteSchemaParser Parse
remoteSchemaParser
HashSet Name
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_
([Name] -> HashSet Name
forall a. (Eq a, Hashable a) => [a] -> HashSet a
duplicates ([Name] -> HashSet Name) -> [Name] -> HashSet Name
forall a b. (a -> b) -> a -> b
$ [Name]
newSchemaQueryFieldNames [Name] -> [Name] -> [Name]
forall a. Semigroup a => a -> a -> a
<> [Name]
previousSchemasQueryFieldNames)
\Name
name -> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
reportInconsistency (Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$ Text
"Duplicate remote field " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
forall t. ToTxt t => t -> Text
squote Name
name
HashSet Name
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ([Name] -> HashSet Name
forall a. (Eq a, Hashable a) => [a] -> HashSet a
duplicates ([Name] -> HashSet Name) -> [Name] -> HashSet Name
forall a b. (a -> b) -> a -> b
$ [Name]
newSchemaQueryFieldNames [Name] -> [Name] -> [Name]
forall a. Semigroup a => a -> a -> a
<> [Name]
sourcesQueryFieldNames) ((Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$
\Name
name -> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
reportInconsistency (Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$ Text
"Field cannot be overwritten by remote field " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
forall t. ToTxt t => t -> Text
squote Name
name
Bool
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Name] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Name]
newSchemaMutationFieldNames) do
HashSet Name
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ([Name] -> HashSet Name
forall a. (Eq a, Hashable a) => [a] -> HashSet a
duplicates ([Name] -> HashSet Name) -> [Name] -> HashSet Name
forall a b. (a -> b) -> a -> b
$ [Name]
newSchemaMutationFieldNames [Name] -> [Name] -> [Name]
forall a. Semigroup a => a -> a -> a
<> [Name]
previousSchemasMutationFieldNames) ((Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$
\Name
name -> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
reportInconsistency (Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$ Text
"Duplicate remote field " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
forall t. ToTxt t => t -> Text
squote Name
name
HashSet Name
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ([Name] -> HashSet Name
forall a. (Eq a, Hashable a) => [a] -> HashSet a
duplicates ([Name] -> HashSet Name) -> [Name] -> HashSet Name
forall a b. (a -> b) -> a -> b
$ [Name]
newSchemaMutationFieldNames [Name] -> [Name] -> [Name]
forall a. Semigroup a => a -> a -> a
<> [Name]
sourcesMutationFieldNames) ((Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> (Name
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$
\Name
name -> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
reportInconsistency (Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
())
-> Text
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
()
forall a b. (a -> b) -> a -> b
$ Text
"Field cannot be overwritten by remote field " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
forall t. ToTxt t => t -> Text
squote Name
name
[RemoteSchemaParser Parse]
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([RemoteSchemaParser Parse]
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse])
-> [RemoteSchemaParser Parse]
-> WriterT
(HashSet InconsistentMetadata)
(ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m))
[RemoteSchemaParser Parse]
forall a b. (a -> b) -> a -> b
$
if HashSet InconsistentMetadata -> Bool
forall a. HashSet a -> Bool
Set.null HashSet InconsistentMetadata
inconsistencies
then RemoteSchemaParser Parse
remoteSchemaParser RemoteSchemaParser Parse
-> [RemoteSchemaParser Parse] -> [RemoteSchemaParser Parse]
forall a. a -> [a] -> [a]
: [RemoteSchemaParser Parse]
validatedSchemas
else [RemoteSchemaParser Parse]
validatedSchemas
buildRemoteSchemaParser ::
forall m.
(MonadError QErr m, MonadIO m) =>
Options.RemoteSchemaPermissions ->
RoleName ->
RemoteSchemaCtx ->
ReaderT
( SchemaContext,
SchemaOptions,
MkTypename,
CustomizeRemoteFieldName,
NamingCase
)
(MemoizeT m)
(Maybe (RemoteSchemaParser P.Parse))
buildRemoteSchemaParser :: RemoteSchemaPermissions
-> RoleName
-> RemoteSchemaCtx
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
buildRemoteSchemaParser RemoteSchemaPermissions
remoteSchemaPermsCtx RoleName
roleName RemoteSchemaCtx
context = do
let maybeIntrospection :: Maybe IntrospectionResult
maybeIntrospection = RemoteSchemaPermissions
-> RoleName -> RemoteSchemaCtx -> Maybe IntrospectionResult
getIntrospectionResult RemoteSchemaPermissions
remoteSchemaPermsCtx RoleName
roleName RemoteSchemaCtx
context
Maybe IntrospectionResult
-> (IntrospectionResult
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(RemoteSchemaParser Parse))
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(Maybe (RemoteSchemaParser Parse))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for Maybe IntrospectionResult
maybeIntrospection \IntrospectionResult
introspection ->
IntrospectionResult
-> RemoteSchemaRelationships
-> RemoteSchemaInfo
-> ReaderT
(SchemaContext, SchemaOptions, MkTypename,
CustomizeRemoteFieldName, NamingCase)
(MemoizeT m)
(RemoteSchemaParser Parse)
forall r (m :: * -> *) (n :: * -> *).
MonadBuildRemoteSchema r m n =>
IntrospectionResult
-> RemoteSchemaRelationships
-> RemoteSchemaInfo
-> m (RemoteSchemaParser n)
buildRemoteParser IntrospectionResult
introspection (RemoteSchemaCtx -> RemoteSchemaRelationships
_rscRemoteRelationships RemoteSchemaCtx
context) (RemoteSchemaCtx -> RemoteSchemaInfo
_rscInfo RemoteSchemaCtx
context)
buildQueryAndSubscriptionFields ::
forall b r m n.
MonadBuildSchema b r m n =>
MkRootFieldName ->
SourceInfo b ->
TableCache b ->
FunctionCache b ->
m ([P.FieldParser n (QueryRootField UnpreparedValue)], [P.FieldParser n (SubscriptionRootField UnpreparedValue)], [(G.Name, Parser 'Output n (ApolloFederationParserFunction n))])
buildQueryAndSubscriptionFields :: MkRootFieldName
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)],
[(Name, Parser 'Output n (ApolloFederationParserFunction n))])
buildQueryAndSubscriptionFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo TableCache b
tables (FunctionExposedAs -> FunctionCache b -> FunctionCache b
forall (b :: BackendType).
FunctionExposedAs -> FunctionCache b -> FunctionCache b
takeExposedAs FunctionExposedAs
FEAQuery -> FunctionCache b
functions) = do
RoleName
roleName <- (SchemaContext -> RoleName) -> m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
InferFunctionPermissions
functionPermsCtx <- (SchemaOptions -> InferFunctionPermissions)
-> m InferFunctionPermissions
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> InferFunctionPermissions
Options.soInferFunctionPermissions
[FieldParser n (QueryRootField UnpreparedValue)]
functionSelectExpParsers <-
[[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)])
-> ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]])
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
([Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)])
-> m [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(FunctionName b, FunctionInfo b)]
-> ((FunctionName b, FunctionInfo b)
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)]))
-> m [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (FunctionCache b -> [(FunctionName b, FunctionInfo b)]
forall k v. HashMap k v -> [(k, v)]
Map.toList FunctionCache b
functions) \(FunctionName b
functionName, FunctionInfo b
functionInfo) -> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)]))
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)])
forall a b. (a -> b) -> a -> b
$ do
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$
RoleName
roleName RoleName -> RoleName -> Bool
forall a. Eq a => a -> a -> Bool
== RoleName
adminRoleName
Bool -> Bool -> Bool
|| RoleName
roleName RoleName -> HashMap RoleName FunctionPermissionInfo -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`Map.member` FunctionInfo b -> HashMap RoleName FunctionPermissionInfo
forall (b :: BackendType).
FunctionInfo b -> HashMap RoleName FunctionPermissionInfo
_fiPermissions FunctionInfo b
functionInfo
Bool -> Bool -> Bool
|| InferFunctionPermissions
functionPermsCtx InferFunctionPermissions -> InferFunctionPermissions -> Bool
forall a. Eq a => a -> a -> Bool
== InferFunctionPermissions
Options.InferFunctionPermissions
let targetTableName :: TableName b
targetTableName = FunctionInfo b -> TableName b
forall (b :: BackendType). FunctionInfo b -> TableName b
_fiReturnType FunctionInfo b
functionInfo
m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)])
-> m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
mkRFs (m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)])
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo b
-> FunctionName b
-> FunctionInfo b
-> TableName b
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> SourceInfo b
-> FunctionName b
-> FunctionInfo b
-> TableName b
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildFunctionQueryFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo FunctionName b
functionName FunctionInfo b
functionInfo TableName b
targetTableName
([[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]]
tableQueryFields, [[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]]
tableSubscriptionFields, [Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))]
apolloFedTableParsers) <-
[([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> ([[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n))])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 ([([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> ([[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n))]))
-> ([Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> [([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n)))])
-> [Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> ([[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n))])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> [([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
([Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> ([[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n))]))
-> m [Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
-> m ([[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]],
[Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n))])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(TableName b, TableInfo b)]
-> ((TableName b, TableInfo b)
-> m (Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n)))))
-> m [Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (TableCache b -> [(TableName b, TableInfo b)]
forall k v. HashMap k v -> [(k, v)]
Map.toList TableCache b
tables) \(TableName b
tableName, TableInfo b
tableInfo) -> MaybeT
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> m (Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> m (Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe
(Name, Parser 'Output n (ApolloFederationParserFunction n)))))
-> MaybeT
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> m (Maybe
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))))
forall a b. (a -> b) -> a -> b
$ do
GQLNameIdentifier
tableIdentifierName <- TableInfo b -> MaybeT m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName @b TableInfo b
tableInfo
m ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> MaybeT
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> MaybeT
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))))
-> m ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> MaybeT
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
buildTableQueryAndSubscriptionFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
tableIdentifierName
let tableQueryRootFields :: [FieldParser n (QueryRootField UnpreparedValue)]
tableQueryRootFields = (FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (QueryRootField UnpreparedValue))
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (QueryRootField UnpreparedValue)
mkRF ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser n (QueryRootField UnpreparedValue)])
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]]
tableQueryFields
tableSubscriptionRootFields :: [FieldParser n (QueryRootField UnpreparedValue)]
tableSubscriptionRootFields = (FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (QueryRootField UnpreparedValue))
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (QueryRootField UnpreparedValue)
mkRF ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser n (QueryRootField UnpreparedValue)])
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]]
tableSubscriptionFields
([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)],
[(Name, Parser 'Output n (ApolloFederationParserFunction n))])
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)],
[(Name, Parser 'Output n (ApolloFederationParserFunction n))])
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( [FieldParser n (QueryRootField UnpreparedValue)]
tableQueryRootFields [FieldParser n (QueryRootField UnpreparedValue)]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall a. Semigroup a => a -> a -> a
<> [FieldParser n (QueryRootField UnpreparedValue)]
functionSelectExpParsers,
[FieldParser n (QueryRootField UnpreparedValue)]
tableSubscriptionRootFields [FieldParser n (QueryRootField UnpreparedValue)]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall a. Semigroup a => a -> a -> a
<> [FieldParser n (QueryRootField UnpreparedValue)]
functionSelectExpParsers,
[Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))]
-> [(Name, Parser 'Output n (ApolloFederationParserFunction n))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))]
apolloFedTableParsers
)
where
mkRFs :: m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
mkRFs = SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) a
(db :: BackendType -> *) remote action raw.
(HasTag b, Functor m, Functor n) =>
SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRootFields SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
QueryDB b r (v b) -> QueryDBRoot r v b
QDBR
mkRF :: FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (QueryRootField UnpreparedValue)
mkRF = SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (QueryRootField UnpreparedValue)
forall (b :: BackendType) (n :: * -> *) a (db :: BackendType -> *)
remote action raw.
(HasTag b, Functor n) =>
SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> FieldParser n a
-> FieldParser n (RootField db remote action raw)
mkRootField SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
QueryDB b r (v b) -> QueryDBRoot r v b
QDBR
sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
sourceConfig :: SourceConfig b
sourceConfig = SourceInfo b -> SourceConfig b
forall (b :: BackendType). SourceInfo b -> SourceConfig b
_siConfiguration SourceInfo b
sourceInfo
queryTagsConfig :: Maybe QueryTagsConfig
queryTagsConfig = SourceInfo b -> Maybe QueryTagsConfig
forall (b :: BackendType). SourceInfo b -> Maybe QueryTagsConfig
_siQueryTagsConfig SourceInfo b
sourceInfo
buildRelayQueryAndSubscriptionFields ::
forall b r m n.
MonadBuildSchema b r m n =>
MkRootFieldName ->
SourceInfo b ->
TableCache b ->
FunctionCache b ->
m ([P.FieldParser n (QueryRootField UnpreparedValue)], [P.FieldParser n (SubscriptionRootField UnpreparedValue)])
buildRelayQueryAndSubscriptionFields :: MkRootFieldName
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
buildRelayQueryAndSubscriptionFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo TableCache b
tables (FunctionExposedAs -> FunctionCache b -> FunctionCache b
forall (b :: BackendType).
FunctionExposedAs -> FunctionCache b -> FunctionCache b
takeExposedAs FunctionExposedAs
FEAQuery -> FunctionCache b
functions) = do
RoleName
roleName <- (SchemaContext -> RoleName) -> m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
([Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
tableConnectionQueryFields, [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
tableConnectionSubscriptionFields) <-
[(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]],
[Maybe [FieldParser n (QueryRootField UnpreparedValue)]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]],
[Maybe [FieldParser n (QueryRootField UnpreparedValue)]]))
-> ([Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> [(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])])
-> [Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]],
[Maybe [FieldParser n (QueryRootField UnpreparedValue)]])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> [(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
([Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]],
[Maybe [FieldParser n (QueryRootField UnpreparedValue)]]))
-> m [Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
-> m ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]],
[Maybe [FieldParser n (QueryRootField UnpreparedValue)]])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(TableName b, TableInfo b)]
-> ((TableName b, TableInfo b)
-> m (Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])))
-> m [Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (TableCache b -> [(TableName b, TableInfo b)]
forall k v. HashMap k v -> [(k, v)]
Map.toList TableCache b
tables) \(TableName b
tableName, TableInfo b
tableInfo) -> MaybeT
m
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])
-> m (Maybe
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)]))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
GQLNameIdentifier
tableIdentifierName <- TableInfo b -> MaybeT m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName @b TableInfo b
tableInfo
SelPermInfo {Bool
Maybe Int
HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
HashMap
ComputedFieldName (Maybe (AnnColumnCaseBoolExpPartialSQL b))
HashSet Text
AnnBoolExpPartialSQL b
AllowedRootFields SubscriptionRootFieldType
AllowedRootFields QueryRootFieldType
spiAllowedSubscriptionRootFields :: forall (b :: BackendType).
SelPermInfo b -> AllowedRootFields SubscriptionRootFieldType
spiAllowedQueryRootFields :: forall (b :: BackendType).
SelPermInfo b -> AllowedRootFields QueryRootFieldType
spiRequiredHeaders :: forall (b :: BackendType). SelPermInfo b -> HashSet Text
spiAllowAgg :: forall (b :: BackendType). SelPermInfo b -> Bool
spiLimit :: forall (b :: BackendType). SelPermInfo b -> Maybe Int
spiFilter :: forall (b :: BackendType). SelPermInfo b -> AnnBoolExpPartialSQL b
spiComputedFields :: forall (b :: BackendType).
SelPermInfo b
-> HashMap
ComputedFieldName (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiCols :: forall (b :: BackendType).
SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiAllowedSubscriptionRootFields :: AllowedRootFields SubscriptionRootFieldType
spiAllowedQueryRootFields :: AllowedRootFields QueryRootFieldType
spiRequiredHeaders :: HashSet Text
spiAllowAgg :: Bool
spiLimit :: Maybe Int
spiFilter :: AnnBoolExpPartialSQL b
spiComputedFields :: HashMap
ComputedFieldName (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiCols :: HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
..} <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
NESeq (ColumnInfo b)
pkeyColumns <- Maybe (NESeq (ColumnInfo b)) -> MaybeT m (NESeq (ColumnInfo b))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (NESeq (ColumnInfo b)) -> MaybeT m (NESeq (ColumnInfo b)))
-> Maybe (NESeq (ColumnInfo b)) -> MaybeT m (NESeq (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
tableInfo TableInfo b
-> Getting
(First (NESeq (ColumnInfo b))) (TableInfo b) (NESeq (ColumnInfo b))
-> Maybe (NESeq (ColumnInfo b))
forall s a. s -> Getting (First a) s a -> Maybe a
^? (TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> TableInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableInfo b)
forall (b :: BackendType). Lens' (TableInfo b) (TableCoreInfo b)
tiCoreInfo ((TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> TableInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableInfo b))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> Getting
(First (NESeq (ColumnInfo b))) (TableInfo b) (NESeq (ColumnInfo b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b)
forall (b :: BackendType) field primaryKeyColumn1
primaryKeyColumn2.
Lens
(TableCoreInfoG b field primaryKeyColumn1)
(TableCoreInfoG b field primaryKeyColumn2)
(Maybe (PrimaryKey b primaryKeyColumn1))
(Maybe (PrimaryKey b primaryKeyColumn2))
tciPrimaryKey ((Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b)))
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b))
forall (b :: BackendType) a1 a2.
Lens (PrimaryKey b a1) (PrimaryKey b a2) (NESeq a1) (NESeq a2)
pkColumns
[FieldParser n (QueryRootField UnpreparedValue)]
relayRootFields <- m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)])
-> m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
mkRFs (m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)])
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> NESeq (ColumnInfo b)
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> NESeq (ColumnInfo b)
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableRelayQueryFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
tableIdentifierName NESeq (ColumnInfo b)
pkeyColumns
let includeRelayWhen :: Bool -> Maybe [FieldParser n (QueryRootField UnpreparedValue)]
includeRelayWhen Bool
True = [FieldParser n (QueryRootField UnpreparedValue)]
-> Maybe [FieldParser n (QueryRootField UnpreparedValue)]
forall a. a -> Maybe a
Just [FieldParser n (QueryRootField UnpreparedValue)]
relayRootFields
includeRelayWhen Bool
False = Maybe [FieldParser n (QueryRootField UnpreparedValue)]
forall a. Maybe a
Nothing
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])
-> MaybeT
m
(Maybe [FieldParser n (QueryRootField UnpreparedValue)],
Maybe [FieldParser n (QueryRootField UnpreparedValue)])
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( Bool -> Maybe [FieldParser n (QueryRootField UnpreparedValue)]
includeRelayWhen (QueryRootFieldType -> AllowedRootFields QueryRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed QueryRootFieldType
QRFTSelect AllowedRootFields QueryRootFieldType
spiAllowedQueryRootFields),
Bool -> Maybe [FieldParser n (QueryRootField UnpreparedValue)]
includeRelayWhen (SubscriptionRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed SubscriptionRootFieldType
SRFTSelect AllowedRootFields SubscriptionRootFieldType
spiAllowedSubscriptionRootFields)
)
[Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
functionConnectionFields <- [(FunctionName b, FunctionInfo b)]
-> ((FunctionName b, FunctionInfo b)
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)]))
-> m [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (FunctionCache b -> [(FunctionName b, FunctionInfo b)]
forall k v. HashMap k v -> [(k, v)]
Map.toList FunctionCache b
functions) (((FunctionName b, FunctionInfo b)
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)]))
-> m [Maybe [FieldParser n (QueryRootField UnpreparedValue)]])
-> ((FunctionName b, FunctionInfo b)
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)]))
-> m [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
forall a b. (a -> b) -> a -> b
$ \(FunctionName b
functionName, FunctionInfo b
functionInfo) -> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (QueryRootField UnpreparedValue)])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
let returnTableName :: TableName b
returnTableName = FunctionInfo b -> TableName b
forall (b :: BackendType). FunctionInfo b -> TableName b
_fiReturnType FunctionInfo b
functionInfo
TableInfo b
returnTableInfo <- m (TableInfo b) -> MaybeT m (TableInfo b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo b) -> MaybeT m (TableInfo b))
-> m (TableInfo b) -> MaybeT m (TableInfo b)
forall a b. (a -> b) -> a -> b
$ SourceInfo b -> TableName b -> m (TableInfo b)
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo b
sourceInfo TableName b
returnTableName
NESeq (ColumnInfo b)
pkeyColumns <- m (Maybe (NESeq (ColumnInfo b))) -> MaybeT m (NESeq (ColumnInfo b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (NESeq (ColumnInfo b)))
-> MaybeT m (NESeq (ColumnInfo b)))
-> m (Maybe (NESeq (ColumnInfo b)))
-> MaybeT m (NESeq (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ (TableInfo b
-> Getting
(First (NESeq (ColumnInfo b))) (TableInfo b) (NESeq (ColumnInfo b))
-> Maybe (NESeq (ColumnInfo b))
forall s a. s -> Getting (First a) s a -> Maybe a
^? (TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> TableInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableInfo b)
forall (b :: BackendType). Lens' (TableInfo b) (TableCoreInfo b)
tiCoreInfo ((TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> TableInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableInfo b))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> Getting
(First (NESeq (ColumnInfo b))) (TableInfo b) (NESeq (ColumnInfo b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b)
forall (b :: BackendType) field primaryKeyColumn1
primaryKeyColumn2.
Lens
(TableCoreInfoG b field primaryKeyColumn1)
(TableCoreInfoG b field primaryKeyColumn2)
(Maybe (PrimaryKey b primaryKeyColumn1))
(Maybe (PrimaryKey b primaryKeyColumn2))
tciPrimaryKey ((Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> TableCoreInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableCoreInfo b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b)))
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b))
forall (b :: BackendType) a1 a2.
Lens (PrimaryKey b a1) (PrimaryKey b a2) (NESeq a1) (NESeq a2)
pkColumns) (TableInfo b -> Maybe (NESeq (ColumnInfo b)))
-> m (TableInfo b) -> m (Maybe (NESeq (ColumnInfo b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b -> m (TableInfo b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure TableInfo b
returnTableInfo
m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)])
-> m [FieldParser n (QueryRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
mkRFs (m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)])
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo b
-> FunctionName b
-> FunctionInfo b
-> TableName b
-> NESeq (ColumnInfo b)
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> SourceInfo b
-> FunctionName b
-> FunctionInfo b
-> TableName b
-> NESeq (ColumnInfo b)
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildFunctionRelayQueryFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo FunctionName b
functionName FunctionInfo b
functionInfo TableName b
returnTableName NESeq (ColumnInfo b)
pkeyColumns
([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)]))
-> ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
-> m ([FieldParser n (QueryRootField UnpreparedValue)],
[FieldParser n (QueryRootField UnpreparedValue)])
forall a b. (a -> b) -> a -> b
$
( [[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)])
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]])
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
forall a b. (a -> b) -> a -> b
$ [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
tableConnectionQueryFields [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
forall a. Semigroup a => a -> a -> a
<> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
functionConnectionFields,
[[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)])
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
-> [FieldParser n (QueryRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes ([Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]])
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [[FieldParser n (QueryRootField UnpreparedValue)]]
forall a b. (a -> b) -> a -> b
$ [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
tableConnectionSubscriptionFields [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
-> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
forall a. Semigroup a => a -> a -> a
<> [Maybe [FieldParser n (QueryRootField UnpreparedValue)]]
functionConnectionFields
)
where
mkRFs :: m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
mkRFs = SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (QueryRootField UnpreparedValue)]
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) a
(db :: BackendType -> *) remote action raw.
(HasTag b, Functor m, Functor n) =>
SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRootFields SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
QueryDB b r (v b) -> QueryDBRoot r v b
QDBR
sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
sourceConfig :: SourceConfig b
sourceConfig = SourceInfo b -> SourceConfig b
forall (b :: BackendType). SourceInfo b -> SourceConfig b
_siConfiguration SourceInfo b
sourceInfo
queryTagsConfig :: Maybe QueryTagsConfig
queryTagsConfig = SourceInfo b -> Maybe QueryTagsConfig
forall (b :: BackendType). SourceInfo b -> Maybe QueryTagsConfig
_siQueryTagsConfig SourceInfo b
sourceInfo
buildMutationFields ::
forall b r m n.
MonadBuildSchema b r m n =>
MkRootFieldName ->
Scenario ->
SourceInfo b ->
TableCache b ->
FunctionCache b ->
m [P.FieldParser n (MutationRootField UnpreparedValue)]
buildMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableCache b
-> FunctionCache b
-> m [FieldParser n (MutationRootField UnpreparedValue)]
buildMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo b
sourceInfo TableCache b
tables (FunctionExposedAs -> FunctionCache b -> FunctionCache b
forall (b :: BackendType).
FunctionExposedAs -> FunctionCache b -> FunctionCache b
takeExposedAs FunctionExposedAs
FEAMutation -> FunctionCache b
functions) = do
RoleName
roleName <- (SchemaContext -> RoleName) -> m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
[[FieldParser n (MutationRootField UnpreparedValue)]]
tableMutations <- [(TableName b, TableInfo b)]
-> ((TableName b, TableInfo b)
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> m [[FieldParser n (MutationRootField UnpreparedValue)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (TableCache b -> [(TableName b, TableInfo b)]
forall k v. HashMap k v -> [(k, v)]
Map.toList TableCache b
tables) \(TableName b
tableName, TableInfo b
tableInfo) -> do
GQLNameIdentifier
tableIdentifierName <- TableInfo b -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName @b TableInfo b
tableInfo
[FieldParser n (MutationRootField UnpreparedValue)]
inserts <-
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> m [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a (db :: BackendType -> *) remote action raw.
(a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRFs (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
MutationDB b r (v b) -> MutationDBRoot r v b
MDBR (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> (AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnotatedInsert b r v -> MutationDB b r v
MDBInsert) (m [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> m [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableInsertMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo b
sourceInfo TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
tableIdentifierName
[FieldParser n (MutationRootField UnpreparedValue)]
updates <-
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> m [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a (db :: BackendType -> *) remote action raw.
(a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRFs (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
MutationDB b r (v b) -> MutationDBRoot r v b
MDBR (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> (AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnotatedUpdateG b r v -> MutationDB b r v
MDBUpdate) (m [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> m [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableUpdateMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo b
sourceInfo TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
tableIdentifierName
[FieldParser n (MutationRootField UnpreparedValue)]
deletes <-
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> m [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a (db :: BackendType -> *) remote action raw.
(a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRFs (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
MutationDB b r (v b) -> MutationDBRoot r v b
MDBR (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> (AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. AnnDelG b r v -> MutationDB b r v
MDBDelete) (m [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> m [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableDeleteMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo b
sourceInfo TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
tableIdentifierName
[FieldParser n (MutationRootField UnpreparedValue)]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser n (MutationRootField UnpreparedValue)]
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [[FieldParser n (MutationRootField UnpreparedValue)]]
-> [FieldParser n (MutationRootField UnpreparedValue)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FieldParser n (MutationRootField UnpreparedValue)]
inserts, [FieldParser n (MutationRootField UnpreparedValue)]
updates, [FieldParser n (MutationRootField UnpreparedValue)]
deletes]
[Maybe [FieldParser n (MutationRootField UnpreparedValue)]]
functionMutations <- [(FunctionName b, FunctionInfo b)]
-> ((FunctionName b, FunctionInfo b)
-> m (Maybe [FieldParser n (MutationRootField UnpreparedValue)]))
-> m [Maybe [FieldParser n (MutationRootField UnpreparedValue)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (FunctionCache b -> [(FunctionName b, FunctionInfo b)]
forall k v. HashMap k v -> [(k, v)]
Map.toList FunctionCache b
functions) \(FunctionName b
functionName, FunctionInfo b
functionInfo) -> MaybeT m [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (MutationRootField UnpreparedValue)])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (MutationRootField UnpreparedValue)]))
-> MaybeT m [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe [FieldParser n (MutationRootField UnpreparedValue)])
forall a b. (a -> b) -> a -> b
$ do
let targetTableName :: TableName b
targetTableName = FunctionInfo b -> TableName b
forall (b :: BackendType). FunctionInfo b -> TableName b
_fiReturnType FunctionInfo b
functionInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$
RoleName
roleName RoleName -> RoleName -> Bool
forall a. Eq a => a -> a -> Bool
== RoleName
adminRoleName Bool -> Bool -> Bool
|| RoleName
roleName RoleName -> HashMap RoleName FunctionPermissionInfo -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`Map.member` FunctionInfo b -> HashMap RoleName FunctionPermissionInfo
forall (b :: BackendType).
FunctionInfo b -> HashMap RoleName FunctionPermissionInfo
_fiPermissions FunctionInfo b
functionInfo
m [FieldParser n (MutationRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (MutationRootField UnpreparedValue)]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [FieldParser n (MutationRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (MutationRootField UnpreparedValue)])
-> m [FieldParser n (MutationRootField UnpreparedValue)]
-> MaybeT m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ (MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b)
-> m [FieldParser
n
(MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a (db :: BackendType -> *) remote action raw.
(a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRFs MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue b
forall r (v :: BackendType -> *) (b :: BackendType).
MutationDB b r (v b) -> MutationDBRoot r v b
MDBR (m [FieldParser
n
(MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> m [FieldParser
n
(MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo b
-> FunctionName b
-> FunctionInfo b
-> TableName b
-> m [FieldParser
n
(MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
MkRootFieldName
-> SourceInfo b
-> FunctionName b
-> FunctionInfo b
-> TableName b
-> m [FieldParser
n
(MutationDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildFunctionMutationFields MkRootFieldName
mkRootFieldName SourceInfo b
sourceInfo FunctionName b
functionName FunctionInfo b
functionInfo TableName b
targetTableName
[FieldParser n (MutationRootField UnpreparedValue)]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser n (MutationRootField UnpreparedValue)]
-> m [FieldParser n (MutationRootField UnpreparedValue)])
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [[FieldParser n (MutationRootField UnpreparedValue)]]
-> [FieldParser n (MutationRootField UnpreparedValue)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser n (MutationRootField UnpreparedValue)]]
-> [FieldParser n (MutationRootField UnpreparedValue)])
-> [[FieldParser n (MutationRootField UnpreparedValue)]]
-> [FieldParser n (MutationRootField UnpreparedValue)]
forall a b. (a -> b) -> a -> b
$ [[FieldParser n (MutationRootField UnpreparedValue)]]
tableMutations [[FieldParser n (MutationRootField UnpreparedValue)]]
-> [[FieldParser n (MutationRootField UnpreparedValue)]]
-> [[FieldParser n (MutationRootField UnpreparedValue)]]
forall a. Semigroup a => a -> a -> a
<> [Maybe [FieldParser n (MutationRootField UnpreparedValue)]]
-> [[FieldParser n (MutationRootField UnpreparedValue)]]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe [FieldParser n (MutationRootField UnpreparedValue)]]
functionMutations
where
mkRFs :: forall a db remote action raw. (a -> db b) -> m [FieldParser n a] -> m [FieldParser n (RootField db remote action raw)]
mkRFs :: (a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRFs = SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) a
(db :: BackendType -> *) remote action raw.
(HasTag b, Functor m, Functor n) =>
SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRootFields SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig
sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
sourceConfig :: SourceConfig b
sourceConfig = SourceInfo b -> SourceConfig b
forall (b :: BackendType). SourceInfo b -> SourceConfig b
_siConfiguration SourceInfo b
sourceInfo
queryTagsConfig :: Maybe QueryTagsConfig
queryTagsConfig = SourceInfo b -> Maybe QueryTagsConfig
forall (b :: BackendType). SourceInfo b -> Maybe QueryTagsConfig
_siQueryTagsConfig SourceInfo b
sourceInfo
buildQueryParser ::
forall n m.
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[P.FieldParser n (NamespacedField (QueryRootField UnpreparedValue))] ->
[P.FieldParser n (G.SchemaIntrospection -> QueryRootField UnpreparedValue)] ->
[P.FieldParser n (NamespacedField (RemoteSchemaRootField (RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))] ->
[P.FieldParser n (QueryRootField UnpreparedValue)] ->
Maybe (Parser 'Output n (RootFieldMap (MutationRootField UnpreparedValue))) ->
Maybe (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))) ->
m (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
buildQueryParser :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
buildQueryParser [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
sourceQueryFields [FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)]
apolloFederationFields [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remoteQueryFields [FieldParser n (QueryRootField UnpreparedValue)]
actionQueryFields Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser = do
let partialApolloQueryFP :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
partialApolloQueryFP = [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
sourceQueryFields [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> (FieldParser n (QueryRootField UnpreparedValue)
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser n (QueryRootField UnpreparedValue)
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue)
forall a. a -> NamespacedField a
NotNamespaced) [FieldParser n (QueryRootField UnpreparedValue)]
actionQueryFields [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> (FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> (NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall a b. (a -> b) -> a -> b
$ (RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue)
-> NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue
forall remote (db :: BackendType -> *) action raw.
remote -> RootField db remote action raw
RFRemote) [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remoteQueryFields
Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
basicQueryPForApollo <- [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadError QErr m, MonadParse n) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryRootFromFields [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
partialApolloQueryFP
let buildApolloIntrospection :: (SchemaIntrospection -> QueryRootField UnpreparedValue)
-> n (NamespacedField (QueryRootField UnpreparedValue))
buildApolloIntrospection SchemaIntrospection -> QueryRootField UnpreparedValue
buildQRF = do
Schema MetadataObjId
partialSchema <-
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> n (Schema MetadataObjId)
forall (m :: * -> *).
MonadParse m =>
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> m (Schema MetadataObjId)
parseBuildIntrospectionSchema
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
basicQueryPForApollo)
(Parser 'Output n (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser)
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser)
NamespacedField (QueryRootField UnpreparedValue)
-> n (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NamespacedField (QueryRootField UnpreparedValue)
-> n (NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedField (QueryRootField UnpreparedValue)
-> n (NamespacedField (QueryRootField UnpreparedValue))
forall a b. (a -> b) -> a -> b
$ QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue)
forall a. a -> NamespacedField a
NotNamespaced (QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue))
-> QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue)
forall a b. (a -> b) -> a -> b
$ SchemaIntrospection -> QueryRootField UnpreparedValue
buildQRF (SchemaIntrospection -> QueryRootField UnpreparedValue)
-> SchemaIntrospection -> QueryRootField UnpreparedValue
forall a b. (a -> b) -> a -> b
$ Schema MetadataObjId -> SchemaIntrospection
forall origin. Schema origin -> SchemaIntrospection
convertToSchemaIntrospection Schema MetadataObjId
partialSchema
apolloFederationFieldsWithIntrospection :: [P.FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
apolloFederationFieldsWithIntrospection :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
apolloFederationFieldsWithIntrospection = [FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)]
apolloFederationFields [FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)]
-> (FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (FieldParser
n (SchemaIntrospection -> QueryRootField UnpreparedValue)
-> ((SchemaIntrospection -> QueryRootField UnpreparedValue)
-> n (NamespacedField (QueryRootField UnpreparedValue)))
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (m :: * -> *) origin a b.
Monad m =>
FieldParser origin m a -> (a -> m b) -> FieldParser origin m b
`P.bindField` (SchemaIntrospection -> QueryRootField UnpreparedValue)
-> n (NamespacedField (QueryRootField UnpreparedValue))
buildApolloIntrospection)
allQueryFields :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
allQueryFields = [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
partialApolloQueryFP [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
apolloFederationFieldsWithIntrospection
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadMemoize m, MonadParse n, MonadError QErr m) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryWithIntrospectionHelper [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
allQueryFields Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
mutationParser Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionParser
parseBuildIntrospectionSchema ::
MonadParse m =>
P.Type 'Output ->
Maybe (P.Type 'Output) ->
Maybe (P.Type 'Output) ->
m Schema
parseBuildIntrospectionSchema :: Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> m (Schema MetadataObjId)
parseBuildIntrospectionSchema Type 'Output
q Maybe (Type 'Output)
m Maybe (Type 'Output)
s =
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions (Schema MetadataObjId)
buildIntrospectionSchema Type 'Output
q Maybe (Type 'Output)
m Maybe (Type 'Output)
s Either ConflictingDefinitions (Schema MetadataObjId)
-> (ConflictingDefinitions -> m (Schema MetadataObjId))
-> m (Schema MetadataObjId)
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` (ParseErrorCode -> ErrorMessage -> m (Schema MetadataObjId)
forall (m :: * -> *) a.
MonadParse m =>
ParseErrorCode -> ErrorMessage -> m a
P.parseErrorWith ParseErrorCode
P.ConflictingDefinitionsError (ErrorMessage -> m (Schema MetadataObjId))
-> (ConflictingDefinitions -> ErrorMessage)
-> ConflictingDefinitions
-> m (Schema MetadataObjId)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConflictingDefinitions -> ErrorMessage
forall a. ToErrorValue a => a -> ErrorMessage
toErrorValue)
queryWithIntrospectionHelper ::
forall n m.
(MonadMemoize m, MonadParse n, MonadError QErr m) =>
[P.FieldParser n (NamespacedField (QueryRootField UnpreparedValue))] ->
Maybe (Parser 'Output n (RootFieldMap (MutationRootField UnpreparedValue))) ->
Maybe (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))) ->
m (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryWithIntrospectionHelper :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryWithIntrospectionHelper [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
basicQueryFP Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
mutationP Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionP = do
let
placeholderText :: p
placeholderText = p
"There are no queries available to the current role. Either there are no sources or remote schemas configured, or the current role doesn't have the required permissions."
placeholderField :: FieldParser
origin m (NamespacedField (RootField db remote action Value))
placeholderField = RootField db remote action Value
-> NamespacedField (RootField db remote action Value)
forall a. a -> NamespacedField a
NotNamespaced (Value -> RootField db remote action Value
forall raw (db :: BackendType -> *) remote action.
raw -> RootField db remote action raw
RFRaw (Value -> RootField db remote action Value)
-> Value -> RootField db remote action Value
forall a b. (a -> b) -> a -> b
$ Text -> Value
JO.String Text
forall p. IsString p => p
placeholderText) NamespacedField (RootField db remote action Value)
-> FieldParser origin m ()
-> FieldParser
origin m (NamespacedField (RootField db remote action Value))
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Name
-> Maybe Description
-> Parser origin 'Both m Text
-> FieldParser origin m ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
Name._no_queries_available (Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description Text
forall p. IsString p => p
placeholderText) Parser origin 'Both m Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
fixedQueryFP :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
fixedQueryFP = if [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
basicQueryFP then [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (m :: * -> *) origin (db :: BackendType -> *) remote action.
MonadParse m =>
FieldParser
origin m (NamespacedField (RootField db remote action Value))
placeholderField] else [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
basicQueryFP
Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
basicQueryP <- [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
forall (n :: * -> *) (m :: * -> *).
(MonadError QErr m, MonadParse n) =>
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryRootFromFields [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
fixedQueryFP
let buildIntrospectionResponse :: (Schema MetadataObjId -> Value)
-> n (NamespacedField (QueryRootField UnpreparedValue))
buildIntrospectionResponse Schema MetadataObjId -> Value
printResponseFromSchema =
QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue)
forall a. a -> NamespacedField a
NotNamespaced (QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue))
-> (Schema MetadataObjId -> QueryRootField UnpreparedValue)
-> Schema MetadataObjId
-> NamespacedField (QueryRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> QueryRootField UnpreparedValue
forall raw (db :: BackendType -> *) remote action.
raw -> RootField db remote action raw
RFRaw (Value -> QueryRootField UnpreparedValue)
-> (Schema MetadataObjId -> Value)
-> Schema MetadataObjId
-> QueryRootField UnpreparedValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema MetadataObjId -> Value
printResponseFromSchema
(Schema MetadataObjId
-> NamespacedField (QueryRootField UnpreparedValue))
-> n (Schema MetadataObjId)
-> n (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> n (Schema MetadataObjId)
forall (m :: * -> *).
MonadParse m =>
Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> m (Schema MetadataObjId)
parseBuildIntrospectionSchema
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
basicQueryP)
(Parser 'Output n (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
mutationP)
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> Type origin k
P.parserType (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
-> Type 'Output)
-> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> Maybe (Type 'Output)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
subscriptionP)
introspection :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
introspection = [FieldParser n (Schema MetadataObjId -> Value)
forall (n :: * -> *).
MonadParse n =>
FieldParser n (Schema MetadataObjId -> Value)
schema, FieldParser n (Schema MetadataObjId -> Value)
forall (n :: * -> *).
MonadParse n =>
FieldParser n (Schema MetadataObjId -> Value)
typeIntrospection] [FieldParser n (Schema MetadataObjId -> Value)]
-> (FieldParser n (Schema MetadataObjId -> Value)
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (FieldParser n (Schema MetadataObjId -> Value)
-> ((Schema MetadataObjId -> Value)
-> n (NamespacedField (QueryRootField UnpreparedValue)))
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (m :: * -> *) origin a b.
Monad m =>
FieldParser origin m a -> (a -> m b) -> FieldParser origin m b
`P.bindField` (Schema MetadataObjId -> Value)
-> n (NamespacedField (QueryRootField UnpreparedValue))
buildIntrospectionResponse)
{-# INLINE introspection #-}
partialQueryFields :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
partialQueryFields = [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
fixedQueryFP [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall a. [a] -> [a] -> [a]
++ [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
introspection
Name
-> Maybe Description
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
forall (n :: * -> *) (m :: * -> *) a.
(QErrM n, MonadParse m) =>
Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
queryRoot Maybe Description
forall a. Maybe a
Nothing [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
partialQueryFields m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
-> (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue))
-> Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue)
forall a. NamespacedFieldMap a -> RootFieldMap a
flattenNamespaces (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue))
-> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue)
forall (db :: BackendType -> *) remote action.
ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF)
queryRootFromFields ::
forall n m.
(MonadError QErr m, MonadParse n) =>
[P.FieldParser n (NamespacedField (QueryRootField UnpreparedValue))] ->
m (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryRootFromFields :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
queryRootFromFields [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
fps =
Name
-> Maybe Description
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
forall (n :: * -> *) (m :: * -> *) a.
(QErrM n, MonadParse m) =>
Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
queryRoot Maybe Description
forall a. Maybe a
Nothing [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
fps m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
-> (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue))
-> Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue)
forall a. NamespacedFieldMap a -> RootFieldMap a
flattenNamespaces (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue))
-> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue)
forall (db :: BackendType -> *) remote action.
ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF)
buildMutationParser ::
forall n m.
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[P.FieldParser n (NamespacedField (MutationRootField UnpreparedValue))] ->
[P.FieldParser n (NamespacedField (RemoteSchemaRootField (RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))] ->
[P.FieldParser n (MutationRootField UnpreparedValue)] ->
m (Maybe (Parser 'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
buildMutationParser :: [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
buildMutationParser [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
mutationFields [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remoteFields [FieldParser n (MutationRootField UnpreparedValue)]
actionFields = do
let mutationFieldsParser :: [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
mutationFieldsParser =
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
mutationFields
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> ((NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (MutationRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> MutationRootField UnpreparedValue)
-> NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (MutationRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> MutationRootField UnpreparedValue
forall remote (db :: BackendType -> *) action raw.
remote -> RootField db remote action raw
RFRemote) (FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
n (NamespacedField (MutationRootField UnpreparedValue)))
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remoteFields)
[FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> ((MutationRootField UnpreparedValue
-> NamespacedField (MutationRootField UnpreparedValue))
-> FieldParser n (MutationRootField UnpreparedValue)
-> FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MutationRootField UnpreparedValue
-> NamespacedField (MutationRootField UnpreparedValue)
forall a. a -> NamespacedField a
NotNamespaced (FieldParser n (MutationRootField UnpreparedValue)
-> FieldParser
n (NamespacedField (MutationRootField UnpreparedValue)))
-> [FieldParser n (MutationRootField UnpreparedValue)]
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldParser n (MutationRootField UnpreparedValue)]
actionFields)
Bool
-> m (Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
whenMaybe (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
mutationFieldsParser) (m (Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))))
-> m (Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> m (Maybe
(Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
-> m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))))
forall (n :: * -> *) (m :: * -> *) a.
(QErrM n, MonadParse m) =>
Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
mutationRoot (Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description Text
"mutation root") [FieldParser
n (NamespacedField (MutationRootField UnpreparedValue))]
mutationFieldsParser
m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))))
-> (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))))
-> Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> RootFieldMap (MutationRootField UnpreparedValue))
-> Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))))
-> Parser
'Output n (RootFieldMap (MutationRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NamespacedFieldMap (MutationRootField UnpreparedValue)
-> RootFieldMap (MutationRootField UnpreparedValue)
forall a. NamespacedFieldMap a -> RootFieldMap a
flattenNamespaces (NamespacedFieldMap (MutationRootField UnpreparedValue)
-> RootFieldMap (MutationRootField UnpreparedValue))
-> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> NamespacedFieldMap (MutationRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> RootFieldMap (MutationRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))
-> NamespacedField (MutationRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue)))
-> NamespacedFieldMap (MutationRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParsedSelection
(NamespacedField (MutationRootField UnpreparedValue))
-> NamespacedField (MutationRootField UnpreparedValue)
forall (db :: BackendType -> *) remote action.
ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF)
buildSubscriptionParser ::
forall n m.
(MonadMemoize m, MonadError QErr m, MonadParse n) =>
[P.FieldParser n (NamespacedField (QueryRootField UnpreparedValue))] ->
[P.FieldParser n (NamespacedField (RemoteSchemaRootField (RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))] ->
[P.FieldParser n (QueryRootField UnpreparedValue)] ->
m (Maybe (Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))))
buildSubscriptionParser :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> m (Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))))
buildSubscriptionParser [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
sourceSubscriptionFields [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remoteSubscriptionFields [FieldParser n (QueryRootField UnpreparedValue)]
actionFields = do
let subscriptionFields :: [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields =
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
sourceSubscriptionFields
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> (FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> (NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall a b. (a -> b) -> a -> b
$ (RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue)
-> NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable)
-> NamespacedField (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
-> QueryRootField UnpreparedValue
forall remote (db :: BackendType -> *) action raw.
remote -> RootField db remote action raw
RFRemote) [FieldParser
n
(NamespacedField
(RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))]
remoteSubscriptionFields
[FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall a. Semigroup a => a -> a -> a
<> ((QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue))
-> FieldParser n (QueryRootField UnpreparedValue)
-> FieldParser n (NamespacedField (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap QueryRootField UnpreparedValue
-> NamespacedField (QueryRootField UnpreparedValue)
forall a. a -> NamespacedField a
NotNamespaced (FieldParser n (QueryRootField UnpreparedValue)
-> FieldParser
n (NamespacedField (QueryRootField UnpreparedValue)))
-> [FieldParser n (QueryRootField UnpreparedValue)]
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldParser n (QueryRootField UnpreparedValue)]
actionFields)
Bool
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))))
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
whenMaybe (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields) (m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Maybe
(Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Maybe
(Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> [FieldParser
n (NamespacedField (QueryRootField UnpreparedValue))]
-> m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
forall (n :: * -> *) (m :: * -> *) a.
(QErrM n, MonadParse m) =>
Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
subscriptionRoot Maybe Description
forall a. Maybe a
Nothing [FieldParser n (NamespacedField (QueryRootField UnpreparedValue))]
subscriptionFields
m (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))))
-> (Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (Parser
'Output n (RootFieldMap (QueryRootField UnpreparedValue)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue))
-> Parser
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue))))
-> Parser 'Output n (RootFieldMap (QueryRootField UnpreparedValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue)
forall a. NamespacedFieldMap a -> RootFieldMap a
flattenNamespaces (NamespacedFieldMap (QueryRootField UnpreparedValue)
-> RootFieldMap (QueryRootField UnpreparedValue))
-> (InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> RootFieldMap (QueryRootField UnpreparedValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue))
-> InsOrdHashMap
Name
(ParsedSelection
(NamespacedField (QueryRootField UnpreparedValue)))
-> NamespacedFieldMap (QueryRootField UnpreparedValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParsedSelection (NamespacedField (QueryRootField UnpreparedValue))
-> NamespacedField (QueryRootField UnpreparedValue)
forall (db :: BackendType -> *) remote action.
ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF)
safeSelectionSet ::
forall n m a.
(QErrM n, MonadParse m) =>
G.Name ->
Maybe G.Description ->
[FieldParser m a] ->
n (Parser 'Output m (OMap.InsOrdHashMap G.Name (P.ParsedSelection a)))
safeSelectionSet :: Name
-> Maybe Description
-> [FieldParser m a]
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
safeSelectionSet Name
name Maybe Description
description [FieldParser m a]
fields =
Name
-> Maybe Description
-> [FieldParser m a]
-> Either
ErrorMessage
(Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
forall (n :: * -> *) (m :: * -> *) origin a.
(MonadError ErrorMessage n, MonadParse m, Eq origin,
Hashable origin, ToErrorValue origin) =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> n (Parser
origin 'Output m (InsOrdHashMap Name (ParsedSelection a)))
P.safeSelectionSet Name
name Maybe Description
description [FieldParser m a]
fields Either
ErrorMessage
(Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
-> (ErrorMessage
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a))))
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` (Text
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 (Text
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a))))
-> (ErrorMessage -> Text)
-> ErrorMessage
-> n (Parser 'Output m (InsOrdHashMap Name (ParsedSelection a)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorMessage -> Text
fromErrorMessage)
customizeFields ::
forall f n db remote action.
(Functor f, MonadParse n) =>
SourceCustomization ->
MkTypename ->
f [FieldParser n (RootField db remote action JO.Value)] ->
f [FieldParser n (NamespacedField (RootField db remote action JO.Value))]
customizeFields :: SourceCustomization
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
customizeFields SourceCustomization {Maybe NamingCase
Maybe SourceTypeCustomization
Maybe RootFieldsCustomization
_scTypeNames :: SourceCustomization -> Maybe SourceTypeCustomization
_scRootFields :: SourceCustomization -> Maybe RootFieldsCustomization
_scNamingConvention :: Maybe NamingCase
_scTypeNames :: Maybe SourceTypeCustomization
_scRootFields :: Maybe RootFieldsCustomization
_scNamingConvention :: SourceCustomization -> Maybe NamingCase
..} =
([FieldParser n (RootField db remote action Value)]
-> [FieldParser
n (NamespacedField (RootField db remote action Value))])
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([FieldParser n (RootField db remote action Value)]
-> [FieldParser
n (NamespacedField (RootField db remote action Value))])
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))])
-> (MkTypename
-> [FieldParser n (RootField db remote action Value)]
-> [FieldParser
n (NamespacedField (RootField db remote action Value))])
-> MkTypename
-> f [FieldParser n (RootField db remote action Value)]
-> f [FieldParser
n (NamespacedField (RootField db remote action Value))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Name
-> (Name
-> ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value)
-> MkTypename
-> [FieldParser n (RootField db remote action Value)]
-> [FieldParser
n (NamespacedField (RootField db remote action Value))]
forall (n :: * -> *) a.
MonadParse n =>
Maybe Name
-> (Name -> ParsedSelection a -> a)
-> MkTypename
-> [FieldParser n a]
-> [FieldParser n (NamespacedField a)]
customizeNamespace (RootFieldsCustomization -> Maybe Name
_rootfcNamespace (RootFieldsCustomization -> Maybe Name)
-> Maybe RootFieldsCustomization -> Maybe Name
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe RootFieldsCustomization
_scRootFields) ((ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value)
-> Name
-> ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value
forall a b. a -> b -> a
const ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value
forall (db :: BackendType -> *) remote action.
ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value
typenameToRawRF)
mkRootField ::
forall b n a db remote action raw.
(HasTag b, Functor n) =>
SourceName ->
SourceConfig b ->
Maybe QueryTagsConfig ->
(a -> db b) ->
FieldParser n a ->
FieldParser n (RootField db remote action raw)
mkRootField :: SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> FieldParser n a
-> FieldParser n (RootField db remote action raw)
mkRootField SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig a -> db b
inj =
(a -> RootField db remote action raw)
-> FieldParser n a
-> FieldParser n (RootField db remote action raw)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( SourceName
-> AnyBackend (SourceConfigWith db)
-> RootField db remote action raw
forall (db :: BackendType -> *) remote action raw.
SourceName
-> AnyBackend (SourceConfigWith db)
-> RootField db remote action raw
RFDB SourceName
sourceName
(AnyBackend (SourceConfigWith db)
-> RootField db remote action raw)
-> (a -> AnyBackend (SourceConfigWith db))
-> a
-> RootField db remote action raw
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
forall (i :: BackendType -> *). HasTag b => i b -> AnyBackend i
AB.mkAnyBackend @b
(SourceConfigWith db b -> AnyBackend (SourceConfigWith db))
-> (a -> SourceConfigWith db b)
-> a
-> AnyBackend (SourceConfigWith db)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceConfig b
-> Maybe QueryTagsConfig -> db b -> SourceConfigWith db b
forall (db :: BackendType -> *) (b :: BackendType).
SourceConfig b
-> Maybe QueryTagsConfig -> db b -> SourceConfigWith db b
SourceConfigWith SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig
(db b -> SourceConfigWith db b)
-> (a -> db b) -> a -> SourceConfigWith db b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> db b
inj
)
mkRootFields ::
forall b m n a db remote action raw.
(HasTag b, Functor m, Functor n) =>
SourceName ->
SourceConfig b ->
Maybe QueryTagsConfig ->
(a -> db b) ->
m [FieldParser n a] ->
m [FieldParser n (RootField db remote action raw)]
mkRootFields :: SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
mkRootFields SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig a -> db b
inj =
([FieldParser n a]
-> [FieldParser n (RootField db remote action raw)])
-> m [FieldParser n a]
-> m [FieldParser n (RootField db remote action raw)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( (FieldParser n a -> FieldParser n (RootField db remote action raw))
-> [FieldParser n a]
-> [FieldParser n (RootField db remote action raw)]
forall a b. (a -> b) -> [a] -> [b]
map
(SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> FieldParser n a
-> FieldParser n (RootField db remote action raw)
forall (b :: BackendType) (n :: * -> *) a (db :: BackendType -> *)
remote action raw.
(HasTag b, Functor n) =>
SourceName
-> SourceConfig b
-> Maybe QueryTagsConfig
-> (a -> db b)
-> FieldParser n a
-> FieldParser n (RootField db remote action raw)
mkRootField SourceName
sourceName SourceConfig b
sourceConfig Maybe QueryTagsConfig
queryTagsConfig a -> db b
inj)
)
takeExposedAs :: FunctionExposedAs -> FunctionCache b -> FunctionCache b
takeExposedAs :: FunctionExposedAs -> FunctionCache b -> FunctionCache b
takeExposedAs FunctionExposedAs
x = (FunctionInfo b -> Bool) -> FunctionCache b -> FunctionCache b
forall v k. (v -> Bool) -> HashMap k v -> HashMap k v
Map.filter ((FunctionExposedAs -> FunctionExposedAs -> Bool
forall a. Eq a => a -> a -> Bool
== FunctionExposedAs
x) (FunctionExposedAs -> Bool)
-> (FunctionInfo b -> FunctionExposedAs) -> FunctionInfo b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionInfo b -> FunctionExposedAs
forall (b :: BackendType). FunctionInfo b -> FunctionExposedAs
_fiExposedAs)
subscriptionRoot :: G.Name
subscriptionRoot :: Name
subscriptionRoot = Name
Name._subscription_root
mutationRoot :: G.Name
mutationRoot :: Name
mutationRoot = Name
Name._mutation_root
queryRoot :: G.Name
queryRoot :: Name
queryRoot = Name
Name._query_root
finalizeParser :: Parser 'Output P.Parse a -> ParserFn a
finalizeParser :: Parser 'Output Parse a -> ParserFn a
finalizeParser Parser 'Output Parse a
parser = Either ParseError a -> Either QErr a
forall (m :: * -> *) a.
MonadError QErr m =>
Either ParseError a -> m a
P.toQErr (Either ParseError a -> Either QErr a)
-> (SelectionSet NoFragments Variable -> Either ParseError a)
-> ParserFn a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parse a -> Either ParseError a
forall (m :: * -> *) a. MonadError ParseError m => Parse a -> m a
P.runParse (Parse a -> Either ParseError a)
-> (SelectionSet NoFragments Variable -> Parse a)
-> SelectionSet NoFragments Variable
-> Either ParseError a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser 'Output Parse a -> ParserInput 'Output -> Parse a
forall origin (k :: Kind) (m :: * -> *) a.
Parser origin k m a -> ParserInput k -> m a
P.runParser Parser 'Output Parse a
parser
throwOnConflictingDefinitions :: QErrM m => Either P.ConflictingDefinitions a -> m a
throwOnConflictingDefinitions :: Either ConflictingDefinitions a -> m a
throwOnConflictingDefinitions = (ConflictingDefinitions -> m a)
-> (a -> m a) -> Either ConflictingDefinitions a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> m a
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 (Text -> m a)
-> (ConflictingDefinitions -> Text)
-> ConflictingDefinitions
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorMessage -> Text
fromErrorMessage (ErrorMessage -> Text)
-> (ConflictingDefinitions -> ErrorMessage)
-> ConflictingDefinitions
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConflictingDefinitions -> ErrorMessage
forall a. ToErrorValue a => a -> ErrorMessage
toErrorValue) a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
typenameToNamespacedRawRF ::
P.ParsedSelection (NamespacedField (RootField db remote action JO.Value)) ->
NamespacedField (RootField db remote action JO.Value)
typenameToNamespacedRawRF :: ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
typenameToNamespacedRawRF = (Name -> NamespacedField (RootField db remote action Value))
-> ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
forall a. (Name -> a) -> ParsedSelection a -> a
P.handleTypename ((Name -> NamespacedField (RootField db remote action Value))
-> ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value))
-> (Name -> NamespacedField (RootField db remote action Value))
-> ParsedSelection
(NamespacedField (RootField db remote action Value))
-> NamespacedField (RootField db remote action Value)
forall a b. (a -> b) -> a -> b
$ RootField db remote action Value
-> NamespacedField (RootField db remote action Value)
forall a. a -> NamespacedField a
NotNamespaced (RootField db remote action Value
-> NamespacedField (RootField db remote action Value))
-> (Name -> RootField db remote action Value)
-> Name
-> NamespacedField (RootField db remote action Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> RootField db remote action Value
forall raw (db :: BackendType -> *) remote action.
raw -> RootField db remote action raw
RFRaw (Value -> RootField db remote action Value)
-> (Name -> Value) -> Name -> RootField db remote action Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
JO.String (Text -> Value) -> (Name -> Text) -> Name -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Text
forall t. ToTxt t => t -> Text
toTxt
typenameToRawRF ::
P.ParsedSelection (RootField db remote action JO.Value) ->
RootField db remote action JO.Value
typenameToRawRF :: ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value
typenameToRawRF = (Name -> RootField db remote action Value)
-> ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value
forall a. (Name -> a) -> ParsedSelection a -> a
P.handleTypename ((Name -> RootField db remote action Value)
-> ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value)
-> (Name -> RootField db remote action Value)
-> ParsedSelection (RootField db remote action Value)
-> RootField db remote action Value
forall a b. (a -> b) -> a -> b
$ Value -> RootField db remote action Value
forall raw (db :: BackendType -> *) remote action.
raw -> RootField db remote action raw
RFRaw (Value -> RootField db remote action Value)
-> (Name -> Value) -> Name -> RootField db remote action Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
JO.String (Text -> Value) -> (Name -> Text) -> Name -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Text
forall t. ToTxt t => t -> Text
toTxt