module Stratosphere.DynamoDB.GlobalTable.KinesisStreamSpecificationProperty (
KinesisStreamSpecificationProperty(..),
mkKinesisStreamSpecificationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data KinesisStreamSpecificationProperty
=
KinesisStreamSpecificationProperty {KinesisStreamSpecificationProperty -> ()
haddock_workaround_ :: (),
KinesisStreamSpecificationProperty -> Maybe (Value Text)
approximateCreationDateTimePrecision :: (Prelude.Maybe (Value Prelude.Text)),
KinesisStreamSpecificationProperty -> Value Text
streamArn :: (Value Prelude.Text)}
deriving stock (KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool
(KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool)
-> (KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool)
-> Eq KinesisStreamSpecificationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool
== :: KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool
$c/= :: KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool
/= :: KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty -> Bool
Prelude.Eq, Int -> KinesisStreamSpecificationProperty -> ShowS
[KinesisStreamSpecificationProperty] -> ShowS
KinesisStreamSpecificationProperty -> String
(Int -> KinesisStreamSpecificationProperty -> ShowS)
-> (KinesisStreamSpecificationProperty -> String)
-> ([KinesisStreamSpecificationProperty] -> ShowS)
-> Show KinesisStreamSpecificationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KinesisStreamSpecificationProperty -> ShowS
showsPrec :: Int -> KinesisStreamSpecificationProperty -> ShowS
$cshow :: KinesisStreamSpecificationProperty -> String
show :: KinesisStreamSpecificationProperty -> String
$cshowList :: [KinesisStreamSpecificationProperty] -> ShowS
showList :: [KinesisStreamSpecificationProperty] -> ShowS
Prelude.Show)
mkKinesisStreamSpecificationProperty ::
Value Prelude.Text -> KinesisStreamSpecificationProperty
mkKinesisStreamSpecificationProperty :: Value Text -> KinesisStreamSpecificationProperty
mkKinesisStreamSpecificationProperty Value Text
streamArn
= KinesisStreamSpecificationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), streamArn :: Value Text
streamArn = Value Text
streamArn,
approximateCreationDateTimePrecision :: Maybe (Value Text)
approximateCreationDateTimePrecision = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties KinesisStreamSpecificationProperty where
toResourceProperties :: KinesisStreamSpecificationProperty -> ResourceProperties
toResourceProperties KinesisStreamSpecificationProperty {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: KinesisStreamSpecificationProperty -> ()
approximateCreationDateTimePrecision :: KinesisStreamSpecificationProperty -> Maybe (Value Text)
streamArn :: KinesisStreamSpecificationProperty -> Value Text
haddock_workaround_ :: ()
approximateCreationDateTimePrecision :: Maybe (Value Text)
streamArn :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DynamoDB::GlobalTable.KinesisStreamSpecification",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"StreamArn" 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
streamArn]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"ApproximateCreationDateTimePrecision"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
approximateCreationDateTimePrecision]))}
instance JSON.ToJSON KinesisStreamSpecificationProperty where
toJSON :: KinesisStreamSpecificationProperty -> Value
toJSON KinesisStreamSpecificationProperty {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: KinesisStreamSpecificationProperty -> ()
approximateCreationDateTimePrecision :: KinesisStreamSpecificationProperty -> Maybe (Value Text)
streamArn :: KinesisStreamSpecificationProperty -> Value Text
haddock_workaround_ :: ()
approximateCreationDateTimePrecision :: Maybe (Value Text)
streamArn :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"StreamArn" 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
streamArn]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"ApproximateCreationDateTimePrecision"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
approximateCreationDateTimePrecision])))
instance Property "ApproximateCreationDateTimePrecision" KinesisStreamSpecificationProperty where
type PropertyType "ApproximateCreationDateTimePrecision" KinesisStreamSpecificationProperty = Value Prelude.Text
set :: PropertyType
"ApproximateCreationDateTimePrecision"
KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty
set PropertyType
"ApproximateCreationDateTimePrecision"
KinesisStreamSpecificationProperty
newValue KinesisStreamSpecificationProperty {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: KinesisStreamSpecificationProperty -> ()
approximateCreationDateTimePrecision :: KinesisStreamSpecificationProperty -> Maybe (Value Text)
streamArn :: KinesisStreamSpecificationProperty -> Value Text
haddock_workaround_ :: ()
approximateCreationDateTimePrecision :: Maybe (Value Text)
streamArn :: Value Text
..}
= KinesisStreamSpecificationProperty
{approximateCreationDateTimePrecision :: Maybe (Value Text)
approximateCreationDateTimePrecision = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"ApproximateCreationDateTimePrecision"
KinesisStreamSpecificationProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
streamArn :: Value Text
haddock_workaround_ :: ()
streamArn :: Value Text
..}
instance Property "StreamArn" KinesisStreamSpecificationProperty where
type PropertyType "StreamArn" KinesisStreamSpecificationProperty = Value Prelude.Text
set :: PropertyType "StreamArn" KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty
-> KinesisStreamSpecificationProperty
set PropertyType "StreamArn" KinesisStreamSpecificationProperty
newValue KinesisStreamSpecificationProperty {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: KinesisStreamSpecificationProperty -> ()
approximateCreationDateTimePrecision :: KinesisStreamSpecificationProperty -> Maybe (Value Text)
streamArn :: KinesisStreamSpecificationProperty -> Value Text
haddock_workaround_ :: ()
approximateCreationDateTimePrecision :: Maybe (Value Text)
streamArn :: Value Text
..}
= KinesisStreamSpecificationProperty {streamArn :: Value Text
streamArn = PropertyType "StreamArn" KinesisStreamSpecificationProperty
Value Text
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
approximateCreationDateTimePrecision :: Maybe (Value Text)
haddock_workaround_ :: ()
approximateCreationDateTimePrecision :: Maybe (Value Text)
..}