forked from OSS/graphql
Remove Type Definition support
This commit is contained in:
parent
933cfd2852
commit
10fdf05aa7
@ -17,7 +17,6 @@ newtype Document = Document [Definition] deriving (Eq,Show)
|
||||
|
||||
data Definition = DefinitionOperation OperationDefinition
|
||||
| DefinitionFragment FragmentDefinition
|
||||
| DefinitionType TypeDefinition
|
||||
deriving (Eq,Show)
|
||||
|
||||
data OperationDefinition = Query Node
|
||||
@ -127,48 +126,3 @@ newtype ListType = ListType Type deriving (Eq,Show)
|
||||
data NonNullType = NonNullTypeNamed NamedType
|
||||
| NonNullTypeList ListType
|
||||
deriving (Eq,Show)
|
||||
|
||||
-- * Type definition
|
||||
|
||||
data TypeDefinition = TypeDefinitionObject ObjectTypeDefinition
|
||||
| TypeDefinitionInterface InterfaceTypeDefinition
|
||||
| TypeDefinitionUnion UnionTypeDefinition
|
||||
| TypeDefinitionScalar ScalarTypeDefinition
|
||||
| TypeDefinitionEnum EnumTypeDefinition
|
||||
| TypeDefinitionInputObject InputObjectTypeDefinition
|
||||
| TypeDefinitionTypeExtension TypeExtensionDefinition
|
||||
deriving (Eq,Show)
|
||||
|
||||
data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces [FieldDefinition]
|
||||
deriving (Eq,Show)
|
||||
|
||||
type Interfaces = [NamedType]
|
||||
|
||||
data FieldDefinition = FieldDefinition Name ArgumentsDefinition Type
|
||||
deriving (Eq,Show)
|
||||
|
||||
type ArgumentsDefinition = [InputValueDefinition]
|
||||
|
||||
data InputValueDefinition = InputValueDefinition Name Type (Maybe DefaultValue)
|
||||
deriving (Eq,Show)
|
||||
|
||||
data InterfaceTypeDefinition = InterfaceTypeDefinition Name [FieldDefinition]
|
||||
deriving (Eq,Show)
|
||||
|
||||
data UnionTypeDefinition = UnionTypeDefinition Name [NamedType]
|
||||
deriving (Eq,Show)
|
||||
|
||||
newtype ScalarTypeDefinition = ScalarTypeDefinition Name
|
||||
deriving (Eq,Show)
|
||||
|
||||
data EnumTypeDefinition = EnumTypeDefinition Name [EnumValueDefinition]
|
||||
deriving (Eq,Show)
|
||||
|
||||
newtype EnumValueDefinition = EnumValueDefinition Name
|
||||
deriving (Eq,Show)
|
||||
|
||||
data InputObjectTypeDefinition = InputObjectTypeDefinition Name [InputValueDefinition]
|
||||
deriving (Eq,Show)
|
||||
|
||||
newtype TypeExtensionDefinition = TypeExtensionDefinition ObjectTypeDefinition
|
||||
deriving (Eq,Show)
|
||||
|
@ -17,7 +17,6 @@ document (Document defs) = (`snoc` '\n') . mconcat $ definition <$> defs
|
||||
definition :: Definition -> Text
|
||||
definition (DefinitionOperation x) = operationDefinition x
|
||||
definition (DefinitionFragment x) = fragmentDefinition x
|
||||
definition (DefinitionType x) = typeDefinition x
|
||||
|
||||
operationDefinition :: OperationDefinition -> Text
|
||||
operationDefinition (Query n) = "query " <> node n
|
||||
@ -139,73 +138,6 @@ nonNullType :: NonNullType -> Text
|
||||
nonNullType (NonNullTypeNamed (NamedType x)) = x <> "!"
|
||||
nonNullType (NonNullTypeList x) = listType x <> "!"
|
||||
|
||||
typeDefinition :: TypeDefinition -> Text
|
||||
typeDefinition (TypeDefinitionObject x) = objectTypeDefinition x
|
||||
typeDefinition (TypeDefinitionInterface x) = interfaceTypeDefinition x
|
||||
typeDefinition (TypeDefinitionUnion x) = unionTypeDefinition x
|
||||
typeDefinition (TypeDefinitionScalar x) = scalarTypeDefinition x
|
||||
typeDefinition (TypeDefinitionEnum x) = enumTypeDefinition x
|
||||
typeDefinition (TypeDefinitionInputObject x) = inputObjectTypeDefinition x
|
||||
typeDefinition (TypeDefinitionTypeExtension x) = typeExtensionDefinition x
|
||||
|
||||
objectTypeDefinition :: ObjectTypeDefinition -> Text
|
||||
objectTypeDefinition (ObjectTypeDefinition name ifaces fds) =
|
||||
"type " <> name
|
||||
<> optempty (spaced . interfaces) ifaces
|
||||
<> optempty fieldDefinitions fds
|
||||
|
||||
interfaces :: Interfaces -> Text
|
||||
interfaces = ("implements " <>) . spaces namedType
|
||||
|
||||
fieldDefinitions :: [FieldDefinition] -> Text
|
||||
fieldDefinitions = bracesCommas fieldDefinition
|
||||
|
||||
fieldDefinition :: FieldDefinition -> Text
|
||||
fieldDefinition (FieldDefinition name args ty) =
|
||||
name <> optempty argumentsDefinition args
|
||||
<> ":"
|
||||
<> type_ ty
|
||||
|
||||
argumentsDefinition :: ArgumentsDefinition -> Text
|
||||
argumentsDefinition = parensCommas inputValueDefinition
|
||||
|
||||
interfaceTypeDefinition :: InterfaceTypeDefinition -> Text
|
||||
interfaceTypeDefinition (InterfaceTypeDefinition name fds) =
|
||||
"interface " <> name <> fieldDefinitions fds
|
||||
|
||||
unionTypeDefinition :: UnionTypeDefinition -> Text
|
||||
unionTypeDefinition (UnionTypeDefinition name ums) =
|
||||
"union " <> name <> "=" <> unionMembers ums
|
||||
|
||||
unionMembers :: [NamedType] -> Text
|
||||
unionMembers = intercalate "|" . fmap namedType
|
||||
|
||||
scalarTypeDefinition :: ScalarTypeDefinition -> Text
|
||||
scalarTypeDefinition (ScalarTypeDefinition name) = "scalar " <> name
|
||||
|
||||
enumTypeDefinition :: EnumTypeDefinition -> Text
|
||||
enumTypeDefinition (EnumTypeDefinition name evds) =
|
||||
"enum " <> name
|
||||
<> bracesCommas enumValueDefinition evds
|
||||
|
||||
enumValueDefinition :: EnumValueDefinition -> Text
|
||||
enumValueDefinition (EnumValueDefinition name) = name
|
||||
|
||||
inputObjectTypeDefinition :: InputObjectTypeDefinition -> Text
|
||||
inputObjectTypeDefinition (InputObjectTypeDefinition name ivds) =
|
||||
"input " <> name <> inputValueDefinitions ivds
|
||||
|
||||
inputValueDefinitions :: [InputValueDefinition] -> Text
|
||||
inputValueDefinitions = bracesCommas inputValueDefinition
|
||||
|
||||
inputValueDefinition :: InputValueDefinition -> Text
|
||||
inputValueDefinition (InputValueDefinition name ty dv) =
|
||||
name <> ":" <> type_ ty <> maybe mempty defaultValue dv
|
||||
|
||||
typeExtensionDefinition :: TypeExtensionDefinition -> Text
|
||||
typeExtensionDefinition (TypeExtensionDefinition otd) =
|
||||
"extend " <> objectTypeDefinition otd
|
||||
|
||||
-- * Internal
|
||||
|
||||
spaced :: Text -> Text
|
||||
|
@ -22,7 +22,6 @@ import Data.Attoparsec.Text
|
||||
, manyTill
|
||||
, option
|
||||
, peekChar
|
||||
, sepBy1
|
||||
, takeWhile
|
||||
, takeWhile1
|
||||
)
|
||||
@ -54,7 +53,6 @@ document = whiteSpace
|
||||
definition :: Parser Definition
|
||||
definition = DefinitionOperation <$> operationDefinition
|
||||
<|> DefinitionFragment <$> fragmentDefinition
|
||||
<|> DefinitionType <$> typeDefinition
|
||||
<?> "definition error!"
|
||||
|
||||
operationDefinition :: Parser OperationDefinition
|
||||
@ -207,96 +205,6 @@ nonNullType = NonNullTypeNamed <$> namedType <* tok "!"
|
||||
<|> NonNullTypeList <$> listType <* tok "!"
|
||||
<?> "nonNullType error!"
|
||||
|
||||
-- * Type Definition
|
||||
|
||||
typeDefinition :: Parser TypeDefinition
|
||||
typeDefinition =
|
||||
TypeDefinitionObject <$> objectTypeDefinition
|
||||
<|> TypeDefinitionInterface <$> interfaceTypeDefinition
|
||||
<|> TypeDefinitionUnion <$> unionTypeDefinition
|
||||
<|> TypeDefinitionScalar <$> scalarTypeDefinition
|
||||
<|> TypeDefinitionEnum <$> enumTypeDefinition
|
||||
<|> TypeDefinitionInputObject <$> inputObjectTypeDefinition
|
||||
<|> TypeDefinitionTypeExtension <$> typeExtensionDefinition
|
||||
<?> "typeDefinition error!"
|
||||
|
||||
objectTypeDefinition :: Parser ObjectTypeDefinition
|
||||
objectTypeDefinition = ObjectTypeDefinition
|
||||
<$ tok "type"
|
||||
<*> name
|
||||
<*> optempty interfaces
|
||||
<*> fieldDefinitions
|
||||
|
||||
interfaces :: Parser Interfaces
|
||||
interfaces = tok "implements" *> many1 namedType
|
||||
|
||||
fieldDefinitions :: Parser [FieldDefinition]
|
||||
fieldDefinitions = braces $ many1 fieldDefinition
|
||||
|
||||
fieldDefinition :: Parser FieldDefinition
|
||||
fieldDefinition = FieldDefinition
|
||||
<$> name
|
||||
<*> optempty argumentsDefinition
|
||||
<* tok ":"
|
||||
<*> type_
|
||||
|
||||
argumentsDefinition :: Parser ArgumentsDefinition
|
||||
argumentsDefinition = parens $ many1 inputValueDefinition
|
||||
|
||||
interfaceTypeDefinition :: Parser InterfaceTypeDefinition
|
||||
interfaceTypeDefinition = InterfaceTypeDefinition
|
||||
<$ tok "interface"
|
||||
<*> name
|
||||
<*> fieldDefinitions
|
||||
|
||||
unionTypeDefinition :: Parser UnionTypeDefinition
|
||||
unionTypeDefinition = UnionTypeDefinition
|
||||
<$ tok "union"
|
||||
<*> name
|
||||
<* tok "="
|
||||
<*> unionMembers
|
||||
|
||||
unionMembers :: Parser [NamedType]
|
||||
unionMembers = namedType `sepBy1` tok "|"
|
||||
|
||||
scalarTypeDefinition :: Parser ScalarTypeDefinition
|
||||
scalarTypeDefinition = ScalarTypeDefinition
|
||||
<$ tok "scalar"
|
||||
<*> name
|
||||
|
||||
enumTypeDefinition :: Parser EnumTypeDefinition
|
||||
enumTypeDefinition = EnumTypeDefinition
|
||||
<$ tok "enum"
|
||||
<*> name
|
||||
<*> enumValueDefinitions
|
||||
|
||||
enumValueDefinitions :: Parser [EnumValueDefinition]
|
||||
enumValueDefinitions = braces $ many1 enumValueDefinition
|
||||
|
||||
enumValueDefinition :: Parser EnumValueDefinition
|
||||
enumValueDefinition = EnumValueDefinition <$> name
|
||||
|
||||
inputObjectTypeDefinition :: Parser InputObjectTypeDefinition
|
||||
inputObjectTypeDefinition = InputObjectTypeDefinition
|
||||
<$ tok "input"
|
||||
<*> name
|
||||
<*> inputValueDefinitions
|
||||
|
||||
inputValueDefinitions :: Parser [InputValueDefinition]
|
||||
inputValueDefinitions = braces $ many1 inputValueDefinition
|
||||
|
||||
inputValueDefinition :: Parser InputValueDefinition
|
||||
inputValueDefinition = InputValueDefinition
|
||||
<$> name
|
||||
<* tok ":"
|
||||
<*> type_
|
||||
<*> optional defaultValue
|
||||
|
||||
typeExtensionDefinition :: Parser TypeExtensionDefinition
|
||||
typeExtensionDefinition = TypeExtensionDefinition
|
||||
<$ tok "extend"
|
||||
<*> objectTypeDefinition
|
||||
|
||||
-- * Internal
|
||||
|
||||
tok :: Parser a -> Parser a
|
||||
|
Loading…
Reference in New Issue
Block a user