module Stratosphere.S3.Bucket.SourceSelectionCriteriaProperty (
module Exports, SourceSelectionCriteriaProperty(..),
mkSourceSelectionCriteriaProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.S3.Bucket.ReplicaModificationsProperty as Exports
import {-# SOURCE #-} Stratosphere.S3.Bucket.SseKmsEncryptedObjectsProperty as Exports
import Stratosphere.ResourceProperties
data SourceSelectionCriteriaProperty
=
SourceSelectionCriteriaProperty {SourceSelectionCriteriaProperty -> ()
haddock_workaround_ :: (),
SourceSelectionCriteriaProperty
-> Maybe ReplicaModificationsProperty
replicaModifications :: (Prelude.Maybe ReplicaModificationsProperty),
SourceSelectionCriteriaProperty
-> Maybe SseKmsEncryptedObjectsProperty
sseKmsEncryptedObjects :: (Prelude.Maybe SseKmsEncryptedObjectsProperty)}
deriving stock (SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool
(SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool)
-> (SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool)
-> Eq SourceSelectionCriteriaProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool
== :: SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool
$c/= :: SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool
/= :: SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty -> Bool
Prelude.Eq, Int -> SourceSelectionCriteriaProperty -> ShowS
[SourceSelectionCriteriaProperty] -> ShowS
SourceSelectionCriteriaProperty -> String
(Int -> SourceSelectionCriteriaProperty -> ShowS)
-> (SourceSelectionCriteriaProperty -> String)
-> ([SourceSelectionCriteriaProperty] -> ShowS)
-> Show SourceSelectionCriteriaProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceSelectionCriteriaProperty -> ShowS
showsPrec :: Int -> SourceSelectionCriteriaProperty -> ShowS
$cshow :: SourceSelectionCriteriaProperty -> String
show :: SourceSelectionCriteriaProperty -> String
$cshowList :: [SourceSelectionCriteriaProperty] -> ShowS
showList :: [SourceSelectionCriteriaProperty] -> ShowS
Prelude.Show)
mkSourceSelectionCriteriaProperty ::
SourceSelectionCriteriaProperty
mkSourceSelectionCriteriaProperty :: SourceSelectionCriteriaProperty
mkSourceSelectionCriteriaProperty
= SourceSelectionCriteriaProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), replicaModifications :: Maybe ReplicaModificationsProperty
replicaModifications = Maybe ReplicaModificationsProperty
forall a. Maybe a
Prelude.Nothing,
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
sseKmsEncryptedObjects = Maybe SseKmsEncryptedObjectsProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties SourceSelectionCriteriaProperty where
toResourceProperties :: SourceSelectionCriteriaProperty -> ResourceProperties
toResourceProperties SourceSelectionCriteriaProperty {Maybe ReplicaModificationsProperty
Maybe SseKmsEncryptedObjectsProperty
()
haddock_workaround_ :: SourceSelectionCriteriaProperty -> ()
replicaModifications :: SourceSelectionCriteriaProperty
-> Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: SourceSelectionCriteriaProperty
-> Maybe SseKmsEncryptedObjectsProperty
haddock_workaround_ :: ()
replicaModifications :: Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::S3::Bucket.SourceSelectionCriteria",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ReplicaModificationsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ReplicaModifications" (ReplicaModificationsProperty -> (Key, Value))
-> Maybe ReplicaModificationsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ReplicaModificationsProperty
replicaModifications,
Key -> SseKmsEncryptedObjectsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SseKmsEncryptedObjects"
(SseKmsEncryptedObjectsProperty -> (Key, Value))
-> Maybe SseKmsEncryptedObjectsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SseKmsEncryptedObjectsProperty
sseKmsEncryptedObjects])}
instance JSON.ToJSON SourceSelectionCriteriaProperty where
toJSON :: SourceSelectionCriteriaProperty -> Value
toJSON SourceSelectionCriteriaProperty {Maybe ReplicaModificationsProperty
Maybe SseKmsEncryptedObjectsProperty
()
haddock_workaround_ :: SourceSelectionCriteriaProperty -> ()
replicaModifications :: SourceSelectionCriteriaProperty
-> Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: SourceSelectionCriteriaProperty
-> Maybe SseKmsEncryptedObjectsProperty
haddock_workaround_ :: ()
replicaModifications :: Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ReplicaModificationsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ReplicaModifications" (ReplicaModificationsProperty -> (Key, Value))
-> Maybe ReplicaModificationsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ReplicaModificationsProperty
replicaModifications,
Key -> SseKmsEncryptedObjectsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SseKmsEncryptedObjects"
(SseKmsEncryptedObjectsProperty -> (Key, Value))
-> Maybe SseKmsEncryptedObjectsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SseKmsEncryptedObjectsProperty
sseKmsEncryptedObjects]))
instance Property "ReplicaModifications" SourceSelectionCriteriaProperty where
type PropertyType "ReplicaModifications" SourceSelectionCriteriaProperty = ReplicaModificationsProperty
set :: PropertyType "ReplicaModifications" SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty
set PropertyType "ReplicaModifications" SourceSelectionCriteriaProperty
newValue SourceSelectionCriteriaProperty {Maybe ReplicaModificationsProperty
Maybe SseKmsEncryptedObjectsProperty
()
haddock_workaround_ :: SourceSelectionCriteriaProperty -> ()
replicaModifications :: SourceSelectionCriteriaProperty
-> Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: SourceSelectionCriteriaProperty
-> Maybe SseKmsEncryptedObjectsProperty
haddock_workaround_ :: ()
replicaModifications :: Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
..}
= SourceSelectionCriteriaProperty
{replicaModifications :: Maybe ReplicaModificationsProperty
replicaModifications = ReplicaModificationsProperty -> Maybe ReplicaModificationsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ReplicaModifications" SourceSelectionCriteriaProperty
ReplicaModificationsProperty
newValue, Maybe SseKmsEncryptedObjectsProperty
()
haddock_workaround_ :: ()
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
haddock_workaround_ :: ()
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
..}
instance Property "SseKmsEncryptedObjects" SourceSelectionCriteriaProperty where
type PropertyType "SseKmsEncryptedObjects" SourceSelectionCriteriaProperty = SseKmsEncryptedObjectsProperty
set :: PropertyType
"SseKmsEncryptedObjects" SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty
-> SourceSelectionCriteriaProperty
set PropertyType
"SseKmsEncryptedObjects" SourceSelectionCriteriaProperty
newValue SourceSelectionCriteriaProperty {Maybe ReplicaModificationsProperty
Maybe SseKmsEncryptedObjectsProperty
()
haddock_workaround_ :: SourceSelectionCriteriaProperty -> ()
replicaModifications :: SourceSelectionCriteriaProperty
-> Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: SourceSelectionCriteriaProperty
-> Maybe SseKmsEncryptedObjectsProperty
haddock_workaround_ :: ()
replicaModifications :: Maybe ReplicaModificationsProperty
sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
..}
= SourceSelectionCriteriaProperty
{sseKmsEncryptedObjects :: Maybe SseKmsEncryptedObjectsProperty
sseKmsEncryptedObjects = SseKmsEncryptedObjectsProperty
-> Maybe SseKmsEncryptedObjectsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"SseKmsEncryptedObjects" SourceSelectionCriteriaProperty
SseKmsEncryptedObjectsProperty
newValue, Maybe ReplicaModificationsProperty
()
haddock_workaround_ :: ()
replicaModifications :: Maybe ReplicaModificationsProperty
haddock_workaround_ :: ()
replicaModifications :: Maybe ReplicaModificationsProperty
..}