module Stratosphere.S3.Bucket.S3KeyFilterProperty (
        module Exports, S3KeyFilterProperty(..), mkS3KeyFilterProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.S3.Bucket.FilterRuleProperty as Exports
import Stratosphere.ResourceProperties
data S3KeyFilterProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-s3-bucket-s3keyfilter.html>
    S3KeyFilterProperty {S3KeyFilterProperty -> ()
haddock_workaround_ :: (),
                         -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-s3-bucket-s3keyfilter.html#cfn-s3-bucket-s3keyfilter-rules>
                         S3KeyFilterProperty -> [FilterRuleProperty]
rules :: [FilterRuleProperty]}
  deriving stock (S3KeyFilterProperty -> S3KeyFilterProperty -> Bool
(S3KeyFilterProperty -> S3KeyFilterProperty -> Bool)
-> (S3KeyFilterProperty -> S3KeyFilterProperty -> Bool)
-> Eq S3KeyFilterProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: S3KeyFilterProperty -> S3KeyFilterProperty -> Bool
== :: S3KeyFilterProperty -> S3KeyFilterProperty -> Bool
$c/= :: S3KeyFilterProperty -> S3KeyFilterProperty -> Bool
/= :: S3KeyFilterProperty -> S3KeyFilterProperty -> Bool
Prelude.Eq, Int -> S3KeyFilterProperty -> ShowS
[S3KeyFilterProperty] -> ShowS
S3KeyFilterProperty -> String
(Int -> S3KeyFilterProperty -> ShowS)
-> (S3KeyFilterProperty -> String)
-> ([S3KeyFilterProperty] -> ShowS)
-> Show S3KeyFilterProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> S3KeyFilterProperty -> ShowS
showsPrec :: Int -> S3KeyFilterProperty -> ShowS
$cshow :: S3KeyFilterProperty -> String
show :: S3KeyFilterProperty -> String
$cshowList :: [S3KeyFilterProperty] -> ShowS
showList :: [S3KeyFilterProperty] -> ShowS
Prelude.Show)
mkS3KeyFilterProperty ::
  [FilterRuleProperty] -> S3KeyFilterProperty
mkS3KeyFilterProperty :: [FilterRuleProperty] -> S3KeyFilterProperty
mkS3KeyFilterProperty [FilterRuleProperty]
rules
  = S3KeyFilterProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), rules :: [FilterRuleProperty]
rules = [FilterRuleProperty]
rules}
instance ToResourceProperties S3KeyFilterProperty where
  toResourceProperties :: S3KeyFilterProperty -> ResourceProperties
toResourceProperties S3KeyFilterProperty {[FilterRuleProperty]
()
haddock_workaround_ :: S3KeyFilterProperty -> ()
rules :: S3KeyFilterProperty -> [FilterRuleProperty]
haddock_workaround_ :: ()
rules :: [FilterRuleProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::S3::Bucket.S3KeyFilter",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"Rules" Key -> [FilterRuleProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [FilterRuleProperty]
rules]}
instance JSON.ToJSON S3KeyFilterProperty where
  toJSON :: S3KeyFilterProperty -> Value
toJSON S3KeyFilterProperty {[FilterRuleProperty]
()
haddock_workaround_ :: S3KeyFilterProperty -> ()
rules :: S3KeyFilterProperty -> [FilterRuleProperty]
haddock_workaround_ :: ()
rules :: [FilterRuleProperty]
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Rules" Key -> [FilterRuleProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [FilterRuleProperty]
rules]
instance Property "Rules" S3KeyFilterProperty where
  type PropertyType "Rules" S3KeyFilterProperty = [FilterRuleProperty]
  set :: PropertyType "Rules" S3KeyFilterProperty
-> S3KeyFilterProperty -> S3KeyFilterProperty
set PropertyType "Rules" S3KeyFilterProperty
newValue S3KeyFilterProperty {[FilterRuleProperty]
()
haddock_workaround_ :: S3KeyFilterProperty -> ()
rules :: S3KeyFilterProperty -> [FilterRuleProperty]
haddock_workaround_ :: ()
rules :: [FilterRuleProperty]
..}
    = S3KeyFilterProperty {rules :: [FilterRuleProperty]
rules = [FilterRuleProperty]
PropertyType "Rules" S3KeyFilterProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}