2017-02-10 22:40:08 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-07-08 10:15:47 +02:00
|
|
|
|
2016-03-15 14:02:34 +01:00
|
|
|
-- | This module provides the function to execute a @GraphQL@ request --
|
|
|
|
-- according to a 'Schema'.
|
2019-07-14 05:58:05 +02:00
|
|
|
module Language.GraphQL.Execute
|
|
|
|
( execute
|
2019-07-25 07:37:36 +02:00
|
|
|
, executeWithName
|
2019-07-14 05:58:05 +02:00
|
|
|
) where
|
2015-10-17 13:19:00 +02:00
|
|
|
|
2019-07-08 10:15:47 +02:00
|
|
|
import Control.Monad.IO.Class (MonadIO)
|
2019-07-25 07:37:36 +02:00
|
|
|
import qualified Data.Aeson as Aeson
|
2017-01-29 16:53:15 +01:00
|
|
|
import qualified Data.List.NonEmpty as NE
|
|
|
|
import Data.List.NonEmpty (NonEmpty((:|)))
|
2019-07-25 07:37:36 +02:00
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as Text
|
2019-07-07 06:31:53 +02:00
|
|
|
import qualified Language.GraphQL.AST as AST
|
|
|
|
import qualified Language.GraphQL.AST.Core as AST.Core
|
|
|
|
import qualified Language.GraphQL.AST.Transform as Transform
|
|
|
|
import Language.GraphQL.Error
|
|
|
|
import Language.GraphQL.Schema (Schema)
|
|
|
|
import qualified Language.GraphQL.Schema as Schema
|
2015-10-17 13:19:00 +02:00
|
|
|
|
2016-03-15 14:02:34 +01:00
|
|
|
-- | 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.
|
2019-07-25 07:37:36 +02:00
|
|
|
execute :: MonadIO m
|
|
|
|
=> Schema m
|
|
|
|
-> Schema.Subs
|
|
|
|
-> AST.Document
|
|
|
|
-> m Aeson.Value
|
2019-07-08 10:15:47 +02:00
|
|
|
execute schema subs doc =
|
2019-07-25 07:37:36 +02:00
|
|
|
maybe transformError (document schema Nothing) $ Transform.document subs doc
|
|
|
|
where
|
|
|
|
transformError = return $ singleError "Schema transformation error."
|
|
|
|
|
|
|
|
-- | Takes a 'Schema', operation name, 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.
|
|
|
|
executeWithName :: MonadIO m
|
|
|
|
=> Schema m
|
|
|
|
-> Text
|
|
|
|
-> Schema.Subs
|
|
|
|
-> AST.Document
|
|
|
|
-> m Aeson.Value
|
|
|
|
executeWithName schema name subs doc =
|
|
|
|
maybe transformError (document schema $ Just name) $ Transform.document subs doc
|
2019-07-08 10:15:47 +02:00
|
|
|
where
|
2019-07-23 06:04:33 +02:00
|
|
|
transformError = return $ singleError "Schema transformation error."
|
2017-01-29 16:53:15 +01:00
|
|
|
|
2019-07-25 07:37:36 +02:00
|
|
|
document :: MonadIO m => Schema m -> Maybe Text -> AST.Core.Document -> m Aeson.Value
|
|
|
|
document schema Nothing (op :| []) = operation schema op
|
|
|
|
document schema (Just name) operations = case NE.dropWhile matchingName operations of
|
|
|
|
[] -> return $ singleError
|
|
|
|
$ Text.unwords ["Operation", name, "couldn't be found in the document."]
|
|
|
|
(op:_) -> operation schema op
|
|
|
|
where
|
|
|
|
matchingName (AST.Core.Query (Just name') _) = name == name'
|
|
|
|
matchingName (AST.Core.Mutation (Just name') _) = name == name'
|
|
|
|
matchingName _ = False
|
|
|
|
document _ _ _ = return $ singleError "Missing operation name."
|
2017-01-29 16:53:15 +01:00
|
|
|
|
2019-07-08 10:15:47 +02:00
|
|
|
operation :: MonadIO m => Schema m -> AST.Core.Operation -> m Aeson.Value
|
2019-07-25 07:37:36 +02:00
|
|
|
operation schema (AST.Core.Query _ flds)
|
2019-06-27 08:00:59 +02:00
|
|
|
= runCollectErrs (Schema.resolve (NE.toList schema) (NE.toList flds))
|
2019-07-25 07:37:36 +02:00
|
|
|
operation schema (AST.Core.Mutation _ flds)
|
2019-06-27 08:00:59 +02:00
|
|
|
= runCollectErrs (Schema.resolve (NE.toList schema) (NE.toList flds))
|