module Stratosphere.GameLift.ContainerFleet (
module Exports, ContainerFleet(..), mkContainerFleet
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.ConnectionPortRangeProperty as Exports
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.DeploymentConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.GameSessionCreationLimitPolicyProperty as Exports
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.IpPermissionProperty as Exports
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.LocationConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.LogConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.GameLift.ContainerFleet.ScalingPolicyProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data ContainerFleet
=
ContainerFleet {ContainerFleet -> ()
haddock_workaround_ :: (),
ContainerFleet -> Maybe (Value Text)
billingType :: (Prelude.Maybe (Value Prelude.Text)),
ContainerFleet -> Maybe DeploymentConfigurationProperty
deploymentConfiguration :: (Prelude.Maybe DeploymentConfigurationProperty),
ContainerFleet -> Maybe (Value Text)
description :: (Prelude.Maybe (Value Prelude.Text)),
ContainerFleet -> Value Text
fleetRoleArn :: (Value Prelude.Text),
ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupDefinitionName :: (Prelude.Maybe (Value Prelude.Text)),
ContainerFleet -> Maybe (Value Integer)
gameServerContainerGroupsPerInstance :: (Prelude.Maybe (Value Prelude.Integer)),
ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
gameSessionCreationLimitPolicy :: (Prelude.Maybe GameSessionCreationLimitPolicyProperty),
ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceConnectionPortRange :: (Prelude.Maybe ConnectionPortRangeProperty),
ContainerFleet -> Maybe [IpPermissionProperty]
instanceInboundPermissions :: (Prelude.Maybe [IpPermissionProperty]),
ContainerFleet -> Maybe (Value Text)
instanceType :: (Prelude.Maybe (Value Prelude.Text)),
ContainerFleet -> Maybe [LocationConfigurationProperty]
locations :: (Prelude.Maybe [LocationConfigurationProperty]),
ContainerFleet -> Maybe LogConfigurationProperty
logConfiguration :: (Prelude.Maybe LogConfigurationProperty),
ContainerFleet -> Maybe (ValueList Text)
metricGroups :: (Prelude.Maybe (ValueList Prelude.Text)),
ContainerFleet -> Maybe (Value Text)
newGameSessionProtectionPolicy :: (Prelude.Maybe (Value Prelude.Text)),
ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: (Prelude.Maybe (Value Prelude.Text)),
ContainerFleet -> Maybe [ScalingPolicyProperty]
scalingPolicies :: (Prelude.Maybe [ScalingPolicyProperty]),
ContainerFleet -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag])}
deriving stock (ContainerFleet -> ContainerFleet -> Bool
(ContainerFleet -> ContainerFleet -> Bool)
-> (ContainerFleet -> ContainerFleet -> Bool) -> Eq ContainerFleet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContainerFleet -> ContainerFleet -> Bool
== :: ContainerFleet -> ContainerFleet -> Bool
$c/= :: ContainerFleet -> ContainerFleet -> Bool
/= :: ContainerFleet -> ContainerFleet -> Bool
Prelude.Eq, Int -> ContainerFleet -> ShowS
[ContainerFleet] -> ShowS
ContainerFleet -> String
(Int -> ContainerFleet -> ShowS)
-> (ContainerFleet -> String)
-> ([ContainerFleet] -> ShowS)
-> Show ContainerFleet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContainerFleet -> ShowS
showsPrec :: Int -> ContainerFleet -> ShowS
$cshow :: ContainerFleet -> String
show :: ContainerFleet -> String
$cshowList :: [ContainerFleet] -> ShowS
showList :: [ContainerFleet] -> ShowS
Prelude.Show)
mkContainerFleet :: Value Prelude.Text -> ContainerFleet
mkContainerFleet :: Value Text -> ContainerFleet
mkContainerFleet Value Text
fleetRoleArn
= ContainerFleet
{haddock_workaround_ :: ()
haddock_workaround_ = (), fleetRoleArn :: Value Text
fleetRoleArn = Value Text
fleetRoleArn,
billingType :: Maybe (Value Text)
billingType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentConfiguration = Maybe DeploymentConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
description :: Maybe (Value Text)
description = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupDefinitionName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameServerContainerGroupsPerInstance = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
gameSessionCreationLimitPolicy = Maybe GameSessionCreationLimitPolicyProperty
forall a. Maybe a
Prelude.Nothing,
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceConnectionPortRange = Maybe ConnectionPortRangeProperty
forall a. Maybe a
Prelude.Nothing,
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceInboundPermissions = Maybe [IpPermissionProperty]
forall a. Maybe a
Prelude.Nothing,
instanceType :: Maybe (Value Text)
instanceType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, locations :: Maybe [LocationConfigurationProperty]
locations = Maybe [LocationConfigurationProperty]
forall a. Maybe a
Prelude.Nothing,
logConfiguration :: Maybe LogConfigurationProperty
logConfiguration = Maybe LogConfigurationProperty
forall a. Maybe a
Prelude.Nothing, metricGroups :: Maybe (ValueList Text)
metricGroups = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
newGameSessionProtectionPolicy :: Maybe (Value Text)
newGameSessionProtectionPolicy = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
scalingPolicies :: Maybe [ScalingPolicyProperty]
scalingPolicies = Maybe [ScalingPolicyProperty]
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ContainerFleet where
toResourceProperties :: ContainerFleet -> ResourceProperties
toResourceProperties ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::GameLift::ContainerFleet",
supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"FleetRoleArn" 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..= Value Text
fleetRoleArn]
([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
"BillingType" (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)
billingType,
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 -> 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
"Description" (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)
description,
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
"GameServerContainerGroupDefinitionName"
(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)
gameServerContainerGroupDefinitionName,
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
"GameServerContainerGroupsPerInstance"
(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)
gameServerContainerGroupsPerInstance,
Key -> GameSessionCreationLimitPolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GameSessionCreationLimitPolicy"
(GameSessionCreationLimitPolicyProperty -> (Key, Value))
-> Maybe GameSessionCreationLimitPolicyProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GameSessionCreationLimitPolicyProperty
gameSessionCreationLimitPolicy,
Key -> ConnectionPortRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceConnectionPortRange"
(ConnectionPortRangeProperty -> (Key, Value))
-> Maybe ConnectionPortRangeProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConnectionPortRangeProperty
instanceConnectionPortRange,
Key -> [IpPermissionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceInboundPermissions"
([IpPermissionProperty] -> (Key, Value))
-> Maybe [IpPermissionProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [IpPermissionProperty]
instanceInboundPermissions,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceType" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceType,
Key -> [LocationConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Locations" ([LocationConfigurationProperty] -> (Key, Value))
-> Maybe [LocationConfigurationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LocationConfigurationProperty]
locations,
Key -> LogConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LogConfiguration" (LogConfigurationProperty -> (Key, Value))
-> Maybe LogConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LogConfigurationProperty
logConfiguration,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetricGroups" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
metricGroups,
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
"NewGameSessionProtectionPolicy"
(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)
newGameSessionProtectionPolicy,
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
"PerInstanceContainerGroupDefinitionName"
(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)
perInstanceContainerGroupDefinitionName,
Key -> [ScalingPolicyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ScalingPolicies" ([ScalingPolicyProperty] -> (Key, Value))
-> Maybe [ScalingPolicyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ScalingPolicyProperty]
scalingPolicies,
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]))}
instance JSON.ToJSON ContainerFleet where
toJSON :: ContainerFleet -> Value
toJSON ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"FleetRoleArn" 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..= Value Text
fleetRoleArn]
([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
"BillingType" (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)
billingType,
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 -> 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
"Description" (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)
description,
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
"GameServerContainerGroupDefinitionName"
(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)
gameServerContainerGroupDefinitionName,
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
"GameServerContainerGroupsPerInstance"
(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)
gameServerContainerGroupsPerInstance,
Key -> GameSessionCreationLimitPolicyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GameSessionCreationLimitPolicy"
(GameSessionCreationLimitPolicyProperty -> (Key, Value))
-> Maybe GameSessionCreationLimitPolicyProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GameSessionCreationLimitPolicyProperty
gameSessionCreationLimitPolicy,
Key -> ConnectionPortRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceConnectionPortRange"
(ConnectionPortRangeProperty -> (Key, Value))
-> Maybe ConnectionPortRangeProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConnectionPortRangeProperty
instanceConnectionPortRange,
Key -> [IpPermissionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceInboundPermissions"
([IpPermissionProperty] -> (Key, Value))
-> Maybe [IpPermissionProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [IpPermissionProperty]
instanceInboundPermissions,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InstanceType" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceType,
Key -> [LocationConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Locations" ([LocationConfigurationProperty] -> (Key, Value))
-> Maybe [LocationConfigurationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LocationConfigurationProperty]
locations,
Key -> LogConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LogConfiguration" (LogConfigurationProperty -> (Key, Value))
-> Maybe LogConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LogConfigurationProperty
logConfiguration,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MetricGroups" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
metricGroups,
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
"NewGameSessionProtectionPolicy"
(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)
newGameSessionProtectionPolicy,
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
"PerInstanceContainerGroupDefinitionName"
(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)
perInstanceContainerGroupDefinitionName,
Key -> [ScalingPolicyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ScalingPolicies" ([ScalingPolicyProperty] -> (Key, Value))
-> Maybe [ScalingPolicyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ScalingPolicyProperty]
scalingPolicies,
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])))
instance Property "BillingType" ContainerFleet where
type PropertyType "BillingType" ContainerFleet = Value Prelude.Text
set :: PropertyType "BillingType" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "BillingType" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {billingType :: Maybe (Value Text)
billingType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BillingType" ContainerFleet
Value Text
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "DeploymentConfiguration" ContainerFleet where
type PropertyType "DeploymentConfiguration" ContainerFleet = DeploymentConfigurationProperty
set :: PropertyType "DeploymentConfiguration" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "DeploymentConfiguration" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{deploymentConfiguration :: Maybe DeploymentConfigurationProperty
deploymentConfiguration = DeploymentConfigurationProperty
-> Maybe DeploymentConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeploymentConfiguration" ContainerFleet
DeploymentConfigurationProperty
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "Description" ContainerFleet where
type PropertyType "Description" ContainerFleet = Value Prelude.Text
set :: PropertyType "Description" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "Description" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {description :: Maybe (Value Text)
description = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Description" ContainerFleet
Value Text
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "FleetRoleArn" ContainerFleet where
type PropertyType "FleetRoleArn" ContainerFleet = Value Prelude.Text
set :: PropertyType "FleetRoleArn" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "FleetRoleArn" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {fleetRoleArn :: Value Text
fleetRoleArn = PropertyType "FleetRoleArn" ContainerFleet
Value Text
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "GameServerContainerGroupDefinitionName" ContainerFleet where
type PropertyType "GameServerContainerGroupDefinitionName" ContainerFleet = Value Prelude.Text
set :: PropertyType
"GameServerContainerGroupDefinitionName" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType
"GameServerContainerGroupDefinitionName" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupDefinitionName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"GameServerContainerGroupDefinitionName" ContainerFleet
Value Text
newValue,
Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "GameServerContainerGroupsPerInstance" ContainerFleet where
type PropertyType "GameServerContainerGroupsPerInstance" ContainerFleet = Value Prelude.Integer
set :: PropertyType "GameServerContainerGroupsPerInstance" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "GameServerContainerGroupsPerInstance" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameServerContainerGroupsPerInstance = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GameServerContainerGroupsPerInstance" ContainerFleet
Value Integer
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "GameSessionCreationLimitPolicy" ContainerFleet where
type PropertyType "GameSessionCreationLimitPolicy" ContainerFleet = GameSessionCreationLimitPolicyProperty
set :: PropertyType "GameSessionCreationLimitPolicy" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "GameSessionCreationLimitPolicy" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
gameSessionCreationLimitPolicy = GameSessionCreationLimitPolicyProperty
-> Maybe GameSessionCreationLimitPolicyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GameSessionCreationLimitPolicy" ContainerFleet
GameSessionCreationLimitPolicyProperty
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "InstanceConnectionPortRange" ContainerFleet where
type PropertyType "InstanceConnectionPortRange" ContainerFleet = ConnectionPortRangeProperty
set :: PropertyType "InstanceConnectionPortRange" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "InstanceConnectionPortRange" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceConnectionPortRange = ConnectionPortRangeProperty -> Maybe ConnectionPortRangeProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceConnectionPortRange" ContainerFleet
ConnectionPortRangeProperty
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "InstanceInboundPermissions" ContainerFleet where
type PropertyType "InstanceInboundPermissions" ContainerFleet = [IpPermissionProperty]
set :: PropertyType "InstanceInboundPermissions" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "InstanceInboundPermissions" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceInboundPermissions = [IpPermissionProperty] -> Maybe [IpPermissionProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [IpPermissionProperty]
PropertyType "InstanceInboundPermissions" ContainerFleet
newValue, Maybe [Tag]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "InstanceType" ContainerFleet where
type PropertyType "InstanceType" ContainerFleet = Value Prelude.Text
set :: PropertyType "InstanceType" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "InstanceType" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {instanceType :: Maybe (Value Text)
instanceType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceType" ContainerFleet
Value Text
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "Locations" ContainerFleet where
type PropertyType "Locations" ContainerFleet = [LocationConfigurationProperty]
set :: PropertyType "Locations" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "Locations" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {locations :: Maybe [LocationConfigurationProperty]
locations = [LocationConfigurationProperty]
-> Maybe [LocationConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [LocationConfigurationProperty]
PropertyType "Locations" ContainerFleet
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "LogConfiguration" ContainerFleet where
type PropertyType "LogConfiguration" ContainerFleet = LogConfigurationProperty
set :: PropertyType "LogConfiguration" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "LogConfiguration" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {logConfiguration :: Maybe LogConfigurationProperty
logConfiguration = LogConfigurationProperty -> Maybe LogConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LogConfiguration" ContainerFleet
LogConfigurationProperty
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "MetricGroups" ContainerFleet where
type PropertyType "MetricGroups" ContainerFleet = ValueList Prelude.Text
set :: PropertyType "MetricGroups" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "MetricGroups" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {metricGroups :: Maybe (ValueList Text)
metricGroups = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MetricGroups" ContainerFleet
ValueList Text
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "NewGameSessionProtectionPolicy" ContainerFleet where
type PropertyType "NewGameSessionProtectionPolicy" ContainerFleet = Value Prelude.Text
set :: PropertyType "NewGameSessionProtectionPolicy" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "NewGameSessionProtectionPolicy" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{newGameSessionProtectionPolicy :: Maybe (Value Text)
newGameSessionProtectionPolicy = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "NewGameSessionProtectionPolicy" ContainerFleet
Value Text
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "PerInstanceContainerGroupDefinitionName" ContainerFleet where
type PropertyType "PerInstanceContainerGroupDefinitionName" ContainerFleet = Value Prelude.Text
set :: PropertyType
"PerInstanceContainerGroupDefinitionName" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType
"PerInstanceContainerGroupDefinitionName" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet
{perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"PerInstanceContainerGroupDefinitionName" ContainerFleet
Value Text
newValue,
Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
instance Property "ScalingPolicies" ContainerFleet where
type PropertyType "ScalingPolicies" ContainerFleet = [ScalingPolicyProperty]
set :: PropertyType "ScalingPolicies" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "ScalingPolicies" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {scalingPolicies :: Maybe [ScalingPolicyProperty]
scalingPolicies = [ScalingPolicyProperty] -> Maybe [ScalingPolicyProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ScalingPolicyProperty]
PropertyType "ScalingPolicies" ContainerFleet
newValue, Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "Tags" ContainerFleet where
type PropertyType "Tags" ContainerFleet = [Tag]
set :: PropertyType "Tags" ContainerFleet
-> ContainerFleet -> ContainerFleet
set PropertyType "Tags" ContainerFleet
newValue ContainerFleet {Maybe [Tag]
Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ContainerFleet -> ()
billingType :: ContainerFleet -> Maybe (Value Text)
deploymentConfiguration :: ContainerFleet -> Maybe DeploymentConfigurationProperty
description :: ContainerFleet -> Maybe (Value Text)
fleetRoleArn :: ContainerFleet -> Value Text
gameServerContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
gameServerContainerGroupsPerInstance :: ContainerFleet -> Maybe (Value Integer)
gameSessionCreationLimitPolicy :: ContainerFleet -> Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: ContainerFleet -> Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: ContainerFleet -> Maybe [IpPermissionProperty]
instanceType :: ContainerFleet -> Maybe (Value Text)
locations :: ContainerFleet -> Maybe [LocationConfigurationProperty]
logConfiguration :: ContainerFleet -> Maybe LogConfigurationProperty
metricGroups :: ContainerFleet -> Maybe (ValueList Text)
newGameSessionProtectionPolicy :: ContainerFleet -> Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: ContainerFleet -> Maybe (Value Text)
scalingPolicies :: ContainerFleet -> Maybe [ScalingPolicyProperty]
tags :: ContainerFleet -> Maybe [Tag]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
tags :: Maybe [Tag]
..}
= ContainerFleet {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" ContainerFleet
newValue, Maybe [IpPermissionProperty]
Maybe [LocationConfigurationProperty]
Maybe [ScalingPolicyProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe ConnectionPortRangeProperty
Maybe DeploymentConfigurationProperty
Maybe GameSessionCreationLimitPolicyProperty
Maybe LogConfigurationProperty
()
Value Text
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
haddock_workaround_ :: ()
billingType :: Maybe (Value Text)
deploymentConfiguration :: Maybe DeploymentConfigurationProperty
description :: Maybe (Value Text)
fleetRoleArn :: Value Text
gameServerContainerGroupDefinitionName :: Maybe (Value Text)
gameServerContainerGroupsPerInstance :: Maybe (Value Integer)
gameSessionCreationLimitPolicy :: Maybe GameSessionCreationLimitPolicyProperty
instanceConnectionPortRange :: Maybe ConnectionPortRangeProperty
instanceInboundPermissions :: Maybe [IpPermissionProperty]
instanceType :: Maybe (Value Text)
locations :: Maybe [LocationConfigurationProperty]
logConfiguration :: Maybe LogConfigurationProperty
metricGroups :: Maybe (ValueList Text)
newGameSessionProtectionPolicy :: Maybe (Value Text)
perInstanceContainerGroupDefinitionName :: Maybe (Value Text)
scalingPolicies :: Maybe [ScalingPolicyProperty]
..}