Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype QueryDocument = QueryDocument {
- getDefinitions :: [Definition]
- newtype SchemaDocument = SchemaDocument [TypeDefinition]
- data Definition
- data OperationDefinition
- data Node = Node (Maybe Name) [VariableDefinition] [Directive] SelectionSet
- data VariableDefinition = VariableDefinition Variable GType (Maybe DefaultValue)
- newtype Variable = Variable Name
- type SelectionSet = [Selection]
- data Selection
- data Field = Field (Maybe Alias) Name [Argument] [Directive] SelectionSet
- type Alias = Name
- data Argument = Argument Name Value
- data FragmentSpread = FragmentSpread Name [Directive]
- data InlineFragment = InlineFragment (Maybe TypeCondition) [Directive] SelectionSet
- data FragmentDefinition = FragmentDefinition Name TypeCondition [Directive] SelectionSet
- type TypeCondition = NamedType
- data Value
- newtype StringValue = StringValue Text
- newtype ListValue = ListValue [Value]
- newtype ObjectValue = ObjectValue [ObjectField]
- data ObjectField = ObjectField Name Value
- type DefaultValue = Value
- data Directive = Directive Name [Argument]
- data GType
- newtype NamedType = NamedType Name
- newtype ListType = ListType GType
- data NonNullType
- data TypeDefinition
- = TypeDefinitionObject ObjectTypeDefinition
- | TypeDefinitionInterface InterfaceTypeDefinition
- | TypeDefinitionUnion UnionTypeDefinition
- | TypeDefinitionScalar ScalarTypeDefinition
- | TypeDefinitionEnum EnumTypeDefinition
- | TypeDefinitionInputObject InputObjectTypeDefinition
- | TypeDefinitionTypeExtension TypeExtensionDefinition
- data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces [FieldDefinition]
- type Interfaces = [NamedType]
- data FieldDefinition = FieldDefinition Name ArgumentsDefinition GType
- type ArgumentsDefinition = [InputValueDefinition]
- data InputValueDefinition = InputValueDefinition Name GType (Maybe DefaultValue)
- data InterfaceTypeDefinition = InterfaceTypeDefinition Name [FieldDefinition]
- data UnionTypeDefinition = UnionTypeDefinition Name [NamedType]
- newtype ScalarTypeDefinition = ScalarTypeDefinition Name
- data EnumTypeDefinition = EnumTypeDefinition Name [EnumValueDefinition]
- newtype EnumValueDefinition = EnumValueDefinition Name
- data InputObjectTypeDefinition = InputObjectTypeDefinition Name [InputValueDefinition]
- newtype TypeExtensionDefinition = TypeExtensionDefinition ObjectTypeDefinition
Documentation
newtype QueryDocument Source #
A QueryDocument
is something a user might send us.
https://facebook.github.io/graphql/#sec-Language.Query-Document
Instances
Eq QueryDocument Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: QueryDocument -> QueryDocument -> Bool # (/=) :: QueryDocument -> QueryDocument -> Bool # | |
Show QueryDocument Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> QueryDocument -> ShowS # show :: QueryDocument -> String # showList :: [QueryDocument] -> ShowS # |
newtype SchemaDocument Source #
A SchemaDocument
is a document that defines a GraphQL schema.
Instances
Eq SchemaDocument Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: SchemaDocument -> SchemaDocument -> Bool # (/=) :: SchemaDocument -> SchemaDocument -> Bool # | |
Show SchemaDocument Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> SchemaDocument -> ShowS # show :: SchemaDocument -> String # showList :: [SchemaDocument] -> ShowS # |
data Definition Source #
Instances
Eq Definition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: Definition -> Definition -> Bool # (/=) :: Definition -> Definition -> Bool # | |
Show Definition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> Definition -> ShowS # show :: Definition -> String # showList :: [Definition] -> ShowS # |
data OperationDefinition Source #
Instances
Eq OperationDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: OperationDefinition -> OperationDefinition -> Bool # (/=) :: OperationDefinition -> OperationDefinition -> Bool # | |
Show OperationDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> OperationDefinition -> ShowS # show :: OperationDefinition -> String # showList :: [OperationDefinition] -> ShowS # |
data VariableDefinition Source #
Instances
Eq VariableDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: VariableDefinition -> VariableDefinition -> Bool # (/=) :: VariableDefinition -> VariableDefinition -> Bool # | |
Show VariableDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> VariableDefinition -> ShowS # show :: VariableDefinition -> String # showList :: [VariableDefinition] -> ShowS # |
type SelectionSet = [Selection] Source #
data FragmentSpread Source #
Instances
Eq FragmentSpread Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: FragmentSpread -> FragmentSpread -> Bool # (/=) :: FragmentSpread -> FragmentSpread -> Bool # | |
Show FragmentSpread Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> FragmentSpread -> ShowS # show :: FragmentSpread -> String # showList :: [FragmentSpread] -> ShowS # |
data InlineFragment Source #
Instances
Eq InlineFragment Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: InlineFragment -> InlineFragment -> Bool # (/=) :: InlineFragment -> InlineFragment -> Bool # | |
Show InlineFragment Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> InlineFragment -> ShowS # show :: InlineFragment -> String # showList :: [InlineFragment] -> ShowS # |
data FragmentDefinition Source #
Instances
Eq FragmentDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: FragmentDefinition -> FragmentDefinition -> Bool # (/=) :: FragmentDefinition -> FragmentDefinition -> Bool # | |
Show FragmentDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> FragmentDefinition -> ShowS # show :: FragmentDefinition -> String # showList :: [FragmentDefinition] -> ShowS # |
type TypeCondition = NamedType Source #
ValueVariable Variable | |
ValueInt Int32 | |
ValueFloat Double | |
ValueBoolean Bool | |
ValueString StringValue | |
ValueEnum Name | |
ValueList ListValue | |
ValueObject ObjectValue | |
ValueNull |
newtype StringValue Source #
Instances
Eq StringValue Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: StringValue -> StringValue -> Bool # (/=) :: StringValue -> StringValue -> Bool # | |
Show StringValue Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> StringValue -> ShowS # show :: StringValue -> String # showList :: [StringValue] -> ShowS # | |
Arbitrary StringValue Source # | |
Defined in GraphQL.Internal.Syntax.AST arbitrary :: Gen StringValue # shrink :: StringValue -> [StringValue] # |
newtype ObjectValue Source #
Instances
Eq ObjectValue Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: ObjectValue -> ObjectValue -> Bool # (/=) :: ObjectValue -> ObjectValue -> Bool # | |
Show ObjectValue Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> ObjectValue -> ShowS # show :: ObjectValue -> String # showList :: [ObjectValue] -> ShowS # | |
Arbitrary ObjectValue Source # | |
Defined in GraphQL.Internal.Syntax.AST arbitrary :: Gen ObjectValue # shrink :: ObjectValue -> [ObjectValue] # |
data ObjectField Source #
Instances
Eq ObjectField Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: ObjectField -> ObjectField -> Bool # (/=) :: ObjectField -> ObjectField -> Bool # | |
Show ObjectField Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> ObjectField -> ShowS # show :: ObjectField -> String # showList :: [ObjectField] -> ShowS # | |
Arbitrary ObjectField Source # | |
Defined in GraphQL.Internal.Syntax.AST arbitrary :: Gen ObjectField # shrink :: ObjectField -> [ObjectField] # |
type DefaultValue = Value Source #
data NonNullType Source #
Instances
Eq NonNullType Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: NonNullType -> NonNullType -> Bool # (/=) :: NonNullType -> NonNullType -> Bool # | |
Ord NonNullType Source # | |
Defined in GraphQL.Internal.Syntax.AST compare :: NonNullType -> NonNullType -> Ordering # (<) :: NonNullType -> NonNullType -> Bool # (<=) :: NonNullType -> NonNullType -> Bool # (>) :: NonNullType -> NonNullType -> Bool # (>=) :: NonNullType -> NonNullType -> Bool # max :: NonNullType -> NonNullType -> NonNullType # min :: NonNullType -> NonNullType -> NonNullType # | |
Show NonNullType Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> NonNullType -> ShowS # show :: NonNullType -> String # showList :: [NonNullType] -> ShowS # |
data TypeDefinition Source #
Instances
Eq TypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: TypeDefinition -> TypeDefinition -> Bool # (/=) :: TypeDefinition -> TypeDefinition -> Bool # | |
Show TypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> TypeDefinition -> ShowS # show :: TypeDefinition -> String # showList :: [TypeDefinition] -> ShowS # |
data ObjectTypeDefinition Source #
Instances
Eq ObjectTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool # (/=) :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool # | |
Show ObjectTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> ObjectTypeDefinition -> ShowS # show :: ObjectTypeDefinition -> String # showList :: [ObjectTypeDefinition] -> ShowS # |
type Interfaces = [NamedType] Source #
data FieldDefinition Source #
Instances
Eq FieldDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: FieldDefinition -> FieldDefinition -> Bool # (/=) :: FieldDefinition -> FieldDefinition -> Bool # | |
Show FieldDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> FieldDefinition -> ShowS # show :: FieldDefinition -> String # showList :: [FieldDefinition] -> ShowS # |
type ArgumentsDefinition = [InputValueDefinition] Source #
data InputValueDefinition Source #
Instances
Eq InputValueDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: InputValueDefinition -> InputValueDefinition -> Bool # (/=) :: InputValueDefinition -> InputValueDefinition -> Bool # | |
Show InputValueDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> InputValueDefinition -> ShowS # show :: InputValueDefinition -> String # showList :: [InputValueDefinition] -> ShowS # |
data InterfaceTypeDefinition Source #
Instances
Eq InterfaceTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST | |
Show InterfaceTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> InterfaceTypeDefinition -> ShowS # show :: InterfaceTypeDefinition -> String # showList :: [InterfaceTypeDefinition] -> ShowS # |
data UnionTypeDefinition Source #
Instances
Eq UnionTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: UnionTypeDefinition -> UnionTypeDefinition -> Bool # (/=) :: UnionTypeDefinition -> UnionTypeDefinition -> Bool # | |
Show UnionTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> UnionTypeDefinition -> ShowS # show :: UnionTypeDefinition -> String # showList :: [UnionTypeDefinition] -> ShowS # |
newtype ScalarTypeDefinition Source #
Instances
Eq ScalarTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool # (/=) :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool # | |
Show ScalarTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> ScalarTypeDefinition -> ShowS # show :: ScalarTypeDefinition -> String # showList :: [ScalarTypeDefinition] -> ShowS # |
data EnumTypeDefinition Source #
Instances
Eq EnumTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: EnumTypeDefinition -> EnumTypeDefinition -> Bool # (/=) :: EnumTypeDefinition -> EnumTypeDefinition -> Bool # | |
Show EnumTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> EnumTypeDefinition -> ShowS # show :: EnumTypeDefinition -> String # showList :: [EnumTypeDefinition] -> ShowS # |
newtype EnumValueDefinition Source #
Instances
Eq EnumValueDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST (==) :: EnumValueDefinition -> EnumValueDefinition -> Bool # (/=) :: EnumValueDefinition -> EnumValueDefinition -> Bool # | |
Show EnumValueDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> EnumValueDefinition -> ShowS # show :: EnumValueDefinition -> String # showList :: [EnumValueDefinition] -> ShowS # |
data InputObjectTypeDefinition Source #
Instances
Eq InputObjectTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST | |
Show InputObjectTypeDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> InputObjectTypeDefinition -> ShowS # show :: InputObjectTypeDefinition -> String # showList :: [InputObjectTypeDefinition] -> ShowS # |
newtype TypeExtensionDefinition Source #
Instances
Eq TypeExtensionDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST | |
Show TypeExtensionDefinition Source # | |
Defined in GraphQL.Internal.Syntax.AST showsPrec :: Int -> TypeExtensionDefinition -> ShowS # show :: TypeExtensionDefinition -> String # showList :: [TypeExtensionDefinition] -> ShowS # |