Parse union definitions
This commit is contained in:
parent
8efb08fda1
commit
f4ed06741d
@ -1,3 +1,5 @@
|
|||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
-- | This module defines an abstract syntax tree for the @GraphQL@ language. It
|
-- | This module defines an abstract syntax tree for the @GraphQL@ language. It
|
||||||
-- follows closely the structure given in the specification. Please refer to
|
-- follows closely the structure given in the specification. Please refer to
|
||||||
-- <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
|
-- <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
|
||||||
@ -14,9 +16,9 @@ module Language.GraphQL.AST.Document
|
|||||||
, FieldDefinition(..)
|
, FieldDefinition(..)
|
||||||
, FragmentDefinition(..)
|
, FragmentDefinition(..)
|
||||||
, ImplementsInterfaces(..)
|
, ImplementsInterfaces(..)
|
||||||
, ImplementsInterfacesOpt(..)
|
|
||||||
, InputValueDefinition(..)
|
, InputValueDefinition(..)
|
||||||
, Name
|
, Name
|
||||||
|
, NamedType
|
||||||
, NonNullType(..)
|
, NonNullType(..)
|
||||||
, ObjectField(..)
|
, ObjectField(..)
|
||||||
, OperationDefinition(..)
|
, OperationDefinition(..)
|
||||||
@ -29,14 +31,18 @@ module Language.GraphQL.AST.Document
|
|||||||
, Type(..)
|
, Type(..)
|
||||||
, TypeCondition
|
, TypeCondition
|
||||||
, TypeDefinition(..)
|
, TypeDefinition(..)
|
||||||
|
, TypeExtension(..)
|
||||||
, TypeSystemDefinition(..)
|
, TypeSystemDefinition(..)
|
||||||
|
, UnionMemberTypes(..)
|
||||||
, Value(..)
|
, Value(..)
|
||||||
, VariableDefinition(..)
|
, VariableDefinition(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Foldable (toList)
|
||||||
import Data.Int (Int32)
|
import Data.Int (Int32)
|
||||||
import Data.List.NonEmpty (NonEmpty)
|
import Data.List.NonEmpty (NonEmpty)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as Text
|
||||||
import Language.GraphQL.AST.DirectiveLocation
|
import Language.GraphQL.AST.DirectiveLocation
|
||||||
|
|
||||||
-- * Language
|
-- * Language
|
||||||
@ -274,9 +280,13 @@ newtype Description = Description (Maybe Text)
|
|||||||
data TypeDefinition
|
data TypeDefinition
|
||||||
= ScalarTypeDefinition Description Name [Directive]
|
= ScalarTypeDefinition Description Name [Directive]
|
||||||
| ObjectTypeDefinition
|
| ObjectTypeDefinition
|
||||||
Description Name ImplementsInterfacesOpt [Directive] [FieldDefinition]
|
Description
|
||||||
|
Name
|
||||||
|
(ImplementsInterfaces [])
|
||||||
|
[Directive]
|
||||||
|
[FieldDefinition]
|
||||||
| InterfaceTypeDefinition Description Name [Directive] [FieldDefinition]
|
| InterfaceTypeDefinition Description Name [Directive] [FieldDefinition]
|
||||||
| UnionTypeDefinition Description Name [Directive] UnionMemberTypesOpt
|
| UnionTypeDefinition Description Name [Directive] (UnionMemberTypes [])
|
||||||
| EnumTypeDefinition Description Name [Directive] [EnumValueDefinition]
|
| EnumTypeDefinition Description Name [Directive] [EnumValueDefinition]
|
||||||
| InputObjectTypeDefinition
|
| InputObjectTypeDefinition
|
||||||
Description Name [Directive] InputFieldsDefinitionOpt
|
Description Name [Directive] InputFieldsDefinitionOpt
|
||||||
@ -285,14 +295,16 @@ data TypeDefinition
|
|||||||
data TypeExtension
|
data TypeExtension
|
||||||
= ScalarTypeExtension Name (NonEmpty Directive)
|
= ScalarTypeExtension Name (NonEmpty Directive)
|
||||||
| ObjectTypeFieldsDefinitionExtension
|
| ObjectTypeFieldsDefinitionExtension
|
||||||
Name ImplementsInterfacesOpt [Directive] (NonEmpty FieldDefinition)
|
Name (ImplementsInterfaces []) [Directive] (NonEmpty FieldDefinition)
|
||||||
| ObjectTypeDirectivesExtension
|
| ObjectTypeDirectivesExtension
|
||||||
Name ImplementsInterfacesOpt (NonEmpty Directive)
|
Name (ImplementsInterfaces []) (NonEmpty Directive)
|
||||||
| ObjectTypeImplementsInterfacesExtension Name ImplementsInterfaces
|
| ObjectTypeImplementsInterfacesExtension
|
||||||
|
Name (ImplementsInterfaces NonEmpty)
|
||||||
| InterfaceTypeFieldsDefinitionExtension
|
| InterfaceTypeFieldsDefinitionExtension
|
||||||
Name [Directive] (NonEmpty FieldDefinition)
|
Name [Directive] (NonEmpty FieldDefinition)
|
||||||
| InterfaceTypeDirectivesExtension Name (NonEmpty Directive)
|
| InterfaceTypeDirectivesExtension Name (NonEmpty Directive)
|
||||||
| UnionTypeUnionMemberTypesExtension Name [Directive] UnionMemberTypes
|
| UnionTypeUnionMemberTypesExtension
|
||||||
|
Name [Directive] (UnionMemberTypes NonEmpty)
|
||||||
| UnionDirectivesExtension Name (NonEmpty Directive)
|
| UnionDirectivesExtension Name (NonEmpty Directive)
|
||||||
| EnumTypeEnumValuesDefinitionExtension
|
| EnumTypeEnumValuesDefinitionExtension
|
||||||
Name [Directive] (NonEmpty EnumValueDefinition)
|
Name [Directive] (NonEmpty EnumValueDefinition)
|
||||||
@ -304,17 +316,17 @@ data TypeExtension
|
|||||||
|
|
||||||
-- ** Objects
|
-- ** Objects
|
||||||
|
|
||||||
newtype ImplementsInterfaces = ImplementsInterfaces (NonEmpty NamedType)
|
newtype ImplementsInterfaces t = ImplementsInterfaces (t NamedType)
|
||||||
deriving (Eq, Show)
|
|
||||||
newtype ImplementsInterfacesOpt = ImplementsInterfacesOpt [NamedType]
|
|
||||||
deriving (Eq, Show)
|
|
||||||
|
|
||||||
instance Semigroup ImplementsInterfacesOpt where
|
instance Foldable t => Eq (ImplementsInterfaces t) where
|
||||||
(ImplementsInterfacesOpt xs) <> (ImplementsInterfacesOpt ys) =
|
(ImplementsInterfaces xs) == (ImplementsInterfaces ys)
|
||||||
ImplementsInterfacesOpt $ xs <> ys
|
= toList xs == toList ys
|
||||||
|
|
||||||
instance Monoid ImplementsInterfacesOpt where
|
instance Foldable t => Show (ImplementsInterfaces t) where
|
||||||
mempty = ImplementsInterfacesOpt []
|
show (ImplementsInterfaces interfaces) = Text.unpack
|
||||||
|
$ Text.append "implements"
|
||||||
|
$ Text.intercalate " & "
|
||||||
|
$ toList interfaces
|
||||||
|
|
||||||
data FieldDefinition
|
data FieldDefinition
|
||||||
= FieldDefinition Description Name ArgumentsDefinition Type [Directive]
|
= FieldDefinition Description Name ArgumentsDefinition Type [Directive]
|
||||||
@ -336,11 +348,15 @@ data InputValueDefinition
|
|||||||
|
|
||||||
-- ** Unions
|
-- ** Unions
|
||||||
|
|
||||||
newtype UnionMemberTypes = UnionMemberTypes (NonEmpty NamedType)
|
newtype UnionMemberTypes t = UnionMemberTypes (t NamedType)
|
||||||
deriving (Eq, Show)
|
|
||||||
|
|
||||||
newtype UnionMemberTypesOpt = UnionMemberTypesOpt [NamedType]
|
instance Foldable t => Eq (UnionMemberTypes t) where
|
||||||
deriving (Eq, Show)
|
(UnionMemberTypes xs) == (UnionMemberTypes ys) = toList xs == toList ys
|
||||||
|
|
||||||
|
instance Foldable t => Show (UnionMemberTypes t) where
|
||||||
|
show (UnionMemberTypes memberTypes) = Text.unpack
|
||||||
|
$ Text.intercalate " | "
|
||||||
|
$ toList memberTypes
|
||||||
|
|
||||||
-- ** Enums
|
-- ** Enums
|
||||||
|
|
||||||
|
@ -8,7 +8,8 @@ module Language.GraphQL.AST.Parser
|
|||||||
|
|
||||||
import Control.Applicative (Alternative(..), optional)
|
import Control.Applicative (Alternative(..), optional)
|
||||||
import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
|
import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
|
||||||
import Control.Applicative.Combinators (sepBy)
|
import Control.Applicative.Combinators (sepBy, sepBy1)
|
||||||
|
import Data.Text (Text)
|
||||||
import Language.GraphQL.AST.Document
|
import Language.GraphQL.AST.Document
|
||||||
import Language.GraphQL.AST.Lexer
|
import Language.GraphQL.AST.Lexer
|
||||||
import Text.Megaparsec (lookAhead, option, try, (<?>))
|
import Text.Megaparsec (lookAhead, option, try, (<?>))
|
||||||
@ -37,6 +38,7 @@ typeSystemDefinition = schemaDefinition
|
|||||||
typeDefinition :: Parser TypeDefinition
|
typeDefinition :: Parser TypeDefinition
|
||||||
typeDefinition = scalarTypeDefinition
|
typeDefinition = scalarTypeDefinition
|
||||||
<|> objectTypeDefinition
|
<|> objectTypeDefinition
|
||||||
|
<|> unionTypeDefinition
|
||||||
<?> "TypeDefinition"
|
<?> "TypeDefinition"
|
||||||
|
|
||||||
scalarTypeDefinition :: Parser TypeDefinition
|
scalarTypeDefinition :: Parser TypeDefinition
|
||||||
@ -52,7 +54,7 @@ objectTypeDefinition = ObjectTypeDefinition
|
|||||||
<$> description
|
<$> description
|
||||||
<* symbol "type"
|
<* symbol "type"
|
||||||
<*> name
|
<*> name
|
||||||
<*> opt implementsInterfacesOpt
|
<*> option (ImplementsInterfaces []) (implementsInterfaces sepBy1)
|
||||||
<*> opt directives
|
<*> opt directives
|
||||||
<*> braces (many fieldDefinition)
|
<*> braces (many fieldDefinition)
|
||||||
<?> "ObjectTypeDefinition"
|
<?> "ObjectTypeDefinition"
|
||||||
@ -62,19 +64,33 @@ description = Description
|
|||||||
<$> optional (string <|> blockString)
|
<$> optional (string <|> blockString)
|
||||||
<?> "Description"
|
<?> "Description"
|
||||||
|
|
||||||
{- TODO:
|
unionTypeDefinition :: Parser TypeDefinition
|
||||||
implementsInterfaces :: Parser ImplementsInterfaces
|
unionTypeDefinition = UnionTypeDefinition
|
||||||
implementsInterfaces = ImplementsInterfaces
|
<$> description
|
||||||
<$ symbol "implements"
|
<* symbol "union"
|
||||||
<* optional amp
|
<*> name
|
||||||
<*> name `sepBy1` amp
|
<*> opt directives
|
||||||
<?> "ImplementsInterfaces" -}
|
<*> option (UnionMemberTypes []) (unionMemberTypes sepBy1)
|
||||||
|
<?> "UnionTypeDefinition"
|
||||||
|
|
||||||
implementsInterfacesOpt :: Parser ImplementsInterfacesOpt
|
unionMemberTypes ::
|
||||||
implementsInterfacesOpt = ImplementsInterfacesOpt
|
Foldable t =>
|
||||||
|
(Parser Text -> Parser Text -> Parser (t NamedType)) ->
|
||||||
|
Parser (UnionMemberTypes t)
|
||||||
|
unionMemberTypes sepBy' = UnionMemberTypes
|
||||||
|
<$ equals
|
||||||
|
<* optional pipe
|
||||||
|
<*> name `sepBy'` pipe
|
||||||
|
<?> "UnionMemberTypes"
|
||||||
|
|
||||||
|
implementsInterfaces ::
|
||||||
|
Foldable t =>
|
||||||
|
(Parser Text -> Parser Text -> Parser (t NamedType)) ->
|
||||||
|
Parser (ImplementsInterfaces t)
|
||||||
|
implementsInterfaces sepBy' = ImplementsInterfaces
|
||||||
<$ symbol "implements"
|
<$ symbol "implements"
|
||||||
<* optional amp
|
<* optional amp
|
||||||
<*> name `sepBy` amp
|
<*> name `sepBy'` amp
|
||||||
<?> "ImplementsInterfaces"
|
<?> "ImplementsInterfaces"
|
||||||
|
|
||||||
inputValueDefinition :: Parser InputValueDefinition
|
inputValueDefinition :: Parser InputValueDefinition
|
||||||
|
@ -69,3 +69,8 @@ spec = describe "Parser" $ do
|
|||||||
name(first: String, last: String): String
|
name(first: String, last: String): String
|
||||||
}
|
}
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
it "parses minimal union type definition" $
|
||||||
|
parse document "" `shouldSucceedOn` [r|
|
||||||
|
union SearchResult = Photo | Person
|
||||||
|
|]
|
||||||
|
Loading…
Reference in New Issue
Block a user