{-# LANGUAGE OverloadedStrings #-}
module Data.Morpheus.Error.Variable
( undefinedVariable
, unknownType
, variableGotInvalidValue
, uninitializedVariable
, unusedVariables
, incompatibleVariableType
)
where
import Data.Morpheus.Error.Utils ( errorMessage )
import Data.Morpheus.Types.Internal.AST.Base
( Ref(..)
, Position
)
import Data.Morpheus.Types.Internal.Resolving.Core
( GQLError(..)
, GQLErrors
)
import Data.Semigroup ( (<>) )
import Data.Text ( Text )
import qualified Data.Text as T
( concat )
incompatibleVariableType :: Text -> Text -> Text -> Position -> GQLErrors
incompatibleVariableType variableName variableType argType argPosition =
errorMessage argPosition text
where
text =
"Variable \"$"
<> variableName
<> "\" of type \""
<> variableType
<> "\" used in position expecting type \""
<> argType
<> "\"."
unusedVariables :: Text -> [Ref] -> GQLErrors
unusedVariables operator' = map keyToError
where
keyToError (Ref key' position') =
GQLError { message = text key', locations = [position'] }
text key' = T.concat
["Variable \"$", key', "\" is never used in operation \"", operator', "\"."]
variableGotInvalidValue :: Text -> Text -> Position -> GQLErrors
variableGotInvalidValue name' inputMessage' position' = errorMessage
position'
text
where
text =
T.concat ["Variable \"$", name', "\" got invalid value; ", inputMessage']
unknownType :: Text -> Position -> GQLErrors
unknownType type' position' = errorMessage position' text
where text = T.concat ["Unknown type \"", type', "\"."]
undefinedVariable :: Text -> Position -> Text -> GQLErrors
undefinedVariable operation' position' key' = errorMessage position' text
where
text = T.concat
[ "Variable \""
, key'
, "\" is not defined by operation \""
, operation'
, "\"."
]
uninitializedVariable :: Position -> Text -> Text -> GQLErrors
uninitializedVariable position' type' key' = errorMessage position' text
where
text = T.concat
[ "Variable \"$"
, key'
, "\" of required type \""
, type'
, "!\" was not provided."
]