module Stratosphere.Glue.Partition.PartitionInputProperty (
module Exports, PartitionInputProperty(..),
mkPartitionInputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Glue.Partition.StorageDescriptorProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data PartitionInputProperty
=
PartitionInputProperty {PartitionInputProperty -> ()
haddock_workaround_ :: (),
PartitionInputProperty -> Maybe Object
parameters :: (Prelude.Maybe JSON.Object),
PartitionInputProperty -> Maybe StorageDescriptorProperty
storageDescriptor :: (Prelude.Maybe StorageDescriptorProperty),
PartitionInputProperty -> ValueList Text
values :: (ValueList Prelude.Text)}
deriving stock (PartitionInputProperty -> PartitionInputProperty -> Bool
(PartitionInputProperty -> PartitionInputProperty -> Bool)
-> (PartitionInputProperty -> PartitionInputProperty -> Bool)
-> Eq PartitionInputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PartitionInputProperty -> PartitionInputProperty -> Bool
== :: PartitionInputProperty -> PartitionInputProperty -> Bool
$c/= :: PartitionInputProperty -> PartitionInputProperty -> Bool
/= :: PartitionInputProperty -> PartitionInputProperty -> Bool
Prelude.Eq, Int -> PartitionInputProperty -> ShowS
[PartitionInputProperty] -> ShowS
PartitionInputProperty -> String
(Int -> PartitionInputProperty -> ShowS)
-> (PartitionInputProperty -> String)
-> ([PartitionInputProperty] -> ShowS)
-> Show PartitionInputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PartitionInputProperty -> ShowS
showsPrec :: Int -> PartitionInputProperty -> ShowS
$cshow :: PartitionInputProperty -> String
show :: PartitionInputProperty -> String
$cshowList :: [PartitionInputProperty] -> ShowS
showList :: [PartitionInputProperty] -> ShowS
Prelude.Show)
mkPartitionInputProperty ::
ValueList Prelude.Text -> PartitionInputProperty
mkPartitionInputProperty :: ValueList Text -> PartitionInputProperty
mkPartitionInputProperty ValueList Text
values
= PartitionInputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), values :: ValueList Text
values = ValueList Text
values,
parameters :: Maybe Object
parameters = Maybe Object
forall a. Maybe a
Prelude.Nothing, storageDescriptor :: Maybe StorageDescriptorProperty
storageDescriptor = Maybe StorageDescriptorProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties PartitionInputProperty where
toResourceProperties :: PartitionInputProperty -> ResourceProperties
toResourceProperties PartitionInputProperty {Maybe Object
Maybe StorageDescriptorProperty
()
ValueList Text
haddock_workaround_ :: PartitionInputProperty -> ()
parameters :: PartitionInputProperty -> Maybe Object
storageDescriptor :: PartitionInputProperty -> Maybe StorageDescriptorProperty
values :: PartitionInputProperty -> ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Glue::Partition.PartitionInput",
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
"Values" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
values]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Parameters" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
parameters,
Key -> StorageDescriptorProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StorageDescriptor" (StorageDescriptorProperty -> (Key, Value))
-> Maybe StorageDescriptorProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StorageDescriptorProperty
storageDescriptor]))}
instance JSON.ToJSON PartitionInputProperty where
toJSON :: PartitionInputProperty -> Value
toJSON PartitionInputProperty {Maybe Object
Maybe StorageDescriptorProperty
()
ValueList Text
haddock_workaround_ :: PartitionInputProperty -> ()
parameters :: PartitionInputProperty -> Maybe Object
storageDescriptor :: PartitionInputProperty -> Maybe StorageDescriptorProperty
values :: PartitionInputProperty -> ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList 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
"Values" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
values]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Parameters" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
parameters,
Key -> StorageDescriptorProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StorageDescriptor" (StorageDescriptorProperty -> (Key, Value))
-> Maybe StorageDescriptorProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StorageDescriptorProperty
storageDescriptor])))
instance Property "Parameters" PartitionInputProperty where
type PropertyType "Parameters" PartitionInputProperty = JSON.Object
set :: PropertyType "Parameters" PartitionInputProperty
-> PartitionInputProperty -> PartitionInputProperty
set PropertyType "Parameters" PartitionInputProperty
newValue PartitionInputProperty {Maybe Object
Maybe StorageDescriptorProperty
()
ValueList Text
haddock_workaround_ :: PartitionInputProperty -> ()
parameters :: PartitionInputProperty -> Maybe Object
storageDescriptor :: PartitionInputProperty -> Maybe StorageDescriptorProperty
values :: PartitionInputProperty -> ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList Text
..}
= PartitionInputProperty {parameters :: Maybe Object
parameters = Object -> Maybe Object
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Object
PropertyType "Parameters" PartitionInputProperty
newValue, Maybe StorageDescriptorProperty
()
ValueList Text
haddock_workaround_ :: ()
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList Text
haddock_workaround_ :: ()
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList Text
..}
instance Property "StorageDescriptor" PartitionInputProperty where
type PropertyType "StorageDescriptor" PartitionInputProperty = StorageDescriptorProperty
set :: PropertyType "StorageDescriptor" PartitionInputProperty
-> PartitionInputProperty -> PartitionInputProperty
set PropertyType "StorageDescriptor" PartitionInputProperty
newValue PartitionInputProperty {Maybe Object
Maybe StorageDescriptorProperty
()
ValueList Text
haddock_workaround_ :: PartitionInputProperty -> ()
parameters :: PartitionInputProperty -> Maybe Object
storageDescriptor :: PartitionInputProperty -> Maybe StorageDescriptorProperty
values :: PartitionInputProperty -> ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList Text
..}
= PartitionInputProperty
{storageDescriptor :: Maybe StorageDescriptorProperty
storageDescriptor = StorageDescriptorProperty -> Maybe StorageDescriptorProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "StorageDescriptor" PartitionInputProperty
StorageDescriptorProperty
newValue, Maybe Object
()
ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
values :: ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
values :: ValueList Text
..}
instance Property "Values" PartitionInputProperty where
type PropertyType "Values" PartitionInputProperty = ValueList Prelude.Text
set :: PropertyType "Values" PartitionInputProperty
-> PartitionInputProperty -> PartitionInputProperty
set PropertyType "Values" PartitionInputProperty
newValue PartitionInputProperty {Maybe Object
Maybe StorageDescriptorProperty
()
ValueList Text
haddock_workaround_ :: PartitionInputProperty -> ()
parameters :: PartitionInputProperty -> Maybe Object
storageDescriptor :: PartitionInputProperty -> Maybe StorageDescriptorProperty
values :: PartitionInputProperty -> ValueList Text
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
values :: ValueList Text
..}
= PartitionInputProperty {values :: ValueList Text
values = PropertyType "Values" PartitionInputProperty
ValueList Text
newValue, Maybe Object
Maybe StorageDescriptorProperty
()
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
haddock_workaround_ :: ()
parameters :: Maybe Object
storageDescriptor :: Maybe StorageDescriptorProperty
..}