module Stratosphere.Batch.JobDefinition.EcsTaskPropertiesProperty (
        module Exports, EcsTaskPropertiesProperty(..),
        mkEcsTaskPropertiesProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.EphemeralStorageProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.NetworkConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.RuntimePlatformProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.TaskContainerPropertiesProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.VolumeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data EcsTaskPropertiesProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html>
    EcsTaskPropertiesProperty {EcsTaskPropertiesProperty -> ()
haddock_workaround_ :: (),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-containers>
                               EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
containers :: (Prelude.Maybe [TaskContainerPropertiesProperty]),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-enableexecutecommand>
                               EcsTaskPropertiesProperty -> Maybe (Value Bool)
enableExecuteCommand :: (Prelude.Maybe (Value Prelude.Bool)),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-ephemeralstorage>
                               EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
ephemeralStorage :: (Prelude.Maybe EphemeralStorageProperty),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-executionrolearn>
                               EcsTaskPropertiesProperty -> Maybe (Value Text)
executionRoleArn :: (Prelude.Maybe (Value Prelude.Text)),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-ipcmode>
                               EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: (Prelude.Maybe (Value Prelude.Text)),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-networkconfiguration>
                               EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
networkConfiguration :: (Prelude.Maybe NetworkConfigurationProperty),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-pidmode>
                               EcsTaskPropertiesProperty -> Maybe (Value Text)
pidMode :: (Prelude.Maybe (Value Prelude.Text)),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-platformversion>
                               EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: (Prelude.Maybe (Value Prelude.Text)),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-runtimeplatform>
                               EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
runtimePlatform :: (Prelude.Maybe RuntimePlatformProperty),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-taskrolearn>
                               EcsTaskPropertiesProperty -> Maybe (Value Text)
taskRoleArn :: (Prelude.Maybe (Value Prelude.Text)),
                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-batch-jobdefinition-ecstaskproperties.html#cfn-batch-jobdefinition-ecstaskproperties-volumes>
                               EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
volumes :: (Prelude.Maybe [VolumeProperty])}
  deriving stock (EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool
(EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool)
-> (EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool)
-> Eq EcsTaskPropertiesProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool
== :: EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool
$c/= :: EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool
/= :: EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty -> Bool
Prelude.Eq, Int -> EcsTaskPropertiesProperty -> ShowS
[EcsTaskPropertiesProperty] -> ShowS
EcsTaskPropertiesProperty -> String
(Int -> EcsTaskPropertiesProperty -> ShowS)
-> (EcsTaskPropertiesProperty -> String)
-> ([EcsTaskPropertiesProperty] -> ShowS)
-> Show EcsTaskPropertiesProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EcsTaskPropertiesProperty -> ShowS
showsPrec :: Int -> EcsTaskPropertiesProperty -> ShowS
$cshow :: EcsTaskPropertiesProperty -> String
show :: EcsTaskPropertiesProperty -> String
$cshowList :: [EcsTaskPropertiesProperty] -> ShowS
showList :: [EcsTaskPropertiesProperty] -> ShowS
Prelude.Show)
mkEcsTaskPropertiesProperty :: EcsTaskPropertiesProperty
mkEcsTaskPropertiesProperty :: EcsTaskPropertiesProperty
mkEcsTaskPropertiesProperty
  = EcsTaskPropertiesProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), containers :: Maybe [TaskContainerPropertiesProperty]
containers = Maybe [TaskContainerPropertiesProperty]
forall a. Maybe a
Prelude.Nothing,
       enableExecuteCommand :: Maybe (Value Bool)
enableExecuteCommand = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       ephemeralStorage :: Maybe EphemeralStorageProperty
ephemeralStorage = Maybe EphemeralStorageProperty
forall a. Maybe a
Prelude.Nothing,
       executionRoleArn :: Maybe (Value Text)
executionRoleArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, ipcMode :: Maybe (Value Text)
ipcMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       networkConfiguration :: Maybe NetworkConfigurationProperty
networkConfiguration = Maybe NetworkConfigurationProperty
forall a. Maybe a
Prelude.Nothing, pidMode :: Maybe (Value Text)
pidMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       platformVersion :: Maybe (Value Text)
platformVersion = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       runtimePlatform :: Maybe RuntimePlatformProperty
runtimePlatform = Maybe RuntimePlatformProperty
forall a. Maybe a
Prelude.Nothing, taskRoleArn :: Maybe (Value Text)
taskRoleArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       volumes :: Maybe [VolumeProperty]
volumes = Maybe [VolumeProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties EcsTaskPropertiesProperty where
  toResourceProperties :: EcsTaskPropertiesProperty -> ResourceProperties
toResourceProperties EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Batch::JobDefinition.EcsTaskProperties",
         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 -> [TaskContainerPropertiesProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Containers" ([TaskContainerPropertiesProperty] -> (Key, Value))
-> Maybe [TaskContainerPropertiesProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TaskContainerPropertiesProperty]
containers,
                            Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnableExecuteCommand" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enableExecuteCommand,
                            Key -> EphemeralStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EphemeralStorage" (EphemeralStorageProperty -> (Key, Value))
-> Maybe EphemeralStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EphemeralStorageProperty
ephemeralStorage,
                            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
"ExecutionRoleArn" (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)
executionRoleArn,
                            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
"IpcMode" (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)
ipcMode,
                            Key -> NetworkConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NetworkConfiguration" (NetworkConfigurationProperty -> (Key, Value))
-> Maybe NetworkConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NetworkConfigurationProperty
networkConfiguration,
                            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
"PidMode" (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)
pidMode,
                            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
"PlatformVersion" (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)
platformVersion,
                            Key -> RuntimePlatformProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RuntimePlatform" (RuntimePlatformProperty -> (Key, Value))
-> Maybe RuntimePlatformProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RuntimePlatformProperty
runtimePlatform,
                            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
"TaskRoleArn" (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)
taskRoleArn,
                            Key -> [VolumeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Volumes" ([VolumeProperty] -> (Key, Value))
-> Maybe [VolumeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VolumeProperty]
volumes])}
instance JSON.ToJSON EcsTaskPropertiesProperty where
  toJSON :: EcsTaskPropertiesProperty -> Value
