forked from OSS/graphql
Move Core module out of AST
This commit is contained in:
parent
705e506c13
commit
8b164c4844
@ -7,9 +7,15 @@ and this project adheres to
|
||||
[Haskell Package Versioning Policy](https://pvp.haskell.org/).
|
||||
|
||||
## [Unreleased]
|
||||
## Added
|
||||
- `AST` reexports `AST.Parser`.
|
||||
|
||||
## Changed
|
||||
- `Trans.ActionT` is renamed to `ResolverT`. Since `Type.Out.Resolver` has gone
|
||||
it is a better name for GraphQL resolvers.
|
||||
- `AST.Core` contained only `Arguments` which was moved to `Type.Definition`.
|
||||
`AST` provides now only functionality related to parsing and encoding, as it
|
||||
should be.
|
||||
|
||||
## Removed
|
||||
- `Type.Out.Resolver`: It is an unneeded layer of complexity. Resolvers are a
|
||||
|
@ -1,6 +1,8 @@
|
||||
-- | Target AST for Parser.
|
||||
-- | Target AST for parser.
|
||||
module Language.GraphQL.AST
|
||||
( module Language.GraphQL.AST.Document
|
||||
, module Language.GraphQL.AST.Parser
|
||||
) where
|
||||
|
||||
import Language.GraphQL.AST.Document
|
||||
import Language.GraphQL.AST.Parser
|
||||
|
@ -1,19 +0,0 @@
|
||||
-- | This is the AST meant to be executed.
|
||||
module Language.GraphQL.AST.Core
|
||||
( Arguments(..)
|
||||
) where
|
||||
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
import Language.GraphQL.AST (Name)
|
||||
import Language.GraphQL.Type.Definition
|
||||
|
||||
-- | Argument list.
|
||||
newtype Arguments = Arguments (HashMap Name Value)
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance Semigroup Arguments where
|
||||
(Arguments x) <> (Arguments y) = Arguments $ x <> y
|
||||
|
||||
instance Monoid Arguments where
|
||||
mempty = Arguments mempty
|
||||
|
@ -19,7 +19,6 @@ import Data.Maybe (fromMaybe)
|
||||
import Data.Sequence (Seq(..))
|
||||
import Data.Text (Text)
|
||||
import Language.GraphQL.AST (Name)
|
||||
import Language.GraphQL.AST.Core
|
||||
import Language.GraphQL.Error
|
||||
import Language.GraphQL.Execute.Coerce
|
||||
import qualified Language.GraphQL.Execute.Transform as Transform
|
||||
@ -36,7 +35,7 @@ resolveFieldValue :: Monad m
|
||||
-> ResolverT m a
|
||||
-> m (Either Text a)
|
||||
resolveFieldValue result args =
|
||||
flip runReaderT (Context {arguments = Arguments args, values = result})
|
||||
flip runReaderT (Context {arguments = Type.Arguments args, values = result})
|
||||
. runExceptT
|
||||
. runResolverT
|
||||
|
||||
|
@ -44,7 +44,6 @@ import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import qualified Language.GraphQL.AST as Full
|
||||
import Language.GraphQL.AST (Name)
|
||||
import Language.GraphQL.AST.Core
|
||||
import qualified Language.GraphQL.Execute.Coerce as Coerce
|
||||
import Language.GraphQL.Type.Directive (Directive(..))
|
||||
import qualified Language.GraphQL.Type.Directive as Directive
|
||||
@ -341,7 +340,7 @@ directives :: [Full.Directive] -> State (Replacement m) [Directive]
|
||||
directives = traverse directive
|
||||
where
|
||||
directive (Full.Directive directiveName directiveArguments)
|
||||
= Directive directiveName . Arguments
|
||||
= Directive directiveName . Type.Arguments
|
||||
<$> foldM go HashMap.empty directiveArguments
|
||||
go arguments (Full.Argument name value') = do
|
||||
substitutedValue <- value value'
|
||||
|
@ -15,7 +15,6 @@ import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Text (Text)
|
||||
import Language.GraphQL.AST (Name)
|
||||
import Language.GraphQL.AST.Core
|
||||
import Language.GraphQL.Type.Definition
|
||||
import Prelude hiding (lookup)
|
||||
|
||||
|
@ -2,7 +2,8 @@
|
||||
|
||||
-- | Types that can be used as both input and output types.
|
||||
module Language.GraphQL.Type.Definition
|
||||
( EnumType(..)
|
||||
( Arguments(..)
|
||||
, EnumType(..)
|
||||
, EnumValue(..)
|
||||
, ScalarType(..)
|
||||
, Subs
|
||||
@ -40,6 +41,16 @@ instance IsString Value where
|
||||
-- and the value is the variable value.
|
||||
type Subs = HashMap Name Value
|
||||
|
||||
-- | Argument list.
|
||||
newtype Arguments = Arguments (HashMap Name Value)
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance Semigroup Arguments where
|
||||
(Arguments x) <> (Arguments y) = Arguments $ x <> y
|
||||
|
||||
instance Monoid Arguments where
|
||||
mempty = Arguments mempty
|
||||
|
||||
-- | Scalar type definition.
|
||||
--
|
||||
-- The leaf values of any request and input values to arguments are Scalars (or
|
||||
|
@ -7,7 +7,6 @@ module Language.GraphQL.Type.Directive
|
||||
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Language.GraphQL.AST (Name)
|
||||
import Language.GraphQL.AST.Core
|
||||
import Language.GraphQL.Type.Definition
|
||||
|
||||
-- | Directive.
|
||||
|
Loading…
Reference in New Issue
Block a user