2019-11-11 15:46:52 +01:00
|
|
|
{-# LANGUAGE ExplicitForAll #-}
|
2020-05-21 10:20:59 +02:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
2020-05-22 10:11:48 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-12-06 22:52:24 +01:00
|
|
|
{-# LANGUAGE TupleSections #-}
|
2019-11-03 10:42:10 +01:00
|
|
|
|
2019-09-25 05:35:36 +02:00
|
|
|
-- | After the document is parsed, before getting executed the AST is
|
|
|
|
-- transformed into a similar, simpler AST. This module is responsible for
|
|
|
|
-- this transformation.
|
2019-12-07 09:46:00 +01:00
|
|
|
module Language.GraphQL.Execute.Transform
|
2020-05-21 10:20:59 +02:00
|
|
|
( Document(..)
|
2020-05-22 10:11:48 +02:00
|
|
|
, QueryError(..)
|
2020-05-21 10:20:59 +02:00
|
|
|
, document
|
2020-05-22 10:11:48 +02:00
|
|
|
, queryError
|
2019-07-14 05:58:05 +02:00
|
|
|
) where
|
2017-01-29 22:44:03 +01:00
|
|
|
|
2019-11-11 15:46:52 +01:00
|
|
|
import Control.Monad (foldM, unless)
|
2019-11-06 06:34:36 +01:00
|
|
|
import Control.Monad.Trans.Class (lift)
|
2020-05-23 06:46:21 +02:00
|
|
|
import Control.Monad.Trans.State (State, evalStateT, gets, modify)
|
2020-05-22 10:11:48 +02:00
|
|
|
import Data.Foldable (find)
|
2020-05-23 06:46:21 +02:00
|
|
|
import Data.Functor.Identity (Identity(..))
|
2019-10-31 07:32:51 +01:00
|
|
|
import Data.HashMap.Strict (HashMap)
|
|
|
|
import qualified Data.HashMap.Strict as HashMap
|
2020-05-23 06:46:21 +02:00
|
|
|
import Data.Maybe (fromMaybe)
|
2020-05-22 10:11:48 +02:00
|
|
|
import Data.List.NonEmpty (NonEmpty(..))
|
2017-01-29 22:44:03 +01:00
|
|
|
import qualified Data.List.NonEmpty as NonEmpty
|
2019-11-16 11:41:40 +01:00
|
|
|
import Data.Sequence (Seq, (<|), (><))
|
2020-05-22 10:11:48 +02:00
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as Text
|
2019-07-07 06:31:53 +02:00
|
|
|
import qualified Language.GraphQL.AST as Full
|
|
|
|
import qualified Language.GraphQL.AST.Core as Core
|
2020-05-22 10:11:48 +02:00
|
|
|
import Language.GraphQL.Execute.Coerce
|
2019-07-07 06:31:53 +02:00
|
|
|
import qualified Language.GraphQL.Schema as Schema
|
2019-12-17 09:03:18 +01:00
|
|
|
import qualified Language.GraphQL.Type.Directive as Directive
|
2020-05-24 13:51:00 +02:00
|
|
|
import qualified Language.GraphQL.Type.In as In
|
2020-05-22 10:11:48 +02:00
|
|
|
import Language.GraphQL.Type.Schema
|
2017-01-29 22:44:03 +01:00
|
|
|
|
2019-10-31 07:32:51 +01:00
|
|
|
-- | Associates a fragment name with a list of 'Core.Field's.
|
2019-11-06 06:34:36 +01:00
|
|
|
data Replacement = Replacement
|
2019-12-01 20:43:19 +01:00
|
|
|
{ fragments :: HashMap Core.Name Core.Fragment
|
2019-11-11 15:46:52 +01:00
|
|
|
, fragmentDefinitions :: HashMap Full.Name Full.FragmentDefinition
|
2020-05-23 06:46:21 +02:00
|
|
|
, variableValues :: Schema.Subs
|
2019-11-06 06:34:36 +01:00
|
|
|
}
|
|
|
|
|
2020-05-23 06:46:21 +02:00
|
|
|
type TransformT a = State Replacement a
|
2019-12-07 09:46:00 +01:00
|
|
|
|
2020-05-21 10:20:59 +02:00
|
|
|
-- | GraphQL document is a non-empty list of operations.
|
2020-05-23 06:46:21 +02:00
|
|
|
newtype Document = Document Core.Operation
|
2020-05-21 10:20:59 +02:00
|
|
|
|
|
|
|
data OperationDefinition = OperationDefinition
|
|
|
|
Full.OperationType
|
|
|
|
(Maybe Full.Name)
|
|
|
|
[Full.VariableDefinition]
|
|
|
|
[Full.Directive]
|
|
|
|
Full.SelectionSet
|
|
|
|
|
2020-05-22 10:11:48 +02:00
|
|
|
-- | Query error types.
|
|
|
|
data QueryError
|
|
|
|
= OperationNotFound Text
|
|
|
|
| OperationNameRequired
|
|
|
|
| CoercionError
|
|
|
|
| TransformationError
|
|
|
|
| EmptyDocument
|
|
|
|
|
|
|
|
queryError :: QueryError -> Text
|
|
|
|
queryError (OperationNotFound operationName) = Text.unwords
|
|
|
|
["Operation", operationName, "couldn't be found in the document."]
|
|
|
|
queryError OperationNameRequired = "Missing operation name."
|
|
|
|
queryError CoercionError = "Coercion error."
|
|
|
|
queryError TransformationError = "Schema transformation error."
|
|
|
|
queryError EmptyDocument =
|
|
|
|
"The document doesn't contain any executable operations."
|
|
|
|
|
|
|
|
getOperation
|
|
|
|
:: Maybe Full.Name
|
|
|
|
-> NonEmpty OperationDefinition
|
|
|
|
-> Either QueryError OperationDefinition
|
|
|
|
getOperation Nothing (operation' :| []) = pure operation'
|
|
|
|
getOperation Nothing _ = Left OperationNameRequired
|
|
|
|
getOperation (Just operationName) operations
|
|
|
|
| Just operation' <- find matchingName operations = pure operation'
|
|
|
|
| otherwise = Left $ OperationNotFound operationName
|
|
|
|
where
|
|
|
|
matchingName (OperationDefinition _ name _ _ _) =
|
|
|
|
name == Just operationName
|
|
|
|
|
|
|
|
lookupInputType
|
|
|
|
:: Full.Type
|
2020-05-25 07:41:21 +02:00
|
|
|
-> HashMap.HashMap Full.Name (Type m)
|
|
|
|
-> Maybe In.Type
|
2020-05-22 10:11:48 +02:00
|
|
|
lookupInputType (Full.TypeNamed name) types =
|
|
|
|
case HashMap.lookup name types of
|
2020-05-25 07:41:21 +02:00
|
|
|
Just (ScalarType scalarType) ->
|
|
|
|
Just $ In.NamedScalarType scalarType
|
|
|
|
Just (EnumType enumType) ->
|
|
|
|
Just $ In.NamedEnumType enumType
|
|
|
|
Just (InputObjectType objectType) ->
|
|
|
|
Just $ In.NamedInputObjectType objectType
|
2020-05-22 10:11:48 +02:00
|
|
|
_ -> Nothing
|
|
|
|
lookupInputType (Full.TypeList list) types
|
2020-05-25 07:41:21 +02:00
|
|
|
= In.ListType
|
2020-05-22 10:11:48 +02:00
|
|
|
<$> lookupInputType list types
|
|
|
|
lookupInputType (Full.TypeNonNull (Full.NonNullTypeNamed nonNull)) types =
|
|
|
|
case HashMap.lookup nonNull types of
|
2020-05-25 07:41:21 +02:00
|
|
|
Just (ScalarType scalarType) ->
|
|
|
|
Just $ In.NonNullScalarType scalarType
|
|
|
|
Just (EnumType enumType) ->
|
|
|
|
Just $ In.NonNullEnumType enumType
|
|
|
|
Just (InputObjectType objectType) ->
|
|
|
|
Just $ In.NonNullInputObjectType objectType
|
2020-05-22 10:11:48 +02:00
|
|
|
_ -> Nothing
|
|
|
|
lookupInputType (Full.TypeNonNull (Full.NonNullTypeList nonNull)) types
|
2020-05-25 07:41:21 +02:00
|
|
|
= In.NonNullListType
|
2020-05-22 10:11:48 +02:00
|
|
|
<$> lookupInputType nonNull types
|
|
|
|
|
|
|
|
coerceVariableValues :: (Monad m, VariableValue a)
|
|
|
|
=> Schema m
|
|
|
|
-> OperationDefinition
|
|
|
|
-> HashMap.HashMap Full.Name a
|
|
|
|
-> Either QueryError Schema.Subs
|
2020-05-23 06:46:21 +02:00
|
|
|
coerceVariableValues schema operationDefinition variableValues' =
|
2020-05-22 10:11:48 +02:00
|
|
|
let referencedTypes = collectReferencedTypes schema
|
2020-05-23 06:46:21 +02:00
|
|
|
OperationDefinition _ _ variableDefinitions _ _ = operationDefinition
|
|
|
|
coerceValue' = coerceValue referencedTypes
|
2020-05-22 10:11:48 +02:00
|
|
|
in maybe (Left CoercionError) Right
|
2020-05-23 06:46:21 +02:00
|
|
|
$ foldr coerceValue' (Just HashMap.empty) variableDefinitions
|
2020-05-22 10:11:48 +02:00
|
|
|
where
|
|
|
|
coerceValue referencedTypes variableDefinition coercedValues = do
|
2020-05-23 06:46:21 +02:00
|
|
|
let Full.VariableDefinition variableName variableTypeName defaultValue =
|
2020-05-22 10:11:48 +02:00
|
|
|
variableDefinition
|
2020-05-23 06:46:21 +02:00
|
|
|
let defaultValue' = constValue <$> defaultValue
|
|
|
|
let value' = HashMap.lookup variableName variableValues'
|
|
|
|
|
2020-05-22 10:11:48 +02:00
|
|
|
variableType <- lookupInputType variableTypeName referencedTypes
|
2020-05-23 06:46:21 +02:00
|
|
|
HashMap.insert variableName
|
|
|
|
<$> choose value' defaultValue' variableType
|
|
|
|
<*> coercedValues
|
|
|
|
choose Nothing defaultValue variableType
|
|
|
|
| Just _ <- defaultValue = defaultValue
|
2020-05-25 07:41:21 +02:00
|
|
|
| not (In.isNonNullType variableType) = Just In.Null
|
2020-05-23 06:46:21 +02:00
|
|
|
choose (Just value') _ variableType
|
|
|
|
| Just coercedValue <- coerceVariableValue variableType value'
|
2020-05-25 07:41:21 +02:00
|
|
|
, not (In.isNonNullType variableType) || coercedValue /= In.Null =
|
2020-05-23 06:46:21 +02:00
|
|
|
Just coercedValue
|
|
|
|
choose _ _ _ = Nothing
|
|
|
|
|
2020-05-24 13:51:00 +02:00
|
|
|
constValue :: Full.ConstValue -> In.Value
|
|
|
|
constValue (Full.ConstInt i) = In.Int i
|
|
|
|
constValue (Full.ConstFloat f) = In.Float f
|
|
|
|
constValue (Full.ConstString x) = In.String x
|
|
|
|
constValue (Full.ConstBoolean b) = In.Boolean b
|
|
|
|
constValue Full.ConstNull = In.Null
|
|
|
|
constValue (Full.ConstEnum e) = In.Enum e
|
|
|
|
constValue (Full.ConstList l) = In.List $ constValue <$> l
|
2020-05-23 06:46:21 +02:00
|
|
|
constValue (Full.ConstObject o) =
|
2020-05-24 13:51:00 +02:00
|
|
|
In.Object $ HashMap.fromList $ constObjectField <$> o
|
2020-05-23 06:46:21 +02:00
|
|
|
where
|
|
|
|
constObjectField (Full.ObjectField key value') = (key, constValue value')
|
2020-05-22 10:11:48 +02:00
|
|
|
|
2019-08-29 07:40:50 +02:00
|
|
|
-- | Rewrites the original syntax tree into an intermediate representation used
|
|
|
|
-- for query execution.
|
2020-05-22 10:11:48 +02:00
|
|
|
document :: (Monad m, VariableValue a)
|
|
|
|
=> Schema m
|
|
|
|
-> Maybe Full.Name
|
|
|
|
-> HashMap Full.Name a
|
|
|
|
-> Full.Document
|
|
|
|
-> Either QueryError Document
|
|
|
|
document schema operationName subs ast = do
|
2020-05-21 10:20:59 +02:00
|
|
|
let (operations, fragmentTable) = foldr defragment ([], HashMap.empty) ast
|
2020-05-22 10:11:48 +02:00
|
|
|
nonEmptyOperations <- maybe (Left EmptyDocument) Right
|
|
|
|
$ NonEmpty.nonEmpty operations
|
|
|
|
chosenOperation <- getOperation operationName nonEmptyOperations
|
|
|
|
coercedValues <- coerceVariableValues schema chosenOperation subs
|
|
|
|
|
2020-05-23 06:46:21 +02:00
|
|
|
pure $ Document
|
|
|
|
$ operation fragmentTable coercedValues chosenOperation
|
2017-01-29 22:44:03 +01:00
|
|
|
where
|
2020-05-21 10:20:59 +02:00
|
|
|
defragment definition (operations, fragments')
|
|
|
|
| (Full.ExecutableDefinition executable) <- definition
|
|
|
|
, (Full.DefinitionOperation operation') <- executable =
|
|
|
|
(transform operation' : operations, fragments')
|
|
|
|
| (Full.ExecutableDefinition executable) <- definition
|
|
|
|
, (Full.DefinitionFragment fragment) <- executable
|
|
|
|
, (Full.FragmentDefinition name _ _ _) <- fragment =
|
|
|
|
(operations, HashMap.insert name fragment fragments')
|
2019-12-26 13:00:47 +01:00
|
|
|
defragment _ acc = acc
|
2020-05-21 10:20:59 +02:00
|
|
|
transform = \case
|
|
|
|
Full.OperationDefinition type' name variables directives' selections ->
|
|
|
|
OperationDefinition type' name variables directives' selections
|
|
|
|
Full.SelectionSet selectionSet ->
|
|
|
|
OperationDefinition Full.Query Nothing mempty mempty selectionSet
|
2017-01-29 22:44:03 +01:00
|
|
|
|
2017-02-04 01:48:26 +01:00
|
|
|
-- * Operation
|
|
|
|
|
2020-05-21 10:20:59 +02:00
|
|
|
operation
|
|
|
|
:: HashMap Full.Name Full.FragmentDefinition
|
|
|
|
-> Schema.Subs
|
|
|
|
-> OperationDefinition
|
2020-05-23 06:46:21 +02:00
|
|
|
-> Core.Operation
|
|
|
|
operation fragmentTable subs operationDefinition
|
|
|
|
= runIdentity
|
2020-05-21 10:20:59 +02:00
|
|
|
$ evalStateT (collectFragments >> transform operationDefinition)
|
2020-05-23 06:46:21 +02:00
|
|
|
$ Replacement HashMap.empty fragmentTable subs
|
2020-05-21 10:20:59 +02:00
|
|
|
where
|
|
|
|
transform :: OperationDefinition -> TransformT Core.Operation
|
|
|
|
transform (OperationDefinition Full.Query name _ _ sels) =
|
|
|
|
Core.Query name <$> appendSelection sels
|
|
|
|
transform (OperationDefinition Full.Mutation name _ _ sels) =
|
|
|
|
Core.Mutation name <$> appendSelection sels
|
2019-10-31 07:32:51 +01:00
|
|
|
|
2019-12-06 22:52:24 +01:00
|
|
|
-- * Selection
|
|
|
|
|
2019-10-31 07:32:51 +01:00
|
|
|
selection ::
|
|
|
|
Full.Selection ->
|
2019-11-16 11:41:40 +01:00
|
|
|
TransformT (Either (Seq Core.Selection) Core.Selection)
|
2019-12-25 06:45:29 +01:00
|
|
|
selection (Full.Field alias name arguments' directives' selections) =
|
|
|
|
maybe (Left mempty) (Right . Core.SelectionField) <$> do
|
2020-01-01 10:58:11 +01:00
|
|
|
fieldArguments <- arguments arguments'
|
2019-12-25 06:45:29 +01:00
|
|
|
fieldSelections <- appendSelection selections
|
|
|
|
fieldDirectives <- Directive.selection <$> directives directives'
|
|
|
|
let field' = Core.Field alias name fieldArguments fieldSelections
|
|
|
|
pure $ field' <$ fieldDirectives
|
|
|
|
selection (Full.FragmentSpread name directives') =
|
|
|
|
maybe (Left mempty) (Right . Core.SelectionFragment) <$> do
|
|
|
|
spreadDirectives <- Directive.selection <$> directives directives'
|
|
|
|
fragments' <- gets fragments
|
2020-05-23 06:46:21 +02:00
|
|
|
|
2019-12-25 06:45:29 +01:00
|
|
|
fragmentDefinitions' <- gets fragmentDefinitions
|
2020-05-23 06:46:21 +02:00
|
|
|
case HashMap.lookup name fragments' of
|
|
|
|
Just definition -> lift $ pure $ definition <$ spreadDirectives
|
|
|
|
Nothing -> case HashMap.lookup name fragmentDefinitions' of
|
|
|
|
Just definition -> do
|
|
|
|
fragment <- fragmentDefinition definition
|
|
|
|
lift $ pure $ fragment <$ spreadDirectives
|
|
|
|
Nothing -> lift $ pure Nothing
|
2019-12-25 06:45:29 +01:00
|
|
|
selection (Full.InlineFragment type' directives' selections) = do
|
|
|
|
fragmentDirectives <- Directive.selection <$> directives directives'
|
|
|
|
case fragmentDirectives of
|
|
|
|
Nothing -> pure $ Left mempty
|
|
|
|
_ -> do
|
|
|
|
fragmentSelectionSet <- appendSelection selections
|
|
|
|
pure $ maybe Left selectionFragment type' fragmentSelectionSet
|
|
|
|
where
|
|
|
|
selectionFragment typeName = Right
|
|
|
|
. Core.SelectionFragment
|
|
|
|
. Core.Fragment typeName
|
2019-12-06 22:52:24 +01:00
|
|
|
|
|
|
|
appendSelection ::
|
|
|
|
Traversable t =>
|
|
|
|
t Full.Selection ->
|
|
|
|
TransformT (Seq Core.Selection)
|
|
|
|
appendSelection = foldM go mempty
|
|
|
|
where
|
|
|
|
go acc sel = append acc <$> selection sel
|
|
|
|
append acc (Left list) = list >< acc
|
|
|
|
append acc (Right one) = one <| acc
|
|
|
|
|
|
|
|
directives :: [Full.Directive] -> TransformT [Core.Directive]
|
|
|
|
directives = traverse directive
|
|
|
|
where
|
|
|
|
directive (Full.Directive directiveName directiveArguments) =
|
|
|
|
Core.Directive directiveName <$> arguments directiveArguments
|
2017-02-04 01:48:26 +01:00
|
|
|
|
2017-01-29 22:44:03 +01:00
|
|
|
-- * Fragment replacement
|
|
|
|
|
2019-11-11 15:46:52 +01:00
|
|
|
-- | Extract fragment definitions into a single 'HashMap'.
|
|
|
|
collectFragments :: TransformT ()
|
|
|
|
collectFragments = do
|
|
|
|
fragDefs <- gets fragmentDefinitions
|
|
|
|
let nextValue = head $ HashMap.elems fragDefs
|
|
|
|
unless (HashMap.null fragDefs) $ do
|
|
|
|
_ <- fragmentDefinition nextValue
|
|
|
|
collectFragments
|
|
|
|
|
2019-11-13 20:40:09 +01:00
|
|
|
fragmentDefinition ::
|
|
|
|
Full.FragmentDefinition ->
|
2019-12-01 20:43:19 +01:00
|
|
|
TransformT Core.Fragment
|
2019-12-06 22:52:24 +01:00
|
|
|
fragmentDefinition (Full.FragmentDefinition name type' _ selections) = do
|
2019-11-13 20:40:09 +01:00
|
|
|
modify deleteFragmentDefinition
|
2019-12-01 20:43:19 +01:00
|
|
|
fragmentSelection <- appendSelection selections
|
2019-12-06 22:52:24 +01:00
|
|
|
let newValue = Core.Fragment type' fragmentSelection
|
2019-11-13 20:40:09 +01:00
|
|
|
modify $ insertFragment newValue
|
2020-05-23 06:46:21 +02:00
|
|
|
lift $ pure newValue
|
2019-10-31 07:32:51 +01:00
|
|
|
where
|
2020-05-23 06:46:21 +02:00
|
|
|
deleteFragmentDefinition (Replacement fragments' fragmentDefinitions' subs) =
|
|
|
|
Replacement fragments' (HashMap.delete name fragmentDefinitions') subs
|
|
|
|
insertFragment newValue (Replacement fragments' fragmentDefinitions' subs) =
|
2019-11-13 20:40:09 +01:00
|
|
|
let newFragments = HashMap.insert name newValue fragments'
|
2020-05-23 06:46:21 +02:00
|
|
|
in Replacement newFragments fragmentDefinitions' subs
|
2017-01-29 22:44:03 +01:00
|
|
|
|
2019-12-06 22:52:24 +01:00
|
|
|
arguments :: [Full.Argument] -> TransformT Core.Arguments
|
|
|
|
arguments = fmap Core.Arguments . foldM go HashMap.empty
|
|
|
|
where
|
2020-01-01 10:58:11 +01:00
|
|
|
go arguments' (Full.Argument name value') = do
|
|
|
|
substitutedValue <- value value'
|
|
|
|
return $ HashMap.insert name substitutedValue arguments'
|
2019-11-06 06:34:36 +01:00
|
|
|
|
2020-05-24 13:51:00 +02:00
|
|
|
value :: Full.Value -> TransformT In.Value
|
2020-05-23 06:46:21 +02:00
|
|
|
value (Full.Variable name) =
|
2020-05-24 13:51:00 +02:00
|
|
|
gets $ fromMaybe In.Null . HashMap.lookup name . variableValues
|
|
|
|
value (Full.Int i) = pure $ In.Int i
|
|
|
|
value (Full.Float f) = pure $ In.Float f
|
|
|
|
value (Full.String x) = pure $ In.String x
|
|
|
|
value (Full.Boolean b) = pure $ In.Boolean b
|
|
|
|
value Full.Null = pure In.Null
|
|
|
|
value (Full.Enum e) = pure $ In.Enum e
|
2019-11-06 06:34:36 +01:00
|
|
|
value (Full.List l) =
|
2020-05-24 13:51:00 +02:00
|
|
|
In.List <$> traverse value l
|
2019-11-06 06:34:36 +01:00
|
|
|
value (Full.Object o) =
|
2020-05-24 13:51:00 +02:00
|
|
|
In.Object . HashMap.fromList <$> traverse objectField o
|
2019-11-06 06:34:36 +01:00
|
|
|
|
2020-05-24 13:51:00 +02:00
|
|
|
objectField :: Full.ObjectField Full.Value -> TransformT (Core.Name, In.Value)
|
2019-12-06 22:52:24 +01:00
|
|
|
objectField (Full.ObjectField name value') = (name,) <$> value value'
|