{-# LANGUAGE DeriveAnyClass #-} module Hercules.API.Inputs.ImmutableInput where import Data.Aeson ( FromJSON (parseJSON), ToJSON (toEncoding, toJSON), genericParseJSON, genericToEncoding, genericToJSON, ) import Hercules.API.Inputs.ImmutableGitInput import Hercules.API.Prelude data ImmutableInput = GitInput ImmutableGitInput | IgnoreMe () deriving ((forall x. ImmutableInput -> Rep ImmutableInput x) -> (forall x. Rep ImmutableInput x -> ImmutableInput) -> Generic ImmutableInput forall x. Rep ImmutableInput x -> ImmutableInput forall x. ImmutableInput -> Rep ImmutableInput x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ImmutableInput x -> ImmutableInput $cfrom :: forall x. ImmutableInput -> Rep ImmutableInput x Generic, Int -> ImmutableInput -> ShowS [ImmutableInput] -> ShowS ImmutableInput -> String (Int -> ImmutableInput -> ShowS) -> (ImmutableInput -> String) -> ([ImmutableInput] -> ShowS) -> Show ImmutableInput forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ImmutableInput] -> ShowS $cshowList :: [ImmutableInput] -> ShowS show :: ImmutableInput -> String $cshow :: ImmutableInput -> String showsPrec :: Int -> ImmutableInput -> ShowS $cshowsPrec :: Int -> ImmutableInput -> ShowS Show, ImmutableInput -> ImmutableInput -> Bool (ImmutableInput -> ImmutableInput -> Bool) -> (ImmutableInput -> ImmutableInput -> Bool) -> Eq ImmutableInput forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ImmutableInput -> ImmutableInput -> Bool $c/= :: ImmutableInput -> ImmutableInput -> Bool == :: ImmutableInput -> ImmutableInput -> Bool $c== :: ImmutableInput -> ImmutableInput -> Bool Eq, ImmutableInput -> () (ImmutableInput -> ()) -> NFData ImmutableInput forall a. (a -> ()) -> NFData a rnf :: ImmutableInput -> () $crnf :: ImmutableInput -> () NFData, Proxy ImmutableInput -> Declare (Definitions Schema) NamedSchema (Proxy ImmutableInput -> Declare (Definitions Schema) NamedSchema) -> ToSchema ImmutableInput forall a. (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a declareNamedSchema :: Proxy ImmutableInput -> Declare (Definitions Schema) NamedSchema $cdeclareNamedSchema :: Proxy ImmutableInput -> Declare (Definitions Schema) NamedSchema ToSchema) instance FromJSON ImmutableInput where parseJSON :: Value -> Parser ImmutableInput parseJSON = Options -> Value -> Parser ImmutableInput forall a. (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a genericParseJSON Options schemaCompatibleOptions instance ToJSON ImmutableInput where toJSON :: ImmutableInput -> Value toJSON = Options -> ImmutableInput -> Value forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value genericToJSON Options schemaCompatibleOptions toEncoding :: ImmutableInput -> Encoding toEncoding = Options -> ImmutableInput -> Encoding forall a. (Generic a, GToJSON' Encoding Zero (Rep a)) => Options -> a -> Encoding genericToEncoding Options schemaCompatibleOptions