graphql-parser-0.1.0.0: GraphQL API

Copyright(c) 2018 Hasura Technologies Pvt. Ltd.
LicenseBSD3
MaintainerVamshi Surabhi <vamshi@hasura.io>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Language.GraphQL.June2018.Syntax

Description

Parse text into GraphQL ASTs

Synopsis

Documentation

data OperationType Source #

Instances

Eq OperationType Source # 
Show OperationType Source # 
Generic OperationType Source # 

Associated Types

type Rep OperationType :: * -> * #

Lift OperationType Source # 

Methods

lift :: OperationType -> Q Exp #

Hashable OperationType Source # 
type Rep OperationType Source # 
type Rep OperationType = D1 (MetaData "OperationType" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) ((:+:) (C1 (MetaCons "OperationTypeQuery" PrefixI False) U1) ((:+:) (C1 (MetaCons "OperationTypeMutation" PrefixI False) U1) (C1 (MetaCons "OperationTypeSubscription" PrefixI False) U1)))

data TypedOperationDefinition Source #

Instances

Eq TypedOperationDefinition Source # 
Show TypedOperationDefinition Source # 
Generic TypedOperationDefinition Source # 
Lift TypedOperationDefinition Source # 
Hashable TypedOperationDefinition Source # 
type Rep TypedOperationDefinition Source # 
type Rep TypedOperationDefinition = D1 (MetaData "TypedOperationDefinition" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "TypedOperationDefinition" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_todType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OperationType)) (S1 (MetaSel (Just Symbol "_todName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Name)))) ((:*:) (S1 (MetaSel (Just Symbol "_todVariableDefinitions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [VariableDefinition])) ((:*:) (S1 (MetaSel (Just Symbol "_todDirectives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Directive])) (S1 (MetaSel (Just Symbol "_todSelectionSet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SelectionSet))))))

data VariableDefinition Source #

newtype Name Source #

A QueryDocument is something a user might send us.

https://facebook.github.io/graphql/#sec-Language.Query-Document

Constructors

Name 

Fields

data Field Source #

Instances

Eq Field Source # 

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

Show Field Source # 

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Generic Field Source # 

Associated Types

type Rep Field :: * -> * #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

Lift Field Source # 

Methods

lift :: Field -> Q Exp #

Hashable Field Source # 

Methods

hashWithSalt :: Int -> Field -> Int #

hash :: Field -> Int #

type Rep Field Source # 

data Argument Source #

Constructors

Argument 

Fields

Instances

Eq Argument Source # 
Show Argument Source # 
Generic Argument Source # 

Associated Types

type Rep Argument :: * -> * #

Methods

from :: Argument -> Rep Argument x #

to :: Rep Argument x -> Argument #

Lift Argument Source # 

Methods

lift :: Argument -> Q Exp #

Hashable Argument Source # 

Methods

hashWithSalt :: Int -> Argument -> Int #

hash :: Argument -> Int #

