Save fragments in a hash map

Fixes #20.
This commit is contained in:
Eugen Wissner 2019-10-31 07:32:51 +01:00
parent 51d39b69e8
commit 0e3b6184be
2 changed files with 74 additions and 71 deletions

View File

@ -7,106 +7,109 @@ module Language.GraphQL.AST.Transform
( document ( document
) where ) where
import Control.Applicative (empty) import Data.Foldable (fold)
import Data.Bifunctor (first) import Data.HashMap.Strict (HashMap)
import Data.Either (partitionEithers) import qualified Data.HashMap.Strict as HashMap
import Data.Foldable (fold, foldMap)
import Data.List.NonEmpty (NonEmpty) import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NonEmpty import qualified Data.List.NonEmpty as NonEmpty
import Data.Monoid (Alt(Alt,getAlt), (<>)) import Data.Maybe (fromMaybe)
import qualified Language.GraphQL.AST as Full import qualified Language.GraphQL.AST as Full
import qualified Language.GraphQL.AST.Core as Core import qualified Language.GraphQL.AST.Core as Core
import qualified Language.GraphQL.Schema as Schema import qualified Language.GraphQL.Schema as Schema
-- | Replaces a fragment name by a list of 'Core.Field'. If the name doesn't -- | Associates a fragment name with a list of 'Core.Field's.
-- match an empty list is returned. type Fragments = HashMap Core.Name [Core.Field]
type Fragmenter = Core.Name -> [Core.Field]
-- | 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 = operations subs fr ops document subs doc = operations subs fragments operations'
where where
(fr, ops) = first foldFrags (fragments, operations') = foldr (defrag subs) mempty
. partitionEithers $ NonEmpty.toList doc
. NonEmpty.toList
$ defrag subs
<$> doc
foldFrags :: [Fragmenter] -> Fragmenter extractFragment :: Fragments -> Core.Name -> [Core.Selection]
foldFrags fs n = getAlt $ foldMap (Alt . ($ n)) fs extractFragment fragments name = Core.SelectionField
<$> fromMaybe mempty (HashMap.lookup name fragments)
-- * Operation -- * Operation
-- TODO: Replace Maybe by MonadThrow CustomError -- TODO: Replace Maybe by MonadThrow CustomError
operations operations ::
:: Schema.Subs Schema.Subs ->
-> Fragmenter Fragments ->
-> [Full.OperationDefinition] [Full.OperationDefinition] ->
-> Maybe Core.Document Maybe Core.Document
operations subs fr = NonEmpty.nonEmpty . fmap (operation subs fr) operations subs fragments operations' = do
coreOperations <- traverse (operation subs fragments) operations'
NonEmpty.nonEmpty coreOperations
operation operation ::
:: Schema.Subs Schema.Subs ->
-> Fragmenter Fragments ->
-> Full.OperationDefinition Full.OperationDefinition ->
-> Core.Operation Maybe Core.Operation
operation subs fr (Full.OperationSelectionSet sels) = operation subs fragments (Full.OperationSelectionSet sels) =
operation subs fr $ Full.OperationDefinition Full.Query empty empty empty sels operation subs fragments $ Full.OperationDefinition Full.Query mempty mempty mempty sels
-- TODO: Validate Variable definitions with substituter -- TODO: Validate Variable definitions with substituter
operation subs fr (Full.OperationDefinition Full.Query name _vars _dirs sels) = operation subs fragments (Full.OperationDefinition Full.Query name _vars _dirs sels) =
Core.Query name $ appendSelection subs fr sels pure $ Core.Query name $ appendSelection subs fragments sels
operation subs fr (Full.OperationDefinition Full.Mutation name _vars _dirs sels) = operation subs fragments (Full.OperationDefinition Full.Mutation name _vars _dirs sels) =
Core.Mutation name $ appendSelection subs fr sels pure $ Core.Mutation name $ appendSelection subs fragments sels
selection selection ::
:: Schema.Subs Schema.Subs ->
-> Fragmenter Fragments ->
-> Full.Selection Full.Selection ->
-> Either [Core.Selection] Core.Selection Either [Core.Selection] Core.Selection
selection subs fr (Full.SelectionField fld) selection subs fragments (Full.SelectionField fld)
= Right $ Core.SelectionField $ field subs fr fld = Right $ Core.SelectionField $ field subs fragments fld
selection _ fr (Full.SelectionFragmentSpread (Full.FragmentSpread name _)) selection _ fragments (Full.SelectionFragmentSpread (Full.FragmentSpread name _))
= Left $ Core.SelectionField <$> fr name = Left $ extractFragment fragments name
selection subs fr (Full.SelectionInlineFragment fragment) selection subs fragments (Full.SelectionInlineFragment fragment)
| (Full.InlineFragment (Just typeCondition) _ selectionSet) <- fragment | (Full.InlineFragment (Just typeCondition) _ selectionSet) <- fragment
= Right = Right
$ Core.SelectionFragment $ Core.SelectionFragment
$ Core.Fragment typeCondition $ Core.Fragment typeCondition
$ appendSelection subs fr selectionSet $ appendSelection subs fragments selectionSet
| (Full.InlineFragment Nothing _ selectionSet) <- fragment | (Full.InlineFragment Nothing _ selectionSet) <- fragment
= Left $ NonEmpty.toList $ appendSelection subs fr selectionSet = Left $ NonEmpty.toList $ appendSelection subs fragments selectionSet
-- * Fragment replacement -- * Fragment replacement
-- | Extract Fragments into a single Fragmenter function and a Operation -- | Extract fragments into a single 'HashMap' and operation definitions.
-- Definition. defrag ::
defrag Schema.Subs ->
:: Schema.Subs Full.Definition ->
-> Full.Definition (Fragments, [Full.OperationDefinition]) ->
-> Either Fragmenter Full.OperationDefinition (Fragments, [Full.OperationDefinition])
defrag _ (Full.DefinitionOperation op) = defrag _ (Full.DefinitionOperation op) (fragments, operations') =
Right op (fragments, op : operations')
defrag subs (Full.DefinitionFragment fragDef) = defrag subs (Full.DefinitionFragment fragDef) (fragments, operations') =
Left $ fragmentDefinition subs fragDef (fragmentDefinition subs fragments fragDef, operations')
fragmentDefinition :: Schema.Subs -> Full.FragmentDefinition -> Fragmenter fragmentDefinition ::
fragmentDefinition subs (Full.FragmentDefinition name _tc _dirs sels) name' Schema.Subs ->
| name == name' = selection' <$> do Fragments ->
Full.FragmentDefinition ->
Fragments
fragmentDefinition subs fragments (Full.FragmentDefinition name _tc _dirs sels) =
HashMap.insert name (extractField <$> emitValue) fragments
where
emitValue = do
selections <- NonEmpty.toList $ selection subs mempty <$> sels selections <- NonEmpty.toList $ selection subs mempty <$> sels
either id pure selections either id pure selections
| otherwise = empty extractField (Core.SelectionField field') = field'
where extractField _ = error "Fragments within fragments are not supported yet"
selection' (Core.SelectionField field') = field'
selection' _ = error "Fragments within fragments are not supported yet"
field :: Schema.Subs -> Fragmenter -> Full.Field -> Core.Field field :: Schema.Subs -> Fragments -> Full.Field -> Core.Field
field subs fr (Full.Field a n args _dirs sels) = field subs fragments (Full.Field a n args _dirs sels) =
Core.Field a n (fold $ argument subs `traverse` args) (foldr go empty sels) Core.Field a n (fold $ argument subs `traverse` args) (foldr go mempty sels)
where where
go :: Full.Selection -> [Core.Selection] -> [Core.Selection] go :: Full.Selection -> [Core.Selection] -> [Core.Selection]
go (Full.SelectionFragmentSpread (Full.FragmentSpread name _dirs)) = ((Core.SelectionField <$> fr name) <>) go (Full.SelectionFragmentSpread (Full.FragmentSpread name _dirs)) =
go sel = (either id pure (selection subs fr sel) <>) (extractFragment fragments name <>)
go sel = (either id pure (selection subs fragments sel) <>)
argument :: Schema.Subs -> Full.Argument -> Maybe Core.Argument argument :: Schema.Subs -> Full.Argument -> Maybe Core.Argument
argument subs (Full.Argument n v) = Core.Argument n <$> value subs v argument subs (Full.Argument n v) = Core.Argument n <$> value subs v
@ -129,8 +132,8 @@ objectField subs (Full.ObjectField n v) = Core.ObjectField n <$> value subs v
appendSelection :: appendSelection ::
Schema.Subs -> Schema.Subs ->
Fragmenter -> Fragments ->
NonEmpty Full.Selection -> NonEmpty Full.Selection ->
NonEmpty Core.Selection NonEmpty Core.Selection
appendSelection subs fr = NonEmpty.fromList appendSelection subs fragments = NonEmpty.fromList
. foldr (either (++) (:) . selection subs fr) [] . foldr (either (++) (:) . selection subs fragments) []

View File

@ -1,4 +1,4 @@
resolver: lts-14.11 resolver: lts-14.12
packages: packages:
- . - .