{-# LANGUAGE OverloadedStrings #-}
module Data.Morpheus.Error.Selection
( cannotQueryField
, subfieldsNotSelected
, duplicateQuerySelections
, hasNoSubfields
, fieldNotResolved
, resolverError
) where
import Data.Morpheus.Error.Utils (errorMessage)
import Data.Morpheus.Types.Internal.Base (EnhancedKey (..), Position)
import Data.Morpheus.Types.Internal.Validation (GQLError (..), GQLErrors)
import Data.Text (Text, pack)
import qualified Data.Text as T (concat)
resolverError :: Position -> Text -> String -> GQLErrors
resolverError pos name message = fieldNotResolved pos name (pack message)
fieldNotResolved :: Position -> Text -> Text -> GQLErrors
fieldNotResolved position' key' message' = errorMessage position' text
where
text = T.concat ["Failure on Resolving Field \"", key', "\": ", message']
hasNoSubfields :: Text -> Text -> Position -> GQLErrors
hasNoSubfields key typeName position = errorMessage position text
where
text = T.concat ["Field \"", key, "\" must not have a selection since type \"", typeName, "\" has no subfields."]
cannotQueryField :: Text -> Text -> Position -> GQLErrors
cannotQueryField key typeName position = errorMessage position text
where
text = T.concat ["Cannot query field \"", key, "\" on type \"", typeName, "\"."]
duplicateQuerySelections :: Text -> [EnhancedKey] -> GQLErrors
duplicateQuerySelections parentType = map keyToError
where
keyToError (EnhancedKey key' pos) = GQLError {desc = toMessage key', positions = [pos]}
toMessage key' = T.concat ["duplicate selection of key \"", key', "\" on type \"", parentType, "\"."]
subfieldsNotSelected :: Text -> Text -> Position -> GQLErrors
subfieldsNotSelected key typeName position = errorMessage position text
where
text = T.concat ["Field \"", key, "\" of type \"", typeName, "\" must have a selection of subfields"]