module Stratosphere.ECS.TaskDefinition (
module Exports, TaskDefinition(..), mkTaskDefinition
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.ECS.TaskDefinition.ContainerDefinitionProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.TaskDefinition.EphemeralStorageProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.TaskDefinition.ProxyConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.TaskDefinition.RuntimePlatformProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.TaskDefinition.TaskDefinitionPlacementConstraintProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.TaskDefinition.VolumeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data TaskDefinition
=
TaskDefinition {TaskDefinition -> ()
haddock_workaround_ :: (),
TaskDefinition -> Maybe [ContainerDefinitionProperty]
containerDefinitions :: (Prelude.Maybe [ContainerDefinitionProperty]),
TaskDefinition -> Maybe (Value Text)
cpu :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe (Value Bool)
enableFaultInjection :: (Prelude.Maybe (Value Prelude.Bool)),
TaskDefinition -> Maybe EphemeralStorageProperty
ephemeralStorage :: (Prelude.Maybe EphemeralStorageProperty),
TaskDefinition -> Maybe (Value Text)
executionRoleArn :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe (Value Text)
family :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe (Value Text)
ipcMode :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe (Value Text)
memory :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe (Value Text)
networkMode :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe (Value Text)
pidMode :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
placementConstraints :: (Prelude.Maybe [TaskDefinitionPlacementConstraintProperty]),
TaskDefinition -> Maybe ProxyConfigurationProperty
proxyConfiguration :: (Prelude.Maybe ProxyConfigurationProperty),
TaskDefinition -> Maybe (ValueList Text)
requiresCompatibilities :: (Prelude.Maybe (ValueList Prelude.Text)),
TaskDefinition -> Maybe RuntimePlatformProperty
runtimePlatform :: (Prelude.Maybe RuntimePlatformProperty),
TaskDefinition -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
TaskDefinition -> Maybe (Value Text)
taskRoleArn :: (Prelude.Maybe (Value Prelude.Text)),
TaskDefinition -> Maybe [VolumeProperty]
volumes :: (Prelude.Maybe [VolumeProperty])}
deriving stock (TaskDefinition -> TaskDefinition -> Bool
(TaskDefinition -> TaskDefinition -> Bool)
-> (TaskDefinition -> TaskDefinition -> Bool) -> Eq TaskDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TaskDefinition -> TaskDefinition -> Bool
== :: TaskDefinition -> TaskDefinition -> Bool
$c/= :: TaskDefinition -> TaskDefinition -> Bool
/= :: TaskDefinition -> TaskDefinition -> Bool
Prelude.Eq, Int -> TaskDefinition -> ShowS
[TaskDefinition] -> ShowS
TaskDefinition -> String
(Int -> TaskDefinition -> ShowS)
-> (TaskDefinition -> String)
-> ([TaskDefinition] -> ShowS)
-> Show TaskDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TaskDefinition -> ShowS
showsPrec :: Int -> TaskDefinition -> ShowS
$cshow :: TaskDefinition -> String
show :: TaskDefinition -> String
$cshowList :: [TaskDefinition] -> ShowS
showList :: [TaskDefinition] -> ShowS
Prelude.Show)
mkTaskDefinition :: TaskDefinition
mkTaskDefinition :: TaskDefinition
mkTaskDefinition
= TaskDefinition
{haddock_workaround_ :: ()
haddock_workaround_ = (), containerDefinitions :: Maybe [ContainerDefinitionProperty]
containerDefinitions = Maybe [ContainerDefinitionProperty]
forall a. Maybe a
Prelude.Nothing,
cpu :: Maybe (Value Text)
cpu = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, enableFaultInjection :: Maybe (Value Bool)
enableFaultInjection = 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, family :: Maybe (Value Text)
family = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
ipcMode :: Maybe (Value Text)
ipcMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, memory :: Maybe (Value Text)
memory = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
networkMode :: Maybe (Value Text)
networkMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, pidMode :: Maybe (Value Text)
pidMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
placementConstraints = Maybe [TaskDefinitionPlacementConstraintProperty]
forall a. Maybe a
Prelude.Nothing,
proxyConfiguration :: Maybe ProxyConfigurationProperty
proxyConfiguration = Maybe ProxyConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
requiresCompatibilities :: Maybe (ValueList Text)
requiresCompatibilities = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
runtimePlatform :: Maybe RuntimePlatformProperty
runtimePlatform = Maybe RuntimePlatformProperty
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
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 TaskDefinition where
toResourceProperties :: TaskDefinition -> ResourceProperties
toResourceProperties TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::ECS::TaskDefinition", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
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 -> [ContainerDefinitionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ContainerDefinitions" ([ContainerDefinitionProperty] -> (Key, Value))
-> Maybe [ContainerDefinitionProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ContainerDefinitionProperty]
containerDefinitions,
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
"Cpu" (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)
cpu,
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
"EnableFaultInjection" (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)
enableFaultInjection,
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
"Family" (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)
family,
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 -> 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
"Memory" (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)
memory,
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
"NetworkMode" (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)
networkMode,
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 -> [TaskDefinitionPlacementConstraintProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlacementConstraints" ([TaskDefinitionPlacementConstraintProperty] -> (Key, Value))
-> Maybe [TaskDefinitionPlacementConstraintProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TaskDefinitionPlacementConstraintProperty]
placementConstraints,
Key -> ProxyConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ProxyConfiguration" (ProxyConfigurationProperty -> (Key, Value))
-> Maybe ProxyConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ProxyConfigurationProperty
proxyConfiguration,
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
"RequiresCompatibilities"
(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)
requiresCompatibilities,
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 -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
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 TaskDefinition where
toJSON :: TaskDefinition -> Value
toJSON TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
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 -> [ContainerDefinitionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ContainerDefinitions" ([ContainerDefinitionProperty] -> (Key, Value))
-> Maybe [ContainerDefinitionProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ContainerDefinitionProperty]
containerDefinitions,
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
"Cpu" (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)
cpu,
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
"EnableFaultInjection" (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)
enableFaultInjection,
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
"Family" (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)
family,
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 -> 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
"Memory" (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)
memory,
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
"NetworkMode" (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)
networkMode,
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 -> [TaskDefinitionPlacementConstraintProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlacementConstraints" ([TaskDefinitionPlacementConstraintProperty] -> (Key, Value))
-> Maybe [TaskDefinitionPlacementConstraintProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TaskDefinitionPlacementConstraintProperty]
placementConstraints,
Key -> ProxyConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ProxyConfiguration" (ProxyConfigurationProperty -> (Key, Value))
-> Maybe ProxyConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ProxyConfigurationProperty
proxyConfiguration,
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
"RequiresCompatibilities"
(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)
requiresCompatibilities,
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 -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
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 "ContainerDefinitions" TaskDefinition where
type PropertyType "ContainerDefinitions" TaskDefinition = [ContainerDefinitionProperty]
set :: PropertyType "ContainerDefinitions" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "ContainerDefinitions" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {containerDefinitions :: Maybe [ContainerDefinitionProperty]
containerDefinitions = [ContainerDefinitionProperty]
-> Maybe [ContainerDefinitionProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ContainerDefinitionProperty]
PropertyType "ContainerDefinitions" TaskDefinition
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Cpu" TaskDefinition where
type PropertyType "Cpu" TaskDefinition = Value Prelude.Text
set :: PropertyType "Cpu" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "Cpu" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {cpu :: Maybe (Value Text)
cpu = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Cpu" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "EnableFaultInjection" TaskDefinition where
type PropertyType "EnableFaultInjection" TaskDefinition = Value Prelude.Bool
set :: PropertyType "EnableFaultInjection" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "EnableFaultInjection" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {enableFaultInjection :: Maybe (Value Bool)
enableFaultInjection = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnableFaultInjection" TaskDefinition
Value Bool
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "EphemeralStorage" TaskDefinition where
type PropertyType "EphemeralStorage" TaskDefinition = EphemeralStorageProperty
set :: PropertyType "EphemeralStorage" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "EphemeralStorage" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {ephemeralStorage :: Maybe EphemeralStorageProperty
ephemeralStorage = EphemeralStorageProperty -> Maybe EphemeralStorageProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EphemeralStorage" TaskDefinition
EphemeralStorageProperty
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "ExecutionRoleArn" TaskDefinition where
type PropertyType "ExecutionRoleArn" TaskDefinition = Value Prelude.Text
set :: PropertyType "ExecutionRoleArn" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "ExecutionRoleArn" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {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" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Family" TaskDefinition where
type PropertyType "Family" TaskDefinition = Value Prelude.Text
set :: PropertyType "Family" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "Family" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {family :: Maybe (Value Text)
family = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Family" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "IpcMode" TaskDefinition where
type PropertyType "IpcMode" TaskDefinition = Value Prelude.Text
set :: PropertyType "IpcMode" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "IpcMode" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {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" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Memory" TaskDefinition where
type PropertyType "Memory" TaskDefinition = Value Prelude.Text
set :: PropertyType "Memory" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "Memory" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {memory :: Maybe (Value Text)
memory = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Memory" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "NetworkMode" TaskDefinition where
type PropertyType "NetworkMode" TaskDefinition = Value Prelude.Text
set :: PropertyType "NetworkMode" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "NetworkMode" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {networkMode :: Maybe (Value Text)
networkMode = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "NetworkMode" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PidMode" TaskDefinition where
type PropertyType "PidMode" TaskDefinition = Value Prelude.Text
set :: PropertyType "PidMode" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "PidMode" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {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" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "PlacementConstraints" TaskDefinition where
type PropertyType "PlacementConstraints" TaskDefinition = [TaskDefinitionPlacementConstraintProperty]
set :: PropertyType "PlacementConstraints" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "PlacementConstraints" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
placementConstraints = [TaskDefinitionPlacementConstraintProperty]
-> Maybe [TaskDefinitionPlacementConstraintProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TaskDefinitionPlacementConstraintProperty]
PropertyType "PlacementConstraints" TaskDefinition
newValue, Maybe [Tag]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "ProxyConfiguration" TaskDefinition where
type PropertyType "ProxyConfiguration" TaskDefinition = ProxyConfigurationProperty
set :: PropertyType "ProxyConfiguration" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "ProxyConfiguration" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {proxyConfiguration :: Maybe ProxyConfigurationProperty
proxyConfiguration = ProxyConfigurationProperty -> Maybe ProxyConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ProxyConfiguration" TaskDefinition
ProxyConfigurationProperty
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "RequiresCompatibilities" TaskDefinition where
type PropertyType "RequiresCompatibilities" TaskDefinition = ValueList Prelude.Text
set :: PropertyType "RequiresCompatibilities" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "RequiresCompatibilities" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition
{requiresCompatibilities :: Maybe (ValueList Text)
requiresCompatibilities = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RequiresCompatibilities" TaskDefinition
ValueList Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "RuntimePlatform" TaskDefinition where
type PropertyType "RuntimePlatform" TaskDefinition = RuntimePlatformProperty
set :: PropertyType "RuntimePlatform" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "RuntimePlatform" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {runtimePlatform :: Maybe RuntimePlatformProperty
runtimePlatform = RuntimePlatformProperty -> Maybe RuntimePlatformProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RuntimePlatform" TaskDefinition
RuntimePlatformProperty
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "Tags" TaskDefinition where
type PropertyType "Tags" TaskDefinition = [Tag]
set :: PropertyType "Tags" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "Tags" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" TaskDefinition
newValue, Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
instance Property "TaskRoleArn" TaskDefinition where
type PropertyType "TaskRoleArn" TaskDefinition = Value Prelude.Text
set :: PropertyType "TaskRoleArn" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "TaskRoleArn" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {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" TaskDefinition
Value Text
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
volumes :: Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
volumes :: Maybe [VolumeProperty]
..}
instance Property "Volumes" TaskDefinition where
type PropertyType "Volumes" TaskDefinition = [VolumeProperty]
set :: PropertyType "Volumes" TaskDefinition
-> TaskDefinition -> TaskDefinition
set PropertyType "Volumes" TaskDefinition
newValue TaskDefinition {Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe [VolumeProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: TaskDefinition -> ()
containerDefinitions :: TaskDefinition -> Maybe [ContainerDefinitionProperty]
cpu :: TaskDefinition -> Maybe (Value Text)
enableFaultInjection :: TaskDefinition -> Maybe (Value Bool)
ephemeralStorage :: TaskDefinition -> Maybe EphemeralStorageProperty
executionRoleArn :: TaskDefinition -> Maybe (Value Text)
family :: TaskDefinition -> Maybe (Value Text)
ipcMode :: TaskDefinition -> Maybe (Value Text)
memory :: TaskDefinition -> Maybe (Value Text)
networkMode :: TaskDefinition -> Maybe (Value Text)
pidMode :: TaskDefinition -> Maybe (Value Text)
placementConstraints :: TaskDefinition -> Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: TaskDefinition -> Maybe ProxyConfigurationProperty
requiresCompatibilities :: TaskDefinition -> Maybe (ValueList Text)
runtimePlatform :: TaskDefinition -> Maybe RuntimePlatformProperty
tags :: TaskDefinition -> Maybe [Tag]
taskRoleArn :: TaskDefinition -> Maybe (Value Text)
volumes :: TaskDefinition -> Maybe [VolumeProperty]
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
volumes :: Maybe [VolumeProperty]
..}
= TaskDefinition {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" TaskDefinition
newValue, Maybe [Tag]
Maybe [TaskDefinitionPlacementConstraintProperty]
Maybe [ContainerDefinitionProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe EphemeralStorageProperty
Maybe ProxyConfigurationProperty
Maybe RuntimePlatformProperty
()
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
haddock_workaround_ :: ()
containerDefinitions :: Maybe [ContainerDefinitionProperty]
cpu :: Maybe (Value Text)
enableFaultInjection :: Maybe (Value Bool)
ephemeralStorage :: Maybe EphemeralStorageProperty
executionRoleArn :: Maybe (Value Text)
family :: Maybe (Value Text)
ipcMode :: Maybe (Value Text)
memory :: Maybe (Value Text)
networkMode :: Maybe (Value Text)
pidMode :: Maybe (Value Text)
placementConstraints :: Maybe [TaskDefinitionPlacementConstraintProperty]
proxyConfiguration :: Maybe ProxyConfigurationProperty
requiresCompatibilities :: Maybe (ValueList Text)
runtimePlatform :: Maybe RuntimePlatformProperty
tags :: Maybe [Tag]
taskRoleArn :: Maybe (Value Text)
..}