toJSON EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = [(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 -> [TaskContainerPropertiesProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Containers" ([TaskContainerPropertiesProperty] -> (Key, Value))
-> Maybe [TaskContainerPropertiesProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TaskContainerPropertiesProperty]
containers,
               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnableExecuteCommand" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enableExecuteCommand,
               Key -> EphemeralStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EphemeralStorage" (EphemeralStorageProperty -> (Key, Value))
-> Maybe EphemeralStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EphemeralStorageProperty
ephemeralStorage,
               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
"ExecutionRoleArn" (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)
executionRoleArn,
               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
"IpcMode" (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)
ipcMode,
               Key -> NetworkConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NetworkConfiguration" (NetworkConfigurationProperty -> (Key, Value))
-> Maybe NetworkConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NetworkConfigurationProperty
networkConfiguration,
               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
"PidMode" (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)
pidMode,
               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
"PlatformVersion" (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)
platformVersion,
               Key -> RuntimePlatformProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RuntimePlatform" (RuntimePlatformProperty -> (Key, Value))
-> Maybe RuntimePlatformProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RuntimePlatformProperty
runtimePlatform,
               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
"TaskRoleArn" (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)
taskRoleArn,
               Key -> [VolumeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Volumes" ([VolumeProperty] -> (Key, Value))
-> Maybe [VolumeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VolumeProperty]
volumes]))
instance Property "Containers" EcsTaskPropertiesProperty where
  type PropertyType "Containers" EcsTaskPropertiesProperty = [TaskContainerPropertiesProperty]
  set :: PropertyType "Containers" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "Containers" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {containers :: Maybe [TaskContainerPropertiesProperty]
containers = [TaskContainerPropertiesProperty]
-> Maybe [TaskContainerPropertiesProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TaskContainerPropertiesProperty]
PropertyType "Containers" EcsTaskPropertiesProperty
newValue, Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "EnableExecuteCommand" EcsTaskPropertiesProperty where
  type PropertyType "EnableExecuteCommand" EcsTaskPropertiesProperty = Value Prelude.Bool
  set :: PropertyType "EnableExecuteCommand" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "EnableExecuteCommand" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {enableExecuteCommand :: Maybe (Value Bool)
enableExecuteCommand = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnableExecuteCommand" EcsTaskPropertiesProperty
Value Bool
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "EphemeralStorage" EcsTaskPropertiesProperty where
  type PropertyType "EphemeralStorage" EcsTaskPropertiesProperty = EphemeralStorageProperty
  set :: PropertyType "EphemeralStorage" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "EphemeralStorage" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {ephemeralStorage :: Maybe EphemeralStorageProperty
ephemeralStorage = EphemeralStorageProperty -> Maybe EphemeralStorageProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EphemeralStorage" EcsTaskPropertiesProperty
EphemeralStorageProperty
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "ExecutionRoleArn" EcsTaskPropertiesProperty where
  type PropertyType "ExecutionRoleArn" EcsTaskPropertiesProperty = Value Prelude.Text
  set :: PropertyType "ExecutionRoleArn" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "ExecutionRoleArn" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {executionRoleArn :: Maybe (Value Text)
executionRoleArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ExecutionRoleArn" EcsTaskPropertiesProperty
Value Text
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "IpcMode" EcsTaskPropertiesProperty where
  type PropertyType "IpcMode" EcsTaskPropertiesProperty = Value Prelude.Text
  set :: PropertyType "IpcMode" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "IpcMode" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty {ipcMode :: Maybe (Value Text)
ipcMode = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "IpcMode" EcsTaskPropertiesProperty
Value Text
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "NetworkConfiguration" EcsTaskPropertiesProperty where
  type PropertyType "NetworkConfiguration" EcsTaskPropertiesProperty = NetworkConfigurationProperty
  set :: PropertyType "NetworkConfiguration" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "NetworkConfiguration" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {networkConfiguration :: Maybe NetworkConfigurationProperty
networkConfiguration = NetworkConfigurationProperty -> Maybe NetworkConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "NetworkConfiguration" EcsTaskPropertiesProperty
NetworkConfigurationProperty
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PidMode" EcsTaskPropertiesProperty where
  type PropertyType "PidMode" EcsTaskPropertiesProperty = Value Prelude.Text
  set :: PropertyType "PidMode" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "PidMode" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty {pidMode :: Maybe (Value Text)
pidMode = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PidMode" EcsTaskPropertiesProperty
Value Text
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PlatformVersion" EcsTaskPropertiesProperty where
  type PropertyType "PlatformVersion" EcsTaskPropertiesProperty = Value Prelude.Text
  set :: PropertyType "PlatformVersion" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "PlatformVersion" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {platformVersion :: Maybe (Value Text)
platformVersion = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PlatformVersion" EcsTaskPropertiesProperty
Value Text
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "RuntimePlatform" EcsTaskPropertiesProperty where
  type PropertyType "RuntimePlatform" EcsTaskPropertiesProperty = RuntimePlatformProperty
  set :: PropertyType "RuntimePlatform" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "RuntimePlatform" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {runtimePlatform :: Maybe RuntimePlatformProperty
runtimePlatform = RuntimePlatformProperty -> Maybe RuntimePlatformProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RuntimePlatform" EcsTaskPropertiesProperty
RuntimePlatformProperty
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "TaskRoleArn" EcsTaskPropertiesProperty where
  type PropertyType "TaskRoleArn" EcsTaskPropertiesProperty = Value Prelude.Text
  set :: PropertyType "TaskRoleArn" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "TaskRoleArn" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty
        {taskRoleArn :: Maybe (Value Text)
taskRoleArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TaskRoleArn" EcsTaskPropertiesProperty
Value Text
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
volumes :: Maybe [VolumeProperty]
..}
instance Property "Volumes" EcsTaskPropertiesProperty where
  type PropertyType "Volumes" EcsTaskPropertiesProperty = [VolumeProperty]
  set :: PropertyType "Volumes" EcsTaskPropertiesProperty
-> EcsTaskPropertiesProperty -> EcsTaskPropertiesProperty
set PropertyType "Volumes" EcsTaskPropertiesProperty
newValue EcsTaskPropertiesProperty {Maybe [TaskContainerPropertiesProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: EcsTaskPropertiesProperty -> ()
containers :: EcsTaskPropertiesProperty
-> Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: EcsTaskPropertiesProperty -> Maybe (Value Bool)
ephemeralStorage :: EcsTaskPropertiesProperty -> Maybe EphemeralStorageProperty
executionRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
ipcMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
networkConfiguration :: EcsTaskPropertiesProperty -> Maybe NetworkConfigurationProperty
pidMode :: EcsTaskPropertiesProperty -> Maybe (Value Text)
platformVersion :: EcsTaskPropertiesProperty -> Maybe (Value Text)
runtimePlatform :: EcsTaskPropertiesProperty -> Maybe RuntimePlatformProperty
taskRoleArn :: EcsTaskPropertiesProperty -> Maybe (Value Text)
volumes :: EcsTaskPropertiesProperty -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
    = EcsTaskPropertiesProperty {volumes :: Maybe [VolumeProperty]
volumes = [VolumeProperty] -> Maybe [VolumeProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [VolumeProperty]
PropertyType "Volumes" EcsTaskPropertiesProperty
newValue, Maybe [TaskContainerPropertiesProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe NetworkConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
haddock_workaround_ :: ()
containers :: Maybe [TaskContainerPropertiesProperty]
enableExecuteCommand :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
pidMode :: Maybe (Value Text)
platformVersion :: Maybe (Value Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
..}