{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Morpheus.Error.Warning
  ( renderGQLErrors,
    deprecatedEnum,
    deprecatedField,
    gqlWarnings,
  )
where

import Data.Aeson (encode)
import Data.ByteString.Lazy.Char8 (unpack)
import Data.Morpheus.Types.Internal.AST.Base
  ( Description,
    Ref (..),
  )
import Data.Morpheus.Types.Internal.AST.Error
  ( GQLError,
    GQLErrors,
    at,
    msg,
    msg,
  )
import Data.Morpheus.Types.Internal.AST.Name
  ( FieldName,
  )
import Language.Haskell.TH
import Relude

renderGQLErrors :: GQLErrors -> String
renderGQLErrors :: GQLErrors -> String
renderGQLErrors = ByteString -> String
unpack (ByteString -> String)
-> (GQLErrors -> ByteString) -> GQLErrors -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GQLError] -> ByteString
forall a. ToJSON a => a -> ByteString
encode ([GQLError] -> ByteString)
-> (GQLErrors -> [GQLError]) -> GQLErrors -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQLErrors -> [GQLError]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList

-- TODO: implement warnings, is not used
deprecatedEnum :: FieldName -> Ref FieldName -> Maybe Description -> GQLError
deprecatedEnum :: FieldName -> Ref FieldName -> Maybe Description -> GQLError
deprecatedEnum FieldName
typeName Ref {Position
refPosition :: forall name. Ref name -> Position
refPosition :: Position
refPosition, FieldName
refName :: forall name. Ref name -> name
refName :: FieldName
refName} Maybe Description
reason =
  GQLError
"the enum value "
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> FieldName -> GQLError
forall a. Msg a => a -> GQLError
msg FieldName
typeName
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> GQLError
"."
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> FieldName -> GQLError
forall a. Msg a => a -> GQLError
msg FieldName
refName
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> GQLError
" is deprecated."
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> Description -> GQLError
forall a. Msg a => a -> GQLError
msg (Description
-> (Description -> Description) -> Maybe Description -> Description
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Description
"" (Description
" " Description -> Description -> Description
forall a. Semigroup a => a -> a -> a
<>) Maybe Description
reason) GQLError -> Position -> GQLError
`at` Position
refPosition

deprecatedField :: FieldName -> Ref FieldName -> Maybe Description -> GQLError
deprecatedField :: FieldName -> Ref FieldName -> Maybe Description -> GQLError
deprecatedField FieldName
typeName Ref {Position
refPosition :: Position
refPosition :: forall name. Ref name -> Position
refPosition, FieldName
refName :: FieldName
refName :: forall name. Ref name -> name
refName} Maybe Description
reason =
  GQLError
"the field "
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> FieldName -> GQLError
forall a. Msg a => a -> GQLError
msg FieldName
typeName
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> GQLError
"."
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> FieldName -> GQLError
forall a. Msg a => a -> GQLError
msg FieldName
refName
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> GQLError
" is deprecated."
    GQLError -> GQLError -> GQLError
forall a. Semigroup a => a -> a -> a
<> Description -> GQLError
forall a. Msg a => a -> GQLError
msg (Description
-> (Description -> Description) -> Maybe Description -> Description
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Description
"" (Description
" " Description -> Description -> Description
forall a. Semigroup a => a -> a -> a
<>) Maybe Description
reason) GQLError -> Position -> GQLError
`at` Position
refPosition

gqlWarnings :: [GQLError] -> Q ()
gqlWarnings :: [GQLError] -> Q ()
gqlWarnings [] = () -> Q ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
gqlWarnings [GQLError]
warnings = (GQLError -> Q ()) -> [GQLError] -> Q ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ GQLError -> Q ()
forall a. ToJSON a => a -> Q ()
handleWarning [GQLError]
warnings
  where
    handleWarning :: a -> Q ()
handleWarning a
warning =
      String -> Q ()
reportWarning (String
"Morpheus GraphQL Warning: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> (ByteString -> String
unpack (ByteString -> String) -> (a -> ByteString) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. ToJSON a => a -> ByteString
encode) a
warning)