graphql/src/Language/GraphQL/Execute.hs

78 lines
2.9 KiB
Haskell
Raw Normal View History

2017-02-10 22:40:08 +01:00
{-# LANGUAGE OverloadedStrings #-}
-- | This module provides functions to execute a @GraphQL@ request.
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
import Control.Monad.IO.Class (MonadIO)
2019-07-25 07:37:36 +02:00
import qualified Data.Aeson as Aeson
import Data.Foldable (toList)
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NE
2019-07-25 07:37:36 +02:00
import Data.Text (Text)
import qualified Data.Text as Text
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 qualified Language.GraphQL.Schema as Schema
-- | The substitution is applied to the document, and the 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
=> NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-> Schema.Subs -- ^ Variable substitution function.
-> AST.Document -- @GraphQL@ document.
2019-07-25 07:37:36 +02:00
-> m Aeson.Value
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."
-- | The substitution is applied to the document, and the resolvers are applied
-- to the resulting fields. The operation name can be used if the document
-- defines multiple root operations.
2019-07-25 07:37:36 +02:00
--
-- 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
executeWithName :: MonadIO m
=> NonEmpty (Schema.Resolver m) -- ^ Resolvers
-> Text -- ^ Operation name.
-> Schema.Subs -- ^ Variable substitution function.
-> AST.Document -- ^ @GraphQL@ Document.
2019-07-25 07:37:36 +02:00
-> m Aeson.Value
executeWithName schema name subs doc =
maybe transformError (document schema $ Just name) $ Transform.document subs doc
where
2019-07-23 06:04:33 +02:00
transformError = return $ singleError "Schema transformation error."
document :: MonadIO m
=> NonEmpty (Schema.Resolver m)
-> Maybe Text
-> AST.Core.Document
-> m Aeson.Value
2019-07-25 07:37:36 +02:00
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."
operation :: MonadIO m
=> NonEmpty (Schema.Resolver m)
-> AST.Core.Operation
-> m Aeson.Value
2019-07-25 07:37:36 +02:00
operation schema (AST.Core.Query _ flds)
= runCollectErrs (Schema.resolve (toList schema) flds)
2019-07-25 07:37:36 +02:00
operation schema (AST.Core.Mutation _ flds)
= runCollectErrs (Schema.resolve (toList schema) flds)