Copyright | (c) 2018 Hasura Technologies Pvt. Ltd. |
---|---|
License | BSD3 |
Maintainer | Vamshi Surabhi <vamshi@hasura.io> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Language.GraphQL.June2018.Syntax
Description
Parse text into GraphQL ASTs
- newtype ExecutableDocument = ExecutableDocument {}
- newtype SchemaDocument = SchemaDocument [TypeDefinition]
- data Definition
- = DefinitionExecutable !ExecutableDefinition
- | DefinitionTypeSystem !TypeSystemDefinition
- data ExecutableDefinition
- partitionExDefs :: [ExecutableDefinition] -> ([SelectionSet], [TypedOperationDefinition], [FragmentDefinition])
- newtype Document = Document {
- getDefinitions :: [Definition]
- data OperationDefinition
- data OperationType
- data TypedOperationDefinition = TypedOperationDefinition {}
- data VariableDefinition = VariableDefinition {
- _vdVariable :: !Variable
- _vdType :: !GType
- _vdDefaultValue :: !(Maybe DefaultValue)
- newtype Name = Name {}
- newtype Variable = Variable {
- unVariable :: Name
- type SelectionSet = [Selection]
- data Selection
- data Field = Field {
- _fAlias :: !(Maybe Alias)
- _fName :: !Name
- _fArguments :: ![Argument]
- _fDirectives :: ![Directive]
- _fSelectionSet :: !SelectionSet
- newtype Alias = Alias {}
- data Argument = Argument {}
- data FragmentSpread = FragmentSpread {
- _fsName :: !Name
- _fsDirectives :: ![Directive]
- data InlineFragment = InlineFragment {}
- data FragmentDefinition = FragmentDefinition {}
- type TypeCondition = NamedType
- data ValueConst
- = VCInt !Int32
- | VCFloat !Double
- | VCString !StringValue
- | VCBoolean !Bool
- | VCNull
- | VCEnum !EnumValue
- | VCList !ListValueC
- | VCObject !ObjectValueC
- data Value
- newtype StringValue = StringValue {}
- newtype ListValueG a = ListValueG {
- unListValue :: [a]
- type ListValue = ListValueG Value
- type ListValueC = ListValueG ValueConst
- newtype ObjectValueG a = ObjectValueG {
- unObjectValue :: [ObjectFieldG a]
- type ObjectValue = ObjectValueG Value
- type ObjectValueC = ObjectValueG ValueConst
- data ObjectFieldG a = ObjectFieldG {}
- type ObjectField = ObjectFieldG Value
- type ObjectFieldC = ObjectFieldG ValueConst
- type DefaultValue = ValueConst
- data Directive = Directive {
- _dName :: !Name
- _dArguments :: ![Argument]
- data GType
- showGT :: GType -> Text
- class ToGType a where
- toLT :: ToGType a => a -> ListType
- showLT :: ListType -> Text
- class ToNonNullType a where
- isNotNull :: GType -> Bool
- showNT :: NamedType -> Text
- newtype NamedType = NamedType {
- unNamedType :: Name
- newtype ListType = ListType {
- unListType :: GType
- data NonNullType
- showNNT :: NonNullType -> Text
- newtype Description = Description {}
- data TypeDefinition
- data ObjectTypeDefinition = ObjectTypeDefinition {
- _otdDescription :: !(Maybe Description)
- _otdName :: !Name
- _otdImplementsInterfaces :: ![NamedType]
- _otdDirectives :: ![Directive]
- _otdFieldsDefinition :: ![FieldDefinition]
- data FieldDefinition = FieldDefinition {}
- type ArgumentsDefinition = [InputValueDefinition]
- data InputValueDefinition = InputValueDefinition {
- _ivdDescription :: !(Maybe Description)
- _ivdName :: !Name
- _ivdType :: !GType
- _ivdDefaultValue :: !(Maybe DefaultValue)
- data InterfaceTypeDefinition = InterfaceTypeDefinition {
- _itdDescription :: !(Maybe Description)
- _itdName :: !Name
- _itdDirectives :: ![Directive]
- _itdFieldsDefinition :: ![FieldDefinition]
- data UnionTypeDefinition = UnionTypeDefinition {
- _utdDescription :: !(Maybe Description)
- _utdName :: !Name
- _utdDirectives :: ![Directive]
- _utdMemberTypes :: ![NamedType]
- data ScalarTypeDefinition = ScalarTypeDefinition {
- _stdDescription :: !(Maybe Description)
- _stdName :: !Name
- _stdDirectives :: ![Directive]
- data EnumTypeDefinition = EnumTypeDefinition {
- _etdDescription :: !(Maybe Description)
- _etdName :: !Name
- _etdDirectives :: ![Directive]
- _etdValueDefinitions :: ![EnumValueDefinition]
- data EnumValueDefinition = EnumValueDefinition {
- _evdDescription :: !(Maybe Description)
- _evdName :: !EnumValue
- _evdDirectives :: ![Directive]
- newtype EnumValue = EnumValue {
- unEnumValue :: Name
- data InputObjectTypeDefinition = InputObjectTypeDefinition {}
- data DirectiveDefinition = DirectiveDefinition {}
- data DirectiveLocation
- data ExecutableDirectiveLocation
- data TypeSystemDirectiveLocation
Documentation
newtype ExecutableDocument Source #
Constructors
ExecutableDocument | |
Fields |
newtype SchemaDocument Source #
Constructors
SchemaDocument [TypeDefinition] |
data Definition Source #
Constructors
DefinitionExecutable !ExecutableDefinition | |
DefinitionTypeSystem !TypeSystemDefinition |
Instances
data ExecutableDefinition Source #
partitionExDefs :: [ExecutableDefinition] -> ([SelectionSet], [TypedOperationDefinition], [FragmentDefinition]) Source #
Constructors
Document | |
Fields
|
data OperationDefinition Source #
data OperationType Source #
Instances
data TypedOperationDefinition Source #
Constructors
TypedOperationDefinition | |
Fields
|
data VariableDefinition Source #
Constructors
VariableDefinition | |
Fields
|
A QueryDocument
is something a user might send us.
https://facebook.github.io/graphql/#sec-Language.Query-Document
Constructors
Variable | |
Fields
|
type SelectionSet = [Selection] Source #
Constructors
Field | |
Fields
|
data FragmentSpread Source #
Constructors
FragmentSpread | |
Fields
|
data InlineFragment Source #
Constructors
InlineFragment | |
Fields
|
data FragmentDefinition Source #
Constructors
FragmentDefinition | |
Fields
|
type TypeCondition = NamedType Source #
data ValueConst Source #
Constructors
VCInt !Int32 | |
VCFloat !Double | |
VCString !StringValue | |
VCBoolean !Bool | |
VCNull | |
VCEnum !EnumValue | |
VCList !ListValueC | |
VCObject !ObjectValueC |
Instances
newtype ListValueG a Source #
Constructors
ListValueG | |
Fields
|
Instances
Eq a => Eq (ListValueG a) Source # | |
Show a => Show (ListValueG a) Source # | |
Lift a => Lift (ListValueG a) Source # | |
Hashable a => Hashable (ListValueG a) Source # | |
type ListValue = ListValueG Value Source #
type ListValueC = ListValueG ValueConst Source #
newtype ObjectValueG a Source #
Constructors
ObjectValueG | |
Fields
|
Instances
Eq a => Eq (ObjectValueG a) Source # | |
Show a => Show (ObjectValueG a) Source # | |
Lift a => Lift (ObjectValueG a) Source # | |
Hashable a => Hashable (ObjectValueG a) Source # | |
type ObjectValue = ObjectValueG Value Source #
type ObjectValueC = ObjectValueG ValueConst Source #
data ObjectFieldG a Source #
Constructors
ObjectFieldG | |
Instances
Functor ObjectFieldG Source # | |
Foldable ObjectFieldG Source # | |
Traversable ObjectFieldG Source # | |
Eq a => Eq (ObjectFieldG a) Source # | |
Show a => Show (ObjectFieldG a) Source # | |
Generic (ObjectFieldG a) Source # | |
Lift a => Lift (ObjectFieldG a) Source # | |
Hashable a => Hashable (ObjectFieldG a) Source # | |
type Rep (ObjectFieldG a) Source # | |
type ObjectField = ObjectFieldG Value Source #
type ObjectFieldC = ObjectFieldG ValueConst Source #
type DefaultValue = ValueConst Source #
Constructors
Directive | |
Fields
|
Constructors
TypeNamed NamedType | |
TypeList ListType | |
TypeNonNull NonNullType |
class ToNonNullType a where Source #
Minimal complete definition
Methods
toNT :: a -> NonNullType Source #
Instances
Constructors
NamedType | |
Fields
|
Instances
Constructors
ListType | |
Fields
|
showNNT :: NonNullType -> Text Source #
newtype Description Source #
Constructors
Description | |
Fields |
data TypeDefinition Source #
data ObjectTypeDefinition Source #
Constructors
ObjectTypeDefinition | |
Fields
|
data FieldDefinition Source #
Constructors
FieldDefinition | |
Fields
|
type ArgumentsDefinition = [InputValueDefinition] Source #
data InputValueDefinition Source #
Constructors
InputValueDefinition | |
Fields
|
data InterfaceTypeDefinition Source #
Constructors
InterfaceTypeDefinition | |
Fields
|
data UnionTypeDefinition Source #
Constructors
UnionTypeDefinition | |
Fields
|
data ScalarTypeDefinition Source #
Constructors
ScalarTypeDefinition | |
Fields
|
data EnumTypeDefinition Source #
Constructors
EnumTypeDefinition | |
Fields
|
data EnumValueDefinition Source #
Constructors
EnumValueDefinition | |
Fields
|
Constructors
EnumValue | |
Fields
|
data InputObjectTypeDefinition Source #
Constructors
InputObjectTypeDefinition | |
Fields
|
data DirectiveDefinition Source #
Constructors
DirectiveDefinition | |
Fields
|
data DirectiveLocation Source #