module Stratosphere.ECS.Service (
        module Exports, Service(..), mkService
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.ECS.Service.CapacityProviderStrategyItemProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.DeploymentConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.DeploymentControllerProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.ForceNewDeploymentProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.LoadBalancerProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.NetworkConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.PlacementConstraintProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.PlacementStrategyProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.ServiceConnectConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.ServiceRegistryProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.ServiceVolumeConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.ECS.Service.VpcLatticeConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Service
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html>
    Service {Service -> ()
haddock_workaround_ :: (),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-availabilityzonerebalancing>
             Service -> Maybe (Value Text)
availabilityZoneRebalancing :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-capacityproviderstrategy>
             Service -> Maybe [CapacityProviderStrategyItemProperty]
capacityProviderStrategy :: (Prelude.Maybe [CapacityProviderStrategyItemProperty]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-cluster>
             Service -> Maybe (Value Text)
cluster :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-deploymentconfiguration>
             Service -> Maybe DeploymentConfigurationProperty
deploymentConfiguration :: (Prelude.Maybe DeploymentConfigurationProperty),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-deploymentcontroller>
             Service -> Maybe DeploymentControllerProperty
deploymentController :: (Prelude.Maybe DeploymentControllerProperty),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-desiredcount>
             Service -> Maybe (Value Integer)
desiredCount :: (Prelude.Maybe (Value Prelude.Integer)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-enableecsmanagedtags>
             Service -> Maybe (Value Bool)
enableECSManagedTags :: (Prelude.Maybe (Value Prelude.Bool)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-enableexecutecommand>
             Service -> Maybe (Value Bool)
enableExecuteCommand :: (Prelude.Maybe (Value Prelude.Bool)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-forcenewdeployment>
             Service -> Maybe ForceNewDeploymentProperty
forceNewDeployment :: (Prelude.Maybe ForceNewDeploymentProperty),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-healthcheckgraceperiodseconds>
             Service -> Maybe (Value Integer)
healthCheckGracePeriodSeconds :: (Prelude.Maybe (Value Prelude.Integer)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-launchtype>
             Service -> Maybe (Value Text)
launchType :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-loadbalancers>
             Service -> Maybe [LoadBalancerProperty]
loadBalancers :: (Prelude.Maybe [LoadBalancerProperty]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-networkconfiguration>
             Service -> Maybe NetworkConfigurationProperty
networkConfiguration :: (Prelude.Maybe NetworkConfigurationProperty),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-placementconstraints>
             Service -> Maybe [PlacementConstraintProperty]
placementConstraints :: (Prelude.Maybe [PlacementConstraintProperty]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-placementstrategies>
             Service -> Maybe [PlacementStrategyProperty]
placementStrategies :: (Prelude.Maybe [PlacementStrategyProperty]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-platformversion>
             Service -> Maybe (Value Text)
platformVersion :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-propagatetags>
             Service -> Maybe (Value Text)
propagateTags :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-role>
             Service -> Maybe (Value Text)
role :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-schedulingstrategy>
             Service -> Maybe (Value Text)
schedulingStrategy :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-serviceconnectconfiguration>
             Service -> Maybe ServiceConnectConfigurationProperty
serviceConnectConfiguration :: (Prelude.Maybe ServiceConnectConfigurationProperty),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-servicename>
             Service -> Maybe (Value Text)
serviceName :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-serviceregistries>
             Service -> Maybe [ServiceRegistryProperty]
serviceRegistries :: (Prelude.Maybe [ServiceRegistryProperty]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-tags>
             Service -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-taskdefinition>
             Service -> Maybe (Value Text)
taskDefinition :: (Prelude.Maybe (Value Prelude.Text)),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-volumeconfigurations>
             Service -> Maybe [ServiceVolumeConfigurationProperty]
volumeConfigurations :: (Prelude.Maybe [ServiceVolumeConfigurationProperty]),
             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ecs-service.html#cfn-ecs-service-vpclatticeconfigurations>
             Service -> Maybe [VpcLatticeConfigurationProperty]
vpcLatticeConfigurations :: (Prelude.Maybe [VpcLatticeConfigurationProperty])}
  deriving stock (Service -> Service -> Bool
(Service -> Service -> Bool)
-> (Service -> Service -> Bool) -> Eq Service
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Service -> Service -> Bool
== :: Service -> Service -> Bool
$c/= :: Service -> Service -> Bool
/= :: Service -> Service -> Bool
Prelude.Eq, Int -> Service -> ShowS
[Service] -> ShowS
Service -> String
(Int -> Service -> ShowS)
-> (Service -> String) -> ([Service] -> ShowS) -> Show Service
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Service -> ShowS
showsPrec :: Int -> Service -> ShowS
$cshow :: Service -> String
show :: Service -> String
$cshowList :: [Service] -> ShowS
showList :: [Service] -> ShowS
Prelude.Show)
mkService :: Service
mkService :: Service
mkService
  = Service
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       availabilityZoneRebalancing :: Maybe (Value Text)
availabilityZoneRebalancing = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
capacityProviderStrategy = Maybe [CapacityProviderStrategyItemProperty]
forall a. Maybe a
Prelude.Nothing,
       cluster :: Maybe (Value Text)
cluster = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentConfiguration = Maybe DeploymentConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       deploymentController :: Maybe DeploymentControllerProperty
deploymentController = Maybe DeploymentControllerProperty
forall a. Maybe a
Prelude.Nothing,
       desiredCount :: Maybe (Value Integer)
desiredCount = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       enableECSManagedTags :: Maybe (Value Bool)
enableECSManagedTags = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       enableExecuteCommand :: Maybe (Value Bool)
enableExecuteCommand = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
       forceNewDeployment :: Maybe ForceNewDeploymentProperty
forceNewDeployment = Maybe ForceNewDeploymentProperty
forall a. Maybe a
Prelude.Nothing,
       healthCheckGracePeriodSeconds :: Maybe (Value Integer)
healthCheckGracePeriodSeconds = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       launchType :: Maybe (Value Text)
launchType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, loadBalancers :: Maybe [LoadBalancerProperty]
loadBalancers = Maybe [LoadBalancerProperty]
forall a. Maybe a
Prelude.Nothing,
       networkConfiguration :: Maybe NetworkConfigurationProperty
networkConfiguration = Maybe NetworkConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       placementConstraints :: Maybe [PlacementConstraintProperty]
placementConstraints = Maybe [PlacementConstraintProperty]
forall a. Maybe a
Prelude.Nothing,
       placementStrategies :: Maybe [PlacementStrategyProperty]
placementStrategies = Maybe [PlacementStrategyProperty]
forall a. Maybe a
Prelude.Nothing,
       platformVersion :: Maybe (Value Text)
platformVersion = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, propagateTags :: Maybe (Value Text)
propagateTags = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       role :: Maybe (Value Text)
role = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, schedulingStrategy :: Maybe (Value Text)
schedulingStrategy = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceConnectConfiguration = Maybe ServiceConnectConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       serviceName :: Maybe (Value Text)
serviceName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, serviceRegistries :: Maybe [ServiceRegistryProperty]
serviceRegistries = Maybe [ServiceRegistryProperty]
forall a. Maybe a
Prelude.Nothing,
       tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing, taskDefinition :: Maybe (Value Text)
taskDefinition = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
volumeConfigurations = Maybe [ServiceVolumeConfigurationProperty]
forall a. Maybe a
Prelude.Nothing,
       vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
vpcLatticeConfigurations = Maybe [VpcLatticeConfigurationProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Service where
  toResourceProperties :: Service -> ResourceProperties
toResourceProperties Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::ECS::Service", 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 -> 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
"AvailabilityZoneRebalancing"
                              (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)
availabilityZoneRebalancing,
                            Key -> [CapacityProviderStrategyItemProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CapacityProviderStrategy"
                              ([CapacityProviderStrategyItemProperty] -> (Key, Value))
-> Maybe [CapacityProviderStrategyItemProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CapacityProviderStrategyItemProperty]
capacityProviderStrategy,
                            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
"Cluster" (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)
cluster,
                            Key -> DeploymentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeploymentConfiguration"
                              (DeploymentConfigurationProperty -> (Key, Value))
-> Maybe DeploymentConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeploymentConfigurationProperty
deploymentConfiguration,
                            Key -> DeploymentControllerProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeploymentController" (DeploymentControllerProperty -> (Key, Value))
-> Maybe DeploymentControllerProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeploymentControllerProperty
deploymentController,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DesiredCount" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
desiredCount,
                            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
"EnableECSManagedTags" (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)
enableECSManagedTags,
                            Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnableExecuteCommand" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enableExecuteCommand,
                            Key -> ForceNewDeploymentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ForceNewDeployment" (ForceNewDeploymentProperty -> (Key, Value))
-> Maybe ForceNewDeploymentProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForceNewDeploymentProperty
forceNewDeployment,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HealthCheckGracePeriodSeconds"
                              (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
healthCheckGracePeriodSeconds,
                            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
"LaunchType" (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)
launchType,
                            Key -> [LoadBalancerProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LoadBalancers" ([LoadBalancerProperty] -> (Key, Value))
-> Maybe [LoadBalancerProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LoadBalancerProperty]
loadBalancers,
                            Key -> NetworkConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NetworkConfiguration" (NetworkConfigurationProperty -> (Key, Value))
-> Maybe NetworkConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NetworkConfigurationProperty
networkConfiguration,
                            Key -> [PlacementConstraintProperty] -> (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" ([PlacementConstraintProperty] -> (Key, Value))
-> Maybe [PlacementConstraintProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PlacementConstraintProperty]
placementConstraints,
                            Key -> [PlacementStrategyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlacementStrategies" ([PlacementStrategyProperty] -> (Key, Value))
-> Maybe [PlacementStrategyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PlacementStrategyProperty]
placementStrategies,
                            Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlatformVersion" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
platformVersion,
                            Key -> 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
"PropagateTags" (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)
propagateTags,
                            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
"Role" (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)
role,
                            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
"SchedulingStrategy" (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)
schedulingStrategy,
                            Key -> ServiceConnectConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ServiceConnectConfiguration"
                              (ServiceConnectConfigurationProperty -> (Key, Value))
-> Maybe ServiceConnectConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ServiceConnectConfigurationProperty
serviceConnectConfiguration,
                            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
"ServiceName" (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)
serviceName,
                            Key -> [ServiceRegistryProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ServiceRegistries" ([ServiceRegistryProperty] -> (Key, Value))
-> Maybe [ServiceRegistryProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ServiceRegistryProperty]
serviceRegistries,
                            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
"TaskDefinition" (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)
taskDefinition,
                            Key -> [ServiceVolumeConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VolumeConfigurations" ([ServiceVolumeConfigurationProperty] -> (Key, Value))
-> Maybe [ServiceVolumeConfigurationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ServiceVolumeConfigurationProperty]
volumeConfigurations,
                            Key -> [VpcLatticeConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VpcLatticeConfigurations"
                              ([VpcLatticeConfigurationProperty] -> (Key, Value))
-> Maybe [VpcLatticeConfigurationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VpcLatticeConfigurationProperty]
vpcLatticeConfigurations])}
instance JSON.ToJSON Service where
  toJSON :: Service -> Value
toJSON Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = [(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 -> 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
"AvailabilityZoneRebalancing"
                 (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)
availabilityZoneRebalancing,
               Key -> [CapacityProviderStrategyItemProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CapacityProviderStrategy"
                 ([CapacityProviderStrategyItemProperty] -> (Key, Value))
-> Maybe [CapacityProviderStrategyItemProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CapacityProviderStrategyItemProperty]
capacityProviderStrategy,
               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
"Cluster" (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)
cluster,
               Key -> DeploymentConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeploymentConfiguration"
                 (DeploymentConfigurationProperty -> (Key, Value))
-> Maybe DeploymentConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeploymentConfigurationProperty
deploymentConfiguration,
               Key -> DeploymentControllerProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeploymentController" (DeploymentControllerProperty -> (Key, Value))
-> Maybe DeploymentControllerProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeploymentControllerProperty
deploymentController,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DesiredCount" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
desiredCount,
               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
"EnableECSManagedTags" (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)
enableECSManagedTags,
               Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnableExecuteCommand" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
enableExecuteCommand,
               Key -> ForceNewDeploymentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ForceNewDeployment" (ForceNewDeploymentProperty -> (Key, Value))
-> Maybe ForceNewDeploymentProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForceNewDeploymentProperty
forceNewDeployment,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HealthCheckGracePeriodSeconds"
                 (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
healthCheckGracePeriodSeconds,
               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
"LaunchType" (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)
launchType,
               Key -> [LoadBalancerProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LoadBalancers" ([LoadBalancerProperty] -> (Key, Value))
-> Maybe [LoadBalancerProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LoadBalancerProperty]
loadBalancers,
               Key -> NetworkConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NetworkConfiguration" (NetworkConfigurationProperty -> (Key, Value))
-> Maybe NetworkConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NetworkConfigurationProperty
networkConfiguration,
               Key -> [PlacementConstraintProperty] -> (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" ([PlacementConstraintProperty] -> (Key, Value))
-> Maybe [PlacementConstraintProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PlacementConstraintProperty]
placementConstraints,
               Key -> [PlacementStrategyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlacementStrategies" ([PlacementStrategyProperty] -> (Key, Value))
-> Maybe [PlacementStrategyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PlacementStrategyProperty]
placementStrategies,
               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PlatformVersion" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
platformVersion,
               Key -> 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
"PropagateTags" (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)
propagateTags,
               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
"Role" (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)
role,
               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
"SchedulingStrategy" (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)
schedulingStrategy,
               Key -> ServiceConnectConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ServiceConnectConfiguration"
                 (ServiceConnectConfigurationProperty -> (Key, Value))
-> Maybe ServiceConnectConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ServiceConnectConfigurationProperty
serviceConnectConfiguration,
               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
"ServiceName" (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)
serviceName,
               Key -> [ServiceRegistryProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ServiceRegistries" ([ServiceRegistryProperty] -> (Key, Value))
-> Maybe [ServiceRegistryProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ServiceRegistryProperty]
serviceRegistries,
               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
"TaskDefinition" (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)
taskDefinition,
               Key -> [ServiceVolumeConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VolumeConfigurations" ([ServiceVolumeConfigurationProperty] -> (Key, Value))
-> Maybe [ServiceVolumeConfigurationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ServiceVolumeConfigurationProperty]
volumeConfigurations,
               Key -> [VpcLatticeConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VpcLatticeConfigurations"
                 ([VpcLatticeConfigurationProperty] -> (Key, Value))
-> Maybe [VpcLatticeConfigurationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [VpcLatticeConfigurationProperty]
vpcLatticeConfigurations]))
instance Property "AvailabilityZoneRebalancing" Service where
  type PropertyType "AvailabilityZoneRebalancing" Service = Value Prelude.Text
  set :: PropertyType "AvailabilityZoneRebalancing" Service
-> Service -> Service
set PropertyType "AvailabilityZoneRebalancing" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {availabilityZoneRebalancing :: Maybe (Value Text)
availabilityZoneRebalancing = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AvailabilityZoneRebalancing" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "CapacityProviderStrategy" Service where
  type PropertyType "CapacityProviderStrategy" Service = [CapacityProviderStrategyItemProperty]
  set :: PropertyType "CapacityProviderStrategy" Service
-> Service -> Service
set PropertyType "CapacityProviderStrategy" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
capacityProviderStrategy = [CapacityProviderStrategyItemProperty]
-> Maybe [CapacityProviderStrategyItemProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [CapacityProviderStrategyItemProperty]
PropertyType "CapacityProviderStrategy" Service
newValue, Maybe [Tag]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "Cluster" Service where
  type PropertyType "Cluster" Service = Value Prelude.Text
  set :: PropertyType "Cluster" Service -> Service -> Service
set PropertyType "Cluster" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {cluster :: Maybe (Value Text)
cluster = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Cluster" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "DeploymentConfiguration" Service where
  type PropertyType "DeploymentConfiguration" Service = DeploymentConfigurationProperty
  set :: PropertyType "DeploymentConfiguration" Service
-> Service -> Service
set PropertyType "DeploymentConfiguration" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentConfiguration = DeploymentConfigurationProperty
-> Maybe DeploymentConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeploymentConfiguration" Service
DeploymentConfigurationProperty
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "DeploymentController" Service where
  type PropertyType "DeploymentController" Service = DeploymentControllerProperty
  set :: PropertyType "DeploymentController" Service -> Service -> Service
set PropertyType "DeploymentController" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {deploymentController :: Maybe DeploymentControllerProperty
deploymentController = DeploymentControllerProperty -> Maybe DeploymentControllerProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeploymentController" Service
DeploymentControllerProperty
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "DesiredCount" Service where
  type PropertyType "DesiredCount" Service = Value Prelude.Integer
  set :: PropertyType "DesiredCount" Service -> Service -> Service
set PropertyType "DesiredCount" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {desiredCount :: Maybe (Value Integer)
desiredCount = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DesiredCount" Service
Value Integer
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "EnableECSManagedTags" Service where
  type PropertyType "EnableECSManagedTags" Service = Value Prelude.Bool
  set :: PropertyType "EnableECSManagedTags" Service -> Service -> Service
set PropertyType "EnableECSManagedTags" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {enableECSManagedTags :: Maybe (Value Bool)
enableECSManagedTags = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnableECSManagedTags" Service
Value Bool
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "EnableExecuteCommand" Service where
  type PropertyType "EnableExecuteCommand" Service = Value Prelude.Bool
  set :: PropertyType "EnableExecuteCommand" Service -> Service -> Service
set PropertyType "EnableExecuteCommand" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {enableExecuteCommand :: Maybe (Value Bool)
enableExecuteCommand = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnableExecuteCommand" Service
Value Bool
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "ForceNewDeployment" Service where
  type PropertyType "ForceNewDeployment" Service = ForceNewDeploymentProperty
  set :: PropertyType "ForceNewDeployment" Service -> Service -> Service
set PropertyType "ForceNewDeployment" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {forceNewDeployment :: Maybe ForceNewDeploymentProperty
forceNewDeployment = ForceNewDeploymentProperty -> Maybe ForceNewDeploymentProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ForceNewDeployment" Service
ForceNewDeploymentProperty
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "HealthCheckGracePeriodSeconds" Service where
  type PropertyType "HealthCheckGracePeriodSeconds" Service = Value Prelude.Integer
  set :: PropertyType "HealthCheckGracePeriodSeconds" Service
-> Service -> Service
set PropertyType "HealthCheckGracePeriodSeconds" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service
        {healthCheckGracePeriodSeconds :: Maybe (Value Integer)
healthCheckGracePeriodSeconds = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HealthCheckGracePeriodSeconds" Service
Value Integer
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "LaunchType" Service where
  type PropertyType "LaunchType" Service = Value Prelude.Text
  set :: PropertyType "LaunchType" Service -> Service -> Service
set PropertyType "LaunchType" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {launchType :: Maybe (Value Text)
launchType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LaunchType" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "LoadBalancers" Service where
  type PropertyType "LoadBalancers" Service = [LoadBalancerProperty]
  set :: PropertyType "LoadBalancers" Service -> Service -> Service
set PropertyType "LoadBalancers" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {loadBalancers :: Maybe [LoadBalancerProperty]
loadBalancers = [LoadBalancerProperty] -> Maybe [LoadBalancerProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [LoadBalancerProperty]
PropertyType "LoadBalancers" Service
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "NetworkConfiguration" Service where
  type PropertyType "NetworkConfiguration" Service = NetworkConfigurationProperty
  set :: PropertyType "NetworkConfiguration" Service -> Service -> Service
set PropertyType "NetworkConfiguration" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {networkConfiguration :: Maybe NetworkConfigurationProperty
networkConfiguration = NetworkConfigurationProperty -> Maybe NetworkConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "NetworkConfiguration" Service
NetworkConfigurationProperty
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "PlacementConstraints" Service where
  type PropertyType "PlacementConstraints" Service = [PlacementConstraintProperty]
  set :: PropertyType "PlacementConstraints" Service -> Service -> Service
set PropertyType "PlacementConstraints" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {placementConstraints :: Maybe [PlacementConstraintProperty]
placementConstraints = [PlacementConstraintProperty]
-> Maybe [PlacementConstraintProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [PlacementConstraintProperty]
PropertyType "PlacementConstraints" Service
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "PlacementStrategies" Service where
  type PropertyType "PlacementStrategies" Service = [PlacementStrategyProperty]
  set :: PropertyType "PlacementStrategies" Service -> Service -> Service
set PropertyType "PlacementStrategies" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {placementStrategies :: Maybe [PlacementStrategyProperty]
placementStrategies = [PlacementStrategyProperty] -> Maybe [PlacementStrategyProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [PlacementStrategyProperty]
PropertyType "PlacementStrategies" Service
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "PlatformVersion" Service where
  type PropertyType "PlatformVersion" Service = Value Prelude.Text
  set :: PropertyType "PlatformVersion" Service -> Service -> Service
set PropertyType "PlatformVersion" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {platformVersion :: Maybe (Value Text)
platformVersion = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PlatformVersion" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "PropagateTags" Service where
  type PropertyType "PropagateTags" Service = Value Prelude.Text
  set :: PropertyType "PropagateTags" Service -> Service -> Service
set PropertyType "PropagateTags" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {propagateTags :: Maybe (Value Text)
propagateTags = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PropagateTags" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "Role" Service where
  type PropertyType "Role" Service = Value Prelude.Text
  set :: PropertyType "Role" Service -> Service -> Service
set PropertyType "Role" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {role :: Maybe (Value Text)
role = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Role" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "SchedulingStrategy" Service where
  type PropertyType "SchedulingStrategy" Service = Value Prelude.Text
  set :: PropertyType "SchedulingStrategy" Service -> Service -> Service
set PropertyType "SchedulingStrategy" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {schedulingStrategy :: Maybe (Value Text)
schedulingStrategy = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SchedulingStrategy" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "ServiceConnectConfiguration" Service where
  type PropertyType "ServiceConnectConfiguration" Service = ServiceConnectConfigurationProperty
  set :: PropertyType "ServiceConnectConfiguration" Service
-> Service -> Service
set PropertyType "ServiceConnectConfiguration" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceConnectConfiguration = ServiceConnectConfigurationProperty
-> Maybe ServiceConnectConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ServiceConnectConfiguration" Service
ServiceConnectConfigurationProperty
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "ServiceName" Service where
  type PropertyType "ServiceName" Service = Value Prelude.Text
  set :: PropertyType "ServiceName" Service -> Service -> Service
set PropertyType "ServiceName" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {serviceName :: Maybe (Value Text)
serviceName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ServiceName" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "ServiceRegistries" Service where
  type PropertyType "ServiceRegistries" Service = [ServiceRegistryProperty]
  set :: PropertyType "ServiceRegistries" Service -> Service -> Service
set PropertyType "ServiceRegistries" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {serviceRegistries :: Maybe [ServiceRegistryProperty]
serviceRegistries = [ServiceRegistryProperty] -> Maybe [ServiceRegistryProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ServiceRegistryProperty]
PropertyType "ServiceRegistries" Service
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "Tags" Service where
  type PropertyType "Tags" Service = [Tag]
  set :: PropertyType "Tags" Service -> Service -> Service
set PropertyType "Tags" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {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" Service
newValue, Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "TaskDefinition" Service where
  type PropertyType "TaskDefinition" Service = Value Prelude.Text
  set :: PropertyType "TaskDefinition" Service -> Service -> Service
set PropertyType "TaskDefinition" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {taskDefinition :: Maybe (Value Text)
taskDefinition = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TaskDefinition" Service
Value Text
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "VolumeConfigurations" Service where
  type PropertyType "VolumeConfigurations" Service = [ServiceVolumeConfigurationProperty]
  set :: PropertyType "VolumeConfigurations" Service -> Service -> Service
set PropertyType "VolumeConfigurations" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
volumeConfigurations = [ServiceVolumeConfigurationProperty]
-> Maybe [ServiceVolumeConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ServiceVolumeConfigurationProperty]
PropertyType "VolumeConfigurations" Service
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
instance Property "VpcLatticeConfigurations" Service where
  type PropertyType "VpcLatticeConfigurations" Service = [VpcLatticeConfigurationProperty]
  set :: PropertyType "VpcLatticeConfigurations" Service
-> Service -> Service
set PropertyType "VpcLatticeConfigurations" Service
newValue Service {Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe [VpcLatticeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: Service -> ()
availabilityZoneRebalancing :: Service -> Maybe (Value Text)
capacityProviderStrategy :: Service -> Maybe [CapacityProviderStrategyItemProperty]
cluster :: Service -> Maybe (Value Text)
deploymentConfiguration :: Service -> Maybe DeploymentConfigurationProperty
deploymentController :: Service -> Maybe DeploymentControllerProperty
desiredCount :: Service -> Maybe (Value Integer)
enableECSManagedTags :: Service -> Maybe (Value Bool)
enableExecuteCommand :: Service -> Maybe (Value Bool)
forceNewDeployment :: Service -> Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Service -> Maybe (Value Integer)
launchType :: Service -> Maybe (Value Text)
loadBalancers :: Service -> Maybe [LoadBalancerProperty]
networkConfiguration :: Service -> Maybe NetworkConfigurationProperty
placementConstraints :: Service -> Maybe [PlacementConstraintProperty]
placementStrategies :: Service -> Maybe [PlacementStrategyProperty]
platformVersion :: Service -> Maybe (Value Text)
propagateTags :: Service -> Maybe (Value Text)
role :: Service -> Maybe (Value Text)
schedulingStrategy :: Service -> Maybe (Value Text)
serviceConnectConfiguration :: Service -> Maybe ServiceConnectConfigurationProperty
serviceName :: Service -> Maybe (Value Text)
serviceRegistries :: Service -> Maybe [ServiceRegistryProperty]
tags :: Service -> Maybe [Tag]
taskDefinition :: Service -> Maybe (Value Text)
volumeConfigurations :: Service -> Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Service -> Maybe [VpcLatticeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
..}
    = Service {vpcLatticeConfigurations :: Maybe [VpcLatticeConfigurationProperty]
vpcLatticeConfigurations = [VpcLatticeConfigurationProperty]
-> Maybe [VpcLatticeConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [VpcLatticeConfigurationProperty]
PropertyType "VpcLatticeConfigurations" Service
newValue, Maybe [Tag]
Maybe [CapacityProviderStrategyItemProperty]
Maybe [LoadBalancerProperty]
Maybe [PlacementConstraintProperty]
Maybe [PlacementStrategyProperty]
Maybe [ServiceRegistryProperty]
Maybe [ServiceVolumeConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentControllerProperty
Maybe ForceNewDeploymentProperty
Maybe DeploymentConfigurationProperty
Maybe NetworkConfigurationProperty
Maybe ServiceConnectConfigurationProperty
()
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
haddock_workaround_ :: ()
availabilityZoneRebalancing :: Maybe (Value Text)
capacityProviderStrategy :: Maybe [CapacityProviderStrategyItemProperty]
cluster :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentController :: Maybe DeploymentControllerProperty
desiredCount :: Maybe (Value Integer)
enableECSManagedTags :: Maybe (Value Bool)
enableExecuteCommand :: Maybe (Value Bool)
forceNewDeployment :: Maybe ForceNewDeploymentProperty
healthCheckGracePeriodSeconds :: Maybe (Value Integer)
launchType :: Maybe (Value Text)
loadBalancers :: Maybe [LoadBalancerProperty]
networkConfiguration :: Maybe NetworkConfigurationProperty
placementConstraints :: Maybe [PlacementConstraintProperty]
placementStrategies :: Maybe [PlacementStrategyProperty]
platformVersion :: Maybe (Value Text)
propagateTags :: Maybe (Value Text)
role :: Maybe (Value Text)
schedulingStrategy :: Maybe (Value Text)
serviceConnectConfiguration :: Maybe ServiceConnectConfigurationProperty
serviceName :: Maybe (Value Text)
serviceRegistries :: Maybe [ServiceRegistryProperty]
tags :: Maybe [Tag]
taskDefinition :: Maybe (Value Text)
volumeConfigurations :: Maybe [ServiceVolumeConfigurationProperty]
..}