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