module Stratosphere.DataZone.DataSource.RedshiftStorageProperty (
module Exports, RedshiftStorageProperty(..),
mkRedshiftStorageProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DataZone.DataSource.RedshiftClusterStorageProperty as Exports
import {-# SOURCE #-} Stratosphere.DataZone.DataSource.RedshiftServerlessStorageProperty as Exports
import Stratosphere.ResourceProperties
data RedshiftStorageProperty
=
RedshiftStorageProperty {RedshiftStorageProperty -> ()
haddock_workaround_ :: (),
RedshiftStorageProperty -> Maybe RedshiftClusterStorageProperty
redshiftClusterSource :: (Prelude.Maybe RedshiftClusterStorageProperty),
RedshiftStorageProperty -> Maybe RedshiftServerlessStorageProperty
redshiftServerlessSource :: (Prelude.Maybe RedshiftServerlessStorageProperty)}
deriving stock (RedshiftStorageProperty -> RedshiftStorageProperty -> Bool
(RedshiftStorageProperty -> RedshiftStorageProperty -> Bool)
-> (RedshiftStorageProperty -> RedshiftStorageProperty -> Bool)
-> Eq RedshiftStorageProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RedshiftStorageProperty -> RedshiftStorageProperty -> Bool
== :: RedshiftStorageProperty -> RedshiftStorageProperty -> Bool
$c/= :: RedshiftStorageProperty -> RedshiftStorageProperty -> Bool
/= :: RedshiftStorageProperty -> RedshiftStorageProperty -> Bool
Prelude.Eq, Int -> RedshiftStorageProperty -> ShowS
[RedshiftStorageProperty] -> ShowS
RedshiftStorageProperty -> String
(Int -> RedshiftStorageProperty -> ShowS)
-> (RedshiftStorageProperty -> String)
-> ([RedshiftStorageProperty] -> ShowS)
-> Show RedshiftStorageProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RedshiftStorageProperty -> ShowS
showsPrec :: Int -> RedshiftStorageProperty -> ShowS
$cshow :: RedshiftStorageProperty -> String
show :: RedshiftStorageProperty -> String
$cshowList :: [RedshiftStorageProperty] -> ShowS
showList :: [RedshiftStorageProperty] -> ShowS
Prelude.Show)
mkRedshiftStorageProperty :: RedshiftStorageProperty
mkRedshiftStorageProperty :: RedshiftStorageProperty
mkRedshiftStorageProperty
= RedshiftStorageProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
redshiftClusterSource = Maybe RedshiftClusterStorageProperty
forall a. Maybe a
Prelude.Nothing,
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
redshiftServerlessSource = Maybe RedshiftServerlessStorageProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RedshiftStorageProperty where
toResourceProperties :: RedshiftStorageProperty -> ResourceProperties
toResourceProperties RedshiftStorageProperty {Maybe RedshiftClusterStorageProperty
Maybe RedshiftServerlessStorageProperty
()
haddock_workaround_ :: RedshiftStorageProperty -> ()
redshiftClusterSource :: RedshiftStorageProperty -> Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: RedshiftStorageProperty -> Maybe RedshiftServerlessStorageProperty
haddock_workaround_ :: ()
redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DataZone::DataSource.RedshiftStorage",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> RedshiftClusterStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftClusterSource"
(RedshiftClusterStorageProperty -> (Key, Value))
-> Maybe RedshiftClusterStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftClusterStorageProperty
redshiftClusterSource,
Key -> RedshiftServerlessStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftServerlessSource"
(RedshiftServerlessStorageProperty -> (Key, Value))
-> Maybe RedshiftServerlessStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftServerlessStorageProperty
redshiftServerlessSource])}
instance JSON.ToJSON RedshiftStorageProperty where
toJSON :: RedshiftStorageProperty -> Value
toJSON RedshiftStorageProperty {Maybe RedshiftClusterStorageProperty
Maybe RedshiftServerlessStorageProperty
()
haddock_workaround_ :: RedshiftStorageProperty -> ()
redshiftClusterSource :: RedshiftStorageProperty -> Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: RedshiftStorageProperty -> Maybe RedshiftServerlessStorageProperty
haddock_workaround_ :: ()
redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> RedshiftClusterStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftClusterSource"
(RedshiftClusterStorageProperty -> (Key, Value))
-> Maybe RedshiftClusterStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftClusterStorageProperty
redshiftClusterSource,
Key -> RedshiftServerlessStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RedshiftServerlessSource"
(RedshiftServerlessStorageProperty -> (Key, Value))
-> Maybe RedshiftServerlessStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RedshiftServerlessStorageProperty
redshiftServerlessSource]))
instance Property "RedshiftClusterSource" RedshiftStorageProperty where
type PropertyType "RedshiftClusterSource" RedshiftStorageProperty = RedshiftClusterStorageProperty
set :: PropertyType "RedshiftClusterSource" RedshiftStorageProperty
-> RedshiftStorageProperty -> RedshiftStorageProperty
set PropertyType "RedshiftClusterSource" RedshiftStorageProperty
newValue RedshiftStorageProperty {Maybe RedshiftClusterStorageProperty
Maybe RedshiftServerlessStorageProperty
()
haddock_workaround_ :: RedshiftStorageProperty -> ()
redshiftClusterSource :: RedshiftStorageProperty -> Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: RedshiftStorageProperty -> Maybe RedshiftServerlessStorageProperty
haddock_workaround_ :: ()
redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
..}
= RedshiftStorageProperty
{redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
redshiftClusterSource = RedshiftClusterStorageProperty
-> Maybe RedshiftClusterStorageProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RedshiftClusterSource" RedshiftStorageProperty
RedshiftClusterStorageProperty
newValue, Maybe RedshiftServerlessStorageProperty
()
haddock_workaround_ :: ()
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
haddock_workaround_ :: ()
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
..}
instance Property "RedshiftServerlessSource" RedshiftStorageProperty where
type PropertyType "RedshiftServerlessSource" RedshiftStorageProperty = RedshiftServerlessStorageProperty
set :: PropertyType "RedshiftServerlessSource" RedshiftStorageProperty
-> RedshiftStorageProperty -> RedshiftStorageProperty
set PropertyType "RedshiftServerlessSource" RedshiftStorageProperty
newValue RedshiftStorageProperty {Maybe RedshiftClusterStorageProperty
Maybe RedshiftServerlessStorageProperty
()
haddock_workaround_ :: RedshiftStorageProperty -> ()
redshiftClusterSource :: RedshiftStorageProperty -> Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: RedshiftStorageProperty -> Maybe RedshiftServerlessStorageProperty
haddock_workaround_ :: ()
redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
..}
= RedshiftStorageProperty
{redshiftServerlessSource :: Maybe RedshiftServerlessStorageProperty
redshiftServerlessSource = RedshiftServerlessStorageProperty
-> Maybe RedshiftServerlessStorageProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RedshiftServerlessSource" RedshiftStorageProperty
RedshiftServerlessStorageProperty
newValue, Maybe RedshiftClusterStorageProperty
()
haddock_workaround_ :: ()
redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
haddock_workaround_ :: ()
redshiftClusterSource :: Maybe RedshiftClusterStorageProperty
..}