Support inline fragments on types
This commit is contained in:
@ -4,16 +4,18 @@ module Language.GraphQL.AST.Core
|
||||
, Argument(..)
|
||||
, Document
|
||||
, Field(..)
|
||||
, Fragment(..)
|
||||
, Name
|
||||
, ObjectField(..)
|
||||
, Operation(..)
|
||||
, Selection(..)
|
||||
, TypeCondition
|
||||
, Value(..)
|
||||
) where
|
||||
|
||||
import Data.Int (Int32)
|
||||
import Data.List.NonEmpty (NonEmpty)
|
||||
import Data.String
|
||||
|
||||
import Data.Text (Text)
|
||||
|
||||
-- | Name
|
||||
@ -26,8 +28,8 @@ type Document = NonEmpty Operation
|
||||
--
|
||||
-- Currently only queries and mutations are supported.
|
||||
data Operation
|
||||
= Query (Maybe Text) (NonEmpty Field)
|
||||
| Mutation (Maybe Text) (NonEmpty Field)
|
||||
= Query (Maybe Text) (NonEmpty Selection)
|
||||
| Mutation (Maybe Text) (NonEmpty Selection)
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | A single GraphQL field.
|
||||
@ -51,7 +53,7 @@ data Operation
|
||||
-- * "zuck" is an alias for "user". "id" and "name" have no aliases.
|
||||
-- * "id: 4" is an argument for "name". "id" and "name don't have any
|
||||
-- arguments.
|
||||
data Field = Field (Maybe Alias) Name [Argument] [Field] deriving (Eq, Show)
|
||||
data Field = Field (Maybe Alias) Name [Argument] [Selection] deriving (Eq, Show)
|
||||
|
||||
-- | Alternative field name.
|
||||
--
|
||||
@ -100,3 +102,17 @@ instance IsString Value where
|
||||
--
|
||||
-- A list of 'ObjectField's represents a GraphQL object type.
|
||||
data ObjectField = ObjectField Name Value deriving (Eq, Show)
|
||||
|
||||
-- | Type condition.
|
||||
type TypeCondition = Name
|
||||
|
||||
-- | Represents fragments and inline fragments.
|
||||
data Fragment
|
||||
= Fragment TypeCondition (NonEmpty Selection)
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | Single selection element.
|
||||
data Selection
|
||||
= SelectionFragment Fragment
|
||||
| SelectionField Field
|
||||
deriving (Eq, Show)
|
||||
|
@ -65,13 +65,21 @@ selection
|
||||
:: Schema.Subs
|
||||
-> Fragmenter
|
||||
-> Full.Selection
|
||||
-> Either [Core.Field] Core.Field
|
||||
-> Either [Core.Selection] Core.Selection
|
||||
selection subs fr (Full.SelectionField fld) =
|
||||
Right $ field subs fr fld
|
||||
Right $ Core.SelectionField $ field subs fr fld
|
||||
selection _ fr (Full.SelectionFragmentSpread (Full.FragmentSpread n _dirs)) =
|
||||
Left $ fr n
|
||||
selection _ _ (Full.SelectionInlineFragment _) =
|
||||
error "Inline fragments not supported yet"
|
||||
Left $ Core.SelectionField <$> fr n
|
||||
selection subs fr (Full.SelectionInlineFragment fragment)
|
||||
| (Full.InlineFragment (Just typeCondition) _ selectionSet) <- fragment
|
||||
= Right $ Core.SelectionFragment $ Core.Fragment typeCondition $ node selectionSet
|
||||
| otherwise = error "Inline fragments not supported yet"
|
||||
where
|
||||
node selections
|
||||
= NonEmpty.fromList
|
||||
$ foldr (appendSelection . selection subs fr) [] selections
|
||||
appendSelection (Left x) acc = x ++ acc
|
||||
appendSelection (Right x) acc = x : acc
|
||||
|
||||
-- * Fragment replacement
|
||||
|
||||
@ -87,19 +95,23 @@ defrag subs (Full.DefinitionFragment fragDef) =
|
||||
Left $ fragmentDefinition subs fragDef
|
||||
|
||||
fragmentDefinition :: Schema.Subs -> Full.FragmentDefinition -> Fragmenter
|
||||
fragmentDefinition subs (Full.FragmentDefinition name _tc _dirs sels) name' =
|
||||
-- TODO: Support fragments within fragments. Fold instead of map.
|
||||
if name == name'
|
||||
then either id pure =<< NonEmpty.toList (selection subs mempty <$> sels)
|
||||
else empty
|
||||
fragmentDefinition subs (Full.FragmentDefinition name _tc _dirs sels) name'
|
||||
-- TODO: Support fragments within fragments. Fold instead of map.
|
||||
| name == name' = selection' <$> do
|
||||
selections <- NonEmpty.toList $ selection subs mempty <$> sels
|
||||
either id pure selections
|
||||
| otherwise = empty
|
||||
where
|
||||
selection' (Core.SelectionField field') = field'
|
||||
selection' _ = error "Inline fragments not supported yet"
|
||||
|
||||
field :: Schema.Subs -> Fragmenter -> Full.Field -> Core.Field
|
||||
field subs fr (Full.Field a n args _dirs sels) =
|
||||
Core.Field a n (fold $ argument subs `traverse` args) (foldr go empty sels)
|
||||
where
|
||||
go :: Full.Selection -> [Core.Field] -> [Core.Field]
|
||||
go (Full.SelectionFragmentSpread (Full.FragmentSpread name _dirs)) = (fr name <>)
|
||||
go sel = (either id pure (selection subs fr sel) <>)
|
||||
go :: Full.Selection -> [Core.Selection] -> [Core.Selection]
|
||||
go (Full.SelectionFragmentSpread (Full.FragmentSpread name _dirs)) = ((Core.SelectionField <$> fr name) <>)
|
||||
go sel = (either id pure (selection subs fr sel) <>)
|
||||
|
||||
argument :: Schema.Subs -> Full.Argument -> Maybe Core.Argument
|
||||
argument subs (Full.Argument n v) = Core.Argument n <$> value subs v
|
||||
|
Reference in New Issue
Block a user