module Stratosphere.Pipes.Pipe.BatchContainerOverridesProperty (
module Exports, BatchContainerOverridesProperty(..),
mkBatchContainerOverridesProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Pipes.Pipe.BatchEnvironmentVariableProperty as Exports
import {-# SOURCE #-} Stratosphere.Pipes.Pipe.BatchResourceRequirementProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data BatchContainerOverridesProperty
=
BatchContainerOverridesProperty {BatchContainerOverridesProperty -> ()
haddock_workaround_ :: (),
BatchContainerOverridesProperty -> Maybe (ValueList Text)
command :: (Prelude.Maybe (ValueList Prelude.Text)),
BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
environment :: (Prelude.Maybe [BatchEnvironmentVariableProperty]),
BatchContainerOverridesProperty -> Maybe (Value Text)
instanceType :: (Prelude.Maybe (Value Prelude.Text)),
BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
resourceRequirements :: (Prelude.Maybe [BatchResourceRequirementProperty])}
deriving stock (BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool
(BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool)
-> (BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool)
-> Eq BatchContainerOverridesProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool
== :: BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool
$c/= :: BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool
/= :: BatchContainerOverridesProperty
-> BatchContainerOverridesProperty -> Bool
Prelude.Eq, Int -> BatchContainerOverridesProperty -> ShowS
[BatchContainerOverridesProperty] -> ShowS
BatchContainerOverridesProperty -> String
(Int -> BatchContainerOverridesProperty -> ShowS)
-> (BatchContainerOverridesProperty -> String)
-> ([BatchContainerOverridesProperty] -> ShowS)
-> Show BatchContainerOverridesProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BatchContainerOverridesProperty -> ShowS
showsPrec :: Int -> BatchContainerOverridesProperty -> ShowS
$cshow :: BatchContainerOverridesProperty -> String
show :: BatchContainerOverridesProperty -> String
$cshowList :: [BatchContainerOverridesProperty] -> ShowS
showList :: [BatchContainerOverridesProperty] -> ShowS
Prelude.Show)
mkBatchContainerOverridesProperty ::
BatchContainerOverridesProperty
mkBatchContainerOverridesProperty :: BatchContainerOverridesProperty
mkBatchContainerOverridesProperty
= BatchContainerOverridesProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), command :: Maybe (ValueList Text)
command = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
environment :: Maybe [BatchEnvironmentVariableProperty]
environment = Maybe [BatchEnvironmentVariableProperty]
forall a. Maybe a
Prelude.Nothing, instanceType :: Maybe (Value Text)
instanceType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
resourceRequirements = Maybe [BatchResourceRequirementProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties BatchContainerOverridesProperty where
toResourceProperties :: BatchContainerOverridesProperty -> ResourceProperties
toResourceProperties BatchContainerOverridesProperty {Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: BatchContainerOverridesProperty -> ()
command :: BatchContainerOverridesProperty -> Maybe (ValueList Text)
environment :: BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
instanceType :: BatchContainerOverridesProperty -> Maybe (Value Text)
resourceRequirements :: BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Pipes::Pipe.BatchContainerOverrides",
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 -> 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..=) Key
"Command" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
command,
Key -> [BatchEnvironmentVariableProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Environment" ([BatchEnvironmentVariableProperty] -> (Key, Value))
-> Maybe [BatchEnvironmentVariableProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BatchEnvironmentVariableProperty]
environment,
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
"InstanceType" (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)
instanceType,
Key -> [BatchResourceRequirementProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ResourceRequirements"
([BatchResourceRequirementProperty] -> (Key, Value))
-> Maybe [BatchResourceRequirementProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BatchResourceRequirementProperty]
resourceRequirements])}
instance JSON.ToJSON BatchContainerOverridesProperty where
toJSON :: BatchContainerOverridesProperty -> Value
toJSON BatchContainerOverridesProperty {Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: BatchContainerOverridesProperty -> ()
command :: BatchContainerOverridesProperty -> Maybe (ValueList Text)
environment :: BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
instanceType :: BatchContainerOverridesProperty -> Maybe (Value Text)
resourceRequirements :: BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
= [(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 -> 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..=) Key
"Command" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
command,
Key -> [BatchEnvironmentVariableProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Environment" ([BatchEnvironmentVariableProperty] -> (Key, Value))
-> Maybe [BatchEnvironmentVariableProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BatchEnvironmentVariableProperty]
environment,
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
"InstanceType" (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)
instanceType,
Key -> [BatchResourceRequirementProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ResourceRequirements"
([BatchResourceRequirementProperty] -> (Key, Value))
-> Maybe [BatchResourceRequirementProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [BatchResourceRequirementProperty]
resourceRequirements]))
instance Property "Command" BatchContainerOverridesProperty where
type PropertyType "Command" BatchContainerOverridesProperty = ValueList Prelude.Text
set :: PropertyType "Command" BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
set PropertyType "Command" BatchContainerOverridesProperty
newValue BatchContainerOverridesProperty {Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: BatchContainerOverridesProperty -> ()
command :: BatchContainerOverridesProperty -> Maybe (ValueList Text)
environment :: BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
instanceType :: BatchContainerOverridesProperty -> Maybe (Value Text)
resourceRequirements :: BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
= BatchContainerOverridesProperty
{command :: Maybe (ValueList Text)
command = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Command" BatchContainerOverridesProperty
ValueList Text
newValue, Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (Value Text)
()
haddock_workaround_ :: ()
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
instance Property "Environment" BatchContainerOverridesProperty where
type PropertyType "Environment" BatchContainerOverridesProperty = [BatchEnvironmentVariableProperty]
set :: PropertyType "Environment" BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
set PropertyType "Environment" BatchContainerOverridesProperty
newValue BatchContainerOverridesProperty {Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: BatchContainerOverridesProperty -> ()
command :: BatchContainerOverridesProperty -> Maybe (ValueList Text)
environment :: BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
instanceType :: BatchContainerOverridesProperty -> Maybe (Value Text)
resourceRequirements :: BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
= BatchContainerOverridesProperty
{environment :: Maybe [BatchEnvironmentVariableProperty]
environment = [BatchEnvironmentVariableProperty]
-> Maybe [BatchEnvironmentVariableProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [BatchEnvironmentVariableProperty]
PropertyType "Environment" BatchContainerOverridesProperty
newValue, Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
instance Property "InstanceType" BatchContainerOverridesProperty where
type PropertyType "InstanceType" BatchContainerOverridesProperty = Value Prelude.Text
set :: PropertyType "InstanceType" BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
set PropertyType "InstanceType" BatchContainerOverridesProperty
newValue BatchContainerOverridesProperty {Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: BatchContainerOverridesProperty -> ()
command :: BatchContainerOverridesProperty -> Maybe (ValueList Text)
environment :: BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
instanceType :: BatchContainerOverridesProperty -> Maybe (Value Text)
resourceRequirements :: BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
= BatchContainerOverridesProperty
{instanceType :: Maybe (Value Text)
instanceType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceType" BatchContainerOverridesProperty
Value Text
newValue, Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
()
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
instance Property "ResourceRequirements" BatchContainerOverridesProperty where
type PropertyType "ResourceRequirements" BatchContainerOverridesProperty = [BatchResourceRequirementProperty]
set :: PropertyType "ResourceRequirements" BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
-> BatchContainerOverridesProperty
set PropertyType "ResourceRequirements" BatchContainerOverridesProperty
newValue BatchContainerOverridesProperty {Maybe [BatchEnvironmentVariableProperty]
Maybe [BatchResourceRequirementProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: BatchContainerOverridesProperty -> ()
command :: BatchContainerOverridesProperty -> Maybe (ValueList Text)
environment :: BatchContainerOverridesProperty
-> Maybe [BatchEnvironmentVariableProperty]
instanceType :: BatchContainerOverridesProperty -> Maybe (Value Text)
resourceRequirements :: BatchContainerOverridesProperty
-> Maybe [BatchResourceRequirementProperty]
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
resourceRequirements :: Maybe [BatchResourceRequirementProperty]
..}
= BatchContainerOverridesProperty
{resourceRequirements :: Maybe [BatchResourceRequirementProperty]
resourceRequirements = [BatchResourceRequirementProperty]
-> Maybe [BatchResourceRequirementProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [BatchResourceRequirementProperty]
PropertyType "ResourceRequirements" BatchContainerOverridesProperty
newValue, Maybe [BatchEnvironmentVariableProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
haddock_workaround_ :: ()
command :: Maybe (ValueList Text)
environment :: Maybe [BatchEnvironmentVariableProperty]
instanceType :: Maybe (Value Text)
..}