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