forked from OSS/graphql
Split AST in 2
One AST is meant to be a target parser and tries to adhere as much as possible to the spec. The other is a simplified version of that AST meant for execution. Also newtypes have been replaced by type synonyms and NonEmpty lists are being used where it makes sense.
This commit is contained in:
@ -3,7 +3,7 @@
|
||||
-- | This module provides a representation of a @GraphQL@ Schema in addition to
|
||||
-- functions for defining and manipulating Schemas.
|
||||
module Data.GraphQL.Schema
|
||||
( Schema(..)
|
||||
( Schema
|
||||
, Resolver
|
||||
, Subs
|
||||
, object
|
||||
@ -15,31 +15,31 @@ module Data.GraphQL.Schema
|
||||
, enum
|
||||
, enumA
|
||||
, resolvers
|
||||
, fields
|
||||
-- * AST Reexports
|
||||
, Field
|
||||
, Argument(..)
|
||||
, Value(..)
|
||||
) where
|
||||
|
||||
import Data.Bifunctor (first)
|
||||
import Data.Monoid (Alt(Alt,getAlt))
|
||||
import Control.Applicative (Alternative((<|>), empty))
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Bifunctor (first)
|
||||
import Data.Foldable (fold)
|
||||
import Data.List.NonEmpty (NonEmpty)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Monoid (Alt(Alt,getAlt))
|
||||
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T (null, unwords)
|
||||
import qualified Data.Text as T (unwords)
|
||||
|
||||
import Data.GraphQL.AST
|
||||
import Data.GraphQL.AST.Core
|
||||
import Data.GraphQL.Error
|
||||
|
||||
-- | A GraphQL schema.
|
||||
-- @f@ is usually expected to be an instance of 'Alternative'.
|
||||
data Schema f = Schema [Resolver f]
|
||||
type Schema f = NonEmpty (Resolver f)
|
||||
|
||||
-- | Resolves a 'Field' into an @Aeson.@'Aeson.Object' with error information
|
||||
-- (or 'empty'). @f@ is usually expected to be an instance of 'Alternative'.
|
||||
@ -48,18 +48,16 @@ type Resolver f = Field -> CollectErrsT f Aeson.Object
|
||||
-- | Variable substitution function.
|
||||
type Subs = Text -> Maybe Text
|
||||
|
||||
-- | Create a named 'Resolver' from a list of 'Resolver's.
|
||||
object :: Alternative f => Text -> [Resolver f] -> Resolver f
|
||||
object :: Alternative f => Name -> [Resolver f] -> Resolver f
|
||||
object name resolvs = objectA name $ \case
|
||||
[] -> resolvs
|
||||
_ -> empty
|
||||
[] -> resolvs
|
||||
_ -> empty
|
||||
|
||||
-- | Like 'object' but also taking 'Argument's.
|
||||
objectA
|
||||
:: Alternative f
|
||||
=> Text -> ([Argument] -> [Resolver f]) -> Resolver f
|
||||
objectA name f fld@(Field _ _ args _ sels) =
|
||||
withField name (resolvers (f args) $ fields sels) fld
|
||||
=> Name -> ([Argument] -> [Resolver f]) -> Resolver f
|
||||
objectA name f fld@(Field _ _ args sels) = withField name (resolvers (f args) sels) fld
|
||||
|
||||
-- | A scalar represents a primitive value, like a string or an integer.
|
||||
scalar :: (Alternative f, Aeson.ToJSON a) => Text -> a -> Resolver f
|
||||
@ -70,11 +68,10 @@ scalar name s = scalarA name $ \case
|
||||
-- | Like 'scalar' but also taking 'Argument's.
|
||||
scalarA
|
||||
:: (Alternative f, Aeson.ToJSON a)
|
||||
=> Text -> ([Argument] -> f a) -> Resolver f
|
||||
scalarA name f fld@(Field _ _ args _ []) = withField name (errWrap $ f args) fld
|
||||
=> Name -> ([Argument] -> f a) -> Resolver f
|
||||
scalarA name f fld@(Field _ _ args []) = withField name (errWrap $ f args) fld
|
||||
scalarA _ _ _ = empty
|
||||
|
||||
-- | Like 'object' but taking lists of 'Resolver's instead of a single list.
|
||||
array :: Alternative f => Text -> [[Resolver f]] -> Resolver f
|
||||
array name resolvs = arrayA name $ \case
|
||||
[] -> resolvs
|
||||
@ -84,8 +81,8 @@ array name resolvs = arrayA name $ \case
|
||||
arrayA
|
||||
:: Alternative f
|
||||
=> Text -> ([Argument] -> [[Resolver f]]) -> Resolver f
|
||||
arrayA name f fld@(Field _ _ args _ sels) =
|
||||
withField name (joinErrs $ traverse (flip resolvers $ fields sels) $ f args) fld
|
||||
arrayA name f fld@(Field _ _ args sels) =
|
||||
withField name (joinErrs $ traverse (`resolvers` sels) $ f args) fld
|
||||
|
||||
-- | Represents one of a finite set of possible values.
|
||||
-- Used in place of a 'scalar' when the possible responses are easily enumerable.
|
||||
@ -96,19 +93,19 @@ enum name enums = enumA name $ \case
|
||||
|
||||
-- | Like 'enum' but also taking 'Argument's.
|
||||
enumA :: Alternative f => Text -> ([Argument] -> f [Text]) -> Resolver f
|
||||
enumA name f fld@(Field _ _ args _ []) = withField name (errWrap $ f args) fld
|
||||
enumA name f fld@(Field _ _ args []) = withField name (errWrap $ f args) fld
|
||||
enumA _ _ _ = empty
|
||||
|
||||
-- | Helper function to facilitate 'Argument' handling.
|
||||
withField
|
||||
:: (Alternative f, Aeson.ToJSON a)
|
||||
=> Text -> CollectErrsT f a -> Field -> CollectErrsT f (HashMap Text Aeson.Value)
|
||||
withField name f (Field alias name' _ _ _) =
|
||||
=> Name -> CollectErrsT f a -> Field -> CollectErrsT f (HashMap Text Aeson.Value)
|
||||
withField name f (Field alias name' _ _) =
|
||||
if name == name'
|
||||
then fmap (first $ HashMap.singleton aliasOrName . Aeson.toJSON) f
|
||||
else empty
|
||||
where
|
||||
aliasOrName = if T.null alias then name' else alias
|
||||
aliasOrName = fromMaybe name' alias
|
||||
|
||||
-- | Takes a list of 'Resolver's and a list of 'Field's and applies each
|
||||
-- 'Resolver' to each 'Field'. Resolves into a value containing the
|
||||
@ -118,18 +115,8 @@ resolvers resolvs =
|
||||
fmap (first Aeson.toJSON . fold)
|
||||
. traverse (\fld -> getAlt (foldMap (Alt . ($ fld)) resolvs) <|> errmsg fld)
|
||||
where
|
||||
errmsg (Field alias name _ _ _) = addErrMsg msg $ (errWrap . pure) val
|
||||
errmsg (Field alias name _ _) = addErrMsg msg $ (errWrap . pure) val
|
||||
where
|
||||
val = HashMap.singleton aliasOrName Aeson.Null
|
||||
msg = T.unwords ["field", name, "not resolved."]
|
||||
aliasOrName = if T.null alias then name else alias
|
||||
|
||||
-- | Checks whether the given 'Selection' contains a 'Field' and
|
||||
-- returns the 'Field' if so, else returns 'Nothing'.
|
||||
field :: Selection -> Maybe Field
|
||||
field (SelectionField x) = Just x
|
||||
field _ = Nothing
|
||||
|
||||
-- | Returns a list of the 'Field's contained in the given 'SelectionSet'.
|
||||
fields :: SelectionSet -> [Field]
|
||||
fields = catMaybes . fmap field
|
||||
aliasOrName = fromMaybe name alias
|
||||
|
Reference in New Issue
Block a user