{-# 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 = String -> m b forall a. String -> m a forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> m b) -> String -> m b forall a b. (a -> b) -> a -> b $ a -> String forall b a. (Show a, IsString b) => a -> b show a v String -> String -> String 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 Key -> Object -> Maybe Value forall a. Key -> KeyMap a -> Maybe a 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 -> String -> Parser a forall a. String -> Parser a forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Parser a) -> String -> Parser a forall a b. (a -> b) -> a -> b $ String "key \"__typename\" should be string but found: " String -> String -> String forall a. Semigroup a => a -> a -> a <> Value -> String forall b a. (Show a, IsString b) => a -> b show Value val withUnion (String, Value) -> Parser a _ Value _ = String -> Parser a forall a. String -> Parser a forall (m :: * -> *) a. MonadFail m => String -> m a fail String "expected Object" omitNulls :: [Pair] -> Value omitNulls :: [Pair] -> Value omitNulls = [Pair] -> Value object ([Pair] -> Value) -> ([Pair] -> [Pair]) -> [Pair] -> Value forall b c a. (b -> c) -> (a -> b) -> a -> c . (Pair -> Bool) -> [Pair] -> [Pair] forall a. (a -> Bool) -> [a] -> [a] filter Pair -> Bool forall {a}. (a, Value) -> Bool notNull where notNull :: (a, Value) -> Bool notNull (a _, Value Null) = Bool False notNull (a, Value) _ = Bool True