{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Client.Schema.JSON.TypeKind ( TypeKind (..), ) where import Data.Aeson (FromJSON (..)) import GHC.Generics import Relude data TypeKind = SCALAR | OBJECT | INTERFACE | UNION | ENUM | INPUT_OBJECT | LIST | NON_NULL deriving (TypeKind -> TypeKind -> Bool (TypeKind -> TypeKind -> Bool) -> (TypeKind -> TypeKind -> Bool) -> Eq TypeKind forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: TypeKind -> TypeKind -> Bool == :: TypeKind -> TypeKind -> Bool $c/= :: TypeKind -> TypeKind -> Bool /= :: TypeKind -> TypeKind -> Bool Eq, (forall x. TypeKind -> Rep TypeKind x) -> (forall x. Rep TypeKind x -> TypeKind) -> Generic TypeKind forall x. Rep TypeKind x -> TypeKind forall x. TypeKind -> Rep TypeKind x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. TypeKind -> Rep TypeKind x from :: forall x. TypeKind -> Rep TypeKind x $cto :: forall x. Rep TypeKind x -> TypeKind to :: forall x. Rep TypeKind x -> TypeKind Generic, Maybe TypeKind Value -> Parser [TypeKind] Value -> Parser TypeKind (Value -> Parser TypeKind) -> (Value -> Parser [TypeKind]) -> Maybe TypeKind -> FromJSON TypeKind forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe a -> FromJSON a $cparseJSON :: Value -> Parser TypeKind parseJSON :: Value -> Parser TypeKind $cparseJSONList :: Value -> Parser [TypeKind] parseJSONList :: Value -> Parser [TypeKind] $comittedField :: Maybe TypeKind omittedField :: Maybe TypeKind FromJSON, Int -> TypeKind -> ShowS [TypeKind] -> ShowS TypeKind -> String (Int -> TypeKind -> ShowS) -> (TypeKind -> String) -> ([TypeKind] -> ShowS) -> Show TypeKind forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> TypeKind -> ShowS showsPrec :: Int -> TypeKind -> ShowS $cshow :: TypeKind -> String show :: TypeKind -> String $cshowList :: [TypeKind] -> ShowS showList :: [TypeKind] -> ShowS Show)