Merge branch 'all-improvements'
This adds general API documentation, a tutorial and error handling.
This commit is contained in:
@ -1,6 +1,7 @@
|
||||
-- | This module provides the functions to parse and execute @GraphQL@ queries.
|
||||
module Data.GraphQL where
|
||||
|
||||
import Control.Applicative (Alternative, empty)
|
||||
import Control.Applicative (Alternative)
|
||||
|
||||
import Data.Text (Text)
|
||||
|
||||
@ -11,10 +12,23 @@ import Data.GraphQL.Execute
|
||||
import Data.GraphQL.Parser
|
||||
import Data.GraphQL.Schema
|
||||
|
||||
import Data.GraphQL.Error
|
||||
|
||||
-- | Takes a 'Schema' and text representing a @GraphQL@ request document.
|
||||
-- If the text parses correctly as a @GraphQL@ query the query is
|
||||
-- executed according to the given 'Schema'.
|
||||
--
|
||||
-- Returns the response as an @Aeson.@'Aeson.Value'.
|
||||
graphql :: (Alternative m, Monad m) => Schema m -> Text -> m Aeson.Value
|
||||
graphql = flip graphqlSubs $ const Nothing
|
||||
|
||||
-- | Takes a 'Schema', a variable substitution function and text
|
||||
-- representing a @GraphQL@ request document. If the text parses
|
||||
-- correctly as a @GraphQL@ query the substitution is applied to the
|
||||
-- query and the query is then executed according to the given 'Schema'.
|
||||
--
|
||||
-- Returns the response as an @Aeson.@'Aeson.Value'.
|
||||
graphqlSubs :: (Alternative m, Monad m) => Schema m -> Subs -> Text -> m Aeson.Value
|
||||
graphqlSubs schema f =
|
||||
either (const empty) (execute schema f)
|
||||
either parseError (execute schema f)
|
||||
. Attoparsec.parseOnly document
|
||||
|
@ -1,3 +1,6 @@
|
||||
-- | This module defines an abstract syntax tree for the @GraphQL@ language based on
|
||||
-- <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
|
||||
|
||||
module Data.GraphQL.AST where
|
||||
|
||||
import Data.Int (Int32)
|
||||
@ -39,11 +42,26 @@ data Selection = SelectionField Field
|
||||
| SelectionInlineFragment InlineFragment
|
||||
deriving (Eq,Show)
|
||||
|
||||
-- | A 'SelectionSet' is primarily composed of 'Field's. A 'Field' describes one
|
||||
-- discrete piece of information available to request within a 'SelectionSet'.
|
||||
--
|
||||
-- Some 'Field's describe complex data or relationships to other data. In
|
||||
-- order to further explore this data, a 'Field' may itself contain a
|
||||
-- 'SelectionSet', allowing for deeply nested requests. All @GraphQL@ operations
|
||||
-- must specify their 'Selection's down to 'Field's which return scalar values to
|
||||
-- ensure an unambiguously shaped response.
|
||||
--
|
||||
-- <https://facebook.github.io/graphql/#sec-Language.Query-Document.Fields Field Specification>
|
||||
data Field = Field Alias Name [Argument] [Directive] SelectionSet
|
||||
deriving (Eq,Show)
|
||||
|
||||
type Alias = Name
|
||||
|
||||
-- | 'Field's are conceptually functions which return values, and occasionally accept
|
||||
-- 'Argument's which alter their behavior. These 'Argument's often map directly to
|
||||
-- function arguments within a @GraphQL@ server’s implementation.
|
||||
--
|
||||
-- <https://facebook.github.io/graphql/#sec-Language.Query-Document.Arguments Argument Specification>
|
||||
data Argument = Argument Name Value deriving (Eq,Show)
|
||||
|
||||
-- * Fragments
|
||||
@ -63,6 +81,15 @@ type TypeCondition = NamedType
|
||||
|
||||
-- * Values
|
||||
|
||||
-- | 'Field' and 'Directive' 'Arguments' accept input values of various literal
|
||||
-- primitives; input values can be scalars, enumeration values, lists, or input
|
||||
-- objects.
|
||||
--
|
||||
-- If not defined as constant (for example, in 'DefaultValue'), input values
|
||||
-- can be specified as a 'Variable'. List and inputs objects may also contain
|
||||
-- 'Variable's (unless defined to be constant).
|
||||
--
|
||||
-- <https://facebook.github.io/graphql/#sec-Input-Values Input Value Specification>
|
||||
data Value = ValueVariable Variable
|
||||
| ValueInt Int32
|
||||
-- GraphQL Float is double precison
|
||||
|
@ -1,5 +1,6 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
-- | This module defines a printer for the @GraphQL@ language.
|
||||
module Data.GraphQL.Encoder where
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
|
63
Data/GraphQL/Error.hs
Normal file
63
Data/GraphQL/Error.hs
Normal file
@ -0,0 +1,63 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Data.GraphQL.Error (
|
||||
parseError,
|
||||
CollectErrsT,
|
||||
addErr,
|
||||
addErrMsg,
|
||||
runCollectErrs,
|
||||
joinErrs,
|
||||
errWrap
|
||||
) where
|
||||
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.Text (Text, pack)
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative (Applicative, pure)
|
||||
import Data.Foldable (Foldable, concatMap)
|
||||
import Prelude hiding (concatMap)
|
||||
#endif
|
||||
|
||||
-- | Wraps a parse error into a list of errors.
|
||||
parseError :: Applicative f => String -> f Aeson.Value
|
||||
parseError s =
|
||||
pure $ Aeson.object [("errors", Aeson.toJSON [makeErrorMsg $ pack s])]
|
||||
|
||||
-- | A wrapper for an 'Applicative' to pass error messages around.
|
||||
type CollectErrsT f a = f (a,[Aeson.Value])
|
||||
|
||||
-- | Takes a (wrapped) list (foldable functor) of values and errors,
|
||||
-- joins the values into a list and concatenates the errors.
|
||||
joinErrs
|
||||
:: (Functor m, Functor f, Foldable f)
|
||||
=> m (f (a,[Aeson.Value])) -> CollectErrsT m (f a)
|
||||
joinErrs = fmap $ fmap fst &&& concatMap snd
|
||||
|
||||
-- | Wraps the given 'Applicative' to handle errors
|
||||
errWrap :: Functor f => f a -> f (a, [Aeson.Value])
|
||||
errWrap = fmap (flip (,) [])
|
||||
|
||||
-- | Adds an error to the list of errors.
|
||||
addErr :: Functor f => Aeson.Value -> CollectErrsT f a -> CollectErrsT f a
|
||||
addErr v = (fmap . fmap) (v :)
|
||||
|
||||
makeErrorMsg :: Text -> Aeson.Value
|
||||
makeErrorMsg s = Aeson.object [("message",Aeson.toJSON s)]
|
||||
|
||||
-- | Convenience function for just wrapping an error message.
|
||||
addErrMsg :: Functor f => Text -> CollectErrsT f a -> CollectErrsT f a
|
||||
addErrMsg = addErr . makeErrorMsg
|
||||
|
||||
-- | Runs the given query, but collects the errors into an error
|
||||
-- list which is then sent back with the data.
|
||||
runCollectErrs :: Functor f => CollectErrsT f Aeson.Value -> f Aeson.Value
|
||||
runCollectErrs = fmap finalD
|
||||
where
|
||||
finalD (dat,errs) =
|
||||
Aeson.object
|
||||
$ if null errs
|
||||
then [("data",dat)]
|
||||
else [("data",dat),("errors",Aeson.toJSON $ reverse errs)]
|
@ -1,4 +1,6 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
-- | This module provides the function to execute a @GraphQL@ request --
|
||||
-- according to a 'Schema'.
|
||||
module Data.GraphQL.Execute (execute) where
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
@ -13,16 +15,32 @@ import Data.GraphQL.AST
|
||||
import Data.GraphQL.Schema (Schema(..))
|
||||
import qualified Data.GraphQL.Schema as Schema
|
||||
|
||||
execute
|
||||
:: Alternative f
|
||||
=> Schema.Schema f -> Schema.Subs -> Document -> f Aeson.Value
|
||||
execute (Schema resolvs) subs = Schema.resolvers resolvs . rootFields subs
|
||||
import Data.GraphQL.Error
|
||||
|
||||
-- | Takes a 'Schema', a variable substitution function ('Schema.Subs'), and a
|
||||
-- @GraphQL@ 'document'. The substitution is applied to the document using
|
||||
-- 'rootFields', and the 'Schema''s resolvers are applied to the resulting fields.
|
||||
--
|
||||
-- Returns the result of the query against the 'Schema' wrapped in a /data/ field, or
|
||||
-- errors wrapped in an /errors/ field.
|
||||
execute :: Alternative f
|
||||
=> Schema.Schema f -> Schema.Subs -> Document -> f Aeson.Value
|
||||
execute (Schema resolvs) subs doc = runCollectErrs res
|
||||
where res = Schema.resolvers resolvs $ rootFields subs doc
|
||||
|
||||
-- | Takes a variable substitution function and a @GraphQL@ document.
|
||||
-- If the document contains one query (and no other definitions)
|
||||
-- it applies the substitution to the query's set of selections
|
||||
-- and then returns their fields.
|
||||
rootFields :: Schema.Subs -> Document -> [Field]
|
||||
rootFields subs (Document [DefinitionOperation (Query (Node _varDefs _ _ sels))]) =
|
||||
Schema.fields $ substitute subs <$> sels
|
||||
rootFields _ _ = []
|
||||
|
||||
-- | Takes a variable substitution function and a selection. If the
|
||||
-- selection is a field it applies the substitution to the field's
|
||||
-- arguments using 'subsArg', and recursively applies the substitution to
|
||||
-- the arguments of fields nested in the primary field.
|
||||
substitute :: Schema.Subs -> Selection -> Selection
|
||||
substitute subs (SelectionField (Field alias name args directives sels)) =
|
||||
SelectionField $ Field
|
||||
@ -35,6 +53,9 @@ substitute subs (SelectionField (Field alias name args directives sels)) =
|
||||
substitute _ sel = sel
|
||||
|
||||
-- TODO: Support different value types
|
||||
-- | Takes a variable substitution function and an argument. If the
|
||||
-- argument's value is a variable the substitution is applied to the
|
||||
-- variable's name.
|
||||
subsArg :: Schema.Subs -> Argument -> Maybe Argument
|
||||
subsArg subs (Argument n (ValueVariable (Variable v))) =
|
||||
Argument n . ValueString <$> subs v
|
||||
|
@ -1,5 +1,6 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
-- | This module defines a parser for @GraphQL@ request documents.
|
||||
module Data.GraphQL.Parser where
|
||||
|
||||
import Prelude hiding (takeWhile)
|
||||
|
@ -1,5 +1,8 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
-- | This module provides a representation of a @GraphQL@ Schema in addition to
|
||||
-- functions for defining and manipulating Schemas.
|
||||
module Data.GraphQL.Schema
|
||||
( Schema(..)
|
||||
, Resolver
|
||||
@ -21,14 +24,16 @@ module Data.GraphQL.Schema
|
||||
) where
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative (pure, (<|>))
|
||||
import Control.Applicative (pure)
|
||||
import Control.Arrow (first)
|
||||
import Data.Foldable (foldMap)
|
||||
import Data.Traversable (traverse)
|
||||
import Data.Monoid (Monoid(mempty,mappend))
|
||||
#else
|
||||
import Data.Bifunctor (first)
|
||||
import Data.Monoid (Alt(Alt,getAlt))
|
||||
#endif
|
||||
import Control.Applicative (Alternative, empty)
|
||||
import Control.Applicative (Alternative((<|>), empty))
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Foldable (fold)
|
||||
|
||||
@ -36,77 +41,105 @@ 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)
|
||||
import qualified Data.Text as T (null, unwords)
|
||||
|
||||
import Data.GraphQL.AST
|
||||
import Data.GraphQL.Error
|
||||
|
||||
-- | A GraphQL schema.
|
||||
-- @f@ is usually expected to be an instance of 'Alternative'.
|
||||
data Schema f = Schema [Resolver f]
|
||||
|
||||
type Resolver f = Field -> f Aeson.Object
|
||||
-- | Resolves a 'Field' into an @Aeson.@'Aeson.Object' with error information
|
||||
-- (or 'empty'). @f@ is usually expected to be an instance of 'Alternative'.
|
||||
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 name resolvs = objectA name $ \case
|
||||
[] -> 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
|
||||
|
||||
-- | A scalar represents a primitive value, like a string or an integer.
|
||||
scalar :: (Alternative f, Aeson.ToJSON a) => Text -> a -> Resolver f
|
||||
scalar name s = scalarA name $ \case
|
||||
[] -> pure s
|
||||
_ -> empty
|
||||
|
||||
-- | 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 (f args) fld
|
||||
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
|
||||
_ -> empty
|
||||
|
||||
-- | Like 'array' but also taking 'Argument's.
|
||||
arrayA
|
||||
:: Alternative f
|
||||
=> Text -> ([Argument] -> [[Resolver f]]) -> Resolver f
|
||||
arrayA name f fld@(Field _ _ args _ sels) =
|
||||
withField name (traverse (flip resolvers $ fields sels) $ f args) fld
|
||||
withField name (joinErrs $ traverse (flip resolvers $ fields 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.
|
||||
enum :: Alternative f => Text -> f [Text] -> Resolver f
|
||||
enum name enums = enumA name $ \case
|
||||
[] -> enums
|
||||
_ -> empty
|
||||
|
||||
-- | Like 'enum' but also taking 'Argument's.
|
||||
enumA :: Alternative f => Text -> ([Argument] -> f [Text]) -> Resolver f
|
||||
enumA name f fld@(Field _ _ args _ []) = withField name (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 -> f a -> Field -> f (HashMap Text Aeson.Value)
|
||||
=> Text -> CollectErrsT f a -> Field -> CollectErrsT f (HashMap Text Aeson.Value)
|
||||
withField name f (Field alias name' _ _ _) =
|
||||
if name == name'
|
||||
then fmap (HashMap.singleton aliasOrName . Aeson.toJSON) f
|
||||
then fmap (first $ HashMap.singleton aliasOrName . Aeson.toJSON) f
|
||||
else empty
|
||||
where
|
||||
aliasOrName = if T.null alias then name' else alias
|
||||
|
||||
resolvers :: Alternative f => [Resolver f] -> [Field] -> f Aeson.Value
|
||||
-- | 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
|
||||
-- resolved 'Field', or a null value and error information.
|
||||
resolvers :: Alternative f => [Resolver f] -> [Field] -> CollectErrsT f Aeson.Value
|
||||
resolvers resolvs =
|
||||
fmap (Aeson.toJSON . fold)
|
||||
. traverse (\fld -> getAlt $ foldMap (Alt . ($ fld)) 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
|
||||
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
|
||||
|
||||
|
Reference in New Issue
Block a user