module GraphQL.Internal.Execution
( VariableValues
, ExecutionError(..)
, formatError
, getOperation
, substituteVariables
) where
import Protolude
import qualified Data.Map as Map
import GraphQL.Value
( Name
, Value
, pattern ValueNull
, Value'(..)
, List'(..)
, Object'(..)
)
import GraphQL.Internal.Output (GraphQLError(..))
import GraphQL.Internal.Validation
( Operation
, QueryDocument(..)
, VariableDefinition(..)
, VariableValue
, Variable
, Type(..)
)
getOperation :: QueryDocument value -> Maybe Name -> Either ExecutionError (Operation value)
getOperation (LoneAnonymousOperation op) Nothing = pure op
getOperation (MultipleOperations ops) (Just name) = note (NoSuchOperation name) (Map.lookup name ops)
getOperation (MultipleOperations ops) Nothing =
case toList ops of
[op] -> pure op
_ -> throwError NoAnonymousOperation
getOperation _ (Just name) = throwError (NoSuchOperation name)
substituteVariables :: Operation VariableValue -> VariableValues -> Either ExecutionError (Operation Value)
substituteVariables op vars = traverse (replaceVariable vars) op
replaceVariable :: VariableValues -> VariableValue -> Either ExecutionError Value
replaceVariable vars value =
case value of
ValueScalar' (Left defn) -> getValue defn
ValueScalar' (Right v) -> pure (ValueScalar' v)
ValueList' (List' xs) -> ValueList' . List' <$> traverse (replaceVariable vars) xs
ValueObject' (Object' xs) -> ValueObject' . Object' <$> traverse (replaceVariable vars) xs
where
getValue :: VariableDefinition -> Either ExecutionError Value
getValue (VariableDefinition variableName variableType defaultValue) =
note (MissingValue variableName) $
Map.lookup variableName vars <|> defaultValue <|> allowNull variableType
allowNull (TypeNonNull _) = empty
allowNull _ = pure ValueNull
data ExecutionError
= MissingValue Variable
| NoSuchOperation Name
| NoAnonymousOperation
deriving (Eq, Show)
instance GraphQLError ExecutionError where
formatError (MissingValue name) = "Missing value for " <> show name <> " and must be non-null."
formatError (NoSuchOperation name) = "Requested operation " <> show name <> " but couldn't find it."
formatError NoAnonymousOperation = "No name supplied for opertaion, but no anonymous operation."
type VariableValues = Map Variable Value