{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.CustomTypes
(
GraphQLType (..),
isListType,
isNullableType,
isInBuiltScalar,
CustomTypes (..),
emptyCustomTypes,
InputObjectTypeDefinition (..),
InputObjectTypeName (..),
InputObjectFieldDefinition (..),
InputObjectFieldName (..),
ObjectTypeDefinition (..),
ObjectTypeName (..),
ObjectFieldDefinition (..),
ObjectFieldName (..),
ScalarTypeDefinition (..),
defaultGraphQLScalars,
EnumTypeDefinition (..),
EnumTypeName (..),
EnumValueDefinition (..),
TypeRelationshipDefinition (..),
RelationshipName (..),
trdName,
trdType,
trdSource,
trdRemoteTable,
trdFieldMapping,
AnnotatedCustomTypes (..),
AnnotatedInputType (..),
AnnotatedOutputType (..),
AnnotatedObjectType (..),
AnnotatedObjectFieldType (..),
AnnotatedTypeRelationship (..),
AnnotatedScalarType (..),
ScalarWrapper (..),
)
where
import Control.Lens.TH (makeLenses)
import Data.Aeson ((.!=), (.:), (.:?), (.=))
import Data.Aeson qualified as J
import Data.Aeson.TH qualified as J
import Data.HashMap.Strict qualified as Map
import Data.HashSet qualified as Set
import Data.Text qualified as T
import Data.Text.Extended (ToTxt (..))
import Hasura.Backends.Postgres.Instances.Types ()
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.GraphQL.Parser.Name qualified as GName
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.AnyBackend
import Hasura.SQL.Backend
import Language.GraphQL.Draft.Parser qualified as GParse
import Language.GraphQL.Draft.Printer qualified as GPrint
import Language.GraphQL.Draft.Syntax qualified as G
import Text.Builder qualified as T
newtype GraphQLType = GraphQLType {GraphQLType -> GType
unGraphQLType :: G.GType}
deriving (Int -> GraphQLType -> ShowS
[GraphQLType] -> ShowS
GraphQLType -> String
(Int -> GraphQLType -> ShowS)
-> (GraphQLType -> String)
-> ([GraphQLType] -> ShowS)
-> Show GraphQLType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GraphQLType] -> ShowS
$cshowList :: [GraphQLType] -> ShowS
show :: GraphQLType -> String
$cshow :: GraphQLType -> String
showsPrec :: Int -> GraphQLType -> ShowS
$cshowsPrec :: Int -> GraphQLType -> ShowS
Show, GraphQLType -> GraphQLType -> Bool
(GraphQLType -> GraphQLType -> Bool)
-> (GraphQLType -> GraphQLType -> Bool) -> Eq GraphQLType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GraphQLType -> GraphQLType -> Bool
$c/= :: GraphQLType -> GraphQLType -> Bool
== :: GraphQLType -> GraphQLType -> Bool
$c== :: GraphQLType -> GraphQLType -> Bool
Eq, (forall x. GraphQLType -> Rep GraphQLType x)
-> (forall x. Rep GraphQLType x -> GraphQLType)
-> Generic GraphQLType
forall x. Rep GraphQLType x -> GraphQLType
forall x. GraphQLType -> Rep GraphQLType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GraphQLType x -> GraphQLType
$cfrom :: forall x. GraphQLType -> Rep GraphQLType x
Generic, GraphQLType -> ()
(GraphQLType -> ()) -> NFData GraphQLType
forall a. (a -> ()) -> NFData a
rnf :: GraphQLType -> ()
$crnf :: GraphQLType -> ()
NFData, Eq GraphQLType
Eq GraphQLType
-> (Accesses -> GraphQLType -> GraphQLType -> Bool)
-> Cacheable GraphQLType
Accesses -> GraphQLType -> GraphQLType -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> GraphQLType -> GraphQLType -> Bool
$cunchanged :: Accesses -> GraphQLType -> GraphQLType -> Bool
$cp1Cacheable :: Eq GraphQLType
Cacheable)
instance J.ToJSON GraphQLType where
toJSON :: GraphQLType -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Text -> Value) -> (GraphQLType -> Text) -> GraphQLType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
T.run (Builder -> Text)
-> (GraphQLType -> Builder) -> GraphQLType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GType -> Builder
forall a. Printer a => GType -> a
GPrint.graphQLType (GType -> Builder)
-> (GraphQLType -> GType) -> GraphQLType -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GraphQLType -> GType
unGraphQLType
instance J.FromJSON GraphQLType where
parseJSON :: Value -> Parser GraphQLType
parseJSON =
String
-> (Text -> Parser GraphQLType) -> Value -> Parser GraphQLType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
J.withText String
"GraphQLType" ((Text -> Parser GraphQLType) -> Value -> Parser GraphQLType)
-> (Text -> Parser GraphQLType) -> Value -> Parser GraphQLType
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text -> Either Text GType
GParse.parseGraphQLType Text
t of
Left Text
_ -> String -> Parser GraphQLType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser GraphQLType) -> String -> Parser GraphQLType
forall a b. (a -> b) -> a -> b
$ String
"not a valid GraphQL type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t
Right GType
a -> GraphQLType -> Parser GraphQLType
forall (m :: * -> *) a. Monad m => a -> m a
return (GraphQLType -> Parser GraphQLType)
-> GraphQLType -> Parser GraphQLType
forall a b. (a -> b) -> a -> b
$ GType -> GraphQLType
GraphQLType GType
a
isListType :: GraphQLType -> Bool
isListType :: GraphQLType -> Bool
isListType = (GType -> Bool) -> GraphQLType -> Bool
coerce GType -> Bool
G.isListType
isNullableType :: GraphQLType -> Bool
isNullableType :: GraphQLType -> Bool
isNullableType = (GType -> Bool) -> GraphQLType -> Bool
coerce GType -> Bool
G.isNullable
isInBuiltScalar :: Text -> Bool
isInBuiltScalar :: Text -> Bool
isInBuiltScalar Text
s
| Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Text
G.unName Name
GName._Int = Bool
True
| Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Text
G.unName Name
GName._Float = Bool
True
| Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Text
G.unName Name
GName._String = Bool
True
| Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Text
G.unName Name
GName._Boolean = Bool
True
| Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Text
G.unName Name
GName._ID = Bool
True
| Bool
otherwise = Bool
False
data CustomTypes = CustomTypes
{ CustomTypes -> [InputObjectTypeDefinition]
_ctInputObjects :: [InputObjectTypeDefinition],
CustomTypes -> [ObjectTypeDefinition]
_ctObjects :: [ObjectTypeDefinition],
CustomTypes -> [ScalarTypeDefinition]
_ctScalars :: [ScalarTypeDefinition],
CustomTypes -> [EnumTypeDefinition]
_ctEnums :: [EnumTypeDefinition]
}
deriving (Int -> CustomTypes -> ShowS
[CustomTypes] -> ShowS
CustomTypes -> String
(Int -> CustomTypes -> ShowS)
-> (CustomTypes -> String)
-> ([CustomTypes] -> ShowS)
-> Show CustomTypes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomTypes] -> ShowS
$cshowList :: [CustomTypes] -> ShowS
show :: CustomTypes -> String
$cshow :: CustomTypes -> String
showsPrec :: Int -> CustomTypes -> ShowS
$cshowsPrec :: Int -> CustomTypes -> ShowS
Show, CustomTypes -> CustomTypes -> Bool
(CustomTypes -> CustomTypes -> Bool)
-> (CustomTypes -> CustomTypes -> Bool) -> Eq CustomTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomTypes -> CustomTypes -> Bool
$c/= :: CustomTypes -> CustomTypes -> Bool
== :: CustomTypes -> CustomTypes -> Bool
$c== :: CustomTypes -> CustomTypes -> Bool
Eq, (forall x. CustomTypes -> Rep CustomTypes x)
-> (forall x. Rep CustomTypes x -> CustomTypes)
-> Generic CustomTypes
forall x. Rep CustomTypes x -> CustomTypes
forall x. CustomTypes -> Rep CustomTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomTypes x -> CustomTypes
$cfrom :: forall x. CustomTypes -> Rep CustomTypes x
Generic)
instance NFData CustomTypes
instance Cacheable CustomTypes
emptyCustomTypes :: CustomTypes
emptyCustomTypes :: CustomTypes
emptyCustomTypes = [InputObjectTypeDefinition]
-> [ObjectTypeDefinition]
-> [ScalarTypeDefinition]
-> [EnumTypeDefinition]
-> CustomTypes
CustomTypes [] [] [] []
data InputObjectTypeDefinition = InputObjectTypeDefinition
{ InputObjectTypeDefinition -> InputObjectTypeName
_iotdName :: InputObjectTypeName,
InputObjectTypeDefinition -> Maybe Description
_iotdDescription :: Maybe G.Description,
InputObjectTypeDefinition -> NonEmpty InputObjectFieldDefinition
_iotdFields :: NonEmpty InputObjectFieldDefinition
}
deriving (Int -> InputObjectTypeDefinition -> ShowS
[InputObjectTypeDefinition] -> ShowS
InputObjectTypeDefinition -> String
(Int -> InputObjectTypeDefinition -> ShowS)
-> (InputObjectTypeDefinition -> String)
-> ([InputObjectTypeDefinition] -> ShowS)
-> Show InputObjectTypeDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputObjectTypeDefinition] -> ShowS
$cshowList :: [InputObjectTypeDefinition] -> ShowS
show :: InputObjectTypeDefinition -> String
$cshow :: InputObjectTypeDefinition -> String
showsPrec :: Int -> InputObjectTypeDefinition -> ShowS
$cshowsPrec :: Int -> InputObjectTypeDefinition -> ShowS
Show, InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
(InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> Eq InputObjectTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c/= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
== :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c== :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
Eq, (forall x.
InputObjectTypeDefinition -> Rep InputObjectTypeDefinition x)
-> (forall x.
Rep InputObjectTypeDefinition x -> InputObjectTypeDefinition)
-> Generic InputObjectTypeDefinition
forall x.
Rep InputObjectTypeDefinition x -> InputObjectTypeDefinition
forall x.
InputObjectTypeDefinition -> Rep InputObjectTypeDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InputObjectTypeDefinition x -> InputObjectTypeDefinition
$cfrom :: forall x.
InputObjectTypeDefinition -> Rep InputObjectTypeDefinition x
Generic)
instance NFData InputObjectTypeDefinition
instance Cacheable InputObjectTypeDefinition
newtype InputObjectTypeName = InputObjectTypeName {InputObjectTypeName -> Name
unInputObjectTypeName :: G.Name}
deriving (Int -> InputObjectTypeName -> ShowS
[InputObjectTypeName] -> ShowS
InputObjectTypeName -> String
(Int -> InputObjectTypeName -> ShowS)
-> (InputObjectTypeName -> String)
-> ([InputObjectTypeName] -> ShowS)
-> Show InputObjectTypeName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputObjectTypeName] -> ShowS
$cshowList :: [InputObjectTypeName] -> ShowS
show :: InputObjectTypeName -> String
$cshow :: InputObjectTypeName -> String
showsPrec :: Int -> InputObjectTypeName -> ShowS
$cshowsPrec :: Int -> InputObjectTypeName -> ShowS
Show, InputObjectTypeName -> InputObjectTypeName -> Bool
(InputObjectTypeName -> InputObjectTypeName -> Bool)
-> (InputObjectTypeName -> InputObjectTypeName -> Bool)
-> Eq InputObjectTypeName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeName -> InputObjectTypeName -> Bool
$c/= :: InputObjectTypeName -> InputObjectTypeName -> Bool
== :: InputObjectTypeName -> InputObjectTypeName -> Bool
$c== :: InputObjectTypeName -> InputObjectTypeName -> Bool
Eq, Eq InputObjectTypeName
Eq InputObjectTypeName
-> (InputObjectTypeName -> InputObjectTypeName -> Ordering)
-> (InputObjectTypeName -> InputObjectTypeName -> Bool)
-> (InputObjectTypeName -> InputObjectTypeName -> Bool)
-> (InputObjectTypeName -> InputObjectTypeName -> Bool)
-> (InputObjectTypeName -> InputObjectTypeName -> Bool)
-> (InputObjectTypeName
-> InputObjectTypeName -> InputObjectTypeName)
-> (InputObjectTypeName
-> InputObjectTypeName -> InputObjectTypeName)
-> Ord InputObjectTypeName
InputObjectTypeName -> InputObjectTypeName -> Bool
InputObjectTypeName -> InputObjectTypeName -> Ordering
InputObjectTypeName -> InputObjectTypeName -> InputObjectTypeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InputObjectTypeName -> InputObjectTypeName -> InputObjectTypeName
$cmin :: InputObjectTypeName -> InputObjectTypeName -> InputObjectTypeName
max :: InputObjectTypeName -> InputObjectTypeName -> InputObjectTypeName
$cmax :: InputObjectTypeName -> InputObjectTypeName -> InputObjectTypeName
>= :: InputObjectTypeName -> InputObjectTypeName -> Bool
$c>= :: InputObjectTypeName -> InputObjectTypeName -> Bool
> :: InputObjectTypeName -> InputObjectTypeName -> Bool
$c> :: InputObjectTypeName -> InputObjectTypeName -> Bool
<= :: InputObjectTypeName -> InputObjectTypeName -> Bool
$c<= :: InputObjectTypeName -> InputObjectTypeName -> Bool
< :: InputObjectTypeName -> InputObjectTypeName -> Bool
$c< :: InputObjectTypeName -> InputObjectTypeName -> Bool
compare :: InputObjectTypeName -> InputObjectTypeName -> Ordering
$ccompare :: InputObjectTypeName -> InputObjectTypeName -> Ordering
$cp1Ord :: Eq InputObjectTypeName
Ord, Int -> InputObjectTypeName -> Int
InputObjectTypeName -> Int
(Int -> InputObjectTypeName -> Int)
-> (InputObjectTypeName -> Int) -> Hashable InputObjectTypeName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InputObjectTypeName -> Int
$chash :: InputObjectTypeName -> Int
hashWithSalt :: Int -> InputObjectTypeName -> Int
$chashWithSalt :: Int -> InputObjectTypeName -> Int
Hashable, Value -> Parser [InputObjectTypeName]
Value -> Parser InputObjectTypeName
(Value -> Parser InputObjectTypeName)
-> (Value -> Parser [InputObjectTypeName])
-> FromJSON InputObjectTypeName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [InputObjectTypeName]
$cparseJSONList :: Value -> Parser [InputObjectTypeName]
parseJSON :: Value -> Parser InputObjectTypeName
$cparseJSON :: Value -> Parser InputObjectTypeName
J.FromJSON, [InputObjectTypeName] -> Value
[InputObjectTypeName] -> Encoding
InputObjectTypeName -> Value
InputObjectTypeName -> Encoding
(InputObjectTypeName -> Value)
-> (InputObjectTypeName -> Encoding)
-> ([InputObjectTypeName] -> Value)
-> ([InputObjectTypeName] -> Encoding)
-> ToJSON InputObjectTypeName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [InputObjectTypeName] -> Encoding
$ctoEncodingList :: [InputObjectTypeName] -> Encoding
toJSONList :: [InputObjectTypeName] -> Value
$ctoJSONList :: [InputObjectTypeName] -> Value
toEncoding :: InputObjectTypeName -> Encoding
$ctoEncoding :: InputObjectTypeName -> Encoding
toJSON :: InputObjectTypeName -> Value
$ctoJSON :: InputObjectTypeName -> Value
J.ToJSON, InputObjectTypeName -> Text
(InputObjectTypeName -> Text) -> ToTxt InputObjectTypeName
forall a. (a -> Text) -> ToTxt a
toTxt :: InputObjectTypeName -> Text
$ctoTxt :: InputObjectTypeName -> Text
ToTxt, (forall x. InputObjectTypeName -> Rep InputObjectTypeName x)
-> (forall x. Rep InputObjectTypeName x -> InputObjectTypeName)
-> Generic InputObjectTypeName
forall x. Rep InputObjectTypeName x -> InputObjectTypeName
forall x. InputObjectTypeName -> Rep InputObjectTypeName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputObjectTypeName x -> InputObjectTypeName
$cfrom :: forall x. InputObjectTypeName -> Rep InputObjectTypeName x
Generic, InputObjectTypeName -> ()
(InputObjectTypeName -> ()) -> NFData InputObjectTypeName
forall a. (a -> ()) -> NFData a
rnf :: InputObjectTypeName -> ()
$crnf :: InputObjectTypeName -> ()
NFData, Eq InputObjectTypeName
Eq InputObjectTypeName
-> (Accesses -> InputObjectTypeName -> InputObjectTypeName -> Bool)
-> Cacheable InputObjectTypeName
Accesses -> InputObjectTypeName -> InputObjectTypeName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> InputObjectTypeName -> InputObjectTypeName -> Bool
$cunchanged :: Accesses -> InputObjectTypeName -> InputObjectTypeName -> Bool
$cp1Cacheable :: Eq InputObjectTypeName
Cacheable)
data InputObjectFieldDefinition = InputObjectFieldDefinition
{ InputObjectFieldDefinition -> InputObjectFieldName
_iofdName :: InputObjectFieldName,
InputObjectFieldDefinition -> Maybe Description
_iofdDescription :: Maybe G.Description,
InputObjectFieldDefinition -> GraphQLType
_iofdType :: GraphQLType
}
deriving (Int -> InputObjectFieldDefinition -> ShowS
[InputObjectFieldDefinition] -> ShowS
InputObjectFieldDefinition -> String
(Int -> InputObjectFieldDefinition -> ShowS)
-> (InputObjectFieldDefinition -> String)
-> ([InputObjectFieldDefinition] -> ShowS)
-> Show InputObjectFieldDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputObjectFieldDefinition] -> ShowS
$cshowList :: [InputObjectFieldDefinition] -> ShowS
show :: InputObjectFieldDefinition -> String
$cshow :: InputObjectFieldDefinition -> String
showsPrec :: Int -> InputObjectFieldDefinition -> ShowS
$cshowsPrec :: Int -> InputObjectFieldDefinition -> ShowS
Show, InputObjectFieldDefinition -> InputObjectFieldDefinition -> Bool
(InputObjectFieldDefinition -> InputObjectFieldDefinition -> Bool)
-> (InputObjectFieldDefinition
-> InputObjectFieldDefinition -> Bool)
-> Eq InputObjectFieldDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectFieldDefinition -> InputObjectFieldDefinition -> Bool
$c/= :: InputObjectFieldDefinition -> InputObjectFieldDefinition -> Bool
== :: InputObjectFieldDefinition -> InputObjectFieldDefinition -> Bool
$c== :: InputObjectFieldDefinition -> InputObjectFieldDefinition -> Bool
Eq, (forall x.
InputObjectFieldDefinition -> Rep InputObjectFieldDefinition x)
-> (forall x.
Rep InputObjectFieldDefinition x -> InputObjectFieldDefinition)
-> Generic InputObjectFieldDefinition
forall x.
Rep InputObjectFieldDefinition x -> InputObjectFieldDefinition
forall x.
InputObjectFieldDefinition -> Rep InputObjectFieldDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InputObjectFieldDefinition x -> InputObjectFieldDefinition
$cfrom :: forall x.
InputObjectFieldDefinition -> Rep InputObjectFieldDefinition x
Generic)
instance NFData InputObjectFieldDefinition
instance Cacheable InputObjectFieldDefinition
newtype InputObjectFieldName = InputObjectFieldName {InputObjectFieldName -> Name
unInputObjectFieldName :: G.Name}
deriving (Int -> InputObjectFieldName -> ShowS
[InputObjectFieldName] -> ShowS
InputObjectFieldName -> String
(Int -> InputObjectFieldName -> ShowS)
-> (InputObjectFieldName -> String)
-> ([InputObjectFieldName] -> ShowS)
-> Show InputObjectFieldName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputObjectFieldName] -> ShowS
$cshowList :: [InputObjectFieldName] -> ShowS
show :: InputObjectFieldName -> String
$cshow :: InputObjectFieldName -> String
showsPrec :: Int -> InputObjectFieldName -> ShowS
$cshowsPrec :: Int -> InputObjectFieldName -> ShowS
Show, InputObjectFieldName -> InputObjectFieldName -> Bool
(InputObjectFieldName -> InputObjectFieldName -> Bool)
-> (InputObjectFieldName -> InputObjectFieldName -> Bool)
-> Eq InputObjectFieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectFieldName -> InputObjectFieldName -> Bool
$c/= :: InputObjectFieldName -> InputObjectFieldName -> Bool
== :: InputObjectFieldName -> InputObjectFieldName -> Bool
$c== :: InputObjectFieldName -> InputObjectFieldName -> Bool
Eq, Eq InputObjectFieldName
Eq InputObjectFieldName
-> (InputObjectFieldName -> InputObjectFieldName -> Ordering)
-> (InputObjectFieldName -> InputObjectFieldName -> Bool)
-> (InputObjectFieldName -> InputObjectFieldName -> Bool)
-> (InputObjectFieldName -> InputObjectFieldName -> Bool)
-> (InputObjectFieldName -> InputObjectFieldName -> Bool)
-> (InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName)
-> (InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName)
-> Ord InputObjectFieldName
InputObjectFieldName -> InputObjectFieldName -> Bool
InputObjectFieldName -> InputObjectFieldName -> Ordering
InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName
$cmin :: InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName
max :: InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName
$cmax :: InputObjectFieldName
-> InputObjectFieldName -> InputObjectFieldName
>= :: InputObjectFieldName -> InputObjectFieldName -> Bool
$c>= :: InputObjectFieldName -> InputObjectFieldName -> Bool
> :: InputObjectFieldName -> InputObjectFieldName -> Bool
$c> :: InputObjectFieldName -> InputObjectFieldName -> Bool
<= :: InputObjectFieldName -> InputObjectFieldName -> Bool
$c<= :: InputObjectFieldName -> InputObjectFieldName -> Bool
< :: InputObjectFieldName -> InputObjectFieldName -> Bool
$c< :: InputObjectFieldName -> InputObjectFieldName -> Bool
compare :: InputObjectFieldName -> InputObjectFieldName -> Ordering
$ccompare :: InputObjectFieldName -> InputObjectFieldName -> Ordering
$cp1Ord :: Eq InputObjectFieldName
Ord, Int -> InputObjectFieldName -> Int
InputObjectFieldName -> Int
(Int -> InputObjectFieldName -> Int)
-> (InputObjectFieldName -> Int) -> Hashable InputObjectFieldName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InputObjectFieldName -> Int
$chash :: InputObjectFieldName -> Int
hashWithSalt :: Int -> InputObjectFieldName -> Int
$chashWithSalt :: Int -> InputObjectFieldName -> Int
Hashable, Value -> Parser [InputObjectFieldName]
Value -> Parser InputObjectFieldName
(Value -> Parser InputObjectFieldName)
-> (Value -> Parser [InputObjectFieldName])
-> FromJSON InputObjectFieldName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [InputObjectFieldName]
$cparseJSONList :: Value -> Parser [InputObjectFieldName]
parseJSON :: Value -> Parser InputObjectFieldName
$cparseJSON :: Value -> Parser InputObjectFieldName
J.FromJSON, [InputObjectFieldName] -> Value
[InputObjectFieldName] -> Encoding
InputObjectFieldName -> Value
InputObjectFieldName -> Encoding
(InputObjectFieldName -> Value)
-> (InputObjectFieldName -> Encoding)
-> ([InputObjectFieldName] -> Value)
-> ([InputObjectFieldName] -> Encoding)
-> ToJSON InputObjectFieldName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [InputObjectFieldName] -> Encoding
$ctoEncodingList :: [InputObjectFieldName] -> Encoding
toJSONList :: [InputObjectFieldName] -> Value
$ctoJSONList :: [InputObjectFieldName] -> Value
toEncoding :: InputObjectFieldName -> Encoding
$ctoEncoding :: InputObjectFieldName -> Encoding
toJSON :: InputObjectFieldName -> Value
$ctoJSON :: InputObjectFieldName -> Value
J.ToJSON, InputObjectFieldName -> Text
(InputObjectFieldName -> Text) -> ToTxt InputObjectFieldName
forall a. (a -> Text) -> ToTxt a
toTxt :: InputObjectFieldName -> Text
$ctoTxt :: InputObjectFieldName -> Text
ToTxt, (forall x. InputObjectFieldName -> Rep InputObjectFieldName x)
-> (forall x. Rep InputObjectFieldName x -> InputObjectFieldName)
-> Generic InputObjectFieldName
forall x. Rep InputObjectFieldName x -> InputObjectFieldName
forall x. InputObjectFieldName -> Rep InputObjectFieldName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputObjectFieldName x -> InputObjectFieldName
$cfrom :: forall x. InputObjectFieldName -> Rep InputObjectFieldName x
Generic, InputObjectFieldName -> ()
(InputObjectFieldName -> ()) -> NFData InputObjectFieldName
forall a. (a -> ()) -> NFData a
rnf :: InputObjectFieldName -> ()
$crnf :: InputObjectFieldName -> ()
NFData, Eq InputObjectFieldName
Eq InputObjectFieldName
-> (Accesses
-> InputObjectFieldName -> InputObjectFieldName -> Bool)
-> Cacheable InputObjectFieldName
Accesses -> InputObjectFieldName -> InputObjectFieldName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> InputObjectFieldName -> InputObjectFieldName -> Bool
$cunchanged :: Accesses -> InputObjectFieldName -> InputObjectFieldName -> Bool
$cp1Cacheable :: Eq InputObjectFieldName
Cacheable)
data ObjectTypeDefinition = ObjectTypeDefinition
{ ObjectTypeDefinition -> ObjectTypeName
_otdName :: ObjectTypeName,
ObjectTypeDefinition -> Maybe Description
_otdDescription :: Maybe G.Description,
ObjectTypeDefinition
-> NonEmpty (ObjectFieldDefinition GraphQLType)
_otdFields :: NonEmpty (ObjectFieldDefinition GraphQLType),
ObjectTypeDefinition -> [TypeRelationshipDefinition]
_otdRelationships :: [TypeRelationshipDefinition]
}
deriving (Int -> ObjectTypeDefinition -> ShowS
[ObjectTypeDefinition] -> ShowS
ObjectTypeDefinition -> String
(Int -> ObjectTypeDefinition -> ShowS)
-> (ObjectTypeDefinition -> String)
-> ([ObjectTypeDefinition] -> ShowS)
-> Show ObjectTypeDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectTypeDefinition] -> ShowS
$cshowList :: [ObjectTypeDefinition] -> ShowS
show :: ObjectTypeDefinition -> String
$cshow :: ObjectTypeDefinition -> String
showsPrec :: Int -> ObjectTypeDefinition -> ShowS
$cshowsPrec :: Int -> ObjectTypeDefinition -> ShowS
Show, ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
(ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> Eq ObjectTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c/= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
== :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c== :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
Eq, (forall x. ObjectTypeDefinition -> Rep ObjectTypeDefinition x)
-> (forall x. Rep ObjectTypeDefinition x -> ObjectTypeDefinition)
-> Generic ObjectTypeDefinition
forall x. Rep ObjectTypeDefinition x -> ObjectTypeDefinition
forall x. ObjectTypeDefinition -> Rep ObjectTypeDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObjectTypeDefinition x -> ObjectTypeDefinition
$cfrom :: forall x. ObjectTypeDefinition -> Rep ObjectTypeDefinition x
Generic)
instance NFData ObjectTypeDefinition
instance Cacheable ObjectTypeDefinition
newtype ObjectTypeName = ObjectTypeName {ObjectTypeName -> Name
unObjectTypeName :: G.Name}
deriving (Int -> ObjectTypeName -> ShowS
[ObjectTypeName] -> ShowS
ObjectTypeName -> String
(Int -> ObjectTypeName -> ShowS)
-> (ObjectTypeName -> String)
-> ([ObjectTypeName] -> ShowS)
-> Show ObjectTypeName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectTypeName] -> ShowS
$cshowList :: [ObjectTypeName] -> ShowS
show :: ObjectTypeName -> String
$cshow :: ObjectTypeName -> String
showsPrec :: Int -> ObjectTypeName -> ShowS
$cshowsPrec :: Int -> ObjectTypeName -> ShowS
Show, ObjectTypeName -> ObjectTypeName -> Bool
(ObjectTypeName -> ObjectTypeName -> Bool)
-> (ObjectTypeName -> ObjectTypeName -> Bool) -> Eq ObjectTypeName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeName -> ObjectTypeName -> Bool
$c/= :: ObjectTypeName -> ObjectTypeName -> Bool
== :: ObjectTypeName -> ObjectTypeName -> Bool
$c== :: ObjectTypeName -> ObjectTypeName -> Bool
Eq, Eq ObjectTypeName
Eq ObjectTypeName
-> (ObjectTypeName -> ObjectTypeName -> Ordering)
-> (ObjectTypeName -> ObjectTypeName -> Bool)
-> (ObjectTypeName -> ObjectTypeName -> Bool)
-> (ObjectTypeName -> ObjectTypeName -> Bool)
-> (ObjectTypeName -> ObjectTypeName -> Bool)
-> (ObjectTypeName -> ObjectTypeName -> ObjectTypeName)
-> (ObjectTypeName -> ObjectTypeName -> ObjectTypeName)
-> Ord ObjectTypeName
ObjectTypeName -> ObjectTypeName -> Bool
ObjectTypeName -> ObjectTypeName -> Ordering
ObjectTypeName -> ObjectTypeName -> ObjectTypeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ObjectTypeName -> ObjectTypeName -> ObjectTypeName
$cmin :: ObjectTypeName -> ObjectTypeName -> ObjectTypeName
max :: ObjectTypeName -> ObjectTypeName -> ObjectTypeName
$cmax :: ObjectTypeName -> ObjectTypeName -> ObjectTypeName
>= :: ObjectTypeName -> ObjectTypeName -> Bool
$c>= :: ObjectTypeName -> ObjectTypeName -> Bool
> :: ObjectTypeName -> ObjectTypeName -> Bool
$c> :: ObjectTypeName -> ObjectTypeName -> Bool
<= :: ObjectTypeName -> ObjectTypeName -> Bool
$c<= :: ObjectTypeName -> ObjectTypeName -> Bool
< :: ObjectTypeName -> ObjectTypeName -> Bool
$c< :: ObjectTypeName -> ObjectTypeName -> Bool
compare :: ObjectTypeName -> ObjectTypeName -> Ordering
$ccompare :: ObjectTypeName -> ObjectTypeName -> Ordering
$cp1Ord :: Eq ObjectTypeName
Ord, Int -> ObjectTypeName -> Int
ObjectTypeName -> Int
(Int -> ObjectTypeName -> Int)
-> (ObjectTypeName -> Int) -> Hashable ObjectTypeName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ObjectTypeName -> Int
$chash :: ObjectTypeName -> Int
hashWithSalt :: Int -> ObjectTypeName -> Int
$chashWithSalt :: Int -> ObjectTypeName -> Int
Hashable, Value -> Parser [ObjectTypeName]
Value -> Parser ObjectTypeName
(Value -> Parser ObjectTypeName)
-> (Value -> Parser [ObjectTypeName]) -> FromJSON ObjectTypeName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ObjectTypeName]
$cparseJSONList :: Value -> Parser [ObjectTypeName]
parseJSON :: Value -> Parser ObjectTypeName
$cparseJSON :: Value -> Parser ObjectTypeName
J.FromJSON, [ObjectTypeName] -> Value
[ObjectTypeName] -> Encoding
ObjectTypeName -> Value
ObjectTypeName -> Encoding
(ObjectTypeName -> Value)
-> (ObjectTypeName -> Encoding)
-> ([ObjectTypeName] -> Value)
-> ([ObjectTypeName] -> Encoding)
-> ToJSON ObjectTypeName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ObjectTypeName] -> Encoding
$ctoEncodingList :: [ObjectTypeName] -> Encoding
toJSONList :: [ObjectTypeName] -> Value
$ctoJSONList :: [ObjectTypeName] -> Value
toEncoding :: ObjectTypeName -> Encoding
$ctoEncoding :: ObjectTypeName -> Encoding
toJSON :: ObjectTypeName -> Value
$ctoJSON :: ObjectTypeName -> Value
J.ToJSON, ObjectTypeName -> Text
(ObjectTypeName -> Text) -> ToTxt ObjectTypeName
forall a. (a -> Text) -> ToTxt a
toTxt :: ObjectTypeName -> Text
$ctoTxt :: ObjectTypeName -> Text
ToTxt, (forall x. ObjectTypeName -> Rep ObjectTypeName x)
-> (forall x. Rep ObjectTypeName x -> ObjectTypeName)
-> Generic ObjectTypeName
forall x. Rep ObjectTypeName x -> ObjectTypeName
forall x. ObjectTypeName -> Rep ObjectTypeName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObjectTypeName x -> ObjectTypeName
$cfrom :: forall x. ObjectTypeName -> Rep ObjectTypeName x
Generic, ObjectTypeName -> ()
(ObjectTypeName -> ()) -> NFData ObjectTypeName
forall a. (a -> ()) -> NFData a
rnf :: ObjectTypeName -> ()
$crnf :: ObjectTypeName -> ()
NFData, Eq ObjectTypeName
Eq ObjectTypeName
-> (Accesses -> ObjectTypeName -> ObjectTypeName -> Bool)
-> Cacheable ObjectTypeName
Accesses -> ObjectTypeName -> ObjectTypeName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> ObjectTypeName -> ObjectTypeName -> Bool
$cunchanged :: Accesses -> ObjectTypeName -> ObjectTypeName -> Bool
$cp1Cacheable :: Eq ObjectTypeName
Cacheable)
data ObjectFieldDefinition field = ObjectFieldDefinition
{ ObjectFieldDefinition field -> ObjectFieldName
_ofdName :: ObjectFieldName,
ObjectFieldDefinition field -> Maybe Value
_ofdArguments :: Maybe J.Value,
ObjectFieldDefinition field -> Maybe Description
_ofdDescription :: Maybe G.Description,
ObjectFieldDefinition field -> field
_ofdType :: field
}
deriving (Int -> ObjectFieldDefinition field -> ShowS
[ObjectFieldDefinition field] -> ShowS
ObjectFieldDefinition field -> String
(Int -> ObjectFieldDefinition field -> ShowS)
-> (ObjectFieldDefinition field -> String)
-> ([ObjectFieldDefinition field] -> ShowS)
-> Show (ObjectFieldDefinition field)
forall field.
Show field =>
Int -> ObjectFieldDefinition field -> ShowS
forall field. Show field => [ObjectFieldDefinition field] -> ShowS
forall field. Show field => ObjectFieldDefinition field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectFieldDefinition field] -> ShowS
$cshowList :: forall field. Show field => [ObjectFieldDefinition field] -> ShowS
show :: ObjectFieldDefinition field -> String
$cshow :: forall field. Show field => ObjectFieldDefinition field -> String
showsPrec :: Int -> ObjectFieldDefinition field -> ShowS
$cshowsPrec :: forall field.
Show field =>
Int -> ObjectFieldDefinition field -> ShowS
Show, ObjectFieldDefinition field -> ObjectFieldDefinition field -> Bool
(ObjectFieldDefinition field
-> ObjectFieldDefinition field -> Bool)
-> (ObjectFieldDefinition field
-> ObjectFieldDefinition field -> Bool)
-> Eq (ObjectFieldDefinition field)
forall field.
Eq field =>
ObjectFieldDefinition field -> ObjectFieldDefinition field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectFieldDefinition field -> ObjectFieldDefinition field -> Bool
$c/= :: forall field.
Eq field =>
ObjectFieldDefinition field -> ObjectFieldDefinition field -> Bool
== :: ObjectFieldDefinition field -> ObjectFieldDefinition field -> Bool
$c== :: forall field.
Eq field =>
ObjectFieldDefinition field -> ObjectFieldDefinition field -> Bool
Eq, a -> ObjectFieldDefinition b -> ObjectFieldDefinition a
(a -> b) -> ObjectFieldDefinition a -> ObjectFieldDefinition b
(forall a b.
(a -> b) -> ObjectFieldDefinition a -> ObjectFieldDefinition b)
-> (forall a b.
a -> ObjectFieldDefinition b -> ObjectFieldDefinition a)
-> Functor ObjectFieldDefinition
forall a b. a -> ObjectFieldDefinition b -> ObjectFieldDefinition a
forall a b.
(a -> b) -> ObjectFieldDefinition a -> ObjectFieldDefinition b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ObjectFieldDefinition b -> ObjectFieldDefinition a
$c<$ :: forall a b. a -> ObjectFieldDefinition b -> ObjectFieldDefinition a
fmap :: (a -> b) -> ObjectFieldDefinition a -> ObjectFieldDefinition b
$cfmap :: forall a b.
(a -> b) -> ObjectFieldDefinition a -> ObjectFieldDefinition b
Functor, ObjectFieldDefinition a -> Bool
(a -> m) -> ObjectFieldDefinition a -> m
(a -> b -> b) -> b -> ObjectFieldDefinition a -> b
(forall m. Monoid m => ObjectFieldDefinition m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ObjectFieldDefinition a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ObjectFieldDefinition a -> m)
-> (forall a b. (a -> b -> b) -> b -> ObjectFieldDefinition a -> b)
-> (forall a b. (a -> b -> b) -> b -> ObjectFieldDefinition a -> b)
-> (forall b a. (b -> a -> b) -> b -> ObjectFieldDefinition a -> b)
-> (forall b a. (b -> a -> b) -> b -> ObjectFieldDefinition a -> b)
-> (forall a. (a -> a -> a) -> ObjectFieldDefinition a -> a)
-> (forall a. (a -> a -> a) -> ObjectFieldDefinition a -> a)
-> (forall a. ObjectFieldDefinition a -> [a])
-> (forall a. ObjectFieldDefinition a -> Bool)
-> (forall a. ObjectFieldDefinition a -> Int)
-> (forall a. Eq a => a -> ObjectFieldDefinition a -> Bool)
-> (forall a. Ord a => ObjectFieldDefinition a -> a)
-> (forall a. Ord a => ObjectFieldDefinition a -> a)
-> (forall a. Num a => ObjectFieldDefinition a -> a)
-> (forall a. Num a => ObjectFieldDefinition a -> a)
-> Foldable ObjectFieldDefinition
forall a. Eq a => a -> ObjectFieldDefinition a -> Bool
forall a. Num a => ObjectFieldDefinition a -> a
forall a. Ord a => ObjectFieldDefinition a -> a
forall m. Monoid m => ObjectFieldDefinition m -> m
forall a. ObjectFieldDefinition a -> Bool
forall a. ObjectFieldDefinition a -> Int
forall a. ObjectFieldDefinition a -> [a]
forall a. (a -> a -> a) -> ObjectFieldDefinition a -> a
forall m a. Monoid m => (a -> m) -> ObjectFieldDefinition a -> m
forall b a. (b -> a -> b) -> b -> ObjectFieldDefinition a -> b
forall a b. (a -> b -> b) -> b -> ObjectFieldDefinition a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: ObjectFieldDefinition a -> a
$cproduct :: forall a. Num a => ObjectFieldDefinition a -> a
sum :: ObjectFieldDefinition a -> a
$csum :: forall a. Num a => ObjectFieldDefinition a -> a
minimum :: ObjectFieldDefinition a -> a
$cminimum :: forall a. Ord a => ObjectFieldDefinition a -> a
maximum :: ObjectFieldDefinition a -> a
$cmaximum :: forall a. Ord a => ObjectFieldDefinition a -> a
elem :: a -> ObjectFieldDefinition a -> Bool
$celem :: forall a. Eq a => a -> ObjectFieldDefinition a -> Bool
length :: ObjectFieldDefinition a -> Int
$clength :: forall a. ObjectFieldDefinition a -> Int
null :: ObjectFieldDefinition a -> Bool
$cnull :: forall a. ObjectFieldDefinition a -> Bool
toList :: ObjectFieldDefinition a -> [a]
$ctoList :: forall a. ObjectFieldDefinition a -> [a]
foldl1 :: (a -> a -> a) -> ObjectFieldDefinition a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ObjectFieldDefinition a -> a
foldr1 :: (a -> a -> a) -> ObjectFieldDefinition a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> ObjectFieldDefinition a -> a
foldl' :: (b -> a -> b) -> b -> ObjectFieldDefinition a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ObjectFieldDefinition a -> b
foldl :: (b -> a -> b) -> b -> ObjectFieldDefinition a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ObjectFieldDefinition a -> b
foldr' :: (a -> b -> b) -> b -> ObjectFieldDefinition a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ObjectFieldDefinition a -> b
foldr :: (a -> b -> b) -> b -> ObjectFieldDefinition a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> ObjectFieldDefinition a -> b
foldMap' :: (a -> m) -> ObjectFieldDefinition a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ObjectFieldDefinition a -> m
foldMap :: (a -> m) -> ObjectFieldDefinition a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ObjectFieldDefinition a -> m
fold :: ObjectFieldDefinition m -> m
$cfold :: forall m. Monoid m => ObjectFieldDefinition m -> m
Foldable, Functor ObjectFieldDefinition
Foldable ObjectFieldDefinition
Functor ObjectFieldDefinition
-> Foldable ObjectFieldDefinition
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ObjectFieldDefinition a -> f (ObjectFieldDefinition b))
-> (forall (f :: * -> *) a.
Applicative f =>
ObjectFieldDefinition (f a) -> f (ObjectFieldDefinition a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ObjectFieldDefinition a -> m (ObjectFieldDefinition b))
-> (forall (m :: * -> *) a.
Monad m =>
ObjectFieldDefinition (m a) -> m (ObjectFieldDefinition a))
-> Traversable ObjectFieldDefinition
(a -> f b)
-> ObjectFieldDefinition a -> f (ObjectFieldDefinition b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ObjectFieldDefinition (m a) -> m (ObjectFieldDefinition a)
forall (f :: * -> *) a.
Applicative f =>
ObjectFieldDefinition (f a) -> f (ObjectFieldDefinition a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ObjectFieldDefinition a -> m (ObjectFieldDefinition b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ObjectFieldDefinition a -> f (ObjectFieldDefinition b)
sequence :: ObjectFieldDefinition (m a) -> m (ObjectFieldDefinition a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ObjectFieldDefinition (m a) -> m (ObjectFieldDefinition a)
mapM :: (a -> m b)
-> ObjectFieldDefinition a -> m (ObjectFieldDefinition b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ObjectFieldDefinition a -> m (ObjectFieldDefinition b)
sequenceA :: ObjectFieldDefinition (f a) -> f (ObjectFieldDefinition a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ObjectFieldDefinition (f a) -> f (ObjectFieldDefinition a)
traverse :: (a -> f b)
-> ObjectFieldDefinition a -> f (ObjectFieldDefinition b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ObjectFieldDefinition a -> f (ObjectFieldDefinition b)
$cp2Traversable :: Foldable ObjectFieldDefinition
$cp1Traversable :: Functor ObjectFieldDefinition
Traversable, (forall x.
ObjectFieldDefinition field -> Rep (ObjectFieldDefinition field) x)
-> (forall x.
Rep (ObjectFieldDefinition field) x -> ObjectFieldDefinition field)
-> Generic (ObjectFieldDefinition field)
forall x.
Rep (ObjectFieldDefinition field) x -> ObjectFieldDefinition field
forall x.
ObjectFieldDefinition field -> Rep (ObjectFieldDefinition field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field x.
Rep (ObjectFieldDefinition field) x -> ObjectFieldDefinition field
forall field x.
ObjectFieldDefinition field -> Rep (ObjectFieldDefinition field) x
$cto :: forall field x.
Rep (ObjectFieldDefinition field) x -> ObjectFieldDefinition field
$cfrom :: forall field x.
ObjectFieldDefinition field -> Rep (ObjectFieldDefinition field) x
Generic)
instance (NFData field) => NFData (ObjectFieldDefinition field)
instance (Cacheable field) => Cacheable (ObjectFieldDefinition field)
newtype ObjectFieldName = ObjectFieldName {ObjectFieldName -> Name
unObjectFieldName :: G.Name}
deriving (Int -> ObjectFieldName -> ShowS
[ObjectFieldName] -> ShowS
ObjectFieldName -> String
(Int -> ObjectFieldName -> ShowS)
-> (ObjectFieldName -> String)
-> ([ObjectFieldName] -> ShowS)
-> Show ObjectFieldName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectFieldName] -> ShowS
$cshowList :: [ObjectFieldName] -> ShowS
show :: ObjectFieldName -> String
$cshow :: ObjectFieldName -> String
showsPrec :: Int -> ObjectFieldName -> ShowS
$cshowsPrec :: Int -> ObjectFieldName -> ShowS
Show, ObjectFieldName -> ObjectFieldName -> Bool
(ObjectFieldName -> ObjectFieldName -> Bool)
-> (ObjectFieldName -> ObjectFieldName -> Bool)
-> Eq ObjectFieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectFieldName -> ObjectFieldName -> Bool
$c/= :: ObjectFieldName -> ObjectFieldName -> Bool
== :: ObjectFieldName -> ObjectFieldName -> Bool
$c== :: ObjectFieldName -> ObjectFieldName -> Bool
Eq, Eq ObjectFieldName
Eq ObjectFieldName
-> (ObjectFieldName -> ObjectFieldName -> Ordering)
-> (ObjectFieldName -> ObjectFieldName -> Bool)
-> (ObjectFieldName -> ObjectFieldName -> Bool)
-> (ObjectFieldName -> ObjectFieldName -> Bool)
-> (ObjectFieldName -> ObjectFieldName -> Bool)
-> (ObjectFieldName -> ObjectFieldName -> ObjectFieldName)
-> (ObjectFieldName -> ObjectFieldName -> ObjectFieldName)
-> Ord ObjectFieldName
ObjectFieldName -> ObjectFieldName -> Bool
ObjectFieldName -> ObjectFieldName -> Ordering
ObjectFieldName -> ObjectFieldName -> ObjectFieldName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ObjectFieldName -> ObjectFieldName -> ObjectFieldName
$cmin :: ObjectFieldName -> ObjectFieldName -> ObjectFieldName
max :: ObjectFieldName -> ObjectFieldName -> ObjectFieldName
$cmax :: ObjectFieldName -> ObjectFieldName -> ObjectFieldName
>= :: ObjectFieldName -> ObjectFieldName -> Bool
$c>= :: ObjectFieldName -> ObjectFieldName -> Bool
> :: ObjectFieldName -> ObjectFieldName -> Bool
$c> :: ObjectFieldName -> ObjectFieldName -> Bool
<= :: ObjectFieldName -> ObjectFieldName -> Bool
$c<= :: ObjectFieldName -> ObjectFieldName -> Bool
< :: ObjectFieldName -> ObjectFieldName -> Bool
$c< :: ObjectFieldName -> ObjectFieldName -> Bool
compare :: ObjectFieldName -> ObjectFieldName -> Ordering
$ccompare :: ObjectFieldName -> ObjectFieldName -> Ordering
$cp1Ord :: Eq ObjectFieldName
Ord, Int -> ObjectFieldName -> Int
ObjectFieldName -> Int
(Int -> ObjectFieldName -> Int)
-> (ObjectFieldName -> Int) -> Hashable ObjectFieldName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ObjectFieldName -> Int
$chash :: ObjectFieldName -> Int
hashWithSalt :: Int -> ObjectFieldName -> Int
$chashWithSalt :: Int -> ObjectFieldName -> Int
Hashable, Value -> Parser [ObjectFieldName]
Value -> Parser ObjectFieldName
(Value -> Parser ObjectFieldName)
-> (Value -> Parser [ObjectFieldName]) -> FromJSON ObjectFieldName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ObjectFieldName]
$cparseJSONList :: Value -> Parser [ObjectFieldName]
parseJSON :: Value -> Parser ObjectFieldName
$cparseJSON :: Value -> Parser ObjectFieldName
J.FromJSON, [ObjectFieldName] -> Value
[ObjectFieldName] -> Encoding
ObjectFieldName -> Value
ObjectFieldName -> Encoding
(ObjectFieldName -> Value)
-> (ObjectFieldName -> Encoding)
-> ([ObjectFieldName] -> Value)
-> ([ObjectFieldName] -> Encoding)
-> ToJSON ObjectFieldName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ObjectFieldName] -> Encoding
$ctoEncodingList :: [ObjectFieldName] -> Encoding
toJSONList :: [ObjectFieldName] -> Value
$ctoJSONList :: [ObjectFieldName] -> Value
toEncoding :: ObjectFieldName -> Encoding
$ctoEncoding :: ObjectFieldName -> Encoding
toJSON :: ObjectFieldName -> Value
$ctoJSON :: ObjectFieldName -> Value
J.ToJSON, FromJSONKeyFunction [ObjectFieldName]
FromJSONKeyFunction ObjectFieldName
FromJSONKeyFunction ObjectFieldName
-> FromJSONKeyFunction [ObjectFieldName]
-> FromJSONKey ObjectFieldName
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [ObjectFieldName]
$cfromJSONKeyList :: FromJSONKeyFunction [ObjectFieldName]
fromJSONKey :: FromJSONKeyFunction ObjectFieldName
$cfromJSONKey :: FromJSONKeyFunction ObjectFieldName
J.FromJSONKey, ToJSONKeyFunction [ObjectFieldName]
ToJSONKeyFunction ObjectFieldName
ToJSONKeyFunction ObjectFieldName
-> ToJSONKeyFunction [ObjectFieldName] -> ToJSONKey ObjectFieldName
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [ObjectFieldName]
$ctoJSONKeyList :: ToJSONKeyFunction [ObjectFieldName]
toJSONKey :: ToJSONKeyFunction ObjectFieldName
$ctoJSONKey :: ToJSONKeyFunction ObjectFieldName
J.ToJSONKey, ObjectFieldName -> Text
(ObjectFieldName -> Text) -> ToTxt ObjectFieldName
forall a. (a -> Text) -> ToTxt a
toTxt :: ObjectFieldName -> Text
$ctoTxt :: ObjectFieldName -> Text
ToTxt, (forall x. ObjectFieldName -> Rep ObjectFieldName x)
-> (forall x. Rep ObjectFieldName x -> ObjectFieldName)
-> Generic ObjectFieldName
forall x. Rep ObjectFieldName x -> ObjectFieldName
forall x. ObjectFieldName -> Rep ObjectFieldName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObjectFieldName x -> ObjectFieldName
$cfrom :: forall x. ObjectFieldName -> Rep ObjectFieldName x
Generic, ObjectFieldName -> ()
(ObjectFieldName -> ()) -> NFData ObjectFieldName
forall a. (a -> ()) -> NFData a
rnf :: ObjectFieldName -> ()
$crnf :: ObjectFieldName -> ()
NFData, Eq ObjectFieldName
Eq ObjectFieldName
-> (Accesses -> ObjectFieldName -> ObjectFieldName -> Bool)
-> Cacheable ObjectFieldName
Accesses -> ObjectFieldName -> ObjectFieldName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> ObjectFieldName -> ObjectFieldName -> Bool
$cunchanged :: Accesses -> ObjectFieldName -> ObjectFieldName -> Bool
$cp1Cacheable :: Eq ObjectFieldName
Cacheable)
data ScalarTypeDefinition = ScalarTypeDefinition
{ ScalarTypeDefinition -> Name
_stdName :: G.Name,
ScalarTypeDefinition -> Maybe Description
_stdDescription :: Maybe G.Description
}
deriving (Int -> ScalarTypeDefinition -> ShowS
[ScalarTypeDefinition] -> ShowS
ScalarTypeDefinition -> String
(Int -> ScalarTypeDefinition -> ShowS)
-> (ScalarTypeDefinition -> String)
-> ([ScalarTypeDefinition] -> ShowS)
-> Show ScalarTypeDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScalarTypeDefinition] -> ShowS
$cshowList :: [ScalarTypeDefinition] -> ShowS
show :: ScalarTypeDefinition -> String
$cshow :: ScalarTypeDefinition -> String
showsPrec :: Int -> ScalarTypeDefinition -> ShowS
$cshowsPrec :: Int -> ScalarTypeDefinition -> ShowS
Show, ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
(ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> Eq ScalarTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c/= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
== :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c== :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
Eq, (forall x. ScalarTypeDefinition -> Rep ScalarTypeDefinition x)
-> (forall x. Rep ScalarTypeDefinition x -> ScalarTypeDefinition)
-> Generic ScalarTypeDefinition
forall x. Rep ScalarTypeDefinition x -> ScalarTypeDefinition
forall x. ScalarTypeDefinition -> Rep ScalarTypeDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScalarTypeDefinition x -> ScalarTypeDefinition
$cfrom :: forall x. ScalarTypeDefinition -> Rep ScalarTypeDefinition x
Generic)
instance NFData ScalarTypeDefinition
instance Cacheable ScalarTypeDefinition
defaultGraphQLScalars :: HashMap G.Name ScalarTypeDefinition
defaultGraphQLScalars :: HashMap Name ScalarTypeDefinition
defaultGraphQLScalars = [(Name, ScalarTypeDefinition)] -> HashMap Name ScalarTypeDefinition
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Name, ScalarTypeDefinition)]
-> HashMap Name ScalarTypeDefinition)
-> ([Name] -> [(Name, ScalarTypeDefinition)])
-> [Name]
-> HashMap Name ScalarTypeDefinition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name -> (Name, ScalarTypeDefinition))
-> [Name] -> [(Name, ScalarTypeDefinition)]
forall a b. (a -> b) -> [a] -> [b]
map (\Name
name -> (Name
name, Name -> Maybe Description -> ScalarTypeDefinition
ScalarTypeDefinition Name
name Maybe Description
forall a. Maybe a
Nothing)) ([Name] -> HashMap Name ScalarTypeDefinition)
-> [Name] -> HashMap Name ScalarTypeDefinition
forall a b. (a -> b) -> a -> b
$ HashSet Name -> [Name]
forall a. HashSet a -> [a]
Set.toList HashSet Name
GName.builtInScalars
data EnumTypeDefinition = EnumTypeDefinition
{ EnumTypeDefinition -> EnumTypeName
_etdName :: EnumTypeName,
EnumTypeDefinition -> Maybe Description
_etdDescription :: Maybe G.Description,
EnumTypeDefinition -> NonEmpty EnumValueDefinition
_etdValues :: NonEmpty EnumValueDefinition
}
deriving (Int -> EnumTypeDefinition -> ShowS
[EnumTypeDefinition] -> ShowS
EnumTypeDefinition -> String
(Int -> EnumTypeDefinition -> ShowS)
-> (EnumTypeDefinition -> String)
-> ([EnumTypeDefinition] -> ShowS)
-> Show EnumTypeDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnumTypeDefinition] -> ShowS
$cshowList :: [EnumTypeDefinition] -> ShowS
show :: EnumTypeDefinition -> String
$cshow :: EnumTypeDefinition -> String
showsPrec :: Int -> EnumTypeDefinition -> ShowS
$cshowsPrec :: Int -> EnumTypeDefinition -> ShowS
Show, EnumTypeDefinition -> EnumTypeDefinition -> Bool
(EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> (EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> Eq EnumTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c/= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
== :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c== :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
Eq, (forall x. EnumTypeDefinition -> Rep EnumTypeDefinition x)
-> (forall x. Rep EnumTypeDefinition x -> EnumTypeDefinition)
-> Generic EnumTypeDefinition
forall x. Rep EnumTypeDefinition x -> EnumTypeDefinition
forall x. EnumTypeDefinition -> Rep EnumTypeDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnumTypeDefinition x -> EnumTypeDefinition
$cfrom :: forall x. EnumTypeDefinition -> Rep EnumTypeDefinition x
Generic)
instance NFData EnumTypeDefinition
instance Cacheable EnumTypeDefinition
newtype EnumTypeName = EnumTypeName {EnumTypeName -> Name
unEnumTypeName :: G.Name}
deriving (Int -> EnumTypeName -> ShowS
[EnumTypeName] -> ShowS
EnumTypeName -> String
(Int -> EnumTypeName -> ShowS)
-> (EnumTypeName -> String)
-> ([EnumTypeName] -> ShowS)
-> Show EnumTypeName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnumTypeName] -> ShowS
$cshowList :: [EnumTypeName] -> ShowS
show :: EnumTypeName -> String
$cshow :: EnumTypeName -> String
showsPrec :: Int -> EnumTypeName -> ShowS
$cshowsPrec :: Int -> EnumTypeName -> ShowS
Show, EnumTypeName -> EnumTypeName -> Bool
(EnumTypeName -> EnumTypeName -> Bool)
-> (EnumTypeName -> EnumTypeName -> Bool) -> Eq EnumTypeName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeName -> EnumTypeName -> Bool
$c/= :: EnumTypeName -> EnumTypeName -> Bool
== :: EnumTypeName -> EnumTypeName -> Bool
$c== :: EnumTypeName -> EnumTypeName -> Bool
Eq, Eq EnumTypeName
Eq EnumTypeName
-> (EnumTypeName -> EnumTypeName -> Ordering)
-> (EnumTypeName -> EnumTypeName -> Bool)
-> (EnumTypeName -> EnumTypeName -> Bool)
-> (EnumTypeName -> EnumTypeName -> Bool)
-> (EnumTypeName -> EnumTypeName -> Bool)
-> (EnumTypeName -> EnumTypeName -> EnumTypeName)
-> (EnumTypeName -> EnumTypeName -> EnumTypeName)
-> Ord EnumTypeName
EnumTypeName -> EnumTypeName -> Bool
EnumTypeName -> EnumTypeName -> Ordering
EnumTypeName -> EnumTypeName -> EnumTypeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumTypeName -> EnumTypeName -> EnumTypeName
$cmin :: EnumTypeName -> EnumTypeName -> EnumTypeName
max :: EnumTypeName -> EnumTypeName -> EnumTypeName
$cmax :: EnumTypeName -> EnumTypeName -> EnumTypeName
>= :: EnumTypeName -> EnumTypeName -> Bool
$c>= :: EnumTypeName -> EnumTypeName -> Bool
> :: EnumTypeName -> EnumTypeName -> Bool
$c> :: EnumTypeName -> EnumTypeName -> Bool
<= :: EnumTypeName -> EnumTypeName -> Bool
$c<= :: EnumTypeName -> EnumTypeName -> Bool
< :: EnumTypeName -> EnumTypeName -> Bool
$c< :: EnumTypeName -> EnumTypeName -> Bool
compare :: EnumTypeName -> EnumTypeName -> Ordering
$ccompare :: EnumTypeName -> EnumTypeName -> Ordering
$cp1Ord :: Eq EnumTypeName
Ord, Int -> EnumTypeName -> Int
EnumTypeName -> Int
(Int -> EnumTypeName -> Int)
-> (EnumTypeName -> Int) -> Hashable EnumTypeName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: EnumTypeName -> Int
$chash :: EnumTypeName -> Int
hashWithSalt :: Int -> EnumTypeName -> Int
$chashWithSalt :: Int -> EnumTypeName -> Int
Hashable, Value -> Parser [EnumTypeName]
Value -> Parser EnumTypeName
(Value -> Parser EnumTypeName)
-> (Value -> Parser [EnumTypeName]) -> FromJSON EnumTypeName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EnumTypeName]
$cparseJSONList :: Value -> Parser [EnumTypeName]
parseJSON :: Value -> Parser EnumTypeName
$cparseJSON :: Value -> Parser EnumTypeName
J.FromJSON, [EnumTypeName] -> Value
[EnumTypeName] -> Encoding
EnumTypeName -> Value
EnumTypeName -> Encoding
(EnumTypeName -> Value)
-> (EnumTypeName -> Encoding)
-> ([EnumTypeName] -> Value)
-> ([EnumTypeName] -> Encoding)
-> ToJSON EnumTypeName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [EnumTypeName] -> Encoding
$ctoEncodingList :: [EnumTypeName] -> Encoding
toJSONList :: [EnumTypeName] -> Value
$ctoJSONList :: [EnumTypeName] -> Value
toEncoding :: EnumTypeName -> Encoding
$ctoEncoding :: EnumTypeName -> Encoding
toJSON :: EnumTypeName -> Value
$ctoJSON :: EnumTypeName -> Value
J.ToJSON, EnumTypeName -> Text
(EnumTypeName -> Text) -> ToTxt EnumTypeName
forall a. (a -> Text) -> ToTxt a
toTxt :: EnumTypeName -> Text
$ctoTxt :: EnumTypeName -> Text
ToTxt, (forall x. EnumTypeName -> Rep EnumTypeName x)
-> (forall x. Rep EnumTypeName x -> EnumTypeName)
-> Generic EnumTypeName
forall x. Rep EnumTypeName x -> EnumTypeName
forall x. EnumTypeName -> Rep EnumTypeName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnumTypeName x -> EnumTypeName
$cfrom :: forall x. EnumTypeName -> Rep EnumTypeName x
Generic, EnumTypeName -> ()
(EnumTypeName -> ()) -> NFData EnumTypeName
forall a. (a -> ()) -> NFData a
rnf :: EnumTypeName -> ()
$crnf :: EnumTypeName -> ()
NFData, Eq EnumTypeName
Eq EnumTypeName
-> (Accesses -> EnumTypeName -> EnumTypeName -> Bool)
-> Cacheable EnumTypeName
Accesses -> EnumTypeName -> EnumTypeName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> EnumTypeName -> EnumTypeName -> Bool
$cunchanged :: Accesses -> EnumTypeName -> EnumTypeName -> Bool
$cp1Cacheable :: Eq EnumTypeName
Cacheable)
data EnumValueDefinition = EnumValueDefinition
{ EnumValueDefinition -> EnumValue
_evdValue :: G.EnumValue,
EnumValueDefinition -> Maybe Description
_evdDescription :: Maybe G.Description,
EnumValueDefinition -> Maybe Bool
_evdIsDeprecated :: Maybe Bool
}
deriving (Int -> EnumValueDefinition -> ShowS
[EnumValueDefinition] -> ShowS
EnumValueDefinition -> String
(Int -> EnumValueDefinition -> ShowS)
-> (EnumValueDefinition -> String)
-> ([EnumValueDefinition] -> ShowS)
-> Show EnumValueDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnumValueDefinition] -> ShowS
$cshowList :: [EnumValueDefinition] -> ShowS
show :: EnumValueDefinition -> String
$cshow :: EnumValueDefinition -> String
showsPrec :: Int -> EnumValueDefinition -> ShowS
$cshowsPrec :: Int -> EnumValueDefinition -> ShowS
Show, EnumValueDefinition -> EnumValueDefinition -> Bool
(EnumValueDefinition -> EnumValueDefinition -> Bool)
-> (EnumValueDefinition -> EnumValueDefinition -> Bool)
-> Eq EnumValueDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c/= :: EnumValueDefinition -> EnumValueDefinition -> Bool
== :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c== :: EnumValueDefinition -> EnumValueDefinition -> Bool
Eq, (forall x. EnumValueDefinition -> Rep EnumValueDefinition x)
-> (forall x. Rep EnumValueDefinition x -> EnumValueDefinition)
-> Generic EnumValueDefinition
forall x. Rep EnumValueDefinition x -> EnumValueDefinition
forall x. EnumValueDefinition -> Rep EnumValueDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnumValueDefinition x -> EnumValueDefinition
$cfrom :: forall x. EnumValueDefinition -> Rep EnumValueDefinition x
Generic)
instance NFData EnumValueDefinition
instance Cacheable EnumValueDefinition
data TypeRelationshipDefinition = TypeRelationshipDefinition
{ TypeRelationshipDefinition -> RelationshipName
_trdName :: RelationshipName,
TypeRelationshipDefinition -> RelType
_trdType :: RelType,
TypeRelationshipDefinition -> SourceName
_trdSource :: SourceName,
TypeRelationshipDefinition -> QualifiedTable
_trdRemoteTable :: PG.QualifiedTable,
TypeRelationshipDefinition -> HashMap ObjectFieldName PGCol
_trdFieldMapping :: HashMap ObjectFieldName PG.PGCol
}
deriving (Int -> TypeRelationshipDefinition -> ShowS
[TypeRelationshipDefinition] -> ShowS
TypeRelationshipDefinition -> String
(Int -> TypeRelationshipDefinition -> ShowS)
-> (TypeRelationshipDefinition -> String)
-> ([TypeRelationshipDefinition] -> ShowS)
-> Show TypeRelationshipDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeRelationshipDefinition] -> ShowS
$cshowList :: [TypeRelationshipDefinition] -> ShowS
show :: TypeRelationshipDefinition -> String
$cshow :: TypeRelationshipDefinition -> String
showsPrec :: Int -> TypeRelationshipDefinition -> ShowS
$cshowsPrec :: Int -> TypeRelationshipDefinition -> ShowS
Show, TypeRelationshipDefinition -> TypeRelationshipDefinition -> Bool
(TypeRelationshipDefinition -> TypeRelationshipDefinition -> Bool)
-> (TypeRelationshipDefinition
-> TypeRelationshipDefinition -> Bool)
-> Eq TypeRelationshipDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeRelationshipDefinition -> TypeRelationshipDefinition -> Bool
$c/= :: TypeRelationshipDefinition -> TypeRelationshipDefinition -> Bool
== :: TypeRelationshipDefinition -> TypeRelationshipDefinition -> Bool
$c== :: TypeRelationshipDefinition -> TypeRelationshipDefinition -> Bool
Eq, (forall x.
TypeRelationshipDefinition -> Rep TypeRelationshipDefinition x)
-> (forall x.
Rep TypeRelationshipDefinition x -> TypeRelationshipDefinition)
-> Generic TypeRelationshipDefinition
forall x.
Rep TypeRelationshipDefinition x -> TypeRelationshipDefinition
forall x.
TypeRelationshipDefinition -> Rep TypeRelationshipDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TypeRelationshipDefinition x -> TypeRelationshipDefinition
$cfrom :: forall x.
TypeRelationshipDefinition -> Rep TypeRelationshipDefinition x
Generic)
instance NFData TypeRelationshipDefinition
instance Cacheable TypeRelationshipDefinition
instance J.FromJSON TypeRelationshipDefinition where
parseJSON :: Value -> Parser TypeRelationshipDefinition
parseJSON = String
-> (Object -> Parser TypeRelationshipDefinition)
-> Value
-> Parser TypeRelationshipDefinition
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"TypeRelationshipDefinition" ((Object -> Parser TypeRelationshipDefinition)
-> Value -> Parser TypeRelationshipDefinition)
-> (Object -> Parser TypeRelationshipDefinition)
-> Value
-> Parser TypeRelationshipDefinition
forall a b. (a -> b) -> a -> b
$ \Object
o ->
RelationshipName
-> RelType
-> SourceName
-> QualifiedTable
-> HashMap ObjectFieldName PGCol
-> TypeRelationshipDefinition
TypeRelationshipDefinition
(RelationshipName
-> RelType
-> SourceName
-> QualifiedTable
-> HashMap ObjectFieldName PGCol
-> TypeRelationshipDefinition)
-> Parser RelationshipName
-> Parser
(RelType
-> SourceName
-> QualifiedTable
-> HashMap ObjectFieldName PGCol
-> TypeRelationshipDefinition)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser RelationshipName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser
(RelType
-> SourceName
-> QualifiedTable
-> HashMap ObjectFieldName PGCol
-> TypeRelationshipDefinition)
-> Parser RelType
-> Parser
(SourceName
-> QualifiedTable
-> HashMap ObjectFieldName PGCol
-> TypeRelationshipDefinition)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser RelType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser
(SourceName
-> QualifiedTable
-> HashMap ObjectFieldName PGCol
-> TypeRelationshipDefinition)
-> Parser SourceName
-> Parser
(QualifiedTable
-> HashMap ObjectFieldName PGCol -> TypeRelationshipDefinition)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source" Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
defaultSource
Parser
(QualifiedTable
-> HashMap ObjectFieldName PGCol -> TypeRelationshipDefinition)
-> Parser QualifiedTable
-> Parser
(HashMap ObjectFieldName PGCol -> TypeRelationshipDefinition)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser QualifiedTable
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"remote_table"
Parser
(HashMap ObjectFieldName PGCol -> TypeRelationshipDefinition)
-> Parser (HashMap ObjectFieldName PGCol)
-> Parser TypeRelationshipDefinition
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (HashMap ObjectFieldName PGCol)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"field_mapping"
newtype RelationshipName = RelationshipName {RelationshipName -> Name
unRelationshipName :: G.Name}
deriving (Int -> RelationshipName -> ShowS
[RelationshipName] -> ShowS
RelationshipName -> String
(Int -> RelationshipName -> ShowS)
-> (RelationshipName -> String)
-> ([RelationshipName] -> ShowS)
-> Show RelationshipName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationshipName] -> ShowS
$cshowList :: [RelationshipName] -> ShowS
show :: RelationshipName -> String
$cshow :: RelationshipName -> String
showsPrec :: Int -> RelationshipName -> ShowS
$cshowsPrec :: Int -> RelationshipName -> ShowS
Show, RelationshipName -> RelationshipName -> Bool
(RelationshipName -> RelationshipName -> Bool)
-> (RelationshipName -> RelationshipName -> Bool)
-> Eq RelationshipName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationshipName -> RelationshipName -> Bool
$c/= :: RelationshipName -> RelationshipName -> Bool
== :: RelationshipName -> RelationshipName -> Bool
$c== :: RelationshipName -> RelationshipName -> Bool
Eq, Eq RelationshipName
Eq RelationshipName
-> (RelationshipName -> RelationshipName -> Ordering)
-> (RelationshipName -> RelationshipName -> Bool)
-> (RelationshipName -> RelationshipName -> Bool)
-> (RelationshipName -> RelationshipName -> Bool)
-> (RelationshipName -> RelationshipName -> Bool)
-> (RelationshipName -> RelationshipName -> RelationshipName)
-> (RelationshipName -> RelationshipName -> RelationshipName)
-> Ord RelationshipName
RelationshipName -> RelationshipName -> Bool
RelationshipName -> RelationshipName -> Ordering
RelationshipName -> RelationshipName -> RelationshipName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationshipName -> RelationshipName -> RelationshipName
$cmin :: RelationshipName -> RelationshipName -> RelationshipName
max :: RelationshipName -> RelationshipName -> RelationshipName
$cmax :: RelationshipName -> RelationshipName -> RelationshipName
>= :: RelationshipName -> RelationshipName -> Bool
$c>= :: RelationshipName -> RelationshipName -> Bool
> :: RelationshipName -> RelationshipName -> Bool
$c> :: RelationshipName -> RelationshipName -> Bool
<= :: RelationshipName -> RelationshipName -> Bool
$c<= :: RelationshipName -> RelationshipName -> Bool
< :: RelationshipName -> RelationshipName -> Bool
$c< :: RelationshipName -> RelationshipName -> Bool
compare :: RelationshipName -> RelationshipName -> Ordering
$ccompare :: RelationshipName -> RelationshipName -> Ordering
$cp1Ord :: Eq RelationshipName
Ord, Int -> RelationshipName -> Int
RelationshipName -> Int
(Int -> RelationshipName -> Int)
-> (RelationshipName -> Int) -> Hashable RelationshipName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RelationshipName -> Int
$chash :: RelationshipName -> Int
hashWithSalt :: Int -> RelationshipName -> Int
$chashWithSalt :: Int -> RelationshipName -> Int
Hashable, Value -> Parser [RelationshipName]
Value -> Parser RelationshipName
(Value -> Parser RelationshipName)
-> (Value -> Parser [RelationshipName])
-> FromJSON RelationshipName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RelationshipName]
$cparseJSONList :: Value -> Parser [RelationshipName]
parseJSON :: Value -> Parser RelationshipName
$cparseJSON :: Value -> Parser RelationshipName
J.FromJSON, [RelationshipName] -> Value
[RelationshipName] -> Encoding
RelationshipName -> Value
RelationshipName -> Encoding
(RelationshipName -> Value)
-> (RelationshipName -> Encoding)
-> ([RelationshipName] -> Value)
-> ([RelationshipName] -> Encoding)
-> ToJSON RelationshipName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RelationshipName] -> Encoding
$ctoEncodingList :: [RelationshipName] -> Encoding
toJSONList :: [RelationshipName] -> Value
$ctoJSONList :: [RelationshipName] -> Value
toEncoding :: RelationshipName -> Encoding
$ctoEncoding :: RelationshipName -> Encoding
toJSON :: RelationshipName -> Value
$ctoJSON :: RelationshipName -> Value
J.ToJSON, RelationshipName -> Text
(RelationshipName -> Text) -> ToTxt RelationshipName
forall a. (a -> Text) -> ToTxt a
toTxt :: RelationshipName -> Text
$ctoTxt :: RelationshipName -> Text
ToTxt, (forall x. RelationshipName -> Rep RelationshipName x)
-> (forall x. Rep RelationshipName x -> RelationshipName)
-> Generic RelationshipName
forall x. Rep RelationshipName x -> RelationshipName
forall x. RelationshipName -> Rep RelationshipName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationshipName x -> RelationshipName
$cfrom :: forall x. RelationshipName -> Rep RelationshipName x
Generic, RelationshipName -> ()
(RelationshipName -> ()) -> NFData RelationshipName
forall a. (a -> ()) -> NFData a
rnf :: RelationshipName -> ()
$crnf :: RelationshipName -> ()
NFData, Eq RelationshipName
Eq RelationshipName
-> (Accesses -> RelationshipName -> RelationshipName -> Bool)
-> Cacheable RelationshipName
Accesses -> RelationshipName -> RelationshipName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> RelationshipName -> RelationshipName -> Bool
$cunchanged :: Accesses -> RelationshipName -> RelationshipName -> Bool
$cp1Cacheable :: Eq RelationshipName
Cacheable)
data AnnotatedCustomTypes = AnnotatedCustomTypes
{ AnnotatedCustomTypes -> HashMap Name AnnotatedInputType
_actInputTypes :: HashMap G.Name AnnotatedInputType,
AnnotatedCustomTypes -> HashMap Name AnnotatedObjectType
_actObjectTypes :: HashMap G.Name AnnotatedObjectType
}
instance Semigroup AnnotatedCustomTypes where
AnnotatedCustomTypes HashMap Name AnnotatedInputType
no1 HashMap Name AnnotatedObjectType
o1 <> :: AnnotatedCustomTypes
-> AnnotatedCustomTypes -> AnnotatedCustomTypes
<> AnnotatedCustomTypes HashMap Name AnnotatedInputType
no2 HashMap Name AnnotatedObjectType
o2 =
HashMap Name AnnotatedInputType
-> HashMap Name AnnotatedObjectType -> AnnotatedCustomTypes
AnnotatedCustomTypes (HashMap Name AnnotatedInputType
no1 HashMap Name AnnotatedInputType
-> HashMap Name AnnotatedInputType
-> HashMap Name AnnotatedInputType
forall a. Semigroup a => a -> a -> a
<> HashMap Name AnnotatedInputType
no2) (HashMap Name AnnotatedObjectType
o1 HashMap Name AnnotatedObjectType
-> HashMap Name AnnotatedObjectType
-> HashMap Name AnnotatedObjectType
forall a. Semigroup a => a -> a -> a
<> HashMap Name AnnotatedObjectType
o2)
instance Monoid AnnotatedCustomTypes where
mempty :: AnnotatedCustomTypes
mempty = HashMap Name AnnotatedInputType
-> HashMap Name AnnotatedObjectType -> AnnotatedCustomTypes
AnnotatedCustomTypes HashMap Name AnnotatedInputType
forall a. Monoid a => a
mempty HashMap Name AnnotatedObjectType
forall a. Monoid a => a
mempty
data AnnotatedInputType
= NOCTScalar AnnotatedScalarType
| NOCTEnum EnumTypeDefinition
| NOCTInputObject InputObjectTypeDefinition
deriving (AnnotatedInputType -> AnnotatedInputType -> Bool
(AnnotatedInputType -> AnnotatedInputType -> Bool)
-> (AnnotatedInputType -> AnnotatedInputType -> Bool)
-> Eq AnnotatedInputType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotatedInputType -> AnnotatedInputType -> Bool
$c/= :: AnnotatedInputType -> AnnotatedInputType -> Bool
== :: AnnotatedInputType -> AnnotatedInputType -> Bool
$c== :: AnnotatedInputType -> AnnotatedInputType -> Bool
Eq, (forall x. AnnotatedInputType -> Rep AnnotatedInputType x)
-> (forall x. Rep AnnotatedInputType x -> AnnotatedInputType)
-> Generic AnnotatedInputType
forall x. Rep AnnotatedInputType x -> AnnotatedInputType
forall x. AnnotatedInputType -> Rep AnnotatedInputType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnnotatedInputType x -> AnnotatedInputType
$cfrom :: forall x. AnnotatedInputType -> Rep AnnotatedInputType x
Generic)
data AnnotatedScalarType
= ASTCustom ScalarTypeDefinition
| ASTReusedScalar G.Name (AnyBackend ScalarWrapper)
deriving (AnnotatedScalarType -> AnnotatedScalarType -> Bool
(AnnotatedScalarType -> AnnotatedScalarType -> Bool)
-> (AnnotatedScalarType -> AnnotatedScalarType -> Bool)
-> Eq AnnotatedScalarType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotatedScalarType -> AnnotatedScalarType -> Bool
$c/= :: AnnotatedScalarType -> AnnotatedScalarType -> Bool
== :: AnnotatedScalarType -> AnnotatedScalarType -> Bool
$c== :: AnnotatedScalarType -> AnnotatedScalarType -> Bool
Eq, (forall x. AnnotatedScalarType -> Rep AnnotatedScalarType x)
-> (forall x. Rep AnnotatedScalarType x -> AnnotatedScalarType)
-> Generic AnnotatedScalarType
forall x. Rep AnnotatedScalarType x -> AnnotatedScalarType
forall x. AnnotatedScalarType -> Rep AnnotatedScalarType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnnotatedScalarType x -> AnnotatedScalarType
$cfrom :: forall x. AnnotatedScalarType -> Rep AnnotatedScalarType x
Generic)
newtype ScalarWrapper b = ScalarWrapper {ScalarWrapper b -> ScalarType b
unwrapScalar :: (ScalarType b)}
deriving instance (Backend b) => Eq (ScalarWrapper b)
data AnnotatedOutputType
= AOTObject AnnotatedObjectType
| AOTScalar AnnotatedScalarType
deriving ((forall x. AnnotatedOutputType -> Rep AnnotatedOutputType x)
-> (forall x. Rep AnnotatedOutputType x -> AnnotatedOutputType)
-> Generic AnnotatedOutputType
forall x. Rep AnnotatedOutputType x -> AnnotatedOutputType
forall x. AnnotatedOutputType -> Rep AnnotatedOutputType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnnotatedOutputType x -> AnnotatedOutputType
$cfrom :: forall x. AnnotatedOutputType -> Rep AnnotatedOutputType x
Generic)
data AnnotatedObjectType = AnnotatedObjectType
{ AnnotatedObjectType -> ObjectTypeName
_aotName :: ObjectTypeName,
AnnotatedObjectType -> Maybe Description
_aotDescription :: Maybe G.Description,
AnnotatedObjectType
-> NonEmpty
(ObjectFieldDefinition (GType, AnnotatedObjectFieldType))
_aotFields :: NonEmpty (ObjectFieldDefinition (G.GType, AnnotatedObjectFieldType)),
AnnotatedObjectType -> [AnnotatedTypeRelationship]
_aotRelationships :: [AnnotatedTypeRelationship]
}
deriving ((forall x. AnnotatedObjectType -> Rep AnnotatedObjectType x)
-> (forall x. Rep AnnotatedObjectType x -> AnnotatedObjectType)
-> Generic AnnotatedObjectType
forall x. Rep AnnotatedObjectType x -> AnnotatedObjectType
forall x. AnnotatedObjectType -> Rep AnnotatedObjectType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnnotatedObjectType x -> AnnotatedObjectType
$cfrom :: forall x. AnnotatedObjectType -> Rep AnnotatedObjectType x
Generic)
data AnnotatedObjectFieldType
= AOFTScalar AnnotatedScalarType
| AOFTEnum EnumTypeDefinition
| AOFTObject G.Name
deriving ((forall x.
AnnotatedObjectFieldType -> Rep AnnotatedObjectFieldType x)
-> (forall x.
Rep AnnotatedObjectFieldType x -> AnnotatedObjectFieldType)
-> Generic AnnotatedObjectFieldType
forall x.
Rep AnnotatedObjectFieldType x -> AnnotatedObjectFieldType
forall x.
AnnotatedObjectFieldType -> Rep AnnotatedObjectFieldType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AnnotatedObjectFieldType x -> AnnotatedObjectFieldType
$cfrom :: forall x.
AnnotatedObjectFieldType -> Rep AnnotatedObjectFieldType x
Generic)
data AnnotatedTypeRelationship = AnnotatedTypeRelationship
{ AnnotatedTypeRelationship -> RelationshipName
_atrName :: RelationshipName,
AnnotatedTypeRelationship -> RelType
_atrType :: RelType,
AnnotatedTypeRelationship -> SourceName
_atrSource :: SourceName,
AnnotatedTypeRelationship -> SourceConfig ('Postgres 'Vanilla)
_atrSourceConfig :: SourceConfig ('Postgres 'Vanilla),
AnnotatedTypeRelationship -> SourceTypeCustomization
_atrSourceCustomization :: SourceTypeCustomization,
AnnotatedTypeRelationship -> TableInfo ('Postgres 'Vanilla)
_atrTableInfo :: TableInfo ('Postgres 'Vanilla),
AnnotatedTypeRelationship
-> HashMap ObjectFieldName (ColumnInfo ('Postgres 'Vanilla))
_atrFieldMapping :: HashMap ObjectFieldName (ColumnInfo ('Postgres 'Vanilla))
}
deriving ((forall x.
AnnotatedTypeRelationship -> Rep AnnotatedTypeRelationship x)
-> (forall x.
Rep AnnotatedTypeRelationship x -> AnnotatedTypeRelationship)
-> Generic AnnotatedTypeRelationship
forall x.
Rep AnnotatedTypeRelationship x -> AnnotatedTypeRelationship
forall x.
AnnotatedTypeRelationship -> Rep AnnotatedTypeRelationship x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AnnotatedTypeRelationship x -> AnnotatedTypeRelationship
$cfrom :: forall x.
AnnotatedTypeRelationship -> Rep AnnotatedTypeRelationship x
Generic)
$(J.deriveJSON hasuraJSON ''InputObjectFieldDefinition)
$(J.deriveJSON hasuraJSON ''InputObjectTypeDefinition)
$(J.deriveJSON hasuraJSON ''ObjectFieldDefinition)
$(J.deriveJSON hasuraJSON ''ScalarTypeDefinition)
$(J.deriveJSON hasuraJSON ''EnumValueDefinition)
$(J.deriveToJSON hasuraJSON ''TypeRelationshipDefinition)
instance J.ToJSON AnnotatedScalarType where
toJSON :: AnnotatedScalarType -> Value
toJSON = \case
ASTCustom ScalarTypeDefinition
std ->
[Pair] -> Value
J.object [Key
"tag" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
J.String Text
"ASTCustom", Key
"contents" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ScalarTypeDefinition -> Value
forall a. ToJSON a => a -> Value
J.toJSON ScalarTypeDefinition
std]
ASTReusedScalar Name
name AnyBackend ScalarWrapper
_scalar ->
[Pair] -> Value
J.object [Key
"tag" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
J.String Text
"ASTReusedScalar", Key
"contents" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Name -> Value
forall a. ToJSON a => a -> Value
J.toJSON Name
name]
$(makeLenses ''TypeRelationshipDefinition)
$(J.deriveJSON hasuraJSON ''EnumTypeDefinition)
instance J.FromJSON CustomTypes where
parseJSON :: Value -> Parser CustomTypes
parseJSON = String
-> (Object -> Parser CustomTypes) -> Value -> Parser CustomTypes
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"CustomTypes" \Object
o ->
[InputObjectTypeDefinition]
-> [ObjectTypeDefinition]
-> [ScalarTypeDefinition]
-> [EnumTypeDefinition]
-> CustomTypes
CustomTypes
([InputObjectTypeDefinition]
-> [ObjectTypeDefinition]
-> [ScalarTypeDefinition]
-> [EnumTypeDefinition]
-> CustomTypes)
-> Parser [InputObjectTypeDefinition]
-> Parser
([ObjectTypeDefinition]
-> [ScalarTypeDefinition] -> [EnumTypeDefinition] -> CustomTypes)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe [InputObjectTypeDefinition])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"input_objects" Parser (Maybe [InputObjectTypeDefinition])
-> [InputObjectTypeDefinition]
-> Parser [InputObjectTypeDefinition]
forall a. Parser (Maybe a) -> a -> Parser a
.!= [])
Parser
([ObjectTypeDefinition]
-> [ScalarTypeDefinition] -> [EnumTypeDefinition] -> CustomTypes)
-> Parser [ObjectTypeDefinition]
-> Parser
([ScalarTypeDefinition] -> [EnumTypeDefinition] -> CustomTypes)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe [ObjectTypeDefinition])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"objects" Parser (Maybe [ObjectTypeDefinition])
-> [ObjectTypeDefinition] -> Parser [ObjectTypeDefinition]
forall a. Parser (Maybe a) -> a -> Parser a
.!= [])
Parser
([ScalarTypeDefinition] -> [EnumTypeDefinition] -> CustomTypes)
-> Parser [ScalarTypeDefinition]
-> Parser ([EnumTypeDefinition] -> CustomTypes)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe [ScalarTypeDefinition])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"scalars" Parser (Maybe [ScalarTypeDefinition])
-> [ScalarTypeDefinition] -> Parser [ScalarTypeDefinition]
forall a. Parser (Maybe a) -> a -> Parser a
.!= [])
Parser ([EnumTypeDefinition] -> CustomTypes)
-> Parser [EnumTypeDefinition] -> Parser CustomTypes
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe [EnumTypeDefinition])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"enums" Parser (Maybe [EnumTypeDefinition])
-> [EnumTypeDefinition] -> Parser [EnumTypeDefinition]
forall a. Parser (Maybe a) -> a -> Parser a
.!= [])
instance J.FromJSON ObjectTypeDefinition where
parseJSON :: Value -> Parser ObjectTypeDefinition
parseJSON = String
-> (Object -> Parser ObjectTypeDefinition)
-> Value
-> Parser ObjectTypeDefinition
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"ObjectTypeDefinition" \Object
o ->
ObjectTypeName
-> Maybe Description
-> NonEmpty (ObjectFieldDefinition GraphQLType)
-> [TypeRelationshipDefinition]
-> ObjectTypeDefinition
ObjectTypeDefinition
(ObjectTypeName
-> Maybe Description
-> NonEmpty (ObjectFieldDefinition GraphQLType)
-> [TypeRelationshipDefinition]
-> ObjectTypeDefinition)
-> Parser ObjectTypeName
-> Parser
(Maybe Description
-> NonEmpty (ObjectFieldDefinition GraphQLType)
-> [TypeRelationshipDefinition]
-> ObjectTypeDefinition)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser ObjectTypeName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name")
Parser
(Maybe Description
-> NonEmpty (ObjectFieldDefinition GraphQLType)
-> [TypeRelationshipDefinition]
-> ObjectTypeDefinition)
-> Parser (Maybe Description)
-> Parser
(NonEmpty (ObjectFieldDefinition GraphQLType)
-> [TypeRelationshipDefinition] -> ObjectTypeDefinition)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe Description)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description")
Parser
(NonEmpty (ObjectFieldDefinition GraphQLType)
-> [TypeRelationshipDefinition] -> ObjectTypeDefinition)
-> Parser (NonEmpty (ObjectFieldDefinition GraphQLType))
-> Parser ([TypeRelationshipDefinition] -> ObjectTypeDefinition)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object
-> Key -> Parser (NonEmpty (ObjectFieldDefinition GraphQLType))
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fields")
Parser ([TypeRelationshipDefinition] -> ObjectTypeDefinition)
-> Parser [TypeRelationshipDefinition]
-> Parser ObjectTypeDefinition
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe [TypeRelationshipDefinition])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"relationships" Parser (Maybe [TypeRelationshipDefinition])
-> [TypeRelationshipDefinition]
-> Parser [TypeRelationshipDefinition]
forall a. Parser (Maybe a) -> a -> Parser a
.!= [])
$(J.deriveToJSON hasuraJSON ''ObjectTypeDefinition)
$(J.deriveToJSON hasuraJSON ''CustomTypes)
$(J.deriveToJSON hasuraJSON ''AnnotatedInputType)
$(J.deriveToJSON hasuraJSON ''AnnotatedObjectFieldType)
$(J.deriveToJSON hasuraJSON ''AnnotatedTypeRelationship)
$(J.deriveToJSON hasuraJSON ''AnnotatedObjectType)
$(J.deriveToJSON hasuraJSON ''AnnotatedOutputType)