type Rep Argument Source # 
type Rep Argument = D1 (MetaData "Argument" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "Argument" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name)) (S1 (MetaSel (Just Symbol "_aValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Value))))

data FragmentDefinition Source #

data ValueConst Source #

Instances

Eq ValueConst Source # 
Show ValueConst Source # 
Generic ValueConst Source # 

Associated Types

type Rep ValueConst :: * -> * #

Lift ValueConst Source # 

Methods

lift :: ValueConst -> Q Exp #

Hashable ValueConst Source # 
type Rep ValueConst Source # 

data Value Source #

Instances

Eq Value Source # 

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Lift Value Source # 

Methods

lift :: Value -> Q Exp #

Hashable Value Source # 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

type Rep Value Source # 

newtype ListValueG a Source #

Constructors

ListValueG 

Fields

Instances

Eq a => Eq (ListValueG a) Source # 

Methods

(==) :: ListValueG a -> ListValueG a -> Bool #

(/=) :: ListValueG a -> ListValueG a -> Bool #

Show a => Show (ListValueG a) Source # 
Lift a => Lift (ListValueG a) Source # 

Methods

lift :: ListValueG a -> Q Exp #

Hashable a => Hashable (ListValueG a) Source # 

Methods

hashWithSalt :: Int -> ListValueG a -> Int #

hash :: ListValueG a -> Int #

data ObjectFieldG a Source #

Constructors

ObjectFieldG 

Fields

Instances

Functor ObjectFieldG Source # 

Methods

fmap :: (a -> b) -> ObjectFieldG a -> ObjectFieldG b #

(<$) :: a -> ObjectFieldG b -> ObjectFieldG a #

Foldable ObjectFieldG Source # 

Methods

fold :: Monoid m => ObjectFieldG m -> m #

foldMap :: Monoid m => (a -> m) -> ObjectFieldG a -> m #

foldr :: (a -> b -> b) -> b -> ObjectFieldG a -> b #

foldr' :: (a -> b -> b) -> b -> ObjectFieldG a -> b #

foldl :: (b -> a -> b) -> b -> ObjectFieldG a -> b #

foldl' :: (b -> a -> b) -> b -> ObjectFieldG a -> b #

foldr1 :: (a -> a -> a) -> ObjectFieldG a -> a #

foldl1 :: (a -> a -> a) -> ObjectFieldG a -> a #

toList :: ObjectFieldG a -> [a] #

null :: ObjectFieldG a -> Bool #

length :: ObjectFieldG a -> Int #

elem :: Eq a => a -> ObjectFieldG a -> Bool #

maximum :: Ord a => ObjectFieldG a -> a #

minimum :: Ord a => ObjectFieldG a -> a #

sum :: Num a => ObjectFieldG a -> a #

product :: Num a => ObjectFieldG a -> a #

Traversable ObjectFieldG Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ObjectFieldG a -> f (ObjectFieldG b) #

sequenceA :: Applicative f => ObjectFieldG (f a) -> f (ObjectFieldG a) #

mapM :: Monad m => (a -> m b) -> ObjectFieldG a -> m (ObjectFieldG b) #

sequence :: Monad m => ObjectFieldG (m a) -> m (ObjectFieldG a) #

Eq a => Eq (ObjectFieldG a) Source # 
Show a => Show (ObjectFieldG a) Source # 
Generic (ObjectFieldG a) Source # 

Associated Types

type Rep (ObjectFieldG a) :: * -> * #

Methods

from :: ObjectFieldG a -> Rep (ObjectFieldG a) x #

to :: Rep (ObjectFieldG a) x -> ObjectFieldG a #

Lift a => Lift (ObjectFieldG a) Source # 

Methods

lift :: ObjectFieldG a -> Q Exp #

Hashable a => Hashable (ObjectFieldG a) Source # 
type Rep (ObjectFieldG a) Source # 
type Rep (ObjectFieldG a) = D1 (MetaData "ObjectFieldG" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "ObjectFieldG" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ofName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Just Symbol "_ofValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

data Directive Source #

Constructors

Directive 

Fields

Instances

Eq Directive Source # 
Show Directive Source # 
Generic Directive Source # 

Associated Types

type Rep Directive :: * -> * #

Lift Directive Source # 

Methods

lift :: Directive -> Q Exp #

Hashable Directive Source # 
type Rep Directive Source # 
type Rep Directive = D1 (MetaData "Directive" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "Directive" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name)) (S1 (MetaSel (Just Symbol "_dArguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Argument]))))

data GType Source #

Instances

Eq GType Source # 

Methods

(==) :: GType -> GType -> Bool #

(/=) :: GType -> GType -> Bool #

Ord GType Source # 

Methods

compare :: GType -> GType -> Ordering #

(<) :: GType -> GType -> Bool #

(<=) :: GType -> GType -> Bool #

(>) :: GType -> GType -> Bool #

(>=) :: GType -> GType -> Bool #

max :: GType -> GType -> GType #

min :: GType -> GType -> GType #

Show GType Source # 

Methods

showsPrec :: Int -> GType -> ShowS #

show :: GType -> String #

showList :: [GType] -> ShowS #

Generic GType Source # 

Associated Types

type Rep GType :: * -> * #

Methods

from :: GType -> Rep GType x #

to :: Rep GType x -> GType #

Lift GType Source # 

Methods

lift :: GType -> Q Exp #

Hashable GType Source # 

Methods

hashWithSalt :: Int -> GType -> Int #

hash :: GType -> Int #

type Rep GType Source # 

class ToGType a where Source #

Minimal complete definition

toGT

Methods

toGT :: a -> GType Source #

class ToNonNullType a where Source #

Minimal complete definition

toNT

Methods

toNT :: a -> NonNullType Source #

newtype NamedType Source #

Constructors

NamedType 

Fields

data NonNullType Source #

Instances

Eq NonNullType Source # 
Ord NonNullType Source # 
Show NonNullType Source # 
Generic NonNullType Source # 

Associated Types

type Rep NonNullType :: * -> * #

Lift NonNullType Source # 

Methods

lift :: NonNullType -> Q Exp #

Hashable NonNullType Source # 
ToGType NonNullType Source # 
type Rep NonNullType Source # 
type Rep NonNullType = D1 (MetaData "NonNullType" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) ((:+:) (C1 (MetaCons "NonNullTypeNamed" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NamedType))) (C1 (MetaCons "NonNullTypeList" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ListType))))

data TypeDefinition Source #

Instances

Eq TypeDefinition Source # 
Show TypeDefinition Source # 
Generic TypeDefinition Source # 

Associated Types

type Rep TypeDefinition :: * -> * #

Lift TypeDefinition Source # 

Methods

lift :: TypeDefinition -> Q Exp #

Hashable TypeDefinition Source # 
type Rep TypeDefinition Source # 

data ObjectTypeDefinition Source #

Instances

Eq ObjectTypeDefinition Source # 
Show ObjectTypeDefinition Source # 
Generic ObjectTypeDefinition Source # 
Lift ObjectTypeDefinition Source # 
Hashable ObjectTypeDefinition Source # 
type Rep ObjectTypeDefinition Source # 
type Rep ObjectTypeDefinition = D1 (MetaData "ObjectTypeDefinition" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "ObjectTypeDefinition" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_otdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Description))) (S1 (MetaSel (Just Symbol "_otdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name))) ((:*:) (S1 (MetaSel (Just Symbol "_otdImplementsInterfaces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [NamedType])) ((:*:) (S1 (MetaSel (Just Symbol "_otdDirectives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Directive])) (S1 (MetaSel (Just Symbol "_otdFieldsDefinition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FieldDefinition]))))))

