Replace MonadIO constraint with just Monad

And make the tests use Identity instead of IO.
This commit is contained in:
Eugen Wissner 2020-02-01 20:46:35 +01:00
parent e8b82122c6
commit 67bebf853c
8 changed files with 32 additions and 37 deletions

View File

@ -23,6 +23,8 @@ and this project adheres to
`key -> Maybe value` before). `key -> Maybe value` before).
- Make `AST.Lexer.at` a text (symbol) parser. It was a char before and is - Make `AST.Lexer.at` a text (symbol) parser. It was a char before and is
`symbol "@"` now. `symbol "@"` now.
- Replace `MonadIO` with a plain `Monad`. Since the tests don't use IO,
set the inner monad to `Identity`.
### Removed ### Removed
- `AST.Field`, `AST.InlineFragment` and `AST.FragmentSpread`. - `AST.Field`, `AST.InlineFragment` and `AST.FragmentSpread`.

View File

@ -4,7 +4,6 @@ module Language.GraphQL
, graphqlSubs , graphqlSubs
) where ) where
import Control.Monad.IO.Class (MonadIO)
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import Data.List.NonEmpty (NonEmpty) import Data.List.NonEmpty (NonEmpty)
import qualified Data.Text as T import qualified Data.Text as T
@ -16,7 +15,7 @@ import Text.Megaparsec (parse)
-- | If the text parses correctly as a @GraphQL@ query the query is -- | If the text parses correctly as a @GraphQL@ query the query is
-- executed using the given 'Schema.Resolver's. -- executed using the given 'Schema.Resolver's.
graphql :: MonadIO m graphql :: Monad m
=> NonEmpty (Schema.Resolver m) -- ^ Resolvers. => NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-> T.Text -- ^ Text representing a @GraphQL@ request document. -> T.Text -- ^ Text representing a @GraphQL@ request document.
-> m Aeson.Value -- ^ Response. -> m Aeson.Value -- ^ Response.
@ -25,7 +24,7 @@ graphql = flip graphqlSubs mempty
-- | If the text parses correctly as a @GraphQL@ query the substitution is -- | If the text parses correctly as a @GraphQL@ query the substitution is
-- applied to the query and the query is then executed using to the given -- applied to the query and the query is then executed using to the given
-- 'Schema.Resolver's. -- 'Schema.Resolver's.
graphqlSubs :: MonadIO m graphqlSubs :: Monad m
=> NonEmpty (Schema.Resolver m) -- ^ Resolvers. => NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-> Schema.Subs -- ^ Variable substitution function. -> Schema.Subs -- ^ Variable substitution function.
-> T.Text -- ^ Text representing a @GraphQL@ request document. -> T.Text -- ^ Text representing a @GraphQL@ request document.

View File

@ -6,7 +6,6 @@ module Language.GraphQL.Execute
, executeWithName , executeWithName
) where ) where
import Control.Monad.IO.Class (MonadIO)
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import Data.Foldable (toList) import Data.Foldable (toList)
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
@ -24,7 +23,7 @@ import qualified Language.GraphQL.Schema as Schema
-- --
-- Returns the result of the query against the schema wrapped in a /data/ -- Returns the result of the query against the schema wrapped in a /data/
-- field, or errors wrapped in an /errors/ field. -- field, or errors wrapped in an /errors/ field.
execute :: MonadIO m execute :: Monad m
=> NonEmpty (Schema.Resolver m) -- ^ Resolvers. => NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-> Schema.Subs -- ^ Variable substitution function. -> Schema.Subs -- ^ Variable substitution function.
-> Document -- @GraphQL@ document. -> Document -- @GraphQL@ document.
@ -40,7 +39,7 @@ execute schema subs doc =
-- --
-- Returns the result of the query against the schema wrapped in a /data/ -- Returns the result of the query against the schema wrapped in a /data/
-- field, or errors wrapped in an /errors/ field. -- field, or errors wrapped in an /errors/ field.
executeWithName :: MonadIO m executeWithName :: Monad m
=> NonEmpty (Schema.Resolver m) -- ^ Resolvers => NonEmpty (Schema.Resolver m) -- ^ Resolvers
-> Text -- ^ Operation name. -> Text -- ^ Operation name.
-> Schema.Subs -- ^ Variable substitution function. -> Schema.Subs -- ^ Variable substitution function.
@ -51,7 +50,7 @@ executeWithName schema name subs doc =
where where
transformError = return $ singleError "Schema transformation error." transformError = return $ singleError "Schema transformation error."
document :: MonadIO m document :: Monad m
=> NonEmpty (Schema.Resolver m) => NonEmpty (Schema.Resolver m)
-> Maybe Text -> Maybe Text
-> AST.Core.Document -> AST.Core.Document
@ -67,7 +66,7 @@ document schema (Just name) operations = case NE.dropWhile matchingName operatio
matchingName _ = False matchingName _ = False
document _ _ _ = return $ singleError "Missing operation name." document _ _ _ = return $ singleError "Missing operation name."
operation :: MonadIO m operation :: Monad m
=> NonEmpty (Schema.Resolver m) => NonEmpty (Schema.Resolver m)
-> AST.Core.Operation -> AST.Core.Operation
-> m Aeson.Value -> m Aeson.Value

View File

@ -15,7 +15,6 @@ module Language.GraphQL.Schema
, Value(..) , Value(..)
) where ) where
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Except (runExceptT) import Control.Monad.Trans.Except (runExceptT)
import Control.Monad.Trans.Reader (runReaderT) import Control.Monad.Trans.Reader (runReaderT)
@ -33,8 +32,8 @@ import Language.GraphQL.Trans
import qualified Language.GraphQL.Type as Type import qualified Language.GraphQL.Type as Type
-- | Resolves a 'Field' into an @Aeson.@'Data.Aeson.Types.Object' with error -- | Resolves a 'Field' into an @Aeson.@'Data.Aeson.Types.Object' with error
-- information (if an error has occurred). @m@ is usually expected to be an -- information (if an error has occurred). @m@ is an arbitrary monad, usually
-- instance of 'MonadIO'. -- 'IO'.
data Resolver m = Resolver data Resolver m = Resolver
Text -- ^ Name Text -- ^ Name
(Field -> CollectErrsT m Aeson.Object) -- ^ Resolver (Field -> CollectErrsT m Aeson.Object) -- ^ Resolver
@ -44,14 +43,14 @@ data Resolver m = Resolver
type Subs = HashMap Name Value type Subs = HashMap Name Value
-- | Create a new 'Resolver' with the given 'Name' from the given 'Resolver's. -- | Create a new 'Resolver' with the given 'Name' from the given 'Resolver's.
object :: MonadIO m => Name -> ActionT m [Resolver m] -> Resolver m object :: Monad m => Name -> ActionT m [Resolver m] -> Resolver m
object name f = Resolver name $ resolveFieldValue f resolveRight object name f = Resolver name $ resolveFieldValue f resolveRight
where where
resolveRight fld@(Field _ _ _ flds) resolver = withField (resolve resolver flds) fld resolveRight fld@(Field _ _ _ flds) resolver = withField (resolve resolver flds) fld
-- | Like 'object' but can be null or a list of objects. -- | Like 'object' but can be null or a list of objects.
wrappedObject :: wrappedObject ::
MonadIO m => Monad m =>
Name -> Name ->
ActionT m (Type.Wrapping [Resolver m]) -> ActionT m (Type.Wrapping [Resolver m]) ->
Resolver m Resolver m
@ -61,14 +60,14 @@ wrappedObject name f = Resolver name $ resolveFieldValue f resolveRight
= withField (traverse (`resolve` sels) resolver) fld = withField (traverse (`resolve` sels) resolver) fld
-- | A scalar represents a primitive value, like a string or an integer. -- | A scalar represents a primitive value, like a string or an integer.
scalar :: (MonadIO m, Aeson.ToJSON a) => Name -> ActionT m a -> Resolver m scalar :: (Monad m, Aeson.ToJSON a) => Name -> ActionT m a -> Resolver m
scalar name f = Resolver name $ resolveFieldValue f resolveRight scalar name f = Resolver name $ resolveFieldValue f resolveRight
where where
resolveRight fld result = withField (return result) fld resolveRight fld result = withField (return result) fld
-- | Like 'scalar' but can be null or a list of scalars. -- | Like 'scalar' but can be null or a list of scalars.
wrappedScalar :: wrappedScalar ::
(MonadIO m, Aeson.ToJSON a) => (Monad m, Aeson.ToJSON a) =>
Name -> Name ->
ActionT m (Type.Wrapping a) -> ActionT m (Type.Wrapping a) ->
Resolver m Resolver m
@ -80,7 +79,7 @@ wrappedScalar name f = Resolver name $ resolveFieldValue f resolveRight
resolveRight fld (Type.List result) = withField (return result) fld resolveRight fld (Type.List result) = withField (return result) fld
resolveFieldValue :: resolveFieldValue ::
MonadIO m => Monad m =>
ActionT m a -> ActionT m a ->
(Field -> a -> CollectErrsT m (HashMap Text Aeson.Value)) -> (Field -> a -> CollectErrsT m (HashMap Text Aeson.Value)) ->
Field -> Field ->
@ -95,7 +94,7 @@ resolveFieldValue f resolveRight fld@(Field _ _ args _) = do
return $ HashMap.singleton (aliasOrName fld) Aeson.Null return $ HashMap.singleton (aliasOrName fld) Aeson.Null
-- | Helper function to facilitate error handling and result emitting. -- | Helper function to facilitate error handling and result emitting.
withField :: (MonadIO m, Aeson.ToJSON a) withField :: (Monad m, Aeson.ToJSON a)
=> CollectErrsT m a -> Field -> CollectErrsT m (HashMap Text Aeson.Value) => CollectErrsT m a -> Field -> CollectErrsT m (HashMap Text Aeson.Value)
withField v fld withField v fld
= HashMap.singleton (aliasOrName fld) . Aeson.toJSON <$> runAppendErrs v = HashMap.singleton (aliasOrName fld) . Aeson.toJSON <$> runAppendErrs v
@ -103,7 +102,7 @@ withField v fld
-- | Takes a list of 'Resolver's and a list of 'Field's and applies each -- | 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 -- 'Resolver' to each 'Field'. Resolves into a value containing the
-- resolved 'Field', or a null value and error information. -- resolved 'Field', or a null value and error information.
resolve :: MonadIO m resolve :: Monad m
=> [Resolver m] -> Seq Selection -> CollectErrsT m Aeson.Value => [Resolver m] -> Seq Selection -> CollectErrsT m Aeson.Value
resolve resolvers = fmap (Aeson.toJSON . fold) . traverse tryResolvers resolve resolvers = fmap (Aeson.toJSON . fold) . traverse tryResolvers
where where

View File

@ -56,7 +56,7 @@ instance Monad m => MonadPlus (ActionT m) where
-- | Retrieves an argument by its name. If the argument with this name couldn't -- | Retrieves an argument by its name. If the argument with this name couldn't
-- be found, returns 'Value.Null' (i.e. the argument is assumed to -- be found, returns 'Value.Null' (i.e. the argument is assumed to
-- be optional then). -- be optional then).
argument :: MonadIO m => Name -> ActionT m Value argument :: Monad m => Name -> ActionT m Value
argument argumentName = do argument argumentName = do
argumentValue <- ActionT $ lift $ asks $ lookup . arguments argumentValue <- ActionT $ lift $ asks $ lookup . arguments
pure $ fromMaybe Null argumentValue pure $ fromMaybe Null argumentValue

View File

@ -8,7 +8,6 @@ module Test.StarWars.Data
, getEpisode , getEpisode
, getFriends , getFriends
, getHero , getHero
, getHeroIO
, getHuman , getHuman
, id_ , id_
, homePlanet , homePlanet
@ -18,10 +17,8 @@ module Test.StarWars.Data
) where ) where
import Data.Monoid (mempty) import Data.Monoid (mempty)
import Control.Applicative ( Alternative(..) import Data.Functor.Identity (Identity)
, liftA2 import Control.Applicative (Alternative(..), liftA2)
)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Except (throwE) import Control.Monad.Trans.Except (throwE)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.Text (Text) import Data.Text (Text)
@ -71,7 +68,7 @@ appearsIn :: Character -> [Int]
appearsIn (Left x) = _appearsIn . _droidChar $ x appearsIn (Left x) = _appearsIn . _droidChar $ x
appearsIn (Right x) = _appearsIn . _humanChar $ x appearsIn (Right x) = _appearsIn . _humanChar $ x
secretBackstory :: MonadIO m => Character -> ActionT m Text secretBackstory :: Character -> ActionT Identity Text
secretBackstory = const $ ActionT $ throwE "secretBackstory is secret." secretBackstory = const $ ActionT $ throwE "secretBackstory is secret."
typeName :: Character -> Text typeName :: Character -> Text
@ -166,9 +163,6 @@ getHero :: Int -> Character
getHero 5 = luke getHero 5 = luke
getHero _ = artoo getHero _ = artoo
getHeroIO :: Int -> IO Character
getHeroIO = pure . getHero
getHuman :: Alternative f => ID -> f Character getHuman :: Alternative f => ID -> f Character
getHuman = fmap Right . getHuman' getHuman = fmap Right . getHuman'

View File

@ -6,6 +6,7 @@ module Test.StarWars.QuerySpec
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import Data.Aeson ((.=)) import Data.Aeson ((.=))
import Data.Functor.Identity (Identity(..))
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text) import Data.Text (Text)
import Language.GraphQL import Language.GraphQL
@ -357,7 +358,8 @@ spec = describe "Star Wars Query Tests" $ do
alderaan = "homePlanet" .= ("Alderaan" :: Text) alderaan = "homePlanet" .= ("Alderaan" :: Text)
testQuery :: Text -> Aeson.Value -> Expectation testQuery :: Text -> Aeson.Value -> Expectation
testQuery q expected = graphql schema q >>= flip shouldBe expected testQuery q expected = runIdentity (graphql schema q) `shouldBe` expected
testQueryParams :: Subs -> Text -> Aeson.Value -> Expectation testQueryParams :: Subs -> Text -> Aeson.Value -> Expectation
testQueryParams f q expected = graphqlSubs schema f q >>= flip shouldBe expected testQueryParams f q expected =
runIdentity (graphqlSubs schema f q) `shouldBe` expected

View File

@ -7,9 +7,9 @@ module Test.StarWars.Schema
, schema , schema
) where ) where
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Except (throwE) import Control.Monad.Trans.Except (throwE)
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Data.Functor.Identity (Identity)
import Data.List.NonEmpty (NonEmpty(..)) import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import qualified Language.GraphQL.Schema as Schema import qualified Language.GraphQL.Schema as Schema
@ -19,10 +19,10 @@ import Test.StarWars.Data
-- See https://github.com/graphql/graphql-js/blob/master/src/__tests__/starWarsSchema.js -- See https://github.com/graphql/graphql-js/blob/master/src/__tests__/starWarsSchema.js
schema :: MonadIO m => NonEmpty (Schema.Resolver m) schema :: NonEmpty (Schema.Resolver Identity)
schema = hero :| [human, droid] schema = hero :| [human, droid]
hero :: MonadIO m => Schema.Resolver m hero :: Schema.Resolver Identity
hero = Schema.object "hero" $ do hero = Schema.object "hero" $ do
episode <- argument "episode" episode <- argument "episode"
character $ case episode of character $ case episode of
@ -31,7 +31,7 @@ hero = Schema.object "hero" $ do
Schema.Enum "JEDI" -> getHero 6 Schema.Enum "JEDI" -> getHero 6
_ -> artoo _ -> artoo
human :: MonadIO m => Schema.Resolver m human :: Schema.Resolver Identity
human = Schema.wrappedObject "human" $ do human = Schema.wrappedObject "human" $ do
id' <- argument "id" id' <- argument "id"
case id' of case id' of
@ -42,14 +42,14 @@ human = Schema.wrappedObject "human" $ do
Just e -> Type.Named <$> character e Just e -> Type.Named <$> character e
_ -> ActionT $ throwE "Invalid arguments." _ -> ActionT $ throwE "Invalid arguments."
droid :: MonadIO m => Schema.Resolver m droid :: Schema.Resolver Identity
droid = Schema.object "droid" $ do droid = Schema.object "droid" $ do
id' <- argument "id" id' <- argument "id"
case id' of case id' of
Schema.String i -> character =<< liftIO (getDroid i) Schema.String i -> character =<< getDroid i
_ -> ActionT $ throwE "Invalid arguments." _ -> ActionT $ throwE "Invalid arguments."
character :: MonadIO m => Character -> ActionT m [Schema.Resolver m] character :: Character -> ActionT Identity [Schema.Resolver Identity]
character char = return character char = return
[ Schema.scalar "id" $ return $ id_ char [ Schema.scalar "id" $ return $ id_ char
, Schema.scalar "name" $ return $ name char , Schema.scalar "name" $ return $ name char