Constrain the resolvers with MonadIO
This replaces the most usages of MonadPlus, which is not appropriate for the resolvers, since a resolver is unambiguously chosen by the name (no need for 'mplus'), and the resolvers are often doing IO.
This commit is contained in:
@ -1,9 +1,10 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
-- | This module provides the function to execute a @GraphQL@ request --
|
||||
-- according to a 'Schema'.
|
||||
module Language.GraphQL.Execute (execute) where
|
||||
|
||||
import Control.Monad (MonadPlus(..))
|
||||
import Control.Monad.IO.Class (MonadIO)
|
||||
import qualified Data.List.NonEmpty as NE
|
||||
import Data.List.NonEmpty (NonEmpty((:|)))
|
||||
import qualified Data.Aeson as Aeson
|
||||
@ -21,17 +22,22 @@ import qualified Language.GraphQL.Schema as Schema
|
||||
-- Returns the result of the query against the 'Schema' wrapped in a /data/ field, or
|
||||
-- errors wrapped in an /errors/ field.
|
||||
execute
|
||||
:: (MonadPlus m)
|
||||
=> Schema m -> Schema.Subs -> AST.Document -> m Aeson.Value
|
||||
execute schema subs doc = do
|
||||
coreDocument <- maybe mzero pure (Transform.document subs doc)
|
||||
document schema coreDocument
|
||||
:: MonadIO m
|
||||
=> Schema m -> Schema.Subs -> AST.Document -> m Aeson.Value
|
||||
execute schema subs doc =
|
||||
maybe transformError (document schema) $ Transform.document subs doc
|
||||
where
|
||||
transformError = return $ Aeson.object
|
||||
[("errors", Aeson.toJSON
|
||||
[ Aeson.object [("message", "Schema transformation error.")]
|
||||
]
|
||||
)]
|
||||
|
||||
document :: MonadPlus m => Schema m -> AST.Core.Document -> m Aeson.Value
|
||||
document :: MonadIO m => Schema m -> AST.Core.Document -> m Aeson.Value
|
||||
document schema (op :| []) = operation schema op
|
||||
document _ _ = error "Multiple operations not supported yet"
|
||||
|
||||
operation :: MonadPlus m => Schema m -> AST.Core.Operation -> m Aeson.Value
|
||||
operation :: MonadIO m => Schema m -> AST.Core.Operation -> m Aeson.Value
|
||||
operation schema (AST.Core.Query flds)
|
||||
= runCollectErrs (Schema.resolve (NE.toList schema) (NE.toList flds))
|
||||
operation schema (AST.Core.Mutation flds)
|
||||
|
Reference in New Issue
Block a user