data FieldDefinition Source #

Instances

Eq FieldDefinition Source # 
Show FieldDefinition Source # 
Generic FieldDefinition Source # 
Lift FieldDefinition Source # 

Methods

lift :: FieldDefinition -> Q Exp #

Hashable FieldDefinition Source # 
type Rep FieldDefinition Source # 
type Rep FieldDefinition = D1 (MetaData "FieldDefinition" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "FieldDefinition" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fldDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Description))) (S1 (MetaSel (Just Symbol "_fldName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name))) ((:*:) (S1 (MetaSel (Just Symbol "_fldArgumentsDefinition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ArgumentsDefinition)) ((:*:) (S1 (MetaSel (Just Symbol "_fldType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GType)) (S1 (MetaSel (Just Symbol "_fldDirectives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Directive]))))))

data InputValueDefinition Source #

Instances

Eq InputValueDefinition Source # 
Show InputValueDefinition Source # 
Generic InputValueDefinition Source # 
Lift InputValueDefinition Source # 
Hashable InputValueDefinition Source # 
type Rep InputValueDefinition Source # 
type Rep InputValueDefinition = D1 (MetaData "InputValueDefinition" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "InputValueDefinition" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ivdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Description))) (S1 (MetaSel (Just Symbol "_ivdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name))) ((:*:) (S1 (MetaSel (Just Symbol "_ivdType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GType)) (S1 (MetaSel (Just Symbol "_ivdDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefaultValue))))))

data InterfaceTypeDefinition Source #

Instances

Eq InterfaceTypeDefinition Source # 
Show InterfaceTypeDefinition Source # 
Generic InterfaceTypeDefinition Source # 
Lift InterfaceTypeDefinition Source # 
Hashable InterfaceTypeDefinition Source # 
type Rep InterfaceTypeDefinition Source # 
type Rep InterfaceTypeDefinition = D1 (MetaData "InterfaceTypeDefinition" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "InterfaceTypeDefinition" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_itdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Description))) (S1 (MetaSel (Just Symbol "_itdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name))) ((:*:) (S1 (MetaSel (Just Symbol "_itdDirectives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Directive])) (S1 (MetaSel (Just Symbol "_itdFieldsDefinition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FieldDefinition])))))

data UnionTypeDefinition Source #

data ScalarTypeDefinition Source #

data EnumTypeDefinition Source #

data EnumValueDefinition Source #

data InputObjectTypeDefinition Source #

Instances

Eq InputObjectTypeDefinition Source # 
Show InputObjectTypeDefinition Source # 
Generic InputObjectTypeDefinition Source # 
Lift InputObjectTypeDefinition Source # 
Hashable InputObjectTypeDefinition Source # 
type Rep InputObjectTypeDefinition Source # 
type Rep InputObjectTypeDefinition = D1 (MetaData "InputObjectTypeDefinition" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) (C1 (MetaCons "InputObjectTypeDefinition" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_iotdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Description))) (S1 (MetaSel (Just Symbol "_iotdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name))) ((:*:) (S1 (MetaSel (Just Symbol "_iotdDirectives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Directive])) (S1 (MetaSel (Just Symbol "_iotdValueDefinitions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [InputValueDefinition])))))

data DirectiveDefinition Source #

Instances

data ExecutableDirectiveLocation Source #

Instances

Eq ExecutableDirectiveLocation Source # 
Show ExecutableDirectiveLocation Source # 
Generic ExecutableDirectiveLocation Source # 
Lift ExecutableDirectiveLocation Source # 
Hashable ExecutableDirectiveLocation Source # 
type Rep ExecutableDirectiveLocation Source # 
type Rep ExecutableDirectiveLocation = D1 (MetaData "ExecutableDirectiveLocation" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) ((:+:) ((:+:) (C1 (MetaCons "EDLQUERY" PrefixI False) U1) ((:+:) (C1 (MetaCons "EDLMUTATION" PrefixI False) U1) (C1 (MetaCons "EDLSUBSCRIPTION" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "EDLFIELD" PrefixI False) U1) (C1 (MetaCons "EDLFRAGMENT_DEFINITION" PrefixI False) U1)) ((:+:) (C1 (MetaCons "EDLFRAGMENT_SPREAD" PrefixI False) U1) (C1 (MetaCons "EDLINLINE_FRAGMENT" PrefixI False) U1))))

data TypeSystemDirectiveLocation Source #

Instances

Eq TypeSystemDirectiveLocation Source # 
Show TypeSystemDirectiveLocation Source # 
Generic TypeSystemDirectiveLocation Source # 
Lift TypeSystemDirectiveLocation Source # 
Hashable TypeSystemDirectiveLocation Source # 
type Rep TypeSystemDirectiveLocation Source # 
type Rep TypeSystemDirectiveLocation = D1 (MetaData "TypeSystemDirectiveLocation" "Language.GraphQL.June2018.Syntax" "graphql-parser-0.1.0.0-FFEgkRwfaX97Co9ScNPTYa" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TSDLSCHEMA" PrefixI False) U1) (C1 (MetaCons "TSDLSCALAR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TSDLOBJECT" PrefixI False) U1) ((:+:) (C1 (MetaCons "TSDLFIELD_DEFINITION" PrefixI False) U1) (C1 (MetaCons "TSDLARGUMENT_DEFINITION" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "TSDLINTERFACE" PrefixI False) U1) ((:+:) (C1 (MetaCons "TSDLUNION" PrefixI False) U1) (C1 (MetaCons "TSDLENUM" PrefixI False) U1))) ((:+:) (C1 (MetaCons "TSDLENUM_VALUE" PrefixI False) U1) ((:+:) (C1 (MetaCons "TSDLINPUT_OBJECT" PrefixI False) U1) (C1 (MetaCons "TSDLINPUT_FIELD_DEFINITION" PrefixI False) U1)))))