forked from OSS/graphql
parent
1dd6b7b013
commit
31c516927d
@ -13,12 +13,8 @@ All notable changes to this project will be documented in this file.
|
|||||||
- Make `Language.GraphQL.AST.Core.Object` is now just a HashMap.
|
- Make `Language.GraphQL.AST.Core.Object` is now just a HashMap.
|
||||||
- `Language.GraphQL.AST.Transform` is now isn't exposed publically anymore.
|
- `Language.GraphQL.AST.Transform` is now isn't exposed publically anymore.
|
||||||
|
|
||||||
### Fixed
|
|
||||||
- (Unsupported) nested fragments doesn't throw a runtime error but return a
|
|
||||||
transformation error.
|
|
||||||
|
|
||||||
### Added
|
### Added
|
||||||
- Nested fragments support without forward lookup.
|
- Nested fragment support.
|
||||||
|
|
||||||
## [0.5.1.0] - 2019-10-22
|
## [0.5.1.0] - 2019-10-22
|
||||||
### Deprecated
|
### Deprecated
|
||||||
|
@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
{-# LANGUAGE ExplicitForAll #-}
|
||||||
|
|
||||||
-- | After the document is parsed, before getting executed the AST is
|
-- | After the document is parsed, before getting executed the AST is
|
||||||
-- transformed into a similar, simpler AST. This module is responsible for
|
-- transformed into a similar, simpler AST. This module is responsible for
|
||||||
@ -7,9 +8,11 @@ module Language.GraphQL.AST.Transform
|
|||||||
( document
|
( document
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad (foldM)
|
import Control.Arrow (first)
|
||||||
|
import Control.Monad (foldM, unless)
|
||||||
import Control.Monad.Trans.Class (lift)
|
import Control.Monad.Trans.Class (lift)
|
||||||
import Control.Monad.Trans.Reader (ReaderT, asks, runReaderT)
|
import Control.Monad.Trans.Reader (ReaderT, ask, runReaderT)
|
||||||
|
import Control.Monad.Trans.State (StateT, evalStateT, gets, modify)
|
||||||
import Data.HashMap.Strict (HashMap)
|
import Data.HashMap.Strict (HashMap)
|
||||||
import qualified Data.HashMap.Strict as HashMap
|
import qualified Data.HashMap.Strict as HashMap
|
||||||
import Data.List.NonEmpty (NonEmpty)
|
import Data.List.NonEmpty (NonEmpty)
|
||||||
@ -19,26 +22,27 @@ import qualified Language.GraphQL.AST.Core as Core
|
|||||||
import qualified Language.GraphQL.Schema as Schema
|
import qualified Language.GraphQL.Schema as Schema
|
||||||
|
|
||||||
-- | Associates a fragment name with a list of 'Core.Field's.
|
-- | Associates a fragment name with a list of 'Core.Field's.
|
||||||
type Fragments = HashMap Core.Name (NonEmpty Core.Selection)
|
|
||||||
|
|
||||||
data Replacement = Replacement
|
data Replacement = Replacement
|
||||||
{ substitute :: Schema.Subs
|
{ fragments :: HashMap Core.Name (NonEmpty Core.Selection)
|
||||||
, fragments :: Fragments
|
, fragmentDefinitions :: HashMap Full.Name Full.FragmentDefinition
|
||||||
}
|
}
|
||||||
|
|
||||||
type TransformT a = ReaderT Replacement Maybe a
|
type TransformT a = StateT Replacement (ReaderT Schema.Subs Maybe) a
|
||||||
|
|
||||||
-- | Rewrites the original syntax tree into an intermediate representation used
|
-- | Rewrites the original syntax tree into an intermediate representation used
|
||||||
-- for query execution.
|
-- for query execution.
|
||||||
document :: Schema.Subs -> Full.Document -> Maybe Core.Document
|
document :: Schema.Subs -> Full.Document -> Maybe Core.Document
|
||||||
document subs doc = do
|
document subs document' =
|
||||||
fragmentMap <- foldr go (Just HashMap.empty) fragments'
|
flip runReaderT subs
|
||||||
runReaderT (operations operations') $ Replacement subs fragmentMap
|
$ evalStateT (collectFragments >> operations operationDefinitions)
|
||||||
|
$ Replacement HashMap.empty fragmentTable
|
||||||
where
|
where
|
||||||
(fragments', operations') = foldr defragment ([], []) doc
|
(fragmentTable, operationDefinitions) = foldr defragment mempty document'
|
||||||
go fragDef (Just fragmentsMap) =
|
defragment (Full.DefinitionOperation definition) acc =
|
||||||
runReaderT (fragmentDefinition fragDef) (Replacement subs fragmentsMap)
|
(definition :) <$> acc
|
||||||
go _ Nothing = Nothing
|
defragment (Full.DefinitionFragment definition) acc =
|
||||||
|
let (Full.FragmentDefinition name _ _ _) = definition
|
||||||
|
in first (HashMap.insert name definition) acc
|
||||||
|
|
||||||
-- * Operation
|
-- * Operation
|
||||||
|
|
||||||
@ -46,7 +50,7 @@ document subs doc = do
|
|||||||
operations :: [Full.OperationDefinition] -> TransformT Core.Document
|
operations :: [Full.OperationDefinition] -> TransformT Core.Document
|
||||||
operations operations' = do
|
operations operations' = do
|
||||||
coreOperations <- traverse operation operations'
|
coreOperations <- traverse operation operations'
|
||||||
lift $ NonEmpty.nonEmpty coreOperations
|
lift . lift $ NonEmpty.nonEmpty coreOperations
|
||||||
|
|
||||||
operation :: Full.OperationDefinition -> TransformT Core.Operation
|
operation :: Full.OperationDefinition -> TransformT Core.Operation
|
||||||
operation (Full.OperationSelectionSet sels) =
|
operation (Full.OperationSelectionSet sels) =
|
||||||
@ -62,8 +66,14 @@ selection ::
|
|||||||
TransformT (Either (NonEmpty Core.Selection) Core.Selection)
|
TransformT (Either (NonEmpty Core.Selection) Core.Selection)
|
||||||
selection (Full.SelectionField fld) = Right . Core.SelectionField <$> field fld
|
selection (Full.SelectionField fld) = Right . Core.SelectionField <$> field fld
|
||||||
selection (Full.SelectionFragmentSpread (Full.FragmentSpread name _)) = do
|
selection (Full.SelectionFragmentSpread (Full.FragmentSpread name _)) = do
|
||||||
fragments' <- asks fragments
|
fragments' <- gets fragments
|
||||||
lift $ Left <$> HashMap.lookup name fragments'
|
Left <$> maybe lookupDefinition liftJust (HashMap.lookup name fragments')
|
||||||
|
where
|
||||||
|
lookupDefinition :: TransformT (NonEmpty Core.Selection)
|
||||||
|
lookupDefinition = do
|
||||||
|
fragmentDefinitions' <- gets fragmentDefinitions
|
||||||
|
found <- lift . lift $ HashMap.lookup name fragmentDefinitions'
|
||||||
|
fragmentDefinition found
|
||||||
selection (Full.SelectionInlineFragment fragment)
|
selection (Full.SelectionInlineFragment fragment)
|
||||||
| (Full.InlineFragment (Just typeCondition) _ selectionSet) <- fragment
|
| (Full.InlineFragment (Just typeCondition) _ selectionSet) <- fragment
|
||||||
= Right
|
= Right
|
||||||
@ -75,25 +85,26 @@ selection (Full.SelectionInlineFragment fragment)
|
|||||||
|
|
||||||
-- * Fragment replacement
|
-- * Fragment replacement
|
||||||
|
|
||||||
-- | Extract fragments into a single 'HashMap' and operation definitions.
|
-- | Extract fragment definitions into a single 'HashMap'.
|
||||||
defragment ::
|
collectFragments :: TransformT ()
|
||||||
Full.Definition ->
|
collectFragments = do
|
||||||
([Full.FragmentDefinition], [Full.OperationDefinition]) ->
|
fragDefs <- gets fragmentDefinitions
|
||||||
([Full.FragmentDefinition], [Full.OperationDefinition])
|
let nextValue = head $ HashMap.elems fragDefs
|
||||||
defragment (Full.DefinitionOperation op) (fragments', operations') =
|
unless (HashMap.null fragDefs) $ do
|
||||||
(fragments', op : operations')
|
_ <- fragmentDefinition nextValue
|
||||||
defragment (Full.DefinitionFragment fragDef) (fragments', operations') =
|
collectFragments
|
||||||
(fragDef : fragments', operations')
|
|
||||||
|
|
||||||
fragmentDefinition :: Full.FragmentDefinition -> TransformT Fragments
|
fragmentDefinition :: Full.FragmentDefinition -> TransformT (NonEmpty Core.Selection)
|
||||||
fragmentDefinition (Full.FragmentDefinition name _tc _dirs sels) = do
|
fragmentDefinition (Full.FragmentDefinition name _tc _dirs sels) = do
|
||||||
newValue <- emitValue
|
selections <- traverse selection sels
|
||||||
fragments' <- asks fragments
|
let newValue = either id pure =<< selections
|
||||||
lift . Just $ HashMap.insert name newValue fragments'
|
modify $ moveFragment newValue
|
||||||
|
liftJust newValue
|
||||||
where
|
where
|
||||||
emitValue = do
|
moveFragment newValue (Replacement fullFragments emptyFragDefs) =
|
||||||
selections <- traverse selection sels
|
let newFragments = HashMap.insert name newValue fullFragments
|
||||||
pure $ selections >>= either id pure
|
newDefinitions = HashMap.delete name emptyFragDefs
|
||||||
|
in Replacement newFragments newDefinitions
|
||||||
|
|
||||||
field :: Full.Field -> TransformT Core.Field
|
field :: Full.Field -> TransformT Core.Field
|
||||||
field (Full.Field a n args _dirs sels) = do
|
field (Full.Field a n args _dirs sels) = do
|
||||||
@ -106,8 +117,8 @@ argument (Full.Argument n v) = Core.Argument n <$> value v
|
|||||||
|
|
||||||
value :: Full.Value -> TransformT Core.Value
|
value :: Full.Value -> TransformT Core.Value
|
||||||
value (Full.Variable n) = do
|
value (Full.Variable n) = do
|
||||||
substitute' <- asks substitute
|
substitute' <- lift ask
|
||||||
lift $ substitute' n
|
lift . lift $ substitute' n
|
||||||
value (Full.Int i) = pure $ Core.Int i
|
value (Full.Int i) = pure $ Core.Int i
|
||||||
value (Full.Float f) = pure $ Core.Float f
|
value (Full.Float f) = pure $ Core.Float f
|
||||||
value (Full.String x) = pure $ Core.String x
|
value (Full.String x) = pure $ Core.String x
|
||||||
@ -137,4 +148,7 @@ appendSelection ::
|
|||||||
TransformT (NonEmpty Core.Selection)
|
TransformT (NonEmpty Core.Selection)
|
||||||
appendSelection fullSelection = do
|
appendSelection fullSelection = do
|
||||||
coreSelection <-appendSelectionOpt fullSelection
|
coreSelection <-appendSelectionOpt fullSelection
|
||||||
lift $ NonEmpty.nonEmpty coreSelection
|
lift . lift $ NonEmpty.nonEmpty coreSelection
|
||||||
|
|
||||||
|
liftJust :: forall a. a -> TransformT a
|
||||||
|
liftJust = lift . lift . Just
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
resolver: lts-14.13
|
resolver: lts-14.14
|
||||||
|
|
||||||
packages:
|
packages:
|
||||||
- .
|
- .
|
||||||
|
@ -98,14 +98,37 @@ spec = describe "Inline fragment executor" $ do
|
|||||||
it "evaluates nested fragments" $ do
|
it "evaluates nested fragments" $ do
|
||||||
let query = [r|
|
let query = [r|
|
||||||
{
|
{
|
||||||
...hatFragment
|
...circumferenceFragment
|
||||||
|
}
|
||||||
|
|
||||||
|
fragment circumferenceFragment on Hat {
|
||||||
|
circumference
|
||||||
}
|
}
|
||||||
|
|
||||||
fragment hatFragment on Hat {
|
fragment hatFragment on Hat {
|
||||||
...circumferenceFragment
|
...circumferenceFragment
|
||||||
}
|
}
|
||||||
|
|]
|
||||||
|
|
||||||
|
actual <- graphql (circumference :| []) query
|
||||||
|
let expected = object
|
||||||
|
[ "data" .= object
|
||||||
|
[ "circumference" .= (60 :: Int)
|
||||||
|
]
|
||||||
|
]
|
||||||
|
in actual `shouldBe` expected
|
||||||
|
|
||||||
|
it "evaluates fragments defined in any order" $ do
|
||||||
|
let query = [r|
|
||||||
|
{
|
||||||
|
...circumferenceFragment
|
||||||
|
}
|
||||||
|
|
||||||
fragment circumferenceFragment on Hat {
|
fragment circumferenceFragment on Hat {
|
||||||
|
...hatFragment
|
||||||
|
}
|
||||||
|
|
||||||
|
fragment hatFragment on Hat {
|
||||||
circumference
|
circumference
|
||||||
}
|
}
|
||||||
|]
|
|]
|
||||||
|
Loading…
Reference in New Issue
Block a user