module Stratosphere.Glue.Table.OpenTableFormatInputProperty (
module Exports, OpenTableFormatInputProperty(..),
mkOpenTableFormatInputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Glue.Table.IcebergInputProperty as Exports
import Stratosphere.ResourceProperties
data OpenTableFormatInputProperty
=
OpenTableFormatInputProperty {OpenTableFormatInputProperty -> ()
haddock_workaround_ :: (),
OpenTableFormatInputProperty -> Maybe IcebergInputProperty
icebergInput :: (Prelude.Maybe IcebergInputProperty)}
deriving stock (OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool
(OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool)
-> (OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool)
-> Eq OpenTableFormatInputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool
== :: OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool
$c/= :: OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool
/= :: OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> Bool
Prelude.Eq, Int -> OpenTableFormatInputProperty -> ShowS
[OpenTableFormatInputProperty] -> ShowS
OpenTableFormatInputProperty -> String
(Int -> OpenTableFormatInputProperty -> ShowS)
-> (OpenTableFormatInputProperty -> String)
-> ([OpenTableFormatInputProperty] -> ShowS)
-> Show OpenTableFormatInputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenTableFormatInputProperty -> ShowS
showsPrec :: Int -> OpenTableFormatInputProperty -> ShowS
$cshow :: OpenTableFormatInputProperty -> String
show :: OpenTableFormatInputProperty -> String
$cshowList :: [OpenTableFormatInputProperty] -> ShowS
showList :: [OpenTableFormatInputProperty] -> ShowS
Prelude.Show)
mkOpenTableFormatInputProperty :: OpenTableFormatInputProperty
mkOpenTableFormatInputProperty :: OpenTableFormatInputProperty
mkOpenTableFormatInputProperty
= OpenTableFormatInputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), icebergInput :: Maybe IcebergInputProperty
icebergInput = Maybe IcebergInputProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties OpenTableFormatInputProperty where
toResourceProperties :: OpenTableFormatInputProperty -> ResourceProperties
toResourceProperties OpenTableFormatInputProperty {Maybe IcebergInputProperty
()
haddock_workaround_ :: OpenTableFormatInputProperty -> ()
icebergInput :: OpenTableFormatInputProperty -> Maybe IcebergInputProperty
haddock_workaround_ :: ()
icebergInput :: Maybe IcebergInputProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Glue::Table.OpenTableFormatInput",
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 -> IcebergInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IcebergInput" (IcebergInputProperty -> (Key, Value))
-> Maybe IcebergInputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IcebergInputProperty
icebergInput])}
instance JSON.ToJSON OpenTableFormatInputProperty where
toJSON :: OpenTableFormatInputProperty -> Value
toJSON OpenTableFormatInputProperty {Maybe IcebergInputProperty
()
haddock_workaround_ :: OpenTableFormatInputProperty -> ()
icebergInput :: OpenTableFormatInputProperty -> Maybe IcebergInputProperty
haddock_workaround_ :: ()
icebergInput :: Maybe IcebergInputProperty
..}
= [(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 -> IcebergInputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"IcebergInput" (IcebergInputProperty -> (Key, Value))
-> Maybe IcebergInputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe IcebergInputProperty
icebergInput]))
instance Property "IcebergInput" OpenTableFormatInputProperty where
type PropertyType "IcebergInput" OpenTableFormatInputProperty = IcebergInputProperty
set :: PropertyType "IcebergInput" OpenTableFormatInputProperty
-> OpenTableFormatInputProperty -> OpenTableFormatInputProperty
set PropertyType "IcebergInput" OpenTableFormatInputProperty
newValue OpenTableFormatInputProperty {Maybe IcebergInputProperty
()
haddock_workaround_ :: OpenTableFormatInputProperty -> ()
icebergInput :: OpenTableFormatInputProperty -> Maybe IcebergInputProperty
haddock_workaround_ :: ()
icebergInput :: Maybe IcebergInputProperty
..}
= OpenTableFormatInputProperty
{icebergInput :: Maybe IcebergInputProperty
icebergInput = IcebergInputProperty -> Maybe IcebergInputProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IcebergInput" OpenTableFormatInputProperty
IcebergInputProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}