Safe Haskell | None |
---|---|
Language | Haskell2010 |
Type-level definitions for a GraphQL schema.
- data Object name interfaces fields
- data Field name fieldType
- data Argument name argType
- data DefaultArgument name argType
- data Union name types
- data List elemType
- data Enum name values
- class GraphQLEnum a where
- data Interface name fields
- data a :> b = a :> b
- class HasAnnotatedType a where
- class HasAnnotatedInputType a where
- class HasObjectDefinition a where
- getArgumentDefinition :: HasArgumentDefinition a => Either NameError ArgumentDefinition
- getFieldDefinition :: HasFieldDefinition a => Either NameError FieldDefinition
- getInterfaceDefinition :: HasInterfaceDefinition a => Either NameError InterfaceTypeDefinition
- getAnnotatedInputType :: HasAnnotatedInputType a => Either NameError (AnnotatedType InputType)
Documentation
data Object name interfaces fields Source #
(RunFields m (RunFieldsType m fields), HasObjectDefinition * (Object typeName interfaces fields), Monad m) => HasResolver * m (Object typeName interfaces fields) Source # | |
(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] ts) => HasAnnotatedType * (Object ks is ts) Source # | |
(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] fields) => HasObjectDefinition * (Object ks is fields) Source # | |
type Handler * m (Object typeName interfaces fields) Source # | |
data DefaultArgument name argType Source #
HasAnnotatedInputType t => HasAnnotatedInputType (List t) Source # | |
(Monad m, Applicative m, HasResolver Type m hg) => HasResolver * m (List hg) Source # | |
HasAnnotatedType Type t => HasAnnotatedType * (List t) Source # | |
type Handler * m (List hg) Source # | |
data Enum name values Source #
(Applicative m, GraphQLEnum enum) => HasResolver * m (Enum ksN enum) Source # | |
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedType * (Enum ks enum) Source # | |
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedInputType (Enum ks enum) Source # | |
type Handler * m (Enum ksN enum) Source # | |
class GraphQLEnum a where Source #
For each enum type we need 1) a list of all possible values 2) a way to serialise and 3) deserialise.
TODO: Update this comment to explain what a GraphQLEnum is, why you might want an instance, and any laws that apply to method relations.
enumValues :: [Either NameError Name] Source #
enumValues :: (Generic a, GenericEnumValues (Rep a)) => [Either NameError Name] Source #
enumFromValue :: Name -> Either Text a Source #
enumFromValue :: (Generic a, GenericEnumValues (Rep a)) => Name -> Either Text a Source #
enumToValue :: a -> Name Source #
enumToValue :: (Generic a, GenericEnumValues (Rep a)) => a -> Name Source #
Argument operator. Can only be used with Field
.
Say we have a Company
object that has a field that shows whether
someone is an employee, e.g.
type Company { hasEmployee(employeeName: String!): String! }
Then we might represent that as:
>>>
type Company = Object "Company" '[] '[Argument "employeeName" Text :> Field "hasEmployee" Bool]
For multiple arguments, simply chain them together with :>
, ending
finally with Field
. e.g.
Argument "foo" String :> Argument "bar" Int :> Field "qux" Int
a :> b infixr 8 |
class HasAnnotatedType a where Source #
HasAnnotatedType * Bool Source # | |
HasAnnotatedType * Double Source # | |
HasAnnotatedType * Float Source # | |
HasAnnotatedType * Int Source # | |
HasAnnotatedType * Int32 Source # | |
TypeError Constraint (Text "Cannot encode Integer because it has arbitrary size but the JSON encoding is a number") => HasAnnotatedType * Integer Source # | |
HasAnnotatedType * Text Source # | |
HasAnnotatedType * a => HasAnnotatedType * (Maybe a) Source # | |
HasAnnotatedType Type t => HasAnnotatedType * (List t) Source # | |
(KnownSymbol ks, UnionTypeObjectTypeDefinitionList [Type] as) => HasAnnotatedType * (Union ks as) Source # | |
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedType * (Enum ks enum) Source # | |
(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] ts) => HasAnnotatedType * (Object ks is ts) Source # | |
class HasAnnotatedInputType a where Source #
getAnnotatedInputType :: Either NameError (AnnotatedType InputType) Source #
getAnnotatedInputType :: (Generic a, GenericAnnotatedInputType (Rep a)) => Either NameError (AnnotatedType InputType) Source #
class HasObjectDefinition a where Source #
(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] fields) => HasObjectDefinition * (Object ks is fields) Source # | |
getArgumentDefinition :: HasArgumentDefinition a => Either NameError ArgumentDefinition Source #
Exported for testing. Perhaps should be a different module.
getFieldDefinition :: HasFieldDefinition a => Either NameError FieldDefinition Source #
getInterfaceDefinition :: HasInterfaceDefinition a => Either NameError InterfaceTypeDefinition Source #