module Stratosphere.CleanRooms.Membership.MembershipProtectedJobOutputConfigurationProperty (
module Exports,
MembershipProtectedJobOutputConfigurationProperty(..),
mkMembershipProtectedJobOutputConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.CleanRooms.Membership.ProtectedJobS3OutputConfigurationInputProperty as Exports
import Stratosphere.ResourceProperties
data MembershipProtectedJobOutputConfigurationProperty
=
MembershipProtectedJobOutputConfigurationProperty {MembershipProtectedJobOutputConfigurationProperty -> ()
haddock_workaround_ :: (),
MembershipProtectedJobOutputConfigurationProperty
-> ProtectedJobS3OutputConfigurationInputProperty
s3 :: ProtectedJobS3OutputConfigurationInputProperty}
deriving stock (MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool
(MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool)
-> (MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool)
-> Eq MembershipProtectedJobOutputConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool
== :: MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool
$c/= :: MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool
/= :: MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty -> Bool
Prelude.Eq, Int -> MembershipProtectedJobOutputConfigurationProperty -> ShowS
[MembershipProtectedJobOutputConfigurationProperty] -> ShowS
MembershipProtectedJobOutputConfigurationProperty -> String
(Int -> MembershipProtectedJobOutputConfigurationProperty -> ShowS)
-> (MembershipProtectedJobOutputConfigurationProperty -> String)
-> ([MembershipProtectedJobOutputConfigurationProperty] -> ShowS)
-> Show MembershipProtectedJobOutputConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MembershipProtectedJobOutputConfigurationProperty -> ShowS
showsPrec :: Int -> MembershipProtectedJobOutputConfigurationProperty -> ShowS
$cshow :: MembershipProtectedJobOutputConfigurationProperty -> String
show :: MembershipProtectedJobOutputConfigurationProperty -> String
$cshowList :: [MembershipProtectedJobOutputConfigurationProperty] -> ShowS
showList :: [MembershipProtectedJobOutputConfigurationProperty] -> ShowS
Prelude.Show)
mkMembershipProtectedJobOutputConfigurationProperty ::
ProtectedJobS3OutputConfigurationInputProperty
-> MembershipProtectedJobOutputConfigurationProperty
mkMembershipProtectedJobOutputConfigurationProperty :: ProtectedJobS3OutputConfigurationInputProperty
-> MembershipProtectedJobOutputConfigurationProperty
mkMembershipProtectedJobOutputConfigurationProperty ProtectedJobS3OutputConfigurationInputProperty
s3
= MembershipProtectedJobOutputConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), s3 :: ProtectedJobS3OutputConfigurationInputProperty
s3 = ProtectedJobS3OutputConfigurationInputProperty
s3}
instance ToResourceProperties MembershipProtectedJobOutputConfigurationProperty where
toResourceProperties :: MembershipProtectedJobOutputConfigurationProperty
-> ResourceProperties
toResourceProperties
MembershipProtectedJobOutputConfigurationProperty {()
ProtectedJobS3OutputConfigurationInputProperty
haddock_workaround_ :: MembershipProtectedJobOutputConfigurationProperty -> ()
s3 :: MembershipProtectedJobOutputConfigurationProperty
-> ProtectedJobS3OutputConfigurationInputProperty
haddock_workaround_ :: ()
s3 :: ProtectedJobS3OutputConfigurationInputProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::CleanRooms::Membership.MembershipProtectedJobOutputConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"S3" Key
-> ProtectedJobS3OutputConfigurationInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ProtectedJobS3OutputConfigurationInputProperty
s3]}
instance JSON.ToJSON MembershipProtectedJobOutputConfigurationProperty where
toJSON :: MembershipProtectedJobOutputConfigurationProperty -> Value
toJSON MembershipProtectedJobOutputConfigurationProperty {()
ProtectedJobS3OutputConfigurationInputProperty
haddock_workaround_ :: MembershipProtectedJobOutputConfigurationProperty -> ()
s3 :: MembershipProtectedJobOutputConfigurationProperty
-> ProtectedJobS3OutputConfigurationInputProperty
haddock_workaround_ :: ()
s3 :: ProtectedJobS3OutputConfigurationInputProperty
..}
= [(Key, Value)] -> Value
JSON.object [Key
"S3" Key
-> ProtectedJobS3OutputConfigurationInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ProtectedJobS3OutputConfigurationInputProperty
s3]
instance Property "S3" MembershipProtectedJobOutputConfigurationProperty where
type PropertyType "S3" MembershipProtectedJobOutputConfigurationProperty = ProtectedJobS3OutputConfigurationInputProperty
set :: PropertyType "S3" MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty
-> MembershipProtectedJobOutputConfigurationProperty
set PropertyType "S3" MembershipProtectedJobOutputConfigurationProperty
newValue MembershipProtectedJobOutputConfigurationProperty {()
ProtectedJobS3OutputConfigurationInputProperty
haddock_workaround_ :: MembershipProtectedJobOutputConfigurationProperty -> ()
s3 :: MembershipProtectedJobOutputConfigurationProperty
-> ProtectedJobS3OutputConfigurationInputProperty
haddock_workaround_ :: ()
s3 :: ProtectedJobS3OutputConfigurationInputProperty
..}
= MembershipProtectedJobOutputConfigurationProperty
{s3 :: ProtectedJobS3OutputConfigurationInputProperty
s3 = PropertyType "S3" MembershipProtectedJobOutputConfigurationProperty
ProtectedJobS3OutputConfigurationInputProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}