Deprecate Language.GraphQL.Execute.Schema

It is not a schema (at least not a complete one), but a resolver list,
and the resolvers should be provided by the user separately, because the
schema can originate from a GraphQL document. Schema name should be free
to provide a data type for the real schema later.
This commit is contained in:
Eugen Wissner 2019-08-30 07:26:04 +02:00
parent c1943c1979
commit 22313d05df
5 changed files with 67 additions and 64 deletions

View File

@ -6,7 +6,12 @@ All notable changes to this project will be documented in this file.
- Minimal documentation for all public symbols. - Minimal documentation for all public symbols.
### Deprecated ### Deprecated
- Language.GraphQL.AST.FragmentName. Replaced with Language.GraphQL.AST.Name. - `Language.GraphQL.AST.FragmentName`. Replaced with Language.GraphQL.AST.Name.
- `Language.GraphQL.Execute.Schema` - It is not a schema (at least not a
complete one), but a resolver list, and the resolvers should be provided by
the user separately, because the schema can originate from a GraphQL
document. `Schema` name should be free to provide a data type for the real
schema later.
## [0.5.0.0] - 2019-08-14 ## [0.5.0.0] - 2019-08-14
### Added ### Added

View File

@ -5,32 +5,31 @@ module Language.GraphQL
) where ) where
import Control.Monad.IO.Class (MonadIO) import Control.Monad.IO.Class (MonadIO)
import qualified Data.Text as T
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import Text.Megaparsec (parse) import Data.List.NonEmpty (NonEmpty)
import qualified Data.Text as T
import Language.GraphQL.Error
import Language.GraphQL.Execute import Language.GraphQL.Execute
import Language.GraphQL.Parser import Language.GraphQL.Parser
import Language.GraphQL.Schema import qualified Language.GraphQL.Schema as Schema
import Text.Megaparsec (parse)
import Language.GraphQL.Error -- | If the text parses correctly as a @GraphQL@ query the query is
-- executed using the given 'Schema.Resolver's.
-- | Takes a 'Schema' and text representing a @GraphQL@ request document. graphql :: MonadIO m
-- If the text parses correctly as a @GraphQL@ query the query is => NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-- executed according to the given 'Schema'. -> T.Text -- ^ Text representing a @GraphQL@ request document.
-- -> m Aeson.Value -- ^ Response.
-- Returns the response as an @Aeson.@'Aeson.Value'.
graphql :: MonadIO m => Schema m -> T.Text -> m Aeson.Value
graphql = flip graphqlSubs $ const Nothing graphql = flip graphqlSubs $ const Nothing
-- | Takes a 'Schema', a variable substitution function and text -- | If the text parses correctly as a @GraphQL@ query the substitution is
-- representing a @GraphQL@ request document. If the text parses -- applied to the query and the query is then executed using to the given
-- correctly as a @GraphQL@ query the substitution is applied to the -- 'Schema.Resolver's.
-- query and the query is then executed according to the given 'Schema'. graphqlSubs :: MonadIO m
-- => NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-- Returns the response as an @Aeson.@'Aeson.Value'. -> Schema.Subs -- ^ Variable substitution function.
graphqlSubs :: MonadIO m => Schema m -> Subs -> T.Text -> m Aeson.Value -> T.Text -- ^ Text representing a @GraphQL@ request document.
graphqlSubs schema f = -> m Aeson.Value -- ^ Response.
either parseError (execute schema f) graphqlSubs schema f
= either parseError (execute schema f)
. parse document "" . parse document ""

View File

@ -1,7 +1,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
-- | This module provides the function to execute a @GraphQL@ request -- -- | This module provides functions to execute a @GraphQL@ request.
-- according to a 'Schema'.
module Language.GraphQL.Execute module Language.GraphQL.Execute
( execute ( execute
, executeWithName , executeWithName
@ -9,51 +8,53 @@ module Language.GraphQL.Execute
import Control.Monad.IO.Class (MonadIO) import Control.Monad.IO.Class (MonadIO)
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NE import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as Text import qualified Data.Text as Text
import qualified Language.GraphQL.AST as AST import qualified Language.GraphQL.AST as AST
import qualified Language.GraphQL.AST.Core as AST.Core import qualified Language.GraphQL.AST.Core as AST.Core
import qualified Language.GraphQL.AST.Transform as Transform import qualified Language.GraphQL.AST.Transform as Transform
import Language.GraphQL.Error import Language.GraphQL.Error
import Language.GraphQL.Schema (Schema)
import qualified Language.GraphQL.Schema as Schema import qualified Language.GraphQL.Schema as Schema
-- | Takes a 'Schema', a variable substitution function ('Schema.Subs'), and a -- | The substitution is applied to the document, and the resolvers are applied
-- @GraphQL@ 'document'. The substitution is applied to the document using -- to the resulting fields.
-- '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 -- Returns the result of the query against the schema wrapped in a /data/
-- errors wrapped in an /errors/ field. -- field, or errors wrapped in an /errors/ field.
execute :: MonadIO m execute :: MonadIO m
=> Schema m => NonEmpty (Schema.Resolver m) -- ^ Resolvers.
-> Schema.Subs -> Schema.Subs -- ^ Variable substitution function.
-> AST.Document -> AST.Document -- @GraphQL@ document.
-> m Aeson.Value -> m Aeson.Value
execute schema subs doc = execute schema subs doc =
maybe transformError (document schema Nothing) $ Transform.document subs doc maybe transformError (document schema Nothing) $ Transform.document subs doc
where where
transformError = return $ singleError "Schema transformation error." transformError = return $ singleError "Schema transformation error."
-- | Takes a 'Schema', operation name, a variable substitution function ('Schema.Subs'), -- | The substitution is applied to the document, and the resolvers are applied
-- and a @GraphQL@ 'document'. The substitution is applied to the document using -- to the resulting fields. The operation name can be used if the document
-- 'rootFields', and the 'Schema''s resolvers are applied to the resulting fields. -- defines multiple root operations.
-- --
-- Returns the result of the query against the 'Schema' wrapped in a /data/ field, or -- Returns the result of the query against the schema wrapped in a /data/
-- errors wrapped in an /errors/ field. -- field, or errors wrapped in an /errors/ field.
executeWithName :: MonadIO m executeWithName :: MonadIO m
=> Schema m => NonEmpty (Schema.Resolver m) -- ^ Resolvers
-> Text -> Text -- ^ Operation name.
-> Schema.Subs -> Schema.Subs -- ^ Variable substitution function.
-> AST.Document -> AST.Document -- ^ @GraphQL@ Document.
-> m Aeson.Value -> m Aeson.Value
executeWithName schema name subs doc = executeWithName schema name subs doc =
maybe transformError (document schema $ Just name) $ Transform.document subs doc maybe transformError (document schema $ Just name) $ Transform.document subs doc
where where
transformError = return $ singleError "Schema transformation error." transformError = return $ singleError "Schema transformation error."
document :: MonadIO m => Schema m -> Maybe Text -> AST.Core.Document -> m Aeson.Value document :: MonadIO m
=> NonEmpty (Schema.Resolver m)
-> Maybe Text
-> AST.Core.Document
-> m Aeson.Value
document schema Nothing (op :| []) = operation schema op document schema Nothing (op :| []) = operation schema op
document schema (Just name) operations = case NE.dropWhile matchingName operations of document schema (Just name) operations = case NE.dropWhile matchingName operations of
[] -> return $ singleError [] -> return $ singleError
@ -65,7 +66,10 @@ 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 => Schema m -> AST.Core.Operation -> m Aeson.Value operation :: MonadIO m
=> NonEmpty (Schema.Resolver m)
-> AST.Core.Operation
-> m Aeson.Value
operation schema (AST.Core.Query _ flds) operation schema (AST.Core.Query _ flds)
= runCollectErrs (Schema.resolve (NE.toList schema) (NE.toList flds)) = runCollectErrs (Schema.resolve (NE.toList schema) (NE.toList flds))
operation schema (AST.Core.Mutation _ flds) operation schema (AST.Core.Mutation _ flds)

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
-- | This module provides a representation of a @GraphQL@ Schema in addition to -- | This module provides a representation of a @GraphQL@ Schema in addition to
-- functions for defining and manipulating Schemas. -- functions for defining and manipulating schemas.
module Language.GraphQL.Schema module Language.GraphQL.Schema
( Resolver ( Resolver
, Schema , Schema
@ -43,6 +43,7 @@ import Language.GraphQL.Trans
import Language.GraphQL.Type import Language.GraphQL.Type
import Language.GraphQL.AST.Core import Language.GraphQL.AST.Core
{-# DEPRECATED Schema "Use NonEmpty (Resolver m) instead" #-}
-- | A GraphQL schema. -- | A GraphQL schema.
-- @m@ is usually expected to be an instance of 'MonadIO'. -- @m@ is usually expected to be an instance of 'MonadIO'.
type Schema m = NonEmpty (Resolver m) type Schema m = NonEmpty (Resolver m)

View File

@ -11,46 +11,40 @@ module Test.StarWars.Schema
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 Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.IO.Class (MonadIO(..))
import Data.List.NonEmpty (NonEmpty((:|))) import Data.List.NonEmpty (NonEmpty(..))
import Language.GraphQL.Schema ( Schema
, Resolver
, Argument(..)
, Value(..)
)
import qualified Language.GraphQL.Schema as Schema import qualified Language.GraphQL.Schema as Schema
import Language.GraphQL.Trans import Language.GraphQL.Trans
import Language.GraphQL.Type import Language.GraphQL.Type
import Test.StarWars.Data import Test.StarWars.Data
-- * Schema
-- 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 => Schema m schema :: MonadIO m => NonEmpty (Schema.Resolver m)
schema = hero :| [human, droid] schema = hero :| [human, droid]
hero :: MonadIO m => Resolver m hero :: MonadIO m => Schema.Resolver m
hero = Schema.objectA "hero" $ \case hero = Schema.objectA "hero" $ \case
[] -> character artoo [] -> character artoo
[Argument "episode" (ValueEnum "NEWHOPE")] -> character $ getHero 4 [Schema.Argument "episode" (Schema.ValueEnum "NEWHOPE")] -> character $ getHero 4
[Argument "episode" (ValueEnum "EMPIRE" )] -> character $ getHero 5 [Schema.Argument "episode" (Schema.ValueEnum "EMPIRE" )] -> character $ getHero 5
[Argument "episode" (ValueEnum "JEDI" )] -> character $ getHero 6 [Schema.Argument "episode" (Schema.ValueEnum "JEDI" )] -> character $ getHero 6
_ -> ActionT $ throwE "Invalid arguments." _ -> ActionT $ throwE "Invalid arguments."
human :: MonadIO m => Resolver m human :: MonadIO m => Schema.Resolver m
human = Schema.wrappedObjectA "human" $ \case human = Schema.wrappedObjectA "human" $ \case
[Argument "id" (ValueString i)] -> do [Schema.Argument "id" (Schema.ValueString i)] -> do
humanCharacter <- lift $ return $ getHuman i >>= Just humanCharacter <- lift $ return $ getHuman i >>= Just
case humanCharacter of case humanCharacter of
Nothing -> return Null Nothing -> return Null
Just e -> Named <$> character e Just e -> Named <$> character e
_ -> ActionT $ throwE "Invalid arguments." _ -> ActionT $ throwE "Invalid arguments."
droid :: MonadIO m => Resolver m droid :: MonadIO m => Schema.Resolver m
droid = Schema.objectA "droid" $ \case droid = Schema.objectA "droid" $ \case
[Argument "id" (ValueString i)] -> character =<< liftIO (getDroid i) [Schema.Argument "id" (Schema.ValueString i)] -> character =<< liftIO (getDroid i)
_ -> ActionT $ throwE "Invalid arguments." _ -> ActionT $ throwE "Invalid arguments."
character :: MonadIO m => Character -> ActionT m [Resolver m] character :: MonadIO m => Character -> ActionT m [Schema.Resolver m]
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