module Stratosphere.KinesisAnalytics.Application.InputProperty (
module Exports, InputProperty(..), mkInputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.KinesisAnalytics.Application.InputParallelismProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisAnalytics.Application.InputProcessingConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisAnalytics.Application.InputSchemaProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisAnalytics.Application.KinesisFirehoseInputProperty as Exports
import {-# SOURCE #-} Stratosphere.KinesisAnalytics.Application.KinesisStreamsInputProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data InputProperty
=
InputProperty {InputProperty -> ()
haddock_workaround_ :: (),
InputProperty -> Maybe InputParallelismProperty
inputParallelism :: (Prelude.Maybe InputParallelismProperty),
InputProperty -> Maybe InputProcessingConfigurationProperty
inputProcessingConfiguration :: (Prelude.Maybe InputProcessingConfigurationProperty),
InputProperty -> InputSchemaProperty
inputSchema :: InputSchemaProperty,
InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisFirehoseInput :: (Prelude.Maybe KinesisFirehoseInputProperty),
InputProperty -> Maybe KinesisStreamsInputProperty
kinesisStreamsInput :: (Prelude.Maybe KinesisStreamsInputProperty),
InputProperty -> Value Text
namePrefix :: (Value Prelude.Text)}
deriving stock (InputProperty -> InputProperty -> Bool
(InputProperty -> InputProperty -> Bool)
-> (InputProperty -> InputProperty -> Bool) -> Eq InputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputProperty -> InputProperty -> Bool
== :: InputProperty -> InputProperty -> Bool
$c/= :: InputProperty -> InputProperty -> Bool
/= :: InputProperty -> InputProperty -> Bool
Prelude.Eq, Int -> InputProperty -> ShowS
[InputProperty] -> ShowS
InputProperty -> String
(Int -> InputProperty -> ShowS)
-> (InputProperty -> String)
-> ([InputProperty] -> ShowS)
-> Show InputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputProperty -> ShowS
showsPrec :: Int -> InputProperty -> ShowS
$cshow :: InputProperty -> String
show :: InputProperty -> String
$cshowList :: [InputProperty] -> ShowS
showList :: [InputProperty] -> ShowS
Prelude.Show)
mkInputProperty ::
InputSchemaProperty -> Value Prelude.Text -> InputProperty
mkInputProperty :: InputSchemaProperty -> Value Text -> InputProperty
mkInputProperty InputSchemaProperty
inputSchema Value Text
namePrefix
= InputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), inputSchema :: InputSchemaProperty
inputSchema = InputSchemaProperty
inputSchema,
namePrefix :: Value Text
namePrefix = Value Text
namePrefix, inputParallelism :: Maybe InputParallelismProperty
inputParallelism = Maybe InputParallelismProperty
forall a. Maybe a
Prelude.Nothing,
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputProcessingConfiguration = Maybe InputProcessingConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisFirehoseInput = Maybe KinesisFirehoseInputProperty
forall a. Maybe a
Prelude.Nothing,
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
kinesisStreamsInput = Maybe KinesisStreamsInputProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties InputProperty where
toResourceProperties :: InputProperty -> ResourceProperties
toResourceProperties InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::KinesisAnalytics::Application.Input",
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
"InputSchema" Key -> InputSchemaProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= InputSchemaProperty
inputSchema,
Key
"NamePrefix" 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
namePrefix]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> InputParallelismProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputParallelism" (InputParallelismProperty -> (Key, Value))
-> Maybe InputParallelismProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InputParallelismProperty
inputParallelism,
Key -> InputProcessingConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputProcessingConfiguration"
(InputProcessingConfigurationProperty -> (Key, Value))
-> Maybe InputProcessingConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InputProcessingConfigurationProperty
inputProcessingConfiguration,
Key -> KinesisFirehoseInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KinesisFirehoseInput" (KinesisFirehoseInputProperty -> (Key, Value))
-> Maybe KinesisFirehoseInputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KinesisFirehoseInputProperty
kinesisFirehoseInput,
Key -> KinesisStreamsInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KinesisStreamsInput" (KinesisStreamsInputProperty -> (Key, Value))
-> Maybe KinesisStreamsInputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KinesisStreamsInputProperty
kinesisStreamsInput]))}
instance JSON.ToJSON InputProperty where
toJSON :: InputProperty -> Value
toJSON InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: 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
"InputSchema" Key -> InputSchemaProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= InputSchemaProperty
inputSchema,
Key
"NamePrefix" 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
namePrefix]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> InputParallelismProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputParallelism" (InputParallelismProperty -> (Key, Value))
-> Maybe InputParallelismProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InputParallelismProperty
inputParallelism,
Key -> InputProcessingConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputProcessingConfiguration"
(InputProcessingConfigurationProperty -> (Key, Value))
-> Maybe InputProcessingConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InputProcessingConfigurationProperty
inputProcessingConfiguration,
Key -> KinesisFirehoseInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KinesisFirehoseInput" (KinesisFirehoseInputProperty -> (Key, Value))
-> Maybe KinesisFirehoseInputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KinesisFirehoseInputProperty
kinesisFirehoseInput,
Key -> KinesisStreamsInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KinesisStreamsInput" (KinesisStreamsInputProperty -> (Key, Value))
-> Maybe KinesisStreamsInputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe KinesisStreamsInputProperty
kinesisStreamsInput])))
instance Property "InputParallelism" InputProperty where
type PropertyType "InputParallelism" InputProperty = InputParallelismProperty
set :: PropertyType "InputParallelism" InputProperty
-> InputProperty -> InputProperty
set PropertyType "InputParallelism" InputProperty
newValue InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= InputProperty {inputParallelism :: Maybe InputParallelismProperty
inputParallelism = InputParallelismProperty -> Maybe InputParallelismProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InputParallelism" InputProperty
InputParallelismProperty
newValue, Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: ()
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
haddock_workaround_ :: ()
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
instance Property "InputProcessingConfiguration" InputProperty where
type PropertyType "InputProcessingConfiguration" InputProperty = InputProcessingConfigurationProperty
set :: PropertyType "InputProcessingConfiguration" InputProperty
-> InputProperty -> InputProperty
set PropertyType "InputProcessingConfiguration" InputProperty
newValue InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= InputProperty
{inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputProcessingConfiguration = InputProcessingConfigurationProperty
-> Maybe InputProcessingConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InputProcessingConfiguration" InputProperty
InputProcessingConfigurationProperty
newValue, Maybe InputParallelismProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
instance Property "InputSchema" InputProperty where
type PropertyType "InputSchema" InputProperty = InputSchemaProperty
set :: PropertyType "InputSchema" InputProperty
-> InputProperty -> InputProperty
set PropertyType "InputSchema" InputProperty
newValue InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= InputProperty {inputSchema :: InputSchemaProperty
inputSchema = PropertyType "InputSchema" InputProperty
InputSchemaProperty
newValue, Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
instance Property "KinesisFirehoseInput" InputProperty where
type PropertyType "KinesisFirehoseInput" InputProperty = KinesisFirehoseInputProperty
set :: PropertyType "KinesisFirehoseInput" InputProperty
-> InputProperty -> InputProperty
set PropertyType "KinesisFirehoseInput" InputProperty
newValue InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= InputProperty {kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisFirehoseInput = KinesisFirehoseInputProperty -> Maybe KinesisFirehoseInputProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "KinesisFirehoseInput" InputProperty
KinesisFirehoseInputProperty
newValue, Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
instance Property "KinesisStreamsInput" InputProperty where
type PropertyType "KinesisStreamsInput" InputProperty = KinesisStreamsInputProperty
set :: PropertyType "KinesisStreamsInput" InputProperty
-> InputProperty -> InputProperty
set PropertyType "KinesisStreamsInput" InputProperty
newValue InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= InputProperty {kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
kinesisStreamsInput = KinesisStreamsInputProperty -> Maybe KinesisStreamsInputProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "KinesisStreamsInput" InputProperty
KinesisStreamsInputProperty
newValue, Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
namePrefix :: Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
namePrefix :: Value Text
..}
instance Property "NamePrefix" InputProperty where
type PropertyType "NamePrefix" InputProperty = Value Prelude.Text
set :: PropertyType "NamePrefix" InputProperty
-> InputProperty -> InputProperty
set PropertyType "NamePrefix" InputProperty
newValue InputProperty {Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
Value Text
InputSchemaProperty
haddock_workaround_ :: InputProperty -> ()
inputParallelism :: InputProperty -> Maybe InputParallelismProperty
inputProcessingConfiguration :: InputProperty -> Maybe InputProcessingConfigurationProperty
inputSchema :: InputProperty -> InputSchemaProperty
kinesisFirehoseInput :: InputProperty -> Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: InputProperty -> Maybe KinesisStreamsInputProperty
namePrefix :: InputProperty -> Value Text
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
namePrefix :: Value Text
..}
= InputProperty {namePrefix :: Value Text
namePrefix = PropertyType "NamePrefix" InputProperty
Value Text
newValue, Maybe InputParallelismProperty
Maybe InputProcessingConfigurationProperty
Maybe KinesisFirehoseInputProperty
Maybe KinesisStreamsInputProperty
()
InputSchemaProperty
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
haddock_workaround_ :: ()
inputParallelism :: Maybe InputParallelismProperty
inputProcessingConfiguration :: Maybe InputProcessingConfigurationProperty
inputSchema :: InputSchemaProperty
kinesisFirehoseInput :: Maybe KinesisFirehoseInputProperty
kinesisStreamsInput :: Maybe KinesisStreamsInputProperty
..}