{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DerivingStrategies #-} module Hercules.API.Effects.EffectReference where import Data.OpenApi qualified as O3 import Hercules.API.Prelude import Hercules.API.Projects.SimpleJob (SimpleJob) data EffectReference = EffectReference { EffectReference -> SimpleJob job :: SimpleJob, EffectReference -> [Text] attributePath :: [Text] } deriving ((forall x. EffectReference -> Rep EffectReference x) -> (forall x. Rep EffectReference x -> EffectReference) -> Generic EffectReference forall x. Rep EffectReference x -> EffectReference forall x. EffectReference -> Rep EffectReference x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. EffectReference -> Rep EffectReference x from :: forall x. EffectReference -> Rep EffectReference x $cto :: forall x. Rep EffectReference x -> EffectReference to :: forall x. Rep EffectReference x -> EffectReference Generic, Int -> EffectReference -> ShowS [EffectReference] -> ShowS EffectReference -> String (Int -> EffectReference -> ShowS) -> (EffectReference -> String) -> ([EffectReference] -> ShowS) -> Show EffectReference forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> EffectReference -> ShowS showsPrec :: Int -> EffectReference -> ShowS $cshow :: EffectReference -> String show :: EffectReference -> String $cshowList :: [EffectReference] -> ShowS showList :: [EffectReference] -> ShowS Show, EffectReference -> EffectReference -> Bool (EffectReference -> EffectReference -> Bool) -> (EffectReference -> EffectReference -> Bool) -> Eq EffectReference forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: EffectReference -> EffectReference -> Bool == :: EffectReference -> EffectReference -> Bool $c/= :: EffectReference -> EffectReference -> Bool /= :: EffectReference -> EffectReference -> Bool Eq) deriving anyclass (EffectReference -> () (EffectReference -> ()) -> NFData EffectReference forall a. (a -> ()) -> NFData a $crnf :: EffectReference -> () rnf :: EffectReference -> () NFData, [EffectReference] -> Value [EffectReference] -> Encoding EffectReference -> Value EffectReference -> Encoding (EffectReference -> Value) -> (EffectReference -> Encoding) -> ([EffectReference] -> Value) -> ([EffectReference] -> Encoding) -> ToJSON EffectReference forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a $ctoJSON :: EffectReference -> Value toJSON :: EffectReference -> Value $ctoEncoding :: EffectReference -> Encoding toEncoding :: EffectReference -> Encoding $ctoJSONList :: [EffectReference] -> Value toJSONList :: [EffectReference] -> Value $ctoEncodingList :: [EffectReference] -> Encoding toEncodingList :: [EffectReference] -> Encoding ToJSON, Value -> Parser [EffectReference] Value -> Parser EffectReference (Value -> Parser EffectReference) -> (Value -> Parser [EffectReference]) -> FromJSON EffectReference forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a $cparseJSON :: Value -> Parser EffectReference parseJSON :: Value -> Parser EffectReference $cparseJSONList :: Value -> Parser [EffectReference] parseJSONList :: Value -> Parser [EffectReference] FromJSON, Proxy EffectReference -> Declare (Definitions Schema) NamedSchema (Proxy EffectReference -> Declare (Definitions Schema) NamedSchema) -> ToSchema EffectReference forall a. (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy EffectReference -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy EffectReference -> Declare (Definitions Schema) NamedSchema ToSchema, Typeable EffectReference Typeable EffectReference => (Proxy EffectReference -> Declare (Definitions Schema) NamedSchema) -> ToSchema EffectReference Proxy EffectReference -> Declare (Definitions Schema) NamedSchema forall a. Typeable a => (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy EffectReference -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy EffectReference -> Declare (Definitions Schema) NamedSchema O3.ToSchema)