Safe Haskell | None |
---|---|
Language | Haskell2010 |
GraphQL.Internal.API
Description
Synopsis
- data Object (name :: Symbol) (interfaces :: [Type]) (fields :: [Type])
- data Field (name :: Symbol) (fieldType :: Type)
- data Argument (name :: Symbol) (argType :: Type)
- data Union (name :: Symbol) (types :: [Type])
- data List (elemType :: Type)
- data Enum (name :: Symbol) (values :: Type)
- class GraphQLEnum a where
- enumValues :: [Either NameError Name]
- enumFromValue :: Name -> Either Text a
- enumToValue :: a -> Name
- data Interface (name :: Symbol) (fields :: [Type])
- data a :> b = a :> b
- class Defaultable a where
- defaultFor :: Name -> Maybe a
- class HasAnnotatedType a where
- class HasAnnotatedInputType a
- class HasObjectDefinition a where
- getArgumentDefinition :: HasArgumentDefinition a => Either SchemaError ArgumentDefinition
- data SchemaError
- nameFromSymbol :: forall (n :: Symbol). KnownSymbol n => Either SchemaError Name
- getFieldDefinition :: HasFieldDefinition a => Either SchemaError FieldDefinition
- getInterfaceDefinition :: HasInterfaceDefinition a => Either SchemaError InterfaceTypeDefinition
- getAnnotatedInputType :: HasAnnotatedInputType a => Either SchemaError (AnnotatedType InputType)
Documentation
data Object (name :: Symbol) (interfaces :: [Type]) (fields :: [Type]) Source #
Instances
(RunFields m (RunFieldsType m fields), HasObjectDefinition (Object typeName interfaces fields), Monad m) => HasResolver m (Object typeName interfaces fields :: Type) Source # | |
(KnownSymbol ks, HasInterfaceDefinitions is, HasFieldDefinitions ts) => HasAnnotatedType (Object ks is ts :: Type) Source # | |
Defined in GraphQL.Internal.API Methods getAnnotatedType :: Either SchemaError (AnnotatedType GType) Source # | |
(KnownSymbol ks, HasInterfaceDefinitions is, HasFieldDefinitions fields) => HasObjectDefinition (Object ks is fields :: Type) Source # | |
Defined in GraphQL.Internal.API Methods getDefinition :: Either SchemaError ObjectTypeDefinition Source # | |
type Handler m (Object typeName interfaces fields :: Type) Source # | |
Defined in GraphQL.Internal.Resolver |
data Union (name :: Symbol) (types :: [Type]) Source #
Instances
(Monad m, KnownSymbol unionName, RunUnion m (Union unionName objects) objects) => HasResolver m (Union unionName objects :: Type) Source # | |
(KnownSymbol ks, HasUnionTypeObjectTypeDefinitions as) => HasAnnotatedType (Union ks as :: Type) Source # | |
Defined in GraphQL.Internal.API Methods getAnnotatedType :: Either SchemaError (AnnotatedType GType) Source # | |
type Handler m (Union unionName objects :: Type) Source # | |
Defined in GraphQL.Internal.Resolver |
data List (elemType :: Type) Source #
Instances
HasAnnotatedInputType t => HasAnnotatedInputType (List t) Source # | |
Defined in GraphQL.Internal.API Methods getAnnotatedInputType :: Either SchemaError (AnnotatedType InputType) Source # | |
(Monad m, Applicative m, HasResolver m hg) => HasResolver m (List hg :: Type) Source # | |
HasAnnotatedType t => HasAnnotatedType (List t :: Type) Source # | |
Defined in GraphQL.Internal.API Methods getAnnotatedType :: Either SchemaError (AnnotatedType GType) Source # | |
type Handler m (List hg :: Type) Source # | |
Defined in GraphQL.Internal.Resolver |
data Enum (name :: Symbol) (values :: Type) Source #
Instances
(Applicative m, GraphQLEnum enum) => HasResolver m (Enum ksN enum :: Type) Source # | |
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedType (Enum ks enum :: Type) Source # | |
Defined in GraphQL.Internal.API Methods getAnnotatedType :: Either SchemaError (AnnotatedType GType) Source # | |
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedInputType (Enum ks enum) Source # | |
Defined in GraphQL.Internal.API Methods getAnnotatedInputType :: Either SchemaError (AnnotatedType InputType) Source # | |
type Handler m (Enum ksN enum :: Type) Source # | |
Defined in GraphQL.Internal.Resolver |
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.
Minimal complete definition
Nothing
Methods
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
Constructors
a :> b infixr 8 |
class Defaultable a where Source #
Specify a default value for a type in a GraphQL schema.
GraphQL schema can have default values in certain places. For example, arguments to fields can have default values. Because we cannot lift arbitrary values to the type level, we need some way of getting at those values. This typeclass provides the means.
To specify a default, implement this typeclass.
The default implementation is to say that there *is* no default for this type.
Minimal complete definition
Nothing
Methods
defaultFor :: Name -> Maybe a Source #
defaultFor returns the value to be used when no value has been given.
Instances
Defaultable Bool Source # | |
Defined in GraphQL.Internal.API | |
Defaultable Double Source # | |
Defined in GraphQL.Internal.API | |
Defaultable Int32 Source # | |
Defined in GraphQL.Internal.API | |
Defaultable Text Source # | |
Defined in GraphQL.Internal.API | |
Defaultable (Maybe a) Source # | |
Defined in GraphQL.Internal.API |
class HasAnnotatedType a where Source #
Methods
getAnnotatedType :: Either SchemaError (AnnotatedType GType) Source #
Instances
class HasAnnotatedInputType a Source #
Instances
class HasObjectDefinition a where Source #
Methods
getDefinition :: Either SchemaError ObjectTypeDefinition Source #
Instances
(KnownSymbol ks, HasInterfaceDefinitions is, HasFieldDefinitions fields) => HasObjectDefinition (Object ks is fields :: Type) Source # | |
Defined in GraphQL.Internal.API Methods getDefinition :: Either SchemaError ObjectTypeDefinition Source # |
getArgumentDefinition :: HasArgumentDefinition a => Either SchemaError ArgumentDefinition Source #
data SchemaError Source #
The type-level schema was somehow invalid.
Constructors
NameError NameError | |
EmptyFieldList | |
EmptyUnion |
Instances
Eq SchemaError Source # | |
Defined in GraphQL.Internal.API | |
Show SchemaError Source # | |
Defined in GraphQL.Internal.API Methods showsPrec :: Int -> SchemaError -> ShowS # show :: SchemaError -> String # showList :: [SchemaError] -> ShowS # | |
GraphQLError SchemaError Source # | |
Defined in GraphQL.Internal.API |
nameFromSymbol :: forall (n :: Symbol). KnownSymbol n => Either SchemaError Name Source #
Exported for testing.
getFieldDefinition :: HasFieldDefinition a => Either SchemaError FieldDefinition Source #
getInterfaceDefinition :: HasInterfaceDefinition a => Either SchemaError InterfaceTypeDefinition Source #