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

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

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

renderGQLErrors :: GQLErrors -> String
renderGQLErrors :: GQLErrors -> String
renderGQLErrors = ByteString -> String
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 "
    forall a. Semigroup a => a -> a -> a
<> forall a. Msg a => a -> GQLError
msg FieldName
typeName
    forall a. Semigroup a => a -> a -> a
<> GQLError
"."
    forall a. Semigroup a => a -> a -> a
<> forall a. Msg a => a -> GQLError
msg FieldName
refName
    forall a. Semigroup a => a -> a -> a
<> GQLError
" is deprecated."
    forall a. Semigroup a => a -> a -> a
<> forall a. Msg a => a -> GQLError
msg (forall b a. b -> (a -> b) -> Maybe a -> b
maybe 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 "
    forall a. Semigroup a => a -> a -> a
<> forall a. Msg a => a -> GQLError
msg FieldName
typeName
    forall a. Semigroup a => a -> a -> a
<> GQLError
"."
    forall a. Semigroup a => a -> a -> a
<> forall a. Msg a => a -> GQLError
msg FieldName
refName
    forall a. Semigroup a => a -> a -> a
<> GQLError
" is deprecated."
    forall a. Semigroup a => a -> a -> a
<> forall a. Msg a => a -> GQLError
msg (forall b a. b -> (a -> b) -> Maybe a -> b
maybe 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 [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
gqlWarnings [GQLError]
warnings = forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (String -> Q ()
reportWarning forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQLError -> String
printWarning) [GQLError]
warnings

printWarning :: GQLError -> String
printWarning :: GQLError -> String
printWarning = String -> String -> GQLError -> String
printError String
"warning" String
"\x1b[33m"

printError :: String -> String -> GQLError -> String
printError :: String -> String -> GQLError -> String
printError String
label String
color GQLError
warning =
  String -> String
withColor (String
label forall a. Semigroup a => a -> a -> a
<> String
":")
    forall a. Semigroup a => a -> a -> a
<> String
description
    forall a. Semigroup a => a -> a -> a
<> String
loc
    forall a. Semigroup a => a -> a -> a
<> String
printedPath
    forall a. Semigroup a => a -> a -> a
<> String
"\n"
  where
    propPath :: [PropName]
propPath = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ GQLError -> Maybe [PropName]
path GQLError
warning
    propLoc :: [Position]
propLoc = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ GQLError -> Maybe [Position]
locations GQLError
warning
    description :: String
description = String
indent forall a. Semigroup a => a -> a -> a
<> String -> String
withColor (forall a. ToString a => a -> String
toString (GQLError -> Description
message GQLError
warning))
    loc :: String
loc
      | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PropName]
propPath = String
""
      | Bool
otherwise = String
indent forall a. Semigroup a => a -> a -> a
<> String
"  locations: " forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Position -> String
printLocation [Position]
propLoc
    printedPath :: String
printedPath
      | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PropName]
propPath = String
""
      | Bool
otherwise = String
indent forall a. Semigroup a => a -> a -> a
<> String
"  path: " forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> [[a]] -> [a]
intercalate String
"." (forall a b. (a -> b) -> [a] -> [b]
map PropName -> String
printPath [PropName]
propPath)

    withColor :: String -> String
    withColor :: String -> String
withColor String
x = String
color forall a. Semigroup a => a -> a -> a
<> String
x forall a. Semigroup a => a -> a -> a
<> String
"\x1b[0m"

indent :: String
indent :: String
indent = String
"\n      "

printPath :: PropName -> String
printPath :: PropName -> String
printPath (PropIndex Int
x) = forall b a. (Show a, IsString b) => a -> b
show Int
x
printPath (PropName Description
x) = Description -> String
T.unpack Description
x

printLocation :: Position -> String
printLocation :: Position -> String
printLocation Position {Int
column :: Position -> Int
line :: Position -> Int
column :: Int
line :: Int
..} = forall b a. (Show a, IsString b) => a -> b
show Int
line forall a. Semigroup a => a -> a -> a
<> String
":" forall a. Semigroup a => a -> a -> a
<> forall b a. (Show a, IsString b) => a -> b
show Int
column