module Stratosphere.BCMDataExports.Export.S3OutputConfigurationsProperty (
S3OutputConfigurationsProperty(..),
mkS3OutputConfigurationsProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data S3OutputConfigurationsProperty
=
S3OutputConfigurationsProperty {S3OutputConfigurationsProperty -> ()
haddock_workaround_ :: (),
S3OutputConfigurationsProperty -> Value Text
compression :: (Value Prelude.Text),
S3OutputConfigurationsProperty -> Value Text
format :: (Value Prelude.Text),
S3OutputConfigurationsProperty -> Value Text
outputType :: (Value Prelude.Text),
S3OutputConfigurationsProperty -> Value Text
overwrite :: (Value Prelude.Text)}
deriving stock (S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool
(S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool)
-> (S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool)
-> Eq S3OutputConfigurationsProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool
== :: S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool
$c/= :: S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool
/= :: S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> Bool
Prelude.Eq, Int -> S3OutputConfigurationsProperty -> ShowS
[S3OutputConfigurationsProperty] -> ShowS
S3OutputConfigurationsProperty -> String
(Int -> S3OutputConfigurationsProperty -> ShowS)
-> (S3OutputConfigurationsProperty -> String)
-> ([S3OutputConfigurationsProperty] -> ShowS)
-> Show S3OutputConfigurationsProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> S3OutputConfigurationsProperty -> ShowS
showsPrec :: Int -> S3OutputConfigurationsProperty -> ShowS
$cshow :: S3OutputConfigurationsProperty -> String
show :: S3OutputConfigurationsProperty -> String
$cshowList :: [S3OutputConfigurationsProperty] -> ShowS
showList :: [S3OutputConfigurationsProperty] -> ShowS
Prelude.Show)
mkS3OutputConfigurationsProperty ::
Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text -> S3OutputConfigurationsProperty
mkS3OutputConfigurationsProperty :: Value Text
-> Value Text
-> Value Text
-> Value Text
-> S3OutputConfigurationsProperty
mkS3OutputConfigurationsProperty
Value Text
compression
Value Text
format
Value Text
outputType
Value Text
overwrite
= S3OutputConfigurationsProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), compression :: Value Text
compression = Value Text
compression,
format :: Value Text
format = Value Text
format, outputType :: Value Text
outputType = Value Text
outputType, overwrite :: Value Text
overwrite = Value Text
overwrite}
instance ToResourceProperties S3OutputConfigurationsProperty where
toResourceProperties :: S3OutputConfigurationsProperty -> ResourceProperties
toResourceProperties S3OutputConfigurationsProperty {()
Value Text
haddock_workaround_ :: S3OutputConfigurationsProperty -> ()
compression :: S3OutputConfigurationsProperty -> Value Text
format :: S3OutputConfigurationsProperty -> Value Text
outputType :: S3OutputConfigurationsProperty -> Value Text
overwrite :: S3OutputConfigurationsProperty -> Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::BCMDataExports::Export.S3OutputConfigurations",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Compression" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
compression,
Key
"Format" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
format, Key
"OutputType" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
outputType,
Key
"Overwrite" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
overwrite]}
instance JSON.ToJSON S3OutputConfigurationsProperty where
toJSON :: S3OutputConfigurationsProperty -> Value
toJSON S3OutputConfigurationsProperty {()
Value Text
haddock_workaround_ :: S3OutputConfigurationsProperty -> ()
compression :: S3OutputConfigurationsProperty -> Value Text
format :: S3OutputConfigurationsProperty -> Value Text
outputType :: S3OutputConfigurationsProperty -> Value Text
overwrite :: S3OutputConfigurationsProperty -> Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Compression" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
compression, Key
"Format" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
format,
Key
"OutputType" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
outputType, Key
"Overwrite" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
overwrite]
instance Property "Compression" S3OutputConfigurationsProperty where
type PropertyType "Compression" S3OutputConfigurationsProperty = Value Prelude.Text
set :: PropertyType "Compression" S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> S3OutputConfigurationsProperty
set PropertyType "Compression" S3OutputConfigurationsProperty
newValue S3OutputConfigurationsProperty {()
Value Text
haddock_workaround_ :: S3OutputConfigurationsProperty -> ()
compression :: S3OutputConfigurationsProperty -> Value Text
format :: S3OutputConfigurationsProperty -> Value Text
outputType :: S3OutputConfigurationsProperty -> Value Text
overwrite :: S3OutputConfigurationsProperty -> Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
= S3OutputConfigurationsProperty {compression :: Value Text
compression = PropertyType "Compression" S3OutputConfigurationsProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
haddock_workaround_ :: ()
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
instance Property "Format" S3OutputConfigurationsProperty where
type PropertyType "Format" S3OutputConfigurationsProperty = Value Prelude.Text
set :: PropertyType "Format" S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> S3OutputConfigurationsProperty
set PropertyType "Format" S3OutputConfigurationsProperty
newValue S3OutputConfigurationsProperty {()
Value Text
haddock_workaround_ :: S3OutputConfigurationsProperty -> ()
compression :: S3OutputConfigurationsProperty -> Value Text
format :: S3OutputConfigurationsProperty -> Value Text
outputType :: S3OutputConfigurationsProperty -> Value Text
overwrite :: S3OutputConfigurationsProperty -> Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
= S3OutputConfigurationsProperty {format :: Value Text
format = PropertyType "Format" S3OutputConfigurationsProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
compression :: Value Text
outputType :: Value Text
overwrite :: Value Text
haddock_workaround_ :: ()
compression :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
instance Property "OutputType" S3OutputConfigurationsProperty where
type PropertyType "OutputType" S3OutputConfigurationsProperty = Value Prelude.Text
set :: PropertyType "OutputType" S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> S3OutputConfigurationsProperty
set PropertyType "OutputType" S3OutputConfigurationsProperty
newValue S3OutputConfigurationsProperty {()
Value Text
haddock_workaround_ :: S3OutputConfigurationsProperty -> ()
compression :: S3OutputConfigurationsProperty -> Value Text
format :: S3OutputConfigurationsProperty -> Value Text
outputType :: S3OutputConfigurationsProperty -> Value Text
overwrite :: S3OutputConfigurationsProperty -> Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
= S3OutputConfigurationsProperty {outputType :: Value Text
outputType = PropertyType "OutputType" S3OutputConfigurationsProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
overwrite :: Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
overwrite :: Value Text
..}
instance Property "Overwrite" S3OutputConfigurationsProperty where
type PropertyType "Overwrite" S3OutputConfigurationsProperty = Value Prelude.Text
set :: PropertyType "Overwrite" S3OutputConfigurationsProperty
-> S3OutputConfigurationsProperty -> S3OutputConfigurationsProperty
set PropertyType "Overwrite" S3OutputConfigurationsProperty
newValue S3OutputConfigurationsProperty {()
Value Text
haddock_workaround_ :: S3OutputConfigurationsProperty -> ()
compression :: S3OutputConfigurationsProperty -> Value Text
format :: S3OutputConfigurationsProperty -> Value Text
outputType :: S3OutputConfigurationsProperty -> Value Text
overwrite :: S3OutputConfigurationsProperty -> Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
overwrite :: Value Text
..}
= S3OutputConfigurationsProperty {overwrite :: Value Text
overwrite = PropertyType "Overwrite" S3OutputConfigurationsProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
haddock_workaround_ :: ()
compression :: Value Text
format :: Value Text
outputType :: Value Text
..}