module Stratosphere.DataZone.DataSource.RedshiftRunConfigurationInputProperty (
module Exports, RedshiftRunConfigurationInputProperty(..),
mkRedshiftRunConfigurationInputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DataZone.DataSource.RedshiftCredentialConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.DataZone.DataSource.RedshiftStorageProperty as Exports
import {-# SOURCE #-} Stratosphere.DataZone.DataSource.RelationalFilterConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RedshiftRunConfigurationInputProperty
=
RedshiftRunConfigurationInputProperty {RedshiftRunConfigurationInputProperty -> ()
haddock_workaround_ :: (),
RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
dataAccessRole :: (Prelude.Maybe (Value Prelude.Text)),
RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftCredentialConfiguration :: (Prelude.Maybe RedshiftCredentialConfigurationProperty),
RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
redshiftStorage :: (Prelude.Maybe RedshiftStorageProperty),
RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]}
deriving stock (RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool
(RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool)
-> (RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool)
-> Eq RedshiftRunConfigurationInputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool
== :: RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool
$c/= :: RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool
/= :: RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty -> Bool
Prelude.Eq, Int -> RedshiftRunConfigurationInputProperty -> ShowS
[RedshiftRunConfigurationInputProperty] -> ShowS
RedshiftRunConfigurationInputProperty -> String
(Int -> RedshiftRunConfigurationInputProperty -> ShowS)
-> (RedshiftRunConfigurationInputProperty -> String)
-> ([RedshiftRunConfigurationInputProperty] -> ShowS)
-> Show RedshiftRunConfigurationInputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RedshiftRunConfigurationInputProperty -> ShowS
showsPrec :: Int -> RedshiftRunConfigurationInputProperty -> ShowS
$cshow :: RedshiftRunConfigurationInputProperty -> String
show :: RedshiftRunConfigurationInputProperty -> String
$cshowList :: [RedshiftRunConfigurationInputProperty] -> ShowS
showList :: [RedshiftRunConfigurationInputProperty] -> ShowS
Prelude.Show)
mkRedshiftRunConfigurationInputProperty ::
[RelationalFilterConfigurationProperty]
-> RedshiftRunConfigurationInputProperty
mkRedshiftRunConfigurationInputProperty :: [RelationalFilterConfigurationProperty]
-> RedshiftRunConfigurationInputProperty
mkRedshiftRunConfigurationInputProperty
[RelationalFilterConfigurationProperty]
relationalFilterConfigurations
= RedshiftRunConfigurationInputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
relationalFilterConfigurations = [RelationalFilterConfigurationProperty]
relationalFilterConfigurations,
dataAccessRole :: Maybe (Value Text)
dataAccessRole = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftCredentialConfiguration = Maybe RedshiftCredentialConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
redshiftStorage :: Maybe RedshiftStorageProperty
redshiftStorage = Maybe RedshiftStorageProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RedshiftRunConfigurationInputProperty where
toResourceProperties :: RedshiftRunConfigurationInputProperty -> ResourceProperties
toResourceProperties RedshiftRunConfigurationInputProperty {[RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: RedshiftRunConfigurationInputProperty -> ()
dataAccessRole :: RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
redshiftCredentialConfiguration :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
relationalFilterConfigurations :: RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DataZone::DataSource.RedshiftRunConfigurationInput",
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
"RelationalFilterConfigurations"
Key -> [RelationalFilterConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [RelationalFilterConfigurationProperty]
relationalFilterConfigurations]
([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
"DataAccessRole" (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)
dataAccessRole,
Key -> RedshiftCredentialConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftCredentialConfiguration"
(RedshiftCredentialConfigurationProperty -> (Key, Value))
-> Maybe RedshiftCredentialConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftCredentialConfigurationProperty
redshiftCredentialConfiguration,
Key -> RedshiftStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftStorage" (RedshiftStorageProperty -> (Key, Value))
-> Maybe RedshiftStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftStorageProperty
redshiftStorage]))}
instance JSON.ToJSON RedshiftRunConfigurationInputProperty where
toJSON :: RedshiftRunConfigurationInputProperty -> Value
toJSON RedshiftRunConfigurationInputProperty {[RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: RedshiftRunConfigurationInputProperty -> ()
dataAccessRole :: RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
redshiftCredentialConfiguration :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
relationalFilterConfigurations :: RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
= [(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
"RelationalFilterConfigurations"
Key -> [RelationalFilterConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [RelationalFilterConfigurationProperty]
relationalFilterConfigurations]
([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
"DataAccessRole" (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)
dataAccessRole,
Key -> RedshiftCredentialConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftCredentialConfiguration"
(RedshiftCredentialConfigurationProperty -> (Key, Value))
-> Maybe RedshiftCredentialConfigurationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftCredentialConfigurationProperty
redshiftCredentialConfiguration,
Key -> RedshiftStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftStorage" (RedshiftStorageProperty -> (Key, Value))
-> Maybe RedshiftStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftStorageProperty
redshiftStorage])))
instance Property "DataAccessRole" RedshiftRunConfigurationInputProperty where
type PropertyType "DataAccessRole" RedshiftRunConfigurationInputProperty = Value Prelude.Text
set :: PropertyType "DataAccessRole" RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
set PropertyType "DataAccessRole" RedshiftRunConfigurationInputProperty
newValue RedshiftRunConfigurationInputProperty {[RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: RedshiftRunConfigurationInputProperty -> ()
dataAccessRole :: RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
redshiftCredentialConfiguration :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
relationalFilterConfigurations :: RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
= RedshiftRunConfigurationInputProperty
{dataAccessRole :: Maybe (Value Text)
dataAccessRole = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DataAccessRole" RedshiftRunConfigurationInputProperty
Value Text
newValue, [RelationalFilterConfigurationProperty]
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: ()
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
instance Property "RedshiftCredentialConfiguration" RedshiftRunConfigurationInputProperty where
type PropertyType "RedshiftCredentialConfiguration" RedshiftRunConfigurationInputProperty = RedshiftCredentialConfigurationProperty
set :: PropertyType
"RedshiftCredentialConfiguration"
RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
set PropertyType
"RedshiftCredentialConfiguration"
RedshiftRunConfigurationInputProperty
newValue RedshiftRunConfigurationInputProperty {[RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: RedshiftRunConfigurationInputProperty -> ()
dataAccessRole :: RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
redshiftCredentialConfiguration :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
relationalFilterConfigurations :: RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
= RedshiftRunConfigurationInputProperty
{redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftCredentialConfiguration = RedshiftCredentialConfigurationProperty
-> Maybe RedshiftCredentialConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"RedshiftCredentialConfiguration"
RedshiftRunConfigurationInputProperty
RedshiftCredentialConfigurationProperty
newValue, [RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
instance Property "RedshiftStorage" RedshiftRunConfigurationInputProperty where
type PropertyType "RedshiftStorage" RedshiftRunConfigurationInputProperty = RedshiftStorageProperty
set :: PropertyType
"RedshiftStorage" RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
set PropertyType
"RedshiftStorage" RedshiftRunConfigurationInputProperty
newValue RedshiftRunConfigurationInputProperty {[RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: RedshiftRunConfigurationInputProperty -> ()
dataAccessRole :: RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
redshiftCredentialConfiguration :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
relationalFilterConfigurations :: RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
= RedshiftRunConfigurationInputProperty
{redshiftStorage :: Maybe RedshiftStorageProperty
redshiftStorage = RedshiftStorageProperty -> Maybe RedshiftStorageProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"RedshiftStorage" RedshiftRunConfigurationInputProperty
RedshiftStorageProperty
newValue, [RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
()
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
instance Property "RelationalFilterConfigurations" RedshiftRunConfigurationInputProperty where
type PropertyType "RelationalFilterConfigurations" RedshiftRunConfigurationInputProperty = [RelationalFilterConfigurationProperty]
set :: PropertyType
"RelationalFilterConfigurations"
RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
-> RedshiftRunConfigurationInputProperty
set PropertyType
"RelationalFilterConfigurations"
RedshiftRunConfigurationInputProperty
newValue RedshiftRunConfigurationInputProperty {[RelationalFilterConfigurationProperty]
Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: RedshiftRunConfigurationInputProperty -> ()
dataAccessRole :: RedshiftRunConfigurationInputProperty -> Maybe (Value Text)
redshiftCredentialConfiguration :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: RedshiftRunConfigurationInputProperty
-> Maybe RedshiftStorageProperty
relationalFilterConfigurations :: RedshiftRunConfigurationInputProperty
-> [RelationalFilterConfigurationProperty]
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
..}
= RedshiftRunConfigurationInputProperty
{relationalFilterConfigurations :: [RelationalFilterConfigurationProperty]
relationalFilterConfigurations = [RelationalFilterConfigurationProperty]
PropertyType
"RelationalFilterConfigurations"
RedshiftRunConfigurationInputProperty
newValue, Maybe (Value Text)
Maybe RedshiftCredentialConfigurationProperty
Maybe RedshiftStorageProperty
()
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
haddock_workaround_ :: ()
dataAccessRole :: Maybe (Value Text)
redshiftCredentialConfiguration :: Maybe RedshiftCredentialConfigurationProperty
redshiftStorage :: Maybe RedshiftStorageProperty
..}