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,8 +1,7 @@
|
||||
-- | This module provides the functions to parse and execute @GraphQL@ queries.
|
||||
module Language.GraphQL where
|
||||
|
||||
import Control.Monad (MonadPlus)
|
||||
|
||||
import Control.Monad.IO.Class (MonadIO)
|
||||
import qualified Data.Text as T
|
||||
|
||||
import qualified Data.Aeson as Aeson
|
||||
@ -21,7 +20,7 @@ import Language.GraphQL.Error
|
||||
-- executed according to the given 'Schema'.
|
||||
--
|
||||
-- Returns the response as an @Aeson.@'Aeson.Value'.
|
||||
graphql :: MonadPlus m => Schema m -> T.Text -> m Aeson.Value
|
||||
graphql :: MonadIO m => Schema m -> T.Text -> m Aeson.Value
|
||||
graphql = flip graphqlSubs $ const Nothing
|
||||
|
||||
-- | Takes a 'Schema', a variable substitution function and text
|
||||
@ -30,7 +29,7 @@ graphql = flip graphqlSubs $ const Nothing
|
||||
-- query and the query is then executed according to the given 'Schema'.
|
||||
--
|
||||
-- Returns the response as an @Aeson.@'Aeson.Value'.
|
||||
graphqlSubs :: MonadPlus m => Schema m -> Subs -> T.Text -> m Aeson.Value
|
||||
graphqlSubs :: MonadIO m => Schema m -> Subs -> T.Text -> m Aeson.Value
|
||||
graphqlSubs schema f =
|
||||
either (parseError . errorBundlePretty) (execute schema f)
|
||||
. parse document ""
|
||||
|
@ -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)
|
||||
|
@ -25,7 +25,7 @@ module Language.GraphQL.Schema
|
||||
, Value(..)
|
||||
) where
|
||||
|
||||
import Control.Monad (MonadPlus(..))
|
||||
import Control.Monad.IO.Class (MonadIO(..))
|
||||
import Control.Monad.Trans.Class (lift)
|
||||
import Control.Monad.Trans.Except (runExceptT)
|
||||
import Data.Foldable ( find
|
||||
@ -44,11 +44,11 @@ import Language.GraphQL.Type
|
||||
import Language.GraphQL.AST.Core
|
||||
|
||||
-- | A GraphQL schema.
|
||||
-- @f@ is usually expected to be an instance of 'Alternative'.
|
||||
-- @m@ is usually expected to be an instance of 'MonadIO'.
|
||||
type Schema m = NonEmpty (Resolver m)
|
||||
|
||||
-- | Resolves a 'Field' into an @Aeson.@'Aeson.Object' with error information
|
||||
-- (or 'empty'). @m@ is usually expected to be an instance of 'MonadPlus'.
|
||||
-- (or 'empty'). @m@ is usually expected to be an instance of 'MonadIO.
|
||||
data Resolver m = Resolver
|
||||
Text -- ^ Name
|
||||
(Field -> CollectErrsT m Aeson.Object) -- ^ Resolver
|
||||
@ -61,18 +61,18 @@ type Arguments = [Argument]
|
||||
type Subs = Name -> Maybe Value
|
||||
|
||||
-- | Create a new 'Resolver' with the given 'Name' from the given 'Resolver's.
|
||||
object :: MonadPlus m => Name -> ActionT m [Resolver m] -> Resolver m
|
||||
object :: MonadIO m => Name -> ActionT m [Resolver m] -> Resolver m
|
||||
object name = objectA name . const
|
||||
|
||||
-- | Like 'object' but also taking 'Argument's.
|
||||
objectA :: MonadPlus m
|
||||
objectA :: MonadIO m
|
||||
=> Name -> (Arguments -> ActionT m [Resolver m]) -> Resolver m
|
||||
objectA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
where
|
||||
resolveRight fld@(Field _ _ _ flds) resolver = withField (resolve resolver flds) fld
|
||||
|
||||
-- | Like 'object' but also taking 'Argument's and can be null or a list of objects.
|
||||
wrappedObjectA :: MonadPlus m
|
||||
wrappedObjectA :: MonadIO m
|
||||
=> Name -> (Arguments -> ActionT m (Wrapping [Resolver m])) -> Resolver m
|
||||
wrappedObjectA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
where
|
||||
@ -80,23 +80,23 @@ wrappedObjectA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
= withField (traverse (`resolve` sels) resolver) fld
|
||||
|
||||
-- | Like 'object' but can be null or a list of objects.
|
||||
wrappedObject :: MonadPlus m
|
||||
wrappedObject :: MonadIO m
|
||||
=> Name -> ActionT m (Wrapping [Resolver m]) -> Resolver m
|
||||
wrappedObject name = wrappedObjectA name . const
|
||||
|
||||
-- | A scalar represents a primitive value, like a string or an integer.
|
||||
scalar :: (MonadPlus m, Aeson.ToJSON a) => Name -> ActionT m a -> Resolver m
|
||||
scalar :: (MonadIO m, Aeson.ToJSON a) => Name -> ActionT m a -> Resolver m
|
||||
scalar name = scalarA name . const
|
||||
|
||||
-- | Like 'scalar' but also taking 'Argument's.
|
||||
scalarA :: (MonadPlus m, Aeson.ToJSON a)
|
||||
scalarA :: (MonadIO m, Aeson.ToJSON a)
|
||||
=> Name -> (Arguments -> ActionT m a) -> Resolver m
|
||||
scalarA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
where
|
||||
resolveRight fld result = withField (return result) fld
|
||||
|
||||
-- | Lika 'scalar' but also taking 'Argument's and can be null or a list of scalars.
|
||||
wrappedScalarA :: (MonadPlus m, Aeson.ToJSON a)
|
||||
wrappedScalarA :: (MonadIO m, Aeson.ToJSON a)
|
||||
=> Name -> (Arguments -> ActionT m (Wrapping a)) -> Resolver m
|
||||
wrappedScalarA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
where
|
||||
@ -106,23 +106,23 @@ wrappedScalarA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
resolveRight fld (List result) = withField (return result) fld
|
||||
|
||||
-- | Like 'scalar' but can be null or a list of scalars.
|
||||
wrappedScalar :: (MonadPlus m, Aeson.ToJSON a)
|
||||
wrappedScalar :: (MonadIO m, Aeson.ToJSON a)
|
||||
=> Name -> ActionT m (Wrapping a) -> Resolver m
|
||||
wrappedScalar name = wrappedScalarA name . const
|
||||
|
||||
-- | Represents one of a finite set of possible values.
|
||||
-- Used in place of a 'scalar' when the possible responses are easily enumerable.
|
||||
enum :: MonadPlus m => Name -> ActionT m [Text] -> Resolver m
|
||||
enum :: MonadIO m => Name -> ActionT m [Text] -> Resolver m
|
||||
enum name = enumA name . const
|
||||
|
||||
-- | Like 'enum' but also taking 'Argument's.
|
||||
enumA :: MonadPlus m => Name -> (Arguments -> ActionT m [Text]) -> Resolver m
|
||||
enumA :: MonadIO m => Name -> (Arguments -> ActionT m [Text]) -> Resolver m
|
||||
enumA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
where
|
||||
resolveRight fld resolver = withField (return resolver) fld
|
||||
|
||||
-- | Like 'enum' but also taking 'Argument's and can be null or a list of enums.
|
||||
wrappedEnumA :: MonadPlus m
|
||||
wrappedEnumA :: MonadIO m
|
||||
=> Name -> (Arguments -> ActionT m (Wrapping [Text])) -> Resolver m
|
||||
wrappedEnumA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
where
|
||||
@ -132,10 +132,10 @@ wrappedEnumA name f = Resolver name $ resolveFieldValue f resolveRight
|
||||
resolveRight fld (List resolver) = withField (return resolver) fld
|
||||
|
||||
-- | Like 'enum' but can be null or a list of enums.
|
||||
wrappedEnum :: MonadPlus m => Name -> ActionT m (Wrapping [Text]) -> Resolver m
|
||||
wrappedEnum :: MonadIO m => Name -> ActionT m (Wrapping [Text]) -> Resolver m
|
||||
wrappedEnum name = wrappedEnumA name . const
|
||||
|
||||
resolveFieldValue :: MonadPlus m
|
||||
resolveFieldValue :: MonadIO m
|
||||
=> ([Argument] -> ActionT m a)
|
||||
-> (Field -> a -> CollectErrsT m (HashMap Text Aeson.Value))
|
||||
-> Field
|
||||
@ -149,7 +149,7 @@ resolveFieldValue f resolveRight fld@(Field _ _ args _) = do
|
||||
return $ HashMap.singleton (aliasOrName fld) Aeson.Null
|
||||
|
||||
-- | Helper function to facilitate 'Argument' handling.
|
||||
withField :: (MonadPlus m, Aeson.ToJSON a)
|
||||
withField :: (MonadIO m, Aeson.ToJSON a)
|
||||
=> CollectErrsT m a -> Field -> CollectErrsT m (HashMap Text Aeson.Value)
|
||||
withField v fld
|
||||
= HashMap.singleton (aliasOrName fld) . Aeson.toJSON <$> runAppendErrs v
|
||||
@ -157,11 +157,11 @@ withField v fld
|
||||
-- | 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.
|
||||
resolve :: MonadPlus m
|
||||
resolve :: MonadIO m
|
||||
=> [Resolver m] -> Fields -> CollectErrsT m Aeson.Value
|
||||
resolve resolvers = fmap (Aeson.toJSON . fold) . traverse tryResolvers
|
||||
where
|
||||
tryResolvers fld = mplus (maybe mzero (tryResolver fld) $ find (compareResolvers fld) resolvers) $ errmsg fld
|
||||
tryResolvers fld = maybe (errmsg fld) (tryResolver fld) $ find (compareResolvers fld) resolvers
|
||||
compareResolvers (Field _ name _ _) (Resolver name' _) = name == name'
|
||||
tryResolver fld (Resolver _ resolver) = resolver fld
|
||||
errmsg fld@(Field _ name _ _) = do
|
||||
|
Reference in New Issue
Block a user