{-# LANGUAGE ApplicativeDo #-}
module Hasura.GraphQL.Schema.Introspect
( buildIntrospectionSchema,
schema,
typeIntrospection,
)
where
import Data.Aeson.Ordered qualified as J
import Data.HashMap.Strict qualified as HashMap
import Data.HashMap.Strict.InsOrd qualified as InsOrdHashMap
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Vector qualified as V
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Directives
import Hasura.GraphQL.Parser.Name qualified as GName
import Hasura.GraphQL.Schema.Parser as P
import Hasura.Prelude
import Language.GraphQL.Draft.Printer qualified as GP
import Language.GraphQL.Draft.Syntax qualified as G
import Text.Builder qualified as T
buildIntrospectionSchema ::
P.Type 'Output ->
Maybe (P.Type 'Output) ->
Maybe (P.Type 'Output) ->
Either P.ConflictingDefinitions P.Schema
buildIntrospectionSchema :: Type 'Output
-> Maybe (Type 'Output)
-> Maybe (Type 'Output)
-> Either ConflictingDefinitions Schema
buildIntrospectionSchema Type 'Output
queryRoot' Maybe (Type 'Output)
mutationRoot' Maybe (Type 'Output)
subscriptionRoot' = do
let
[DirectiveInfo]
directives :: [DirectiveInfo] = forall (m :: * -> *) origin. MonadParse m => [DirectiveInfo origin]
directivesInfo @P.Parse
HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
allTypes <-
[TypeDefinitionsWrapper]
-> Either
ConflictingDefinitions
(HashMap Name (SomeDefinitionTypeInfo MetadataObjId))
forall origin a.
HasTypeDefinitions origin a =>
a
-> Either
(ConflictingDefinitions origin)
(HashMap Name (SomeDefinitionTypeInfo origin))
P.collectTypeDefinitions
[ Type 'Output -> TypeDefinitionsWrapper
forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
P.TypeDefinitionsWrapper Type 'Output
queryRoot',
Maybe (Type 'Output) -> TypeDefinitionsWrapper
forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
P.TypeDefinitionsWrapper Maybe (Type 'Output)
mutationRoot',
Maybe (Type 'Output) -> TypeDefinitionsWrapper
forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
P.TypeDefinitionsWrapper Maybe (Type 'Output)
subscriptionRoot',
[Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> TypeDefinitionsWrapper
forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
P.TypeDefinitionsWrapper ([Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> TypeDefinitionsWrapper)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> TypeDefinitionsWrapper
forall a b. (a -> b) -> a -> b
$ DirectiveInfo
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall origin.
DirectiveInfo origin -> [Definition origin (InputFieldInfo origin)]
P.diArguments (DirectiveInfo
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)])
-> [DirectiveInfo]
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [DirectiveInfo]
directives,
Definition MetadataObjId (FieldInfo MetadataObjId)
-> TypeDefinitionsWrapper
forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
P.TypeDefinitionsWrapper (Definition MetadataObjId (FieldInfo MetadataObjId)
-> TypeDefinitionsWrapper)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> TypeDefinitionsWrapper
forall a b. (a -> b) -> a -> b
$ FieldParser MetadataObjId Parse (Schema -> Value)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
forall origin (m :: * -> *) a.
FieldParser origin m a -> Definition origin (FieldInfo origin)
fDefinition (forall (n :: * -> *).
MonadParse n =>
FieldParser n (Schema -> Value)
schema @Parse),
Definition MetadataObjId (FieldInfo MetadataObjId)
-> TypeDefinitionsWrapper
forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
P.TypeDefinitionsWrapper (Definition MetadataObjId (FieldInfo MetadataObjId)
-> TypeDefinitionsWrapper)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> TypeDefinitionsWrapper
forall a b. (a -> b) -> a -> b
$ FieldParser MetadataObjId Parse (Schema -> Value)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
forall origin (m :: * -> *) a.
FieldParser origin m a -> Definition origin (FieldInfo origin)
fDefinition (forall (n :: * -> *).
MonadParse n =>
FieldParser n (Schema -> Value)
typeIntrospection @Parse)
]
pure
$ P.Schema
{ sDescription :: Maybe Description
sDescription = Maybe Description
forall a. Maybe a
Nothing,
sTypes :: HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
sTypes = HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
allTypes,
sQueryType :: Type 'Output
sQueryType = Type 'Output
queryRoot',
sMutationType :: Maybe (Type 'Output)
sMutationType = Maybe (Type 'Output)
mutationRoot',
sSubscriptionType :: Maybe (Type 'Output)
sSubscriptionType = Maybe (Type 'Output)
subscriptionRoot',
sDirectives :: [DirectiveInfo]
sDirectives = [DirectiveInfo]
directives
}
typeIntrospection ::
forall n.
(MonadParse n) =>
FieldParser n (Schema -> J.Value)
{-# INLINE typeIntrospection #-}
typeIntrospection :: forall (n :: * -> *).
MonadParse n =>
FieldParser n (Schema -> Value)
typeIntrospection = do
let nameArg :: P.InputFieldsParser n Text
nameArg :: InputFieldsParser n Text
nameArg = Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> InputFieldsParser n Text
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
P.field Name
GName._name Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
~(Text
nameText, SomeType -> Value
printer) <- Name
-> Maybe Description
-> InputFieldsParser n Text
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (Text, SomeType -> Value)
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Output m b
-> FieldParser origin m (a, b)
P.subselection Name
GName.___type Maybe Description
forall a. Maybe a
Nothing InputFieldsParser n Text
nameArg Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
pure $ \Schema
partialSchema -> Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
J.Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$ do
Name
name <- Text -> Maybe Name
G.mkName Text
nameText
P.SomeDefinitionTypeInfo Definition MetadataObjId (TypeInfo MetadataObjId k)
def <- Name
-> HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
-> Maybe (SomeDefinitionTypeInfo MetadataObjId)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Name
name (HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
-> Maybe (SomeDefinitionTypeInfo MetadataObjId))
-> HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
-> Maybe (SomeDefinitionTypeInfo MetadataObjId)
forall a b. (a -> b) -> a -> b
$ Schema -> HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
forall origin.
Schema origin -> HashMap Name (SomeDefinitionTypeInfo origin)
sTypes Schema
partialSchema
Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type k -> SomeType) -> Type k -> SomeType
forall a b. (a -> b) -> a -> b
$ Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId k) -> Type k
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.Nullable Definition MetadataObjId (TypeInfo MetadataObjId k)
def
schema ::
forall n.
(MonadParse n) =>
FieldParser n (Schema -> J.Value)
{-# INLINE schema #-}
schema :: forall (n :: * -> *).
MonadParse n =>
FieldParser n (Schema -> Value)
schema = Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (Schema -> Value)
-> FieldParser MetadataObjId n (Schema -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName.___schema Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (Schema -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (Schema -> Value)
schemaSet
data SomeType = forall k. SomeType (P.Type k)
typeField ::
forall n.
(MonadParse n) =>
Parser 'Output n (SomeType -> J.Value)
typeField :: forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField =
let includeDeprecated :: P.InputFieldsParser n Bool
includeDeprecated :: InputFieldsParser n Bool
includeDeprecated =
Name
-> Maybe Description
-> Value Void
-> Parser MetadataObjId 'Both n (Maybe Bool)
-> InputFieldsParser MetadataObjId n (Maybe Bool)
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Value Void
-> Parser origin k m a
-> InputFieldsParser origin m a
P.fieldWithDefault Name
GName._includeDeprecated Maybe Description
forall a. Maybe a
Nothing (Bool -> Value Void
forall var. Bool -> Value var
G.VBoolean Bool
False) (Parser MetadataObjId 'Both n Bool
-> Parser MetadataObjId 'Both n (Maybe Bool)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser MetadataObjId 'Both n Bool
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Bool
P.boolean)
InputFieldsParser MetadataObjId n (Maybe Bool)
-> (Maybe Bool -> Bool) -> InputFieldsParser n Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False
kind :: FieldParser n (SomeType -> J.Value)
kind :: FieldParser n (SomeType -> Value)
kind =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n ()
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._kind Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n ()
forall (n :: * -> *). MonadParse n => Parser 'Both n ()
typeKind
FieldParser MetadataObjId n ()
-> (SomeType -> Value) -> FieldParser n (SomeType -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> \case
SomeType Type k
tp ->
case Type k
tp of
P.TList Nullability
P.NonNullable Type k
_ ->
Text -> Value
J.String Text
"NON_NULL"
P.TNamed Nullability
P.NonNullable Definition MetadataObjId (TypeInfo MetadataObjId k)
_ ->
Text -> Value
J.String Text
"NON_NULL"
P.TList Nullability
P.Nullable Type k
_ ->
Text -> Value
J.String Text
"LIST"
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ TypeInfo MetadataObjId k
P.TIScalar) ->
Text -> Value
J.String Text
"SCALAR"
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIEnum NonEmpty (Definition MetadataObjId EnumValueInfo)
_)) ->
Text -> Value
J.String Text
"ENUM"
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIInputObject InputObjectInfo MetadataObjId
_)) ->
Text -> Value
J.String Text
"INPUT_OBJECT"
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIObject ObjectInfo MetadataObjId
_)) ->
Text -> Value
J.String Text
"OBJECT"
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIInterface InterfaceInfo MetadataObjId
_)) ->
Text -> Value
J.String Text
"INTERFACE"
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIUnion UnionInfo MetadataObjId
_)) ->
Text -> Value
J.String Text
"UNION"
name :: FieldParser n (SomeType -> J.Value)
name :: FieldParser n (SomeType -> Value)
name =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._name Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (SomeType -> Value) -> FieldParser n (SomeType -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> \case
SomeType Type k
tp ->
case Type k
tp of
P.TNamed Nullability
P.Nullable (P.Definition Name
name' Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ TypeInfo MetadataObjId k
_) ->
Name -> Value
forall a. HasName a => a -> Value
nameAsJSON Name
name'
Type k
_ -> Value
J.Null
description :: FieldParser n (SomeType -> J.Value)
description :: FieldParser n (SomeType -> Value)
description =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._description Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (SomeType -> Value) -> FieldParser n (SomeType -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> \case
SomeType (P.TNamed Nullability
_ (P.Definition Name
_ (Just Description
desc) Maybe MetadataObjId
_ [Directive Void]
_ TypeInfo MetadataObjId k
_)) ->
Text -> Value
J.String (Description -> Text
G.unDescription Description
desc)
SomeType
_ -> Value
J.Null
fields :: FieldParser n (SomeType -> J.Value)
fields :: FieldParser n (SomeType -> Value)
fields = do
~(Bool
_includeDeprecated, Definition MetadataObjId (FieldInfo MetadataObjId) -> Value
printer) <- Name
-> Maybe Description
-> InputFieldsParser n Bool
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> FieldParser
MetadataObjId
n
(Bool, Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Output m b
-> FieldParser origin m (a, b)
P.subselection Name
GName._fields Maybe Description
forall a. Maybe a
Nothing InputFieldsParser n Bool
includeDeprecated Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser
'Output
n
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
fieldField
return
$ \case
SomeType Type k
tp ->
case Type k
tp of
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIObject (P.ObjectInfo [Definition MetadataObjId (FieldInfo MetadataObjId)]
fields' [Definition MetadataObjId (InterfaceInfo MetadataObjId)]
_interfaces'))) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ Definition MetadataObjId (FieldInfo MetadataObjId) -> Value
printer (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (FieldInfo MetadataObjId)] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Definition MetadataObjId (FieldInfo MetadataObjId)]
fields'
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIInterface (P.InterfaceInfo [Definition MetadataObjId (FieldInfo MetadataObjId)]
fields' [Definition MetadataObjId (ObjectInfo MetadataObjId)]
_objects'))) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ Definition MetadataObjId (FieldInfo MetadataObjId) -> Value
printer (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (FieldInfo MetadataObjId)] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Definition MetadataObjId (FieldInfo MetadataObjId)]
fields'
Type k
_ -> Value
J.Null
interfaces :: FieldParser n (SomeType -> J.Value)
interfaces :: FieldParser n (SomeType -> Value)
interfaces = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._interfaces Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return
$ \case
SomeType Type k
tp ->
case Type k
tp of
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIObject (P.ObjectInfo [Definition MetadataObjId (FieldInfo MetadataObjId)]
_fields' [Definition MetadataObjId (InterfaceInfo MetadataObjId)]
interfaces'))) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ SomeType -> Value
printer (SomeType -> Value)
-> (Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> SomeType)
-> Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type 'Output -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type 'Output -> SomeType)
-> (Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> Type 'Output)
-> Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> SomeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
-> Type 'Output
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.Nullable (Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
-> Type 'Output)
-> (Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output))
-> Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> Type 'Output
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InterfaceInfo MetadataObjId -> TypeInfo MetadataObjId 'Output)
-> Definition MetadataObjId (InterfaceInfo MetadataObjId)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
forall a b.
(a -> b)
-> Definition MetadataObjId a -> Definition MetadataObjId b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InterfaceInfo MetadataObjId -> TypeInfo MetadataObjId 'Output
forall origin. InterfaceInfo origin -> TypeInfo origin 'Output
P.TIInterface (Definition MetadataObjId (InterfaceInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (InterfaceInfo MetadataObjId)]
-> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Definition MetadataObjId (InterfaceInfo MetadataObjId)]
interfaces'
Type k
_ -> Value
J.Null
possibleTypes :: FieldParser n (SomeType -> J.Value)
possibleTypes :: FieldParser n (SomeType -> Value)
possibleTypes = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._possibleTypes Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return
$ \case
SomeType Type k
tp ->
case Type k
tp of
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIInterface (P.InterfaceInfo [Definition MetadataObjId (FieldInfo MetadataObjId)]
_fields' [Definition MetadataObjId (ObjectInfo MetadataObjId)]
objects'))) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ SomeType -> Value
printer (SomeType -> Value)
-> (Definition MetadataObjId (ObjectInfo MetadataObjId)
-> SomeType)
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type 'Output -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type 'Output -> SomeType)
-> (Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Type 'Output)
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> SomeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
-> Type 'Output
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.Nullable (Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
-> Type 'Output)
-> (Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output))
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Type 'Output
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ObjectInfo MetadataObjId -> TypeInfo MetadataObjId 'Output)
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
forall a b.
(a -> b)
-> Definition MetadataObjId a -> Definition MetadataObjId b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ObjectInfo MetadataObjId -> TypeInfo MetadataObjId 'Output
forall origin. ObjectInfo origin -> TypeInfo origin 'Output
P.TIObject (Definition MetadataObjId (ObjectInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (ObjectInfo MetadataObjId)] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Definition MetadataObjId (ObjectInfo MetadataObjId)]
objects'
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIUnion (P.UnionInfo [Definition MetadataObjId (ObjectInfo MetadataObjId)]
objects'))) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ SomeType -> Value
printer (SomeType -> Value)
-> (Definition MetadataObjId (ObjectInfo MetadataObjId)
-> SomeType)
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type 'Output -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type 'Output -> SomeType)
-> (Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Type 'Output)
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> SomeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
-> Type 'Output
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.Nullable (Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
-> Type 'Output)
-> (Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output))
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Type 'Output
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ObjectInfo MetadataObjId -> TypeInfo MetadataObjId 'Output)
-> Definition MetadataObjId (ObjectInfo MetadataObjId)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Output)
forall a b.
(a -> b)
-> Definition MetadataObjId a -> Definition MetadataObjId b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ObjectInfo MetadataObjId -> TypeInfo MetadataObjId 'Output
forall origin. ObjectInfo origin -> TypeInfo origin 'Output
P.TIObject (Definition MetadataObjId (ObjectInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (ObjectInfo MetadataObjId)] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Definition MetadataObjId (ObjectInfo MetadataObjId)]
objects'
Type k
_ -> Value
J.Null
enumValues :: FieldParser n (SomeType -> J.Value)
enumValues :: FieldParser n (SomeType -> Value)
enumValues = do
~(Bool
_includeDeprecated, Definition MetadataObjId EnumValueInfo -> Value
printer) <- Name
-> Maybe Description
-> InputFieldsParser n Bool
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId EnumValueInfo -> Value)
-> FieldParser
MetadataObjId
n
(Bool, Definition MetadataObjId EnumValueInfo -> Value)
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Output m b
-> FieldParser origin m (a, b)
P.subselection Name
GName._enumValues Maybe Description
forall a. Maybe a
Nothing InputFieldsParser n Bool
includeDeprecated Parser
MetadataObjId
'Output
n
(Definition MetadataObjId EnumValueInfo -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (Definition MetadataObjId EnumValueInfo -> Value)
enumValue
return
$ \case
SomeType Type k
tp ->
case Type k
tp of
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIEnum NonEmpty (Definition MetadataObjId EnumValueInfo)
vals)) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ (Definition MetadataObjId EnumValueInfo -> Value)
-> [Definition MetadataObjId EnumValueInfo] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Definition MetadataObjId EnumValueInfo -> Value
printer ([Definition MetadataObjId EnumValueInfo] -> [Value])
-> [Definition MetadataObjId EnumValueInfo] -> [Value]
forall a b. (a -> b) -> a -> b
$ NonEmpty (Definition MetadataObjId EnumValueInfo)
-> [Definition MetadataObjId EnumValueInfo]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty (Definition MetadataObjId EnumValueInfo)
vals
Type k
_ -> Value
J.Null
inputFields :: FieldParser n (SomeType -> J.Value)
inputFields :: FieldParser n (SomeType -> Value)
inputFields = do
Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
printer <- Name
-> Maybe Description
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
-> FieldParser
MetadataObjId
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._inputFields Maybe Description
forall a. Maybe a
Nothing Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
inputValue
return
$ \case
SomeType Type k
tp ->
case Type k
tp of
P.TNamed Nullability
P.Nullable (P.Definition Name
_ Maybe Description
_ Maybe MetadataObjId
_ [Directive Void]
_ (P.TIInputObject (P.InputObjectInfo [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
fieldDefs))) ->
Array -> Value
J.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ (Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Value]
forall a b. (a -> b) -> [a] -> [b]
map Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
printer [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
fieldDefs
Type k
_ -> Value
J.Null
ofType :: FieldParser n (SomeType -> J.Value)
ofType :: FieldParser n (SomeType -> Value)
ofType = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._ofType Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return $ \case
SomeType (P.TNamed Nullability
P.NonNullable Definition MetadataObjId (TypeInfo MetadataObjId k)
x) ->
SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type MetadataObjId k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type MetadataObjId k -> SomeType)
-> Type MetadataObjId k -> SomeType
forall a b. (a -> b) -> a -> b
$ Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId k)
-> Type MetadataObjId k
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.Nullable Definition MetadataObjId (TypeInfo MetadataObjId k)
x
SomeType (P.TList Nullability
P.NonNullable Type MetadataObjId k
x) ->
SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type MetadataObjId k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type MetadataObjId k -> SomeType)
-> Type MetadataObjId k -> SomeType
forall a b. (a -> b) -> a -> b
$ Nullability -> Type MetadataObjId k -> Type MetadataObjId k
forall origin (k :: Kind).
Nullability -> Type origin k -> Type origin k
P.TList Nullability
P.Nullable Type MetadataObjId k
x
SomeType (P.TList Nullability
P.Nullable Type MetadataObjId k
x) ->
SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type MetadataObjId k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType Type MetadataObjId k
x
SomeType
_ -> Value
J.Null
in InsOrdHashMap Name (ParsedSelection (SomeType -> Value))
-> SomeType -> Value
forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter
(InsOrdHashMap Name (ParsedSelection (SomeType -> Value))
-> SomeType -> Value)
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (SomeType -> Value)))
-> Parser MetadataObjId 'Output n (SomeType -> Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser n (SomeType -> Value)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (SomeType -> Value)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet
Name
GName.___Type
Maybe Description
forall a. Maybe a
Nothing
[ FieldParser n (SomeType -> Value)
kind,
FieldParser n (SomeType -> Value)
name,
FieldParser n (SomeType -> Value)
description,
FieldParser n (SomeType -> Value)
fields,
FieldParser n (SomeType -> Value)
interfaces,
FieldParser n (SomeType -> Value)
possibleTypes,
FieldParser n (SomeType -> Value)
enumValues,
FieldParser n (SomeType -> Value)
inputFields,
FieldParser n (SomeType -> Value)
ofType
]
inputValue ::
forall n.
(MonadParse n) =>
Parser 'Output n (P.Definition P.InputFieldInfo -> J.Value)
inputValue :: forall (n :: * -> *).
MonadParse n =>
Parser
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
inputValue =
let name :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
name :: FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
name =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._name Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value)
-> FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Name -> Value
forall a. HasName a => a -> Value
nameAsJSON
(Name -> Value)
-> (Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Name)
-> Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Name
forall origin a. Definition origin a -> Name
P.dName
description :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
description :: FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
description =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._description Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value)
-> FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value -> (Description -> Value) -> Maybe Description -> Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Value
J.Null (Text -> Value
J.String (Text -> Value) -> (Description -> Text) -> Description -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Description -> Text
G.unDescription)
(Maybe Description -> Value)
-> (Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Maybe Description)
-> Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Maybe Description
forall origin a. Definition origin a -> Maybe Description
P.dDescription
typeF :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
typeF :: FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
typeF = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._type Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return $ \Definition MetadataObjId (InputFieldInfo MetadataObjId)
defInfo -> case Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> InputFieldInfo MetadataObjId
forall origin a. Definition origin a -> a
P.dInfo Definition MetadataObjId (InputFieldInfo MetadataObjId)
defInfo of
P.InputFieldInfo Type MetadataObjId k
tp Maybe (Value Void)
_ -> SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type MetadataObjId k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType Type MetadataObjId k
tp
defaultValue :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
defaultValue :: FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
defaultValue =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._defaultValue Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value)
-> FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> \Definition MetadataObjId (InputFieldInfo MetadataObjId)
defInfo -> case Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> InputFieldInfo MetadataObjId
forall origin a. Definition origin a -> a
P.dInfo Definition MetadataObjId (InputFieldInfo MetadataObjId)
defInfo of
P.InputFieldInfo Type MetadataObjId k
_ (Just Value Void
val) -> Text -> Value
J.String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Builder -> Text
T.run (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$ Value Void -> Builder
forall var a. (Print var, Printer a) => Value var -> a
GP.value Value Void
val
InputFieldInfo MetadataObjId
_ -> Value
J.Null
in InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value))
-> Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value))
-> Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value)
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value)))
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (InputFieldInfo MetadataObjId)
-> Value)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet
Name
GName.___InputValue
Maybe Description
forall a. Maybe a
Nothing
[ FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
name,
FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
description,
FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
typeF,
FieldParser
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
defaultValue
]
enumValue ::
forall n.
(MonadParse n) =>
Parser 'Output n (P.Definition P.EnumValueInfo -> J.Value)
enumValue :: forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (Definition MetadataObjId EnumValueInfo -> Value)
enumValue =
let name :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
name :: FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
name =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._name Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId EnumValueInfo -> Value)
-> FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Name -> Value
forall a. HasName a => a -> Value
nameAsJSON
(Name -> Value)
-> (Definition MetadataObjId EnumValueInfo -> Name)
-> Definition MetadataObjId EnumValueInfo
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId EnumValueInfo -> Name
forall origin a. Definition origin a -> Name
P.dName
description :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
description :: FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
description =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._description Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId EnumValueInfo -> Value)
-> FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value -> (Description -> Value) -> Maybe Description -> Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Value
J.Null (Text -> Value
J.String (Text -> Value) -> (Description -> Text) -> Description -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Description -> Text
G.unDescription)
(Maybe Description -> Value)
-> (Definition MetadataObjId EnumValueInfo -> Maybe Description)
-> Definition MetadataObjId EnumValueInfo
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId EnumValueInfo -> Maybe Description
forall origin a. Definition origin a -> Maybe Description
P.dDescription
isDeprecated :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
isDeprecated :: FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
isDeprecated =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._isDeprecated Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId EnumValueInfo -> Value)
-> FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value -> Definition MetadataObjId EnumValueInfo -> Value
forall a b. a -> b -> a
const (Bool -> Value
J.Bool Bool
False)
deprecationReason :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
deprecationReason :: FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
deprecationReason =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._deprecationReason Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId EnumValueInfo -> Value)
-> FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value -> Definition MetadataObjId EnumValueInfo -> Value
forall a b. a -> b -> a
const Value
J.Null
in InsOrdHashMap
Name
(ParsedSelection (Definition MetadataObjId EnumValueInfo -> Value))
-> Definition MetadataObjId EnumValueInfo -> Value
forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter
(InsOrdHashMap
Name
(ParsedSelection (Definition MetadataObjId EnumValueInfo -> Value))
-> Definition MetadataObjId EnumValueInfo -> Value)
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId EnumValueInfo -> Value)))
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId EnumValueInfo -> Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser
n (Definition MetadataObjId EnumValueInfo -> Value)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId EnumValueInfo -> Value)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet
Name
GName.___EnumValue
Maybe Description
forall a. Maybe a
Nothing
[ FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
name,
FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
description,
FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
isDeprecated,
FieldParser n (Definition MetadataObjId EnumValueInfo -> Value)
deprecationReason
]
typeKind ::
forall n.
(MonadParse n) =>
Parser 'Both n ()
typeKind :: forall (n :: * -> *). MonadParse n => Parser 'Both n ()
typeKind =
Name
-> Maybe Description
-> NonEmpty (Definition MetadataObjId EnumValueInfo, ())
-> Parser MetadataObjId 'Both n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> NonEmpty (Definition origin EnumValueInfo, a)
-> Parser origin 'Both m a
P.enum
Name
GName.___TypeKind
Maybe Description
forall a. Maybe a
Nothing
( [(Definition MetadataObjId EnumValueInfo, ())]
-> NonEmpty (Definition MetadataObjId EnumValueInfo, ())
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList
[ Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._ENUM,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._INPUT_OBJECT,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._INTERFACE,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._LIST,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._NON_NULL,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._OBJECT,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._SCALAR,
Name -> (Definition MetadataObjId EnumValueInfo, ())
forall {origin}. Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
GName._UNION
]
)
where
mkDefinition :: Name -> (Definition origin EnumValueInfo, ())
mkDefinition Name
name = (Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> EnumValueInfo
-> Definition origin EnumValueInfo
forall origin a.
Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> a
-> Definition origin a
P.Definition Name
name Maybe Description
forall a. Maybe a
Nothing Maybe origin
forall a. Maybe a
Nothing [] EnumValueInfo
P.EnumValueInfo, ())
fieldField ::
forall n.
(MonadParse n) =>
Parser 'Output n (P.Definition P.FieldInfo -> J.Value)
fieldField :: forall (n :: * -> *).
MonadParse n =>
Parser
'Output
n
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
fieldField =
let name :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
name :: FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
name =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._name Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Name -> Value
forall a. HasName a => a -> Value
nameAsJSON
(Name -> Value)
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> Name)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId (FieldInfo MetadataObjId) -> Name
forall origin a. Definition origin a -> Name
P.dName
description :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
description :: FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
description =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._description Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> \Definition MetadataObjId (FieldInfo MetadataObjId)
defInfo ->
case Definition MetadataObjId (FieldInfo MetadataObjId)
-> Maybe Description
forall origin a. Definition origin a -> Maybe Description
P.dDescription Definition MetadataObjId (FieldInfo MetadataObjId)
defInfo of
Maybe Description
Nothing -> Value
J.Null
Just Description
desc -> Text -> Value
J.String (Description -> Text
G.unDescription Description
desc)
args :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
args :: FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
args = do
Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
printer <- Name
-> Maybe Description
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
-> FieldParser
MetadataObjId
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._args Maybe Description
forall a. Maybe a
Nothing Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
inputValue
return $ Array -> Value
J.Array (Array -> Value)
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> Array)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Array
forall a. [a] -> Vector a
V.fromList ([Value] -> Array)
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> [Value])
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> Array
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Value]
forall a b. (a -> b) -> [a] -> [b]
map Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
printer ([Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Value])
-> (Definition MetadataObjId (FieldInfo MetadataObjId)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)])
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Name)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Name
forall origin a. Definition origin a -> Name
P.dName ([Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)])
-> (Definition MetadataObjId (FieldInfo MetadataObjId)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)])
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldInfo MetadataObjId
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall origin.
FieldInfo origin -> [Definition origin (InputFieldInfo origin)]
P.fArguments (FieldInfo MetadataObjId
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)])
-> (Definition MetadataObjId (FieldInfo MetadataObjId)
-> FieldInfo MetadataObjId)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId (FieldInfo MetadataObjId)
-> FieldInfo MetadataObjId
forall origin a. Definition origin a -> a
P.dInfo
typeF :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
typeF :: FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
typeF = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._type Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return $ SomeType -> Value
printer (SomeType -> Value)
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> SomeType)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\case P.FieldInfo [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
_ Type MetadataObjId k
tp -> Type MetadataObjId k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType Type MetadataObjId k
tp) (FieldInfo MetadataObjId -> SomeType)
-> (Definition MetadataObjId (FieldInfo MetadataObjId)
-> FieldInfo MetadataObjId)
-> Definition MetadataObjId (FieldInfo MetadataObjId)
-> SomeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Definition MetadataObjId (FieldInfo MetadataObjId)
-> FieldInfo MetadataObjId
forall origin a. Definition origin a -> a
P.dInfo
isDeprecated :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
isDeprecated :: FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
isDeprecated =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._isDeprecated Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value
-> Definition MetadataObjId (FieldInfo MetadataObjId) -> Value
forall a b. a -> b -> a
const (Bool -> Value
J.Bool Bool
False)
deprecationReason :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
deprecationReason :: FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
deprecationReason =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._deprecationReason Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value
-> Definition MetadataObjId (FieldInfo MetadataObjId) -> Value
forall a b. a -> b -> a
const Value
J.Null
in InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value))
-> Definition MetadataObjId (FieldInfo MetadataObjId) -> Value
forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value))
-> Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)))
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet
Name
GName.___Field
Maybe Description
forall a. Maybe a
Nothing
[ FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
name,
FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
description,
FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
args,
FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
typeF,
FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
isDeprecated,
FieldParser
n (Definition MetadataObjId (FieldInfo MetadataObjId) -> Value)
deprecationReason
]
directiveSet ::
forall n.
(MonadParse n) =>
Parser 'Output n (P.DirectiveInfo -> J.Value)
directiveSet :: forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (DirectiveInfo -> Value)
directiveSet =
let name :: FieldParser n (P.DirectiveInfo -> J.Value)
name :: FieldParser n (DirectiveInfo -> Value)
name =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._name Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (DirectiveInfo -> Value)
-> FieldParser n (DirectiveInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (Name -> Value
forall a. ToJSON a => a -> Value
J.toOrdered (Name -> Value)
-> (DirectiveInfo -> Name) -> DirectiveInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DirectiveInfo -> Name
forall origin. DirectiveInfo origin -> Name
P.diName)
description :: FieldParser n (P.DirectiveInfo -> J.Value)
description :: FieldParser n (DirectiveInfo -> Value)
description =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._description Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (DirectiveInfo -> Value)
-> FieldParser n (DirectiveInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (Maybe Description -> Value
forall a. ToJSON a => a -> Value
J.toOrdered (Maybe Description -> Value)
-> (DirectiveInfo -> Maybe Description) -> DirectiveInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DirectiveInfo -> Maybe Description
forall origin. DirectiveInfo origin -> Maybe Description
P.diDescription)
locations :: FieldParser n (P.DirectiveInfo -> J.Value)
locations :: FieldParser n (DirectiveInfo -> Value)
locations =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._locations Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (DirectiveInfo -> Value)
-> FieldParser n (DirectiveInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ([Text] -> Value
forall a. ToJSON a => a -> Value
J.toOrdered ([Text] -> Value)
-> (DirectiveInfo -> [Text]) -> DirectiveInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DirectiveLocation -> Text) -> [DirectiveLocation] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DirectiveLocation -> Text
showDirLoc ([DirectiveLocation] -> [Text])
-> (DirectiveInfo -> [DirectiveLocation])
-> DirectiveInfo
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DirectiveInfo -> [DirectiveLocation]
forall origin. DirectiveInfo origin -> [DirectiveLocation]
P.diLocations)
args :: FieldParser n (P.DirectiveInfo -> J.Value)
args :: FieldParser n (DirectiveInfo -> Value)
args = do
Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
printer <- Name
-> Maybe Description
-> Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
-> FieldParser
MetadataObjId
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._args Maybe Description
forall a. Maybe a
Nothing Parser
MetadataObjId
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser
'Output
n
(Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
inputValue
pure $ [Value] -> Value
J.array ([Value] -> Value)
-> (DirectiveInfo -> [Value]) -> DirectiveInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value)
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Value]
forall a b. (a -> b) -> [a] -> [b]
map Definition MetadataObjId (InputFieldInfo MetadataObjId) -> Value
printer ([Definition MetadataObjId (InputFieldInfo MetadataObjId)]
-> [Value])
-> (DirectiveInfo
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)])
-> DirectiveInfo
-> [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DirectiveInfo
-> [Definition MetadataObjId (InputFieldInfo MetadataObjId)]
forall origin.
DirectiveInfo origin -> [Definition origin (InputFieldInfo origin)]
P.diArguments
isRepeatable :: FieldParser n (P.DirectiveInfo -> J.Value)
isRepeatable :: FieldParser n (DirectiveInfo -> Value)
isRepeatable =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._isRepeatable Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (DirectiveInfo -> Value)
-> FieldParser n (DirectiveInfo -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Value -> DirectiveInfo -> Value
forall a b. a -> b -> a
const Value
J.Null
in InsOrdHashMap Name (ParsedSelection (DirectiveInfo -> Value))
-> DirectiveInfo -> Value
forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter
(InsOrdHashMap Name (ParsedSelection (DirectiveInfo -> Value))
-> DirectiveInfo -> Value)
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (DirectiveInfo -> Value)))
-> Parser MetadataObjId 'Output n (DirectiveInfo -> Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser n (DirectiveInfo -> Value)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (DirectiveInfo -> Value)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet
Name
GName.___Directive
Maybe Description
forall a. Maybe a
Nothing
[ FieldParser n (DirectiveInfo -> Value)
name,
FieldParser n (DirectiveInfo -> Value)
description,
FieldParser n (DirectiveInfo -> Value)
locations,
FieldParser n (DirectiveInfo -> Value)
args,
FieldParser n (DirectiveInfo -> Value)
isRepeatable
]
where
showDirLoc :: G.DirectiveLocation -> Text
showDirLoc :: DirectiveLocation -> Text
showDirLoc = \case
G.DLExecutable ExecutableDirectiveLocation
edl -> String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ ExecutableDirectiveLocation -> String
forall a. Show a => a -> String
show ExecutableDirectiveLocation
edl
G.DLTypeSystem TypeSystemDirectiveLocation
tsdl -> String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
4 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ TypeSystemDirectiveLocation -> String
forall a. Show a => a -> String
show TypeSystemDirectiveLocation
tsdl
schemaSet ::
forall n.
(MonadParse n) =>
Parser 'Output n (Schema -> J.Value)
{-# INLINE schemaSet #-}
schemaSet :: forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (Schema -> Value)
schemaSet =
let description :: FieldParser n (Schema -> J.Value)
description :: FieldParser n (Schema -> Value)
description =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
GName._description Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser MetadataObjId n ()
-> (Schema -> Value) -> FieldParser n (Schema -> Value)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> \Schema
partialSchema -> case Schema -> Maybe Description
forall origin. Schema origin -> Maybe Description
sDescription Schema
partialSchema of
Maybe Description
Nothing -> Value
J.Null
Just Description
s -> Text -> Value
J.String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Description -> Text
G.unDescription Description
s
types :: FieldParser n (Schema -> J.Value)
types :: FieldParser n (Schema -> Value)
types = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._types Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return
$ \Schema
partialSchema ->
Array -> Value
J.Array
(Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ [Value] -> Array
forall a. [a] -> Vector a
V.fromList
([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ (SomeDefinitionTypeInfo MetadataObjId -> Value)
-> [SomeDefinitionTypeInfo MetadataObjId] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map (SomeType -> Value
printer (SomeType -> Value)
-> (SomeDefinitionTypeInfo MetadataObjId -> SomeType)
-> SomeDefinitionTypeInfo MetadataObjId
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeDefinitionTypeInfo MetadataObjId -> SomeType
schemaTypeToSomeType)
([SomeDefinitionTypeInfo MetadataObjId] -> [Value])
-> [SomeDefinitionTypeInfo MetadataObjId] -> [Value]
forall a b. (a -> b) -> a -> b
$ (SomeDefinitionTypeInfo MetadataObjId -> Name)
-> [SomeDefinitionTypeInfo MetadataObjId]
-> [SomeDefinitionTypeInfo MetadataObjId]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn SomeDefinitionTypeInfo MetadataObjId -> Name
forall a. HasName a => a -> Name
P.getName
([SomeDefinitionTypeInfo MetadataObjId]
-> [SomeDefinitionTypeInfo MetadataObjId])
-> [SomeDefinitionTypeInfo MetadataObjId]
-> [SomeDefinitionTypeInfo MetadataObjId]
forall a b. (a -> b) -> a -> b
$ HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
-> [SomeDefinitionTypeInfo MetadataObjId]
forall k v. HashMap k v -> [v]
HashMap.elems
(HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
-> [SomeDefinitionTypeInfo MetadataObjId])
-> HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
-> [SomeDefinitionTypeInfo MetadataObjId]
forall a b. (a -> b) -> a -> b
$ Schema -> HashMap Name (SomeDefinitionTypeInfo MetadataObjId)
forall origin.
Schema origin -> HashMap Name (SomeDefinitionTypeInfo origin)
sTypes Schema
partialSchema
where
schemaTypeToSomeType :: P.SomeDefinitionTypeInfo -> SomeType
schemaTypeToSomeType :: SomeDefinitionTypeInfo MetadataObjId -> SomeType
schemaTypeToSomeType (P.SomeDefinitionTypeInfo Definition MetadataObjId (TypeInfo MetadataObjId k)
def) =
Type k -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type k -> SomeType) -> Type k -> SomeType
forall a b. (a -> b) -> a -> b
$ Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId k) -> Type k
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.Nullable Definition MetadataObjId (TypeInfo MetadataObjId k)
def
queryType :: FieldParser n (Schema -> J.Value)
queryType :: FieldParser n (Schema -> Value)
queryType = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._queryType Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return $ \Schema
partialSchema -> SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type 'Output -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType (Type 'Output -> SomeType) -> Type 'Output -> SomeType
forall a b. (a -> b) -> a -> b
$ Schema -> Type 'Output
forall origin. Schema origin -> Type origin 'Output
sQueryType Schema
partialSchema
mutationType :: FieldParser n (Schema -> J.Value)
mutationType :: FieldParser n (Schema -> Value)
mutationType = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._mutationType Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return $ \Schema
partialSchema -> case Schema -> Maybe (Type 'Output)
forall origin. Schema origin -> Maybe (Type origin 'Output)
sMutationType Schema
partialSchema of
Maybe (Type 'Output)
Nothing -> Value
J.Null
Just Type 'Output
tp -> SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type 'Output -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType Type 'Output
tp
subscriptionType :: FieldParser n (Schema -> J.Value)
subscriptionType :: FieldParser n (Schema -> Value)
subscriptionType = do
SomeType -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (SomeType -> Value)
-> FieldParser MetadataObjId n (SomeType -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._subscriptionType Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (SomeType -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (SomeType -> Value)
typeField
return $ \Schema
partialSchema -> case Schema -> Maybe (Type 'Output)
forall origin. Schema origin -> Maybe (Type origin 'Output)
sSubscriptionType Schema
partialSchema of
Maybe (Type 'Output)
Nothing -> Value
J.Null
Just Type 'Output
tp -> SomeType -> Value
printer (SomeType -> Value) -> SomeType -> Value
forall a b. (a -> b) -> a -> b
$ Type 'Output -> SomeType
forall (k :: Kind). Type k -> SomeType
SomeType Type 'Output
tp
directives :: FieldParser n (Schema -> J.Value)
directives :: FieldParser n (Schema -> Value)
directives = do
DirectiveInfo -> Value
printer <- Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (DirectiveInfo -> Value)
-> FieldParser MetadataObjId n (DirectiveInfo -> Value)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
GName._directives Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (DirectiveInfo -> Value)
forall (n :: * -> *).
MonadParse n =>
Parser 'Output n (DirectiveInfo -> Value)
directiveSet
return $ \Schema
partialSchema -> [Value] -> Value
J.array ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ (DirectiveInfo -> Value) -> [DirectiveInfo] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map DirectiveInfo -> Value
printer ([DirectiveInfo] -> [Value]) -> [DirectiveInfo] -> [Value]
forall a b. (a -> b) -> a -> b
$ Schema -> [DirectiveInfo]
forall origin. Schema origin -> [DirectiveInfo origin]
sDirectives Schema
partialSchema
in InsOrdHashMap Name (ParsedSelection (Schema -> Value))
-> Schema -> Value
forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter
(InsOrdHashMap Name (ParsedSelection (Schema -> Value))
-> Schema -> Value)
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (Schema -> Value)))
-> Parser MetadataObjId 'Output n (Schema -> Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser n (Schema -> Value)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (Schema -> Value)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet
Name
GName.___Schema
Maybe Description
forall a. Maybe a
Nothing
[ FieldParser n (Schema -> Value)
description,
FieldParser n (Schema -> Value)
types,
FieldParser n (Schema -> Value)
queryType,
FieldParser n (Schema -> Value)
mutationType,
FieldParser n (Schema -> Value)
subscriptionType,
FieldParser n (Schema -> Value)
directives
]
selectionSetToJSON ::
InsOrdHashMap.InsOrdHashMap G.Name J.Value ->
J.Value
selectionSetToJSON :: InsOrdHashMap Name Value -> Value
selectionSetToJSON = [(Text, Value)] -> Value
J.object ([(Text, Value)] -> Value)
-> (InsOrdHashMap Name Value -> [(Text, Value)])
-> InsOrdHashMap Name Value
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Name, Value) -> (Text, Value))
-> [(Name, Value)] -> [(Text, Value)]
forall a b. (a -> b) -> [a] -> [b]
map ((Name -> Text) -> (Name, Value) -> (Text, Value)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Name -> Text
G.unName) ([(Name, Value)] -> [(Text, Value)])
-> (InsOrdHashMap Name Value -> [(Name, Value)])
-> InsOrdHashMap Name Value
-> [(Text, Value)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InsOrdHashMap Name Value -> [(Name, Value)]
forall k v. InsOrdHashMap k v -> [(k, v)]
InsOrdHashMap.toList
applyPrinter ::
InsOrdHashMap.InsOrdHashMap G.Name (P.ParsedSelection (a -> J.Value)) ->
a ->
J.Value
applyPrinter :: forall a.
InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
applyPrinter = (a -> InsOrdHashMap Name (ParsedSelection (a -> Value)) -> Value)
-> InsOrdHashMap Name (ParsedSelection (a -> Value)) -> a -> Value
forall a b c. (a -> b -> c) -> b -> a -> c
flip (\a
x -> InsOrdHashMap Name Value -> Value
selectionSetToJSON (InsOrdHashMap Name Value -> Value)
-> (InsOrdHashMap Name (ParsedSelection (a -> Value))
-> InsOrdHashMap Name Value)
-> InsOrdHashMap Name (ParsedSelection (a -> Value))
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsedSelection (a -> Value) -> Value)
-> InsOrdHashMap Name (ParsedSelection (a -> Value))
-> InsOrdHashMap Name Value
forall a b.
(a -> b) -> InsOrdHashMap Name a -> InsOrdHashMap Name b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((a -> Value) -> a -> Value
forall a b. (a -> b) -> a -> b
$ a
x) ((a -> Value) -> Value)
-> (ParsedSelection (a -> Value) -> a -> Value)
-> ParsedSelection (a -> Value)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name -> a -> Value) -> ParsedSelection (a -> Value) -> a -> Value
forall a. (Name -> a) -> ParsedSelection a -> a
P.handleTypename (Value -> a -> Value
forall a b. a -> b -> a
const (Value -> a -> Value) -> (Name -> Value) -> Name -> a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Value
forall a. HasName a => a -> Value
nameAsJSON)))
nameAsJSON :: (P.HasName a) => a -> J.Value
nameAsJSON :: forall a. HasName a => a -> Value
nameAsJSON = Text -> Value
J.String (Text -> Value) -> (a -> Text) -> a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Text
G.unName (Name -> Text) -> (a -> Name) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Name
forall a. HasName a => a -> Name
P.getName