module Stratosphere.DataBrew.Job.DatabaseOutputProperty (
module Exports, DatabaseOutputProperty(..),
mkDatabaseOutputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DataBrew.Job.DatabaseTableOutputOptionsProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data DatabaseOutputProperty
=
DatabaseOutputProperty {DatabaseOutputProperty -> ()
haddock_workaround_ :: (),
DatabaseOutputProperty -> DatabaseTableOutputOptionsProperty
databaseOptions :: DatabaseTableOutputOptionsProperty,
DatabaseOutputProperty -> Maybe (Value Text)
databaseOutputMode :: (Prelude.Maybe (Value Prelude.Text)),
DatabaseOutputProperty -> Value Text
glueConnectionName :: (Value Prelude.Text)}
deriving stock (DatabaseOutputProperty -> DatabaseOutputProperty -> Bool
(DatabaseOutputProperty -> DatabaseOutputProperty -> Bool)
-> (DatabaseOutputProperty -> DatabaseOutputProperty -> Bool)
-> Eq DatabaseOutputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DatabaseOutputProperty -> DatabaseOutputProperty -> Bool
== :: DatabaseOutputProperty -> DatabaseOutputProperty -> Bool
$c/= :: DatabaseOutputProperty -> DatabaseOutputProperty -> Bool
/= :: DatabaseOutputProperty -> DatabaseOutputProperty -> Bool
Prelude.Eq, Int -> DatabaseOutputProperty -> ShowS
[DatabaseOutputProperty] -> ShowS
DatabaseOutputProperty -> String
(Int -> DatabaseOutputProperty -> ShowS)
-> (DatabaseOutputProperty -> String)
-> ([DatabaseOutputProperty] -> ShowS)
-> Show DatabaseOutputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DatabaseOutputProperty -> ShowS
showsPrec :: Int -> DatabaseOutputProperty -> ShowS
$cshow :: DatabaseOutputProperty -> String
show :: DatabaseOutputProperty -> String
$cshowList :: [DatabaseOutputProperty] -> ShowS
showList :: [DatabaseOutputProperty] -> ShowS
Prelude.Show)
mkDatabaseOutputProperty ::
DatabaseTableOutputOptionsProperty
-> Value Prelude.Text -> DatabaseOutputProperty
mkDatabaseOutputProperty :: DatabaseTableOutputOptionsProperty
-> Value Text -> DatabaseOutputProperty
mkDatabaseOutputProperty DatabaseTableOutputOptionsProperty
databaseOptions Value Text
glueConnectionName
= DatabaseOutputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOptions = DatabaseTableOutputOptionsProperty
databaseOptions,
glueConnectionName :: Value Text
glueConnectionName = Value Text
glueConnectionName,
databaseOutputMode :: Maybe (Value Text)
databaseOutputMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties DatabaseOutputProperty where
toResourceProperties :: DatabaseOutputProperty -> ResourceProperties
toResourceProperties DatabaseOutputProperty {Maybe (Value Text)
()
Value Text
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: DatabaseOutputProperty -> ()
databaseOptions :: DatabaseOutputProperty -> DatabaseTableOutputOptionsProperty
databaseOutputMode :: DatabaseOutputProperty -> Maybe (Value Text)
glueConnectionName :: DatabaseOutputProperty -> Value Text
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DataBrew::Job.DatabaseOutput",
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
"DatabaseOptions" Key -> DatabaseTableOutputOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= DatabaseTableOutputOptionsProperty
databaseOptions,
Key
"GlueConnectionName" 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
glueConnectionName]
([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
"DatabaseOutputMode" (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)
databaseOutputMode]))}
instance JSON.ToJSON DatabaseOutputProperty where
toJSON :: DatabaseOutputProperty -> Value
toJSON DatabaseOutputProperty {Maybe (Value Text)
()
Value Text
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: DatabaseOutputProperty -> ()
databaseOptions :: DatabaseOutputProperty -> DatabaseTableOutputOptionsProperty
databaseOutputMode :: DatabaseOutputProperty -> Maybe (Value Text)
glueConnectionName :: DatabaseOutputProperty -> Value Text
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: 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
"DatabaseOptions" Key -> DatabaseTableOutputOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= DatabaseTableOutputOptionsProperty
databaseOptions,
Key
"GlueConnectionName" 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
glueConnectionName]
([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
"DatabaseOutputMode" (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)
databaseOutputMode])))
instance Property "DatabaseOptions" DatabaseOutputProperty where
type PropertyType "DatabaseOptions" DatabaseOutputProperty = DatabaseTableOutputOptionsProperty
set :: PropertyType "DatabaseOptions" DatabaseOutputProperty
-> DatabaseOutputProperty -> DatabaseOutputProperty
set PropertyType "DatabaseOptions" DatabaseOutputProperty
newValue DatabaseOutputProperty {Maybe (Value Text)
()
Value Text
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: DatabaseOutputProperty -> ()
databaseOptions :: DatabaseOutputProperty -> DatabaseTableOutputOptionsProperty
databaseOutputMode :: DatabaseOutputProperty -> Maybe (Value Text)
glueConnectionName :: DatabaseOutputProperty -> Value Text
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: Value Text
..}
= DatabaseOutputProperty {databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOptions = PropertyType "DatabaseOptions" DatabaseOutputProperty
DatabaseTableOutputOptionsProperty
newValue, Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: Value Text
haddock_workaround_ :: ()
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: Value Text
..}
instance Property "DatabaseOutputMode" DatabaseOutputProperty where
type PropertyType "DatabaseOutputMode" DatabaseOutputProperty = Value Prelude.Text
set :: PropertyType "DatabaseOutputMode" DatabaseOutputProperty
-> DatabaseOutputProperty -> DatabaseOutputProperty
set PropertyType "DatabaseOutputMode" DatabaseOutputProperty
newValue DatabaseOutputProperty {Maybe (Value Text)
()
Value Text
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: DatabaseOutputProperty -> ()
databaseOptions :: DatabaseOutputProperty -> DatabaseTableOutputOptionsProperty
databaseOutputMode :: DatabaseOutputProperty -> Maybe (Value Text)
glueConnectionName :: DatabaseOutputProperty -> Value Text
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: Value Text
..}
= DatabaseOutputProperty
{databaseOutputMode :: Maybe (Value Text)
databaseOutputMode = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DatabaseOutputMode" DatabaseOutputProperty
Value Text
newValue, ()
Value Text
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
glueConnectionName :: Value Text
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
glueConnectionName :: Value Text
..}
instance Property "GlueConnectionName" DatabaseOutputProperty where
type PropertyType "GlueConnectionName" DatabaseOutputProperty = Value Prelude.Text
set :: PropertyType "GlueConnectionName" DatabaseOutputProperty
-> DatabaseOutputProperty -> DatabaseOutputProperty
set PropertyType "GlueConnectionName" DatabaseOutputProperty
newValue DatabaseOutputProperty {Maybe (Value Text)
()
Value Text
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: DatabaseOutputProperty -> ()
databaseOptions :: DatabaseOutputProperty -> DatabaseTableOutputOptionsProperty
databaseOutputMode :: DatabaseOutputProperty -> Maybe (Value Text)
glueConnectionName :: DatabaseOutputProperty -> Value Text
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
glueConnectionName :: Value Text
..}
= DatabaseOutputProperty {glueConnectionName :: Value Text
glueConnectionName = PropertyType "GlueConnectionName" DatabaseOutputProperty
Value Text
newValue, Maybe (Value Text)
()
DatabaseTableOutputOptionsProperty
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
haddock_workaround_ :: ()
databaseOptions :: DatabaseTableOutputOptionsProperty
databaseOutputMode :: Maybe (Value Text)
..}