module AirGQL.Introspection (
getSchemaResolver,
typeNameResolver,
createType,
)
where
import Protolude (
Applicative (pure),
Bool (False, True),
Eq ((/=)),
Foldable (null),
IO,
Int,
IsString,
Maybe (Just, Nothing),
MonadReader (ask),
Monoid (mempty),
Num ((+)),
Ord ((<)),
Semigroup ((<>)),
Text,
concat,
filter,
forM,
fromMaybe,
not,
($),
(&),
(&&),
(<&>),
(>>=),
)
import Data.HashMap.Strict as HashMap (
HashMap,
empty,
fromList,
lookup,
singleton,
)
import Database.SQLite.Simple (Connection)
import Language.GraphQL.Type (
Value (Boolean, List, Null, Object, String),
boolean,
string,
)
import Language.GraphQL.Type.In as In (Type (NamedScalarType))
import Language.GraphQL.Type.Out as Out (
Context (values),
Field (Field),
Resolver (ValueResolver),
Type (
ListType,
NamedObjectType,
NamedScalarType,
NonNullListType,
NonNullObjectType,
NonNullScalarType
),
)
import AirGQL.GQLWrapper (
InArgument (InArgument, argDescMb, argType, valueMb),
OutField (OutField, arguments, descriptionMb, fieldType),
inArgumentToArgument,
outFieldToField,
)
import AirGQL.Lib (
AccessMode (ReadAndWrite, ReadOnly, WriteOnly),
ColumnEntry,
GqlTypeName (full),
TableEntryRaw (name),
column_name_gql,
datatype_gql,
getColumns,
isOmittable,
notnull,
select_options,
)
import AirGQL.Types.OutObjectType (
OutObjectType (OutObjectType, descriptionMb, fields, interfaceTypes, name),
outObjectTypeToObjectType,
)
import DoubleXEncoding (doubleXEncodeGql)
emptyType :: Value
emptyType :: Value
emptyType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Value -> HashMap Text Value
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton Text
"kind" Value
"OBJECT"
intType :: Value
intType :: Value
intType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Int")
,
( Text
"description"
, Value
"The `Int` scalar type represents \
\non-fractional signed whole numeric values. \
\Int can represent values between -(2^31) and 2^31 - 1."
)
]
floatType :: Value
floatType :: Value
floatType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Float")
,
( Text
"description"
, Value
"Signed double-precision floating-point value."
)
]
stringType :: Value
stringType :: Value
stringType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"String")
,
( Text
"description"
, Value
"The `String` scalar type represents textual data, \
\represented as UTF-8 character sequences. \
\The String type is most often used by GraphQL \
\to represent free-form human-readable text."
)
]
booleanType :: Value
booleanType :: Value
booleanType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Boolean")
,
( Text
"description"
, Value
"The `Boolean` scalar type represents `true` or `false`."
)
]
nonNullString :: Out.Field IO
nonNullString :: Field IO
nonNullString =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"nonNullString description"
, $sel:fieldType:OutField :: Type IO
fieldType = ScalarType -> Type IO
forall (m :: * -> *). ScalarType -> Type m
Out.NonNullScalarType ScalarType
string
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
nullableString :: Out.Field IO
nullableString :: Field IO
nullableString =
Maybe Text -> Type IO -> Arguments -> Field IO
forall (m :: * -> *). Maybe Text -> Type m -> Arguments -> Field m
Out.Field
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"nullableString")
(ScalarType -> Type IO
forall (m :: * -> *). ScalarType -> Type m
Out.NamedScalarType ScalarType
string)
Arguments
forall k v. HashMap k v
HashMap.empty
nonNullBoolean :: Out.Field IO
nonNullBoolean :: Field IO
nonNullBoolean =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"nonNullBoolean description"
, $sel:fieldType:OutField :: Type IO
fieldType = ScalarType -> Type IO
forall (m :: * -> *). ScalarType -> Type m
Out.NonNullScalarType ScalarType
boolean
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
getTypeTuple :: (IsString a) => Value -> Value -> (a, Value)
getTypeTuple :: forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
theKind Value
theType =
( a
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
theKind)
, (Text
"name", Value
theType)
]
)
nonNullType :: Value -> Value
nonNullType :: Value -> Value
nonNullType Value
inner =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
, (Text
"ofType", Value
inner)
]
listType :: Value -> Value
listType :: Value -> Value
listType Value
inner =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
, (Text
"ofType", Value
inner)
]
createType :: Text -> Text -> [Value] -> [Text] -> Text -> Value
createType :: Text -> Text -> [Value] -> [Text] -> Text -> Value
createType Text
rootName Text
description [Value]
args [Text]
nestedTypes Text
name =
let
createChildType :: [Text] -> Text -> Value
createChildType :: [Text] -> Text -> Value
createChildType [Text]
nestedChildTypes Text
childName =
case [Text]
nestedChildTypes of
[] -> Value
Null
(Text
childHeadKind : [Text]
childRestKinds) ->
if Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
childRestKinds
then
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Text -> Value
String Text
childHeadKind)
, (Text
"ofType", [Text] -> Text -> Value
createChildType [Text]
childRestKinds Text
childName)
]
else
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Text -> Value
String Text
childHeadKind)
, (Text
"name", Text -> Value
String Text
name)
]
in
case [Text]
nestedTypes of
[] -> Value
Null
[Text]
kinds ->
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
( [ (Text
"name", Text -> Value
String Text
rootName)
, (Text
"description", Text -> Value
String Text
description)
, (Text
"type", [Text] -> Text -> Value
createChildType [Text]
kinds Text
name)
]
[(Text, Value)] -> [(Text, Value)] -> [(Text, Value)]
forall a. Semigroup a => a -> a -> a
<> if [Value] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Value]
args then [] else [(Text
"args", [Value] -> Value
List [Value]
args)]
)
createField :: Text -> Maybe Text -> Value -> Value
createField :: Text -> Maybe Text -> Value -> Value
createField Text
name Maybe Text
descriptionMb Value
type_ =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Text -> Value
String Text
name)
, (Text
"type", Value
type_)
]
HashMap Text Value -> HashMap Text Value -> HashMap Text Value
forall a. Semigroup a => a -> a -> a
<> case Maybe Text
descriptionMb of
Maybe Text
Nothing -> HashMap Text Value
forall a. Monoid a => a
mempty
Just Text
description ->
Text -> Value -> HashMap Text Value
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton
Text
"description"
(Text -> Value
String Text
description)
nameField :: Value
nameField :: Value
nameField =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"name")
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"String")
]
)
]
descriptionField :: Value
descriptionField :: Value
descriptionField =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"description")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"String"
]
argsFieldValue :: Value
argsFieldValue :: Value
argsFieldValue =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"args")
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
Value -> Value
listType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__InputValue")
]
)
]
locationsFieldValue :: Value
locationsFieldValue :: Value
locationsFieldValue =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"locations")
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
Value -> Value
listType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"ENUM")
, (Text
"name", Value
"__DirectiveLocation")
]
)
]
typeFieldValue :: Value
typeFieldValue :: Value
typeFieldValue =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"type")
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Type")
]
)
]
isDeprecatedFieldValue :: Value
isDeprecatedFieldValue :: Value
isDeprecatedFieldValue =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"isDeprecated")
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Boolean")
]
)
]
typeType :: Int -> Out.Type IO
typeType :: Int -> Type IO
typeType Int
level =
ObjectType IO -> Type IO
forall (m :: * -> *). ObjectType m -> Type m
Out.NamedObjectType (ObjectType IO -> Type IO) -> ObjectType IO -> Type IO
forall a b. (a -> b) -> a -> b
$
OutObjectType IO -> ObjectType IO
forall (m :: * -> *). OutObjectType m -> ObjectType m
outObjectTypeToObjectType (OutObjectType IO -> ObjectType IO)
-> OutObjectType IO -> ObjectType IO
forall a b. (a -> b) -> a -> b
$
OutObjectType
{ $sel:name:OutObjectType :: Text
name = Text
"__Type"
, $sel:descriptionMb:OutObjectType :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"__Type description"
, $sel:interfaceTypes:OutObjectType :: [InterfaceType IO]
interfaceTypes = []
, $sel:fields:OutObjectType :: HashMap Text (Resolver IO)
fields =
[(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(Text, Resolver IO)] -> HashMap Text (Resolver IO))
-> [(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall a b. (a -> b) -> a -> b
$
[
( Text
"__typename"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"__Type"
)
,
( Text
"kind"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"ERROR: kind" (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"kind" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"ERROR: kind"
)
,
( Text
"name"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"name" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"description"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"description" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"fields"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
fieldsField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"fields" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"possibleTypes"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
typesField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"possibleTypes" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"interfaces"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
typesField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe ([Value] -> Value
List []) (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"interfaces" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$ [Value] -> Value
List []
)
,
( Text
"inputFields"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
inputsFieldsField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"inputFields" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"enumValues"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
enumValuesField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"enumValues" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
]
[(Text, Resolver IO)]
-> [(Text, Resolver IO)] -> [(Text, Resolver IO)]
forall a. Semigroup a => a -> a -> a
<> ( if Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
7
then
[
( Text
"ofType"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver (Int -> Field IO
typeField (Int -> Field IO) -> Int -> Field IO
forall a b. (a -> b) -> a -> b
$ Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"ofType" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
]
else []
)
}
typeField :: Int -> Field IO
typeField :: Int -> Field IO
typeField Int
level =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"typeField description"
, $sel:fieldType:OutField :: Type IO
fieldType = Int -> Type IO
typeType Int
level
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
typesField :: Field IO
typesField :: Field IO
typesField =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"typesField description"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO -> Type IO
forall (m :: * -> *). Type m -> Type m
Out.ListType (Type IO -> Type IO) -> Type IO -> Type IO
forall a b. (a -> b) -> a -> b
$ Int -> Type IO
typeType Int
0
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
inputValueType :: Out.Type IO
inputValueType :: Type IO
inputValueType =
ObjectType IO -> Type IO
forall (m :: * -> *). ObjectType m -> Type m
Out.NonNullObjectType (ObjectType IO -> Type IO) -> ObjectType IO -> Type IO
forall a b. (a -> b) -> a -> b
$
OutObjectType IO -> ObjectType IO
forall (m :: * -> *). OutObjectType m -> ObjectType m
outObjectTypeToObjectType (OutObjectType IO -> ObjectType IO)
-> OutObjectType IO -> ObjectType IO
forall a b. (a -> b) -> a -> b
$
OutObjectType
{ $sel:name:OutObjectType :: Text
name = Text
"__InputValue"
, $sel:descriptionMb:OutObjectType :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"__InputValue description"
, $sel:interfaceTypes:OutObjectType :: [InterfaceType IO]
interfaceTypes = []
, $sel:fields:OutObjectType :: HashMap Text (Resolver IO)
fields =
[(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"__typename"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"__InputValue"
)
,
( Text
"name"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"ERROR: name" (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"name" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"ERROR: name"
)
,
( Text
"description"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"description" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"defaultValue"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"defaultValue" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"type"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver (Int -> Field IO
typeField Int
0) (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
emptyType (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"type" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
emptyType
)
]
}
argsField :: Field IO
argsField :: Field IO
argsField =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"argsField description"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO -> Type IO
forall (m :: * -> *). Type m -> Type m
Out.NonNullListType Type IO
inputValueType
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
inputsFieldsField :: Field IO
inputsFieldsField :: Field IO
inputsFieldsField =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"inputsFieldsField description"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO -> Type IO
forall (m :: * -> *). Type m -> Type m
Out.ListType Type IO
inputValueType
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
enumValuesType :: Out.Type IO
enumValuesType :: Type IO
enumValuesType =
Type IO -> Type IO
forall (m :: * -> *). Type m -> Type m
Out.ListType (Type IO -> Type IO) -> Type IO -> Type IO
forall a b. (a -> b) -> a -> b
$
ObjectType IO -> Type IO
forall (m :: * -> *). ObjectType m -> Type m
Out.NonNullObjectType (ObjectType IO -> Type IO) -> ObjectType IO -> Type IO
forall a b. (a -> b) -> a -> b
$
OutObjectType IO -> ObjectType IO
forall (m :: * -> *). OutObjectType m -> ObjectType m
outObjectTypeToObjectType (OutObjectType IO -> ObjectType IO)
-> OutObjectType IO -> ObjectType IO
forall a b. (a -> b) -> a -> b
$
OutObjectType
{ $sel:name:OutObjectType :: Text
name = Text
"__EnumValue"
, $sel:descriptionMb:OutObjectType :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"__EnumValue description"
, $sel:interfaceTypes:OutObjectType :: [InterfaceType IO]
interfaceTypes = []
, $sel:fields:OutObjectType :: HashMap Text (Resolver IO)
fields =
[(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"__typename"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"__EnumValue"
)
,
( Text
"name"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"ERROR: name" (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"name" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"ERROR: name"
)
,
( Text
"description"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"description" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"isDeprecated"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullBoolean (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe (Bool -> Value
Boolean Bool
False) (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"isDeprecated" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Boolean Bool
False
)
,
( Text
"deprecationReason"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"deprecationReason" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
]
}
enumValuesField :: Field IO
enumValuesField :: Field IO
enumValuesField =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"enumValuesField description"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO
enumValuesType
, $sel:arguments:OutField :: Arguments
arguments =
[(Text, Argument)] -> Arguments
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"includeDeprecated"
, InArgument -> Argument
inArgumentToArgument (InArgument -> Argument) -> InArgument -> Argument
forall a b. (a -> b) -> a -> b
$
InArgument
{ $sel:argDescMb:InArgument :: Maybe Text
argDescMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"includeDeprecated description"
, $sel:argType:InArgument :: Type
argType = ScalarType -> Type
In.NamedScalarType ScalarType
boolean
, $sel:valueMb:InArgument :: Maybe Value
valueMb = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Boolean Bool
True
}
)
]
}
queryTypeType :: Field IO
queryTypeType :: Field IO
queryTypeType =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Provides the queryType"
, $sel:fieldType:OutField :: Type IO
fieldType = Int -> Type IO
typeType Int
0
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
mutationTypeType :: Field IO
mutationTypeType :: Field IO
mutationTypeType =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Provides the mutationType"
, $sel:fieldType:OutField :: Type IO
fieldType = Int -> Type IO
typeType Int
0
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
subscriptionTypeType :: Field IO
subscriptionTypeType :: Field IO
subscriptionTypeType =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Provides the subscriptionType"
, $sel:fieldType:OutField :: Type IO
fieldType = Int -> Type IO
typeType Int
0
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
fieldsTypeOutput :: Out.Type IO
fieldsTypeOutput :: Type IO
fieldsTypeOutput =
Type IO -> Type IO
forall (m :: * -> *). Type m -> Type m
Out.ListType (Type IO -> Type IO) -> Type IO -> Type IO
forall a b. (a -> b) -> a -> b
$
ObjectType IO -> Type IO
forall (m :: * -> *). ObjectType m -> Type m
Out.NonNullObjectType (ObjectType IO -> Type IO) -> ObjectType IO -> Type IO
forall a b. (a -> b) -> a -> b
$
OutObjectType IO -> ObjectType IO
forall (m :: * -> *). OutObjectType m -> ObjectType m
outObjectTypeToObjectType (OutObjectType IO -> ObjectType IO)
-> OutObjectType IO -> ObjectType IO
forall a b. (a -> b) -> a -> b
$
OutObjectType
{ $sel:name:OutObjectType :: Text
name = Text
"__Field"
, $sel:descriptionMb:OutObjectType :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"__Field description"
, $sel:interfaceTypes:OutObjectType :: [InterfaceType IO]
interfaceTypes = []
, $sel:fields:OutObjectType :: HashMap Text (Resolver IO)
fields =
[(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"__typename"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"__Field"
)
,
( Text
"name"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"ERROR: name" (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"name" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"ERROR: name"
)
,
( Text
"description"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"description" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"args"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
argsField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe ([Value] -> Value
List []) (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"args" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$ [Value] -> Value
List []
)
,
( Text
"type"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver (Int -> Field IO
typeField Int
0) (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
emptyType (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"type" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
emptyType
)
,
( Text
"isDeprecated"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullBoolean (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe (Bool -> Value
Boolean Bool
False) (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"isDeprecated" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Boolean Bool
False
)
,
( Text
"deprecationReason"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"deprecationReason" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
]
}
fieldsField :: Field IO
fieldsField :: Field IO
fieldsField =
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"The fields type"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO
fieldsTypeOutput
, $sel:arguments:OutField :: Arguments
arguments =
[(Text, Argument)] -> Arguments
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"includeDeprecated"
, InArgument -> Argument
inArgumentToArgument (InArgument -> Argument) -> InArgument -> Argument
forall a b. (a -> b) -> a -> b
$
InArgument
{ $sel:argDescMb:InArgument :: Maybe Text
argDescMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"includeDeprecated description"
, $sel:argType:InArgument :: Type
argType = ScalarType -> Type
In.NamedScalarType ScalarType
boolean
, $sel:valueMb:InArgument :: Maybe Value
valueMb = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value) -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Bool -> Value
Boolean Bool
True
}
)
]
}
directivesType :: Field IO
directivesType :: Field IO
directivesType =
let
directivesTypeOutput :: Out.Type IO
directivesTypeOutput :: Type IO
directivesTypeOutput =
Type IO -> Type IO
forall (m :: * -> *). Type m -> Type m
Out.ListType (Type IO -> Type IO) -> Type IO -> Type IO
forall a b. (a -> b) -> a -> b
$
ObjectType IO -> Type IO
forall (m :: * -> *). ObjectType m -> Type m
Out.NonNullObjectType (ObjectType IO -> Type IO) -> ObjectType IO -> Type IO
forall a b. (a -> b) -> a -> b
$
OutObjectType IO -> ObjectType IO
forall (m :: * -> *). OutObjectType m -> ObjectType m
outObjectTypeToObjectType (OutObjectType IO -> ObjectType IO)
-> OutObjectType IO -> ObjectType IO
forall a b. (a -> b) -> a -> b
$
OutObjectType
{ $sel:name:OutObjectType :: Text
name = Text
"__Directive"
, $sel:descriptionMb:OutObjectType :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"__Directive description"
, $sel:interfaceTypes:OutObjectType :: [InterfaceType IO]
interfaceTypes = []
, $sel:fields:OutObjectType :: HashMap Text (Resolver IO)
fields =
[(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"__typename"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"__Directive"
)
,
( Text
"name"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"ERROR: name" (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"name" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"ERROR: name"
)
,
( Text
"description"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nullableString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
Null (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"description" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"locations"
, let
locationsTypeName :: Field m
locationsTypeName :: forall (m :: * -> *). Field m
locationsTypeName =
Maybe Text -> Type m -> Arguments -> Field m
forall (m :: * -> *). Maybe Text -> Type m -> Arguments -> Field m
Out.Field
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"locationsTypeName name")
(Type m -> Type m
forall (m :: * -> *). Type m -> Type m
Out.ListType (Type m -> Type m) -> Type m -> Type m
forall a b. (a -> b) -> a -> b
$ ScalarType -> Type m
forall (m :: * -> *). ScalarType -> Type m
Out.NonNullScalarType ScalarType
string)
Arguments
forall k v. HashMap k v
HashMap.empty
in
Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
forall (m :: * -> *). Field m
locationsTypeName (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe ([Value] -> Value
List []) (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"locations" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$ [Value] -> Value
List []
)
,
( Text
"args"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
argsField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ do
Context
context <- ReaderT Context IO Context
forall r (m :: * -> *). MonadReader r m => m r
ask
case Context
context Context -> (Context -> Value) -> Value
forall a b. a -> (a -> b) -> b
& Context -> Value
Out.values of
Object HashMap Text Value
obj ->
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe ([Value] -> Value
List []) (Maybe Value -> Value) -> Maybe Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> HashMap Text Value -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup Text
"args" HashMap Text Value
obj
Value
_ -> Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$ [Value] -> Value
List []
)
]
}
in
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Provides the directivesType"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO
directivesTypeOutput
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
filterType :: Bool -> Text -> Value
filterType :: Bool -> Text -> Value
filterType Bool
isRequired Text
tableName =
let
filterObj :: Value
filterObj =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"INPUT_OBJECT")
, (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql Text
tableName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_filter")
,
( Text
"description"
, Value
"Select rows matching the provided filter object"
)
]
in
if Bool
isRequired
then Value -> Value
nonNullType Value
filterObj
else Value
filterObj
getFieldsForQuery :: Text -> Value
getFieldsForQuery :: Text -> Value
getFieldsForQuery Text
tableName =
Text -> Text -> [Value] -> [Text] -> Text -> Value
createType
(Text -> Text
doubleXEncodeGql Text
tableName)
(Text
"Rows from the table \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tableName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\"")
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"filter")
, (Text
"description", Value
"Filter to select specific rows")
, (Text
"type", Bool -> Text -> Value
filterType Bool
False Text
tableName)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"order_by")
, (Text
"description", Value
"Columns used to sort the data")
,
( Text
"type"
, Value -> Value
listType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_order_by"
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"limit")
, (Text
"description", Value
"Limit the number of returned rows")
, (Text
"type", Value
intType)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"offset")
, (Text
"description", Value
"The index to start returning rows from")
, (Text
"type", Value
intType)
]
]
[Text
"NON_NULL", Text
"LIST", Text
"NON_NULL", Text
"OBJECT"]
(Text -> Text
doubleXEncodeGql Text
tableName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_row")
getFieldsForMutation :: Text -> [Value]
getFieldsForMutation :: Text -> [Value]
getFieldsForMutation Text
tableName =
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"insert_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
doubleXEncodeGql Text
tableName)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text
"Insert new rows in table \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tableName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
)
,
( Text
"args"
, [Value] -> Value
List
[ Text -> Maybe Text -> Value -> Value
createField
Text
"objects"
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Rows to be inserted")
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
listType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ HashMap Text Value -> Value
Object
(HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$ [(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql
Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_insert_input"
)
]
, Text -> Maybe Text -> Value -> Value
createField
Text
"on_conflict"
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Specifies how to handle broken UNIQUE constraints")
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
listType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ HashMap Text Value -> Value
Object
(HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$ [(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql
Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_upsert_on_conflict"
)
]
]
)
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_mutation_response"
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"update_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
doubleXEncodeGql Text
tableName)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text
"Update rows in table \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tableName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"filter")
, (Text
"description", Value
"Filter to select rows to be updated")
, (Text
"type", Bool -> Text -> Value
filterType Bool
True Text
tableName)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"set")
, (Text
"description", Value
"Fields to be updated")
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_set_input"
)
]
)
]
]
)
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_mutation_response"
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"delete_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
doubleXEncodeGql Text
tableName)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"Delete rows in table \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tableName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"filter")
, (Text
"description", Value
"Filter to select rows to be deleted")
, (Text
"type", Bool -> Text -> Value
filterType Bool
True Text
tableName)
]
]
)
,
( Text
"type"
, Value -> Value
nonNullType (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql Text
tableName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_mutation_response"
)
]
)
]
]
makeComparisonType :: Text -> Text -> Value -> Value
makeComparisonType :: Text -> Text -> Value -> Value
makeComparisonType Text
typeName Text
description Value
type_ =
let field :: Text -> Value
field Text
fieldName = Text -> Maybe Text -> Value -> Value
createField Text
fieldName Maybe Text
forall a. Maybe a
Nothing Value
type_
in HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"INPUT_OBJECT")
, (Text
"name", Text -> Value
String Text
typeName)
,
( Text
"description"
, Text -> Value
String Text
description
)
,
( Text
"inputFields"
, [Value] -> Value
List
[ Text -> Value
field Text
"eq"
, Text -> Value
field Text
"neq"
, Text -> Value
field Text
"gt"
, Text -> Value
field Text
"gte"
, Text -> Value
field Text
"lt"
, Text -> Value
field Text
"lte"
, Text -> Value
field Text
"like"
, Text -> Value
field Text
"ilike"
, Text -> Maybe Text -> Value -> Value
createField
Text
"in"
Maybe Text
forall a. Maybe a
Nothing
(Value -> Value
listType Value
type_)
, Text -> Maybe Text -> Value -> Value
createField
Text
"nin"
Maybe Text
forall a. Maybe a
Nothing
(Value -> Value
listType Value
type_)
]
)
]
comparisonTypes :: AccessMode -> [Value]
comparisonTypes :: AccessMode -> [Value]
comparisonTypes AccessMode
accessMode =
case AccessMode
accessMode of
AccessMode
ReadOnly -> []
AccessMode
_ ->
[ Text -> Text -> Value -> Value
makeComparisonType Text
"IntComparison" Text
"Compare to an Int" Value
intType
, Text -> Text -> Value -> Value
makeComparisonType Text
"FloatComparison" Text
"Compare to a Float" Value
floatType
, Text -> Text -> Value -> Value
makeComparisonType Text
"StringComparison" Text
"Compare to a String" Value
stringType
, Text -> Text -> Value -> Value
makeComparisonType Text
"BooleanComparison" Text
"Compare to a Boolean" Value
booleanType
]
orderingTermType :: Value
orderingTermType :: Value
orderingTermType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"ENUM")
, (Text
"name", Text -> Value
String Text
"OrderingTerm")
,
( Text
"description"
, Text -> Value
String Text
"Ordering options when ordering by a column"
)
,
( Text
"enumValues"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"ASC")
, (Text
"description", Value
"In ascending order")
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"asc")
, (Text
"description", Value
"In ascending order")
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
True)
,
( Text
"deprecationReason"
, Text -> Value
String Text
"GraphQL spec recommends all caps for enums"
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"DESC")
, (Text
"description", Value
"In descending order")
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"desc")
, (Text
"description", Value
"In descending order")
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
True)
,
( Text
"deprecationReason"
, Text -> Value
String Text
"GraphQL spec recommends all caps for enums"
)
]
]
)
]
getFullDatatype :: ColumnEntry -> Text
getFullDatatype :: ColumnEntry -> Text
getFullDatatype ColumnEntry
entry = case ColumnEntry
entry.datatype_gql of
Maybe GqlTypeName
Nothing -> Text
"String"
Just GqlTypeName
type_ -> GqlTypeName
type_.full
getSchemaFieldOutput
:: Text
-> Connection
-> AccessMode
-> [TableEntryRaw]
-> IO (Out.Type IO)
getSchemaFieldOutput :: Text -> Connection -> AccessMode -> [TableEntryRaw] -> IO (Type IO)
getSchemaFieldOutput Text
dbId Connection
conn AccessMode
accessMode [TableEntryRaw]
tables = do
[[Value]]
typesForTables <- [TableEntryRaw] -> (TableEntryRaw -> IO [Value]) -> IO [[Value]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [TableEntryRaw]
tables ((TableEntryRaw -> IO [Value]) -> IO [[Value]])
-> (TableEntryRaw -> IO [Value]) -> IO [[Value]]
forall a b. (a -> b) -> a -> b
$ \TableEntryRaw
table -> do
[ColumnEntry]
columns <- Text -> Connection -> Text -> IO [ColumnEntry]
getColumns Text
dbId Connection
conn TableEntryRaw
table.name
[Value]
fields <- [ColumnEntry] -> (ColumnEntry -> IO Value) -> IO [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ColumnEntry]
columns ((ColumnEntry -> IO Value) -> IO [Value])
-> (ColumnEntry -> IO Value) -> IO [Value]
forall a b. (a -> b) -> a -> b
$ \ColumnEntry
columnEntry -> do
let colName :: Text
colName = ColumnEntry
columnEntry.column_name_gql
Value -> IO Value
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> IO Value) -> Value -> IO Value
forall a b. (a -> b) -> a -> b
$
Text -> Text -> [Value] -> [Text] -> Text -> Value
createType
Text
colName
Text
""
[]
( if ColumnEntry
columnEntry.notnull Bool -> Bool -> Bool
&& Bool -> Bool
not ColumnEntry
columnEntry.isOmittable
then [Text
"NON_NULL", Text
"SCALAR"]
else [Text
"SCALAR"]
)
(ColumnEntry -> Text
getFullDatatype ColumnEntry
columnEntry)
[Value]
fieldsNullable <- [ColumnEntry] -> (ColumnEntry -> IO Value) -> IO [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ColumnEntry]
columns ((ColumnEntry -> IO Value) -> IO [Value])
-> (ColumnEntry -> IO Value) -> IO [Value]
forall a b. (a -> b) -> a -> b
$ \ColumnEntry
columnEntry -> do
let colName :: Text
colName = ColumnEntry
columnEntry.column_name_gql
Value -> IO Value
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> IO Value) -> Value -> IO Value
forall a b. (a -> b) -> a -> b
$
Text -> Text -> [Value] -> [Text] -> Text -> Value
createType
Text
colName
Text
""
[]
[Text
"SCALAR"]
(ColumnEntry -> Text
getFullDatatype ColumnEntry
columnEntry)
[Value]
fieldsWithComparisonExp <- [ColumnEntry] -> (ColumnEntry -> IO Value) -> IO [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ColumnEntry]
columns ((ColumnEntry -> IO Value) -> IO [Value])
-> (ColumnEntry -> IO Value) -> IO [Value]
forall a b. (a -> b) -> a -> b
$ \ColumnEntry
columnEntry -> do
let colName :: Text
colName = ColumnEntry
columnEntry.column_name_gql
Value -> IO Value
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> IO Value) -> Value -> IO Value
forall a b. (a -> b) -> a -> b
$
Text -> Text -> [Value] -> [Text] -> Text -> Value
createType
Text
colName
Text
""
[]
[Text
"INPUT_OBJECT"]
(ColumnEntry -> Text
getFullDatatype ColumnEntry
columnEntry Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"Comparison")
[Value]
fieldsWithOrderingTerm <- [ColumnEntry] -> (ColumnEntry -> IO Value) -> IO [Value]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [ColumnEntry]
columns ((ColumnEntry -> IO Value) -> IO [Value])
-> (ColumnEntry -> IO Value) -> IO [Value]
forall a b. (a -> b) -> a -> b
$ \ColumnEntry
columnEntry -> do
let colName :: Text
colName = ColumnEntry
columnEntry.column_name_gql
Value -> IO Value
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> IO Value) -> Value -> IO Value
forall a b. (a -> b) -> a -> b
$
Text -> Text -> [Value] -> [Text] -> Text -> Value
createType
Text
colName
Text
""
[]
[Text
"INPUT_OBJECT"]
Text
"OrderingTerm"
let
customRowTypes :: [Value]
customRowTypes =
[ColumnEntry]
columns
[ColumnEntry] -> (ColumnEntry -> [Value]) -> [Value]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ColumnEntry
columnEntry ->
case (ColumnEntry
columnEntry.select_options, ColumnEntry
columnEntry.datatype_gql) of
(Just [Text]
_, Just GqlTypeName
name) ->
let
colName :: Text
colName = ColumnEntry
columnEntry.column_name_gql
typeName :: Text
typeName = GqlTypeName
name.full
description :: Text
description = Text
"Data type for column " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
colName
rowType :: Value
rowType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Text -> Value
String Text
typeName)
, (Text
"description", Text -> Value
String Text
description)
]
comparisonType :: Value
comparisonType =
Text -> Text -> Value -> Value
makeComparisonType
(Text
typeName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"Comparison")
(Text
"Compare with values for column" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
colName)
( HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"SCALAR")
, (Text
"name", Text -> Value
String Text
typeName)
, (Text
"description", Text -> Value
String Text
description)
]
)
in
[Value
rowType, Value
comparisonType]
(Maybe [Text], Maybe GqlTypeName)
_ -> []
fieldEnumVariants :: [Value]
fieldEnumVariants =
[ColumnEntry]
columns
[ColumnEntry] -> (ColumnEntry -> Value) -> [Value]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \ColumnEntry
columnEntry ->
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Value -> HashMap Text Value
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton Text
"name" (Value -> HashMap Text Value) -> Value -> HashMap Text Value
forall a b. (a -> b) -> a -> b
$
Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
ColumnEntry -> Text
column_name_gql ColumnEntry
columnEntry
fieldEnumDescription :: Value
fieldEnumDescription =
Value
"This enum contains a variant for each column in the table" :: Value
fieldEnumType :: Value
fieldEnumType =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"ENUM")
, (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_column")
,
( Text
"description"
, Value
fieldEnumDescription
)
, (Text
"enumValues", [Value] -> Value
List [Value]
fieldEnumVariants)
]
fieldEnumTypeReference :: Value
fieldEnumTypeReference =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"INPUT_OBJECT")
, (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_column")
,
( Text
"description"
, Value
fieldEnumDescription
)
]
requiresWrite :: Value -> Value
requiresWrite Value
obj = case AccessMode
accessMode of
AccessMode
ReadOnly -> Value
Null
AccessMode
WriteOnly -> Value
obj
AccessMode
ReadAndWrite -> Value
obj
requiresRead :: Value -> Value
requiresRead Value
obj = case AccessMode
accessMode of
AccessMode
ReadOnly -> Value
Null
AccessMode
WriteOnly -> Value
obj
AccessMode
ReadAndWrite -> Value
obj
[Value] -> IO [Value]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Value] -> IO [Value]) -> [Value] -> IO [Value]
forall a b. (a -> b) -> a -> b
$
[Value]
customRowTypes
[Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<> [ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_row")
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text
"Available columns for table \""
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableEntryRaw
table.name
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
)
, (Text
"fields", [Value] -> Value
List [Value]
fields)
]
, Value -> Value
requiresWrite (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_mutation_response"
)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"Mutation response for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableEntryRaw
table.name
)
,
( Text
"fields"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"affected_rows")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Int")
]
)
]
)
]
, Value -> Value
requiresRead (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"returning")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_row"
)
]
)
]
)
]
)
]
)
]
]
)
]
, Value -> Value
requiresWrite (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_insert_input"
)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"Input object for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableEntryRaw
table.name
)
, (Text
"inputFields", [Value] -> Value
List [Value]
fields)
]
, Value
fieldEnumType
, Value -> Value
requiresWrite (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_upsert_on_conflict"
)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"Specifies how broken UNIQUE constraints for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" should be handled"
)
,
( Text
"inputFields"
, [Value] -> Value
List
[ Text -> Maybe Text -> Value -> Value
createField
Text
"constraint"
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"columns to handle conflicts of")
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
listType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType Value
fieldEnumTypeReference
, Text -> Maybe Text -> Value -> Value
createField
Text
"update_columns"
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"columns to override on conflict")
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
listType
(Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$ Value -> Value
nonNullType Value
fieldEnumTypeReference
, Text -> Maybe Text -> Value -> Value
createField
Text
"where"
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"filter specifying which conflicting columns to update")
(Bool -> Text -> Value
filterType Bool
False TableEntryRaw
table.name)
]
)
]
, Value -> Value
requiresWrite (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_set_input"
)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"Fields to set for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableEntryRaw
table.name
)
, (Text
"inputFields", [Value] -> Value
List [Value]
fieldsNullable)
]
, Value -> Value
requiresWrite (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_filter"
)
,
( Text
"description"
, Text -> Value
String Text
"Filter object to select rows"
)
, (Text
"inputFields", [Value] -> Value
List [Value]
fieldsWithComparisonExp)
]
, Value -> Value
requiresWrite (Value -> Value) -> Value -> Value
forall a b. (a -> b) -> a -> b
$
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"INPUT_OBJECT")
,
( Text
"name"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Text
doubleXEncodeGql TableEntryRaw
table.name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_order_by"
)
,
( Text
"description"
, Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
Text
"Ordering options when selecting data from \""
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableEntryRaw
table.name
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\"."
)
, (Text
"inputFields", [Value] -> Value
List [Value]
fieldsWithOrderingTerm)
]
]
let
queryTypeObj :: Value
queryTypeObj =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"Query")
,
( Text
"fields"
, [Value] -> Value
List ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
[TableEntryRaw]
tables
[TableEntryRaw] -> (TableEntryRaw -> Text) -> [Text]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> TableEntryRaw -> Text
AirGQL.Lib.name
[Text] -> (Text -> Value) -> [Value]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Text -> Value
getFieldsForQuery
)
]
mutationTypeObj :: Value
mutationTypeObj =
HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"Mutation")
,
( Text
"fields"
, [Value] -> Value
List ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
[TableEntryRaw]
tables
[TableEntryRaw] -> (TableEntryRaw -> Text) -> [Text]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> TableEntryRaw -> Text
AirGQL.Lib.name
[Text] -> (Text -> [Value]) -> [[Value]]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Text -> [Value]
getFieldsForMutation
[[Value]] -> ([[Value]] -> [Value]) -> [Value]
forall a b. a -> (a -> b) -> b
& [[Value]] -> [Value]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
)
]
Type IO -> IO (Type IO)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Type IO -> IO (Type IO)) -> Type IO -> IO (Type IO)
forall a b. (a -> b) -> a -> b
$
ObjectType IO -> Type IO
forall (m :: * -> *). ObjectType m -> Type m
Out.NonNullObjectType (ObjectType IO -> Type IO) -> ObjectType IO -> Type IO
forall a b. (a -> b) -> a -> b
$
OutObjectType IO -> ObjectType IO
forall (m :: * -> *). OutObjectType m -> ObjectType m
outObjectTypeToObjectType (OutObjectType IO -> ObjectType IO)
-> OutObjectType IO -> ObjectType IO
forall a b. (a -> b) -> a -> b
$
OutObjectType
{ $sel:name:OutObjectType :: Text
name = Text
"__Schema"
, $sel:descriptionMb:OutObjectType :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"__Schema description"
, $sel:interfaceTypes:OutObjectType :: [InterfaceType IO]
interfaceTypes = []
, $sel:fields:OutObjectType :: HashMap Text (Resolver IO)
fields =
[(Text, Resolver IO)] -> HashMap Text (Resolver IO)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[
( Text
"__typename"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
nonNullString (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"__Schema"
)
,
( Text
"queryType"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
queryTypeType (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
queryTypeObj
)
,
( Text
"mutationType"
, case AccessMode
accessMode of
AccessMode
ReadOnly -> Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
mutationTypeType (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
AccessMode
WriteOnly ->
Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
mutationTypeType (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
mutationTypeObj
AccessMode
ReadAndWrite ->
Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
mutationTypeType (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
mutationTypeObj
)
,
( Text
"subscriptionType"
,
Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
subscriptionTypeType (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null
)
,
( Text
"types"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
typesField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
[Value] -> Value
List ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
[[Value]] -> [Value]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Value]]
typesForTables
[Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<> AccessMode -> [Value]
comparisonTypes AccessMode
accessMode
[Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<> [Value
orderingTermType]
[Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<> [ Value
queryTypeObj
, case AccessMode
accessMode of
AccessMode
ReadOnly -> Value
Null
AccessMode
WriteOnly -> Value
mutationTypeObj
AccessMode
ReadAndWrite -> Value
mutationTypeObj
, Value
booleanType
, Value
intType
, Value
floatType
, Value
stringType
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"ID")
,
( Text
"description"
, Value
"The `ID` scalar type represents a unique identifier, \
\often used to refetch an object or as key for a cache. \
\The ID type appears in a JSON response as a String; \
\however, it is not intended to be human-readable. \
\When expected as an input type, any string \
\(such as `\"4\"`) or integer (such as `4`) input value \
\will be accepted as an ID."
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Upload")
,
( Text
"description"
, Value
"The `Upload` scalar type represents a file upload."
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Schema")
,
( Text
"description"
, Value
"A GraphQL Schema defines the capabilities of a GraphQL server. \
\It exposes all available types and directives on the server, \
\as well as the entry points for \
\query, mutation, and subscription operations."
)
,
( Text
"fields"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"types")
,
( Text
"description"
, Value
"A list of all types supported by this server."
)
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Type")
]
)
]
)
]
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"queryType")
,
( Text
"description"
, Value
"The type that query operations will be rooted at."
)
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Type")
]
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"mutationType")
,
( Text
"description"
, Value
"If this server supports mutation, the type \
\that mutation operations will be rooted at."
)
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"OBJECT" Value
"__Type"
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"subscriptionType")
,
( Text
"description"
, Value
"If this server support subscription, the type \
\that subscription operations will be rooted at."
)
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"OBJECT" Value
"__Type"
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"directives")
,
( Text
"description"
, Value
"A list of all directives supported by this server."
)
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Directive")
]
)
]
)
]
)
]
)
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Type")
,
( Text
"description"
, Value
"The fundamental unit of any GraphQL Schema is the type. \
\There are many kinds of types in GraphQL as represented by the `__TypeKind` enum.\n\n\
\Depending on the kind of a type, certain fields describe information about that type. \
\Scalar types provide no information beyond a name and description, while Enum types provide their values. \
\Object and Interface types provide the fields they describe. \
\Abstract types, Union and Interface, provide the Object types possible at runtime. \
\List and NonNull types compose other types."
)
,
( Text
"fields"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"kind")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"ENUM")
, (Text
"name", Value
"__TypeKind")
]
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"name")
,
Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"String"
]
, Value
descriptionField
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"fields")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Field")
]
)
]
)
]
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"includeDeprecated")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"Boolean"
,
(Text
"defaultValue", Value
"false")
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"interfaces")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Type")
]
)
]
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"possibleTypes")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Type")
]
)
]
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"enumValues")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__EnumValue")
]
)
]
)
]
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"includeDeprecated")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"Boolean"
,
(Text
"defaultValue", Value
"false")
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"inputFields")
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"LIST")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__InputValue")
]
)
]
)
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"ofType")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"OBJECT" Value
"__Type"
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"ENUM")
, (Text
"name", Value
"__TypeKind")
,
( Text
"description"
, Value
"An enum describing what kind of type a given `__Type` is."
)
,
( Text
"enumValues"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"SCALAR")
,
( Text
"description"
, Value
"Indicates this type is a scalar."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"OBJECT")
,
( Text
"description"
, Value
"Indicates this type is an object. `fields` and `interfaces` are valid fields."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"INTERFACE")
,
( Text
"description"
, Value
"Indicates this type is an interface. `fields` and `possibleTypes` are valid fields."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"UNION")
,
( Text
"description"
, Value
"Indicates this type is a union. `possibleTypes` is a valid field."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"ENUM")
,
( Text
"description"
, Value
"Indicates this type is an enum. `enumValues` is a valid field."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"INPUT_OBJECT")
,
( Text
"description"
, Value
"Indicates this type is an input object. `inputFields` is a valid field."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"LIST")
,
( Text
"description"
, Value
"Indicates this type is a list. `ofType` is a valid field."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"NON_NULL")
,
( Text
"description"
, Value
"Indicates this type is a non-null. `ofType` is a valid field."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Field")
,
( Text
"description"
, Value
"Object and Interface types are described by a list of Fields, each of which has a name, potentially a list of arguments, and a return type."
)
,
( Text
"fields"
, [Value] -> Value
List
[ Value
nameField
, Value
descriptionField
, Value
argsFieldValue
, Value
typeFieldValue
, Value
isDeprecatedFieldValue
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"deprecationReason")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"String"
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__InputValue")
,
( Text
"description"
, Value
"Arguments provided to Fields or Directives and the input fields of an InputObject are represented as Input Values which describe their type and optionally a default value."
)
,
( Text
"fields"
, [Value] -> Value
List
[ Value
nameField
, Value
descriptionField
, Value
typeFieldValue
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"defaultValue")
,
( Text
"description"
, Value
"A GraphQL-formatted string representing \
\the default value for this input value."
)
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"String"
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__EnumValue")
,
( Text
"description"
, Value
"One possible value for a given Enum. Enum values are unique values, not a placeholder for a string or numeric value. However an Enum value is returned in a JSON response as a string."
)
,
( Text
"fields"
, [Value] -> Value
List
[ Value
nameField
, Value
descriptionField
, Value
isDeprecatedFieldValue
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"deprecationReason")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"String"
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"OBJECT")
, (Text
"name", Value
"__Directive")
,
( Text
"description"
, Value
"A Directive provides a way to describe alternate runtime execution and type validation behavior in a GraphQL document.\n\nIn some cases, you need to provide options to alter GraphQL's execution behavior in ways field arguments will not suffice, such as conditionally including or skipping a field. Directives provide this by describing additional information to the executor."
)
,
( Text
"fields"
, [Value] -> Value
List
[ Value
nameField
, Value
descriptionField
, Value
locationsFieldValue
, Value
argsFieldValue
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Type")
, (Text
"kind", Value
"ENUM")
, (Text
"name", Value
"__DirectiveLocation")
,
( Text
"description"
, Value
"A Directive can be adjacent to many parts of the GraphQL language, a __DirectiveLocation describes one such possible adjacencies."
)
,
( Text
"enumValues"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"QUERY")
,
( Text
"description"
, Value
"Location adjacent to a query operation."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"MUTATION")
,
( Text
"description"
, Value
"Location adjacent to a mutation operation."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"SUBSCRIPTION")
,
( Text
"description"
, Value
"Location adjacent to a subscription operation."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"FIELD")
,
( Text
"description"
, Value
"Location adjacent to a field."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"FRAGMENT_DEFINITION")
,
( Text
"description"
, Value
"Location adjacent to a fragment definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"FRAGMENT_SPREAD")
,
( Text
"description"
, Value
"Location adjacent to a fragment spread."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"INLINE_FRAGMENT")
,
( Text
"description"
, Value
"Location adjacent to an inline fragment."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"VARIABLE_DEFINITION")
,
( Text
"description"
, Value
"Location adjacent to a variable definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"SCHEMA")
,
( Text
"description"
, Value
"Location adjacent to a schema definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"SCALAR")
,
( Text
"description"
, Value
"Location adjacent to a scalar definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"OBJECT")
,
( Text
"description"
, Value
"Location adjacent to an object type definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"FIELD_DEFINITION")
,
( Text
"description"
, Value
"Location adjacent to a field definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"ARGUMENT_DEFINITION")
,
( Text
"description"
, Value
"Location adjacent to an argument definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"INTERFACE")
,
( Text
"description"
, Value
"Location adjacent to an interface definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"UNION")
,
( Text
"description"
, Value
"Location adjacent to a union definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"ENUM")
,
( Text
"description"
, Value
"Location adjacent to an enum definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"ENUM_VALUE")
,
( Text
"description"
, Value
"Location adjacent to an enum value definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"INPUT_OBJECT")
,
( Text
"description"
, Value
"Location adjacent to an input object \
\type definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"INPUT_FIELD_DEFINITION")
,
( Text
"description"
, Value
"Location adjacent to an input object \
\field definition."
)
, (Text
"isDeprecated", Bool -> Value
Boolean Bool
False)
, (Text
"deprecationReason", Value
Null)
]
]
)
]
]
[Value] -> ([Value] -> [Value]) -> [Value]
forall a b. a -> (a -> b) -> b
& (Value -> Bool) -> [Value] -> [Value]
forall a. (a -> Bool) -> [a] -> [a]
filter (Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
/= Value
Null)
)
,
( Text
"directives"
, Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
directivesType (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$
Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> Resolve IO) -> Value -> Resolve IO
forall a b. (a -> b) -> a -> b
$
[Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Directive")
, (Text
"name", Value
"skip")
,
( Text
"description"
, Value
"Directs the executor to skip this field or fragment \
\when the `if` argument is true."
)
,
( Text
"locations"
, [Value] -> Value
List [Value
"INLINE_FRAGMENT", Value
"FRAGMENT_SPREAD", Value
"FIELD"]
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"if")
, (Text
"description", Value
"Skipped when true.")
, (Text
"defaultValue", Value
Null)
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Boolean")
]
)
]
)
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Directive")
, (Text
"name", Value
"include")
,
( Text
"description"
, Value
"Directs the executor to include this field or fragment \
\only when the `if` argument is true."
)
,
( Text
"locations"
, [Value] -> Value
List [Value
"INLINE_FRAGMENT", Value
"FRAGMENT_SPREAD", Value
"FIELD"]
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"if")
, (Text
"description", Value
"Included when true.")
, (Text
"defaultValue", Value
Null)
,
( Text
"type"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"NON_NULL")
,
( Text
"ofType"
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"kind", Value
"SCALAR")
, (Text
"name", Value
"Boolean")
]
)
]
)
]
]
)
]
, HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"__typename", Value
"__Directive")
, (Text
"name", Value
"deprecated")
,
( Text
"description"
, Value
"Marks an element of a GraphQL schema \
\as no longer supported."
)
,
( Text
"locations"
, [Value] -> Value
List [Value
"ENUM_VALUE", Value
"FIELD_DEFINITION"]
)
,
( Text
"args"
, [Value] -> Value
List
[ HashMap Text Value -> Value
Object (HashMap Text Value -> Value) -> HashMap Text Value -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)] -> HashMap Text Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Text
"name", Value
"reason")
,
( Text
"description"
, Value
"Explains why this element was deprecated, \
\usually also including a suggestion \
\for how to access supported similar data. \
\Formatted using the Markdown syntax \
\(as specified by \
\[CommonMark](https://commonmark.org/)."
)
, (Text
"defaultValue", Value
"\"No longer supported\"")
, Value -> Value -> (Text, Value)
forall a. IsString a => Value -> Value -> (a, Value)
getTypeTuple Value
"SCALAR" Value
"String"
]
]
)
]
]
)
]
}
getSchemaField
:: Text
-> Connection
-> AccessMode
-> [TableEntryRaw]
-> IO (Field IO)
getSchemaField :: Text
-> Connection -> AccessMode -> [TableEntryRaw] -> IO (Field IO)
getSchemaField Text
dbId Connection
conn AccessMode
accessMode [TableEntryRaw]
tables = do
Type IO
schemaFieldOutput <- Text -> Connection -> AccessMode -> [TableEntryRaw] -> IO (Type IO)
getSchemaFieldOutput Text
dbId Connection
conn AccessMode
accessMode [TableEntryRaw]
tables
Field IO -> IO (Field IO)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Field IO -> IO (Field IO)) -> Field IO -> IO (Field IO)
forall a b. (a -> b) -> a -> b
$
OutField IO -> Field IO
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField IO -> Field IO) -> OutField IO -> Field IO
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"The schema"
, $sel:fieldType:OutField :: Type IO
fieldType = Type IO
schemaFieldOutput
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
getSchemaResolver
:: Text
-> Connection
-> AccessMode
-> [TableEntryRaw]
-> IO (HashMap Text (Resolver IO))
getSchemaResolver :: Text
-> Connection
-> AccessMode
-> [TableEntryRaw]
-> IO (HashMap Text (Resolver IO))
getSchemaResolver Text
dbId Connection
conn AccessMode
accessMode [TableEntryRaw]
tables = do
Field IO
schemaField <- Text
-> Connection -> AccessMode -> [TableEntryRaw] -> IO (Field IO)
getSchemaField Text
dbId Connection
conn AccessMode
accessMode [TableEntryRaw]
tables
HashMap Text (Resolver IO) -> IO (HashMap Text (Resolver IO))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HashMap Text (Resolver IO) -> IO (HashMap Text (Resolver IO)))
-> HashMap Text (Resolver IO) -> IO (HashMap Text (Resolver IO))
forall a b. (a -> b) -> a -> b
$
Text -> Resolver IO -> HashMap Text (Resolver IO)
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton
Text
"__schema"
(Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
schemaField (Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
Null))
typeNameOutField :: Field m
typeNameOutField :: forall (m :: * -> *). Field m
typeNameOutField =
OutField m -> Field m
forall (m :: * -> *). OutField m -> Field m
outFieldToField (OutField m -> Field m) -> OutField m -> Field m
forall a b. (a -> b) -> a -> b
$
OutField
{ $sel:descriptionMb:OutField :: Maybe Text
descriptionMb = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"The type name"
, $sel:fieldType:OutField :: Type m
fieldType = ScalarType -> Type m
forall (m :: * -> *). ScalarType -> Type m
Out.NonNullScalarType ScalarType
string
, $sel:arguments:OutField :: Arguments
arguments = Arguments
forall k v. HashMap k v
HashMap.empty
}
typeNameResolver :: HashMap Text (Resolver IO)
typeNameResolver :: HashMap Text (Resolver IO)
typeNameResolver =
Text -> Resolver IO -> HashMap Text (Resolver IO)
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton
Text
"__typename"
(Field IO -> Resolve IO -> Resolver IO
forall (m :: * -> *). Field m -> Resolve m -> Resolver m
ValueResolver Field IO
forall (m :: * -> *). Field m
typeNameOutField (Resolve IO -> Resolver IO) -> Resolve IO -> Resolver IO
forall a b. (a -> b) -> a -> b
$ Value -> Resolve IO
forall a. a -> ReaderT Context IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
"Query")