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

module Data.Morpheus.Client.CodeGen.Internal
  ( FromJSON (..),
    ToJSON (..),
    RequestType (..),
    Generic,
    OperationType (..),
    scalarFromJSON,
    scalarToJSON,
    invalidConstructorError,
    withUnion,
    omitNulls,
    (.=),
    withObject,
    (.:),
    (.:?),
  )
where

import Data.Aeson
  ( FromJSON (..),
    ToJSON (..),
    object,
    withObject,
    (.:),
    (.:?),
    (.=),
  )
import Data.Aeson.Types (Pair, Parser, Value (..))
import Data.Morpheus.Client.Fetch.RequestType
  ( RequestType (..),
  )
import Data.Morpheus.Internal.Utils (IsMap (lookup))
import Data.Morpheus.Types.GQLScalar (scalarFromJSON, scalarToJSON)
import Data.Morpheus.Types.Internal.AST (OperationType (..))
import qualified Data.Text as T
import Relude

invalidConstructorError :: (MonadFail m, Show a) => a -> m b
invalidConstructorError :: forall (m :: * -> *) a b. (MonadFail m, Show a) => a -> m b
invalidConstructorError a
v = forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ forall b a. (Show a, IsString b) => a -> b
show a
v forall a. Semigroup a => a -> a -> a
<> String
" is Not Valid Union Constructor"

withUnion :: ((String, Value) -> Parser a) -> Value -> Parser a
withUnion :: forall a. ((String, Value) -> Parser a) -> Value -> Parser a
withUnion (String, Value) -> Parser a
f v :: Value
v@(Object Object
hMap) = case forall k (m :: * -> *) a. IsMap k m => k -> m a -> Maybe a
lookup Key
"__typename" Object
hMap of
  Maybe Value
Nothing -> (String, Value) -> Parser a
f (String
"__TYPENAME_NOT__FOUND__", Value
v)
  Just (String Text
x) -> (String, Value) -> Parser a
f (Text -> String
T.unpack Text
x, Value
v)
  Just Value
val ->
    forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"key \"__typename\" should be string but found: " forall a. Semigroup a => a -> a -> a
<> forall b a. (Show a, IsString b) => a -> b
show Value
val
withUnion (String, Value) -> Parser a
_ Value
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"expected Object"

omitNulls :: [Pair] -> Value
omitNulls :: [Pair] -> Value
omitNulls = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter forall {a}. (a, Value) -> Bool
notNull
  where
    notNull :: (a, Value) -> Bool
notNull (a
_, Value
Null) = Bool
False
    notNull (a, Value)
_ = Bool
True