module Stratosphere.Deadline.Fleet.CustomerManagedWorkerCapabilitiesProperty (
        module Exports, CustomerManagedWorkerCapabilitiesProperty(..),
        mkCustomerManagedWorkerCapabilitiesProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Deadline.Fleet.AcceleratorCountRangeProperty as Exports
import {-# SOURCE #-} Stratosphere.Deadline.Fleet.AcceleratorTotalMemoryMiBRangeProperty as Exports
import {-# SOURCE #-} Stratosphere.Deadline.Fleet.FleetAmountCapabilityProperty as Exports
import {-# SOURCE #-} Stratosphere.Deadline.Fleet.FleetAttributeCapabilityProperty as Exports
import {-# SOURCE #-} Stratosphere.Deadline.Fleet.MemoryMiBRangeProperty as Exports
import {-# SOURCE #-} Stratosphere.Deadline.Fleet.VCpuCountRangeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data CustomerManagedWorkerCapabilitiesProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html>
    CustomerManagedWorkerCapabilitiesProperty {CustomerManagedWorkerCapabilitiesProperty -> ()
haddock_workaround_ :: (),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-acceleratorcount>
                                               CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorCount :: (Prelude.Maybe AcceleratorCountRangeProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-acceleratortotalmemorymib>
                                               CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTotalMemoryMiB :: (Prelude.Maybe AcceleratorTotalMemoryMiBRangeProperty),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-acceleratortypes>
                                               CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
acceleratorTypes :: (Prelude.Maybe (ValueList Prelude.Text)),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-cpuarchitecturetype>
                                               CustomerManagedWorkerCapabilitiesProperty -> Value Text
cpuArchitectureType :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-customamounts>
                                               CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAmounts :: (Prelude.Maybe [FleetAmountCapabilityProperty]),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-customattributes>
                                               CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
customAttributes :: (Prelude.Maybe [FleetAttributeCapabilityProperty]),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-memorymib>
                                               CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
memoryMiB :: MemoryMiBRangeProperty,
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-osfamily>
                                               CustomerManagedWorkerCapabilitiesProperty -> Value Text
osFamily :: (Value Prelude.Text),
                                               -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-deadline-fleet-customermanagedworkercapabilities.html#cfn-deadline-fleet-customermanagedworkercapabilities-vcpucount>
                                               CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
vCpuCount :: VCpuCountRangeProperty}
  deriving stock (CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty -> Bool
(CustomerManagedWorkerCapabilitiesProperty
 -> CustomerManagedWorkerCapabilitiesProperty -> Bool)
-> (CustomerManagedWorkerCapabilitiesProperty
    -> CustomerManagedWorkerCapabilitiesProperty -> Bool)
-> Eq CustomerManagedWorkerCapabilitiesProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty -> Bool
== :: CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty -> Bool
$c/= :: CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty -> Bool
/= :: CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty -> Bool
Prelude.Eq, Int -> CustomerManagedWorkerCapabilitiesProperty -> ShowS
[CustomerManagedWorkerCapabilitiesProperty] -> ShowS
CustomerManagedWorkerCapabilitiesProperty -> String
(Int -> CustomerManagedWorkerCapabilitiesProperty -> ShowS)
-> (CustomerManagedWorkerCapabilitiesProperty -> String)
-> ([CustomerManagedWorkerCapabilitiesProperty] -> ShowS)
-> Show CustomerManagedWorkerCapabilitiesProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CustomerManagedWorkerCapabilitiesProperty -> ShowS
showsPrec :: Int -> CustomerManagedWorkerCapabilitiesProperty -> ShowS
$cshow :: CustomerManagedWorkerCapabilitiesProperty -> String
show :: CustomerManagedWorkerCapabilitiesProperty -> String
$cshowList :: [CustomerManagedWorkerCapabilitiesProperty] -> ShowS
showList :: [CustomerManagedWorkerCapabilitiesProperty] -> ShowS
Prelude.Show)
mkCustomerManagedWorkerCapabilitiesProperty ::
  Value Prelude.Text
  -> MemoryMiBRangeProperty
     -> Value Prelude.Text
        -> VCpuCountRangeProperty
           -> CustomerManagedWorkerCapabilitiesProperty
mkCustomerManagedWorkerCapabilitiesProperty :: Value Text
-> MemoryMiBRangeProperty
-> Value Text
-> VCpuCountRangeProperty
-> CustomerManagedWorkerCapabilitiesProperty
mkCustomerManagedWorkerCapabilitiesProperty
  Value Text
cpuArchitectureType
  MemoryMiBRangeProperty
memoryMiB
  Value Text
osFamily
  VCpuCountRangeProperty
vCpuCount
  = CustomerManagedWorkerCapabilitiesProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       cpuArchitectureType :: Value Text
cpuArchitectureType = Value Text
cpuArchitectureType, memoryMiB :: MemoryMiBRangeProperty
memoryMiB = MemoryMiBRangeProperty
memoryMiB,
       osFamily :: Value Text
osFamily = Value Text
osFamily, vCpuCount :: VCpuCountRangeProperty
vCpuCount = VCpuCountRangeProperty
vCpuCount,
       acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorCount = Maybe AcceleratorCountRangeProperty
forall a. Maybe a
Prelude.Nothing,
       acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTotalMemoryMiB = Maybe AcceleratorTotalMemoryMiBRangeProperty
forall a. Maybe a
Prelude.Nothing,
       acceleratorTypes :: Maybe (ValueList Text)
acceleratorTypes = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAmounts = Maybe [FleetAmountCapabilityProperty]
forall a. Maybe a
Prelude.Nothing,
       customAttributes :: Maybe [FleetAttributeCapabilityProperty]
customAttributes = Maybe [FleetAttributeCapabilityProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties CustomerManagedWorkerCapabilitiesProperty where
  toResourceProperties :: CustomerManagedWorkerCapabilitiesProperty -> ResourceProperties
toResourceProperties CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Deadline::Fleet.CustomerManagedWorkerCapabilities",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         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
"CpuArchitectureType" 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
cpuArchitectureType,
                            Key
"MemoryMiB" Key -> MemoryMiBRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MemoryMiBRangeProperty
memoryMiB, Key
"OsFamily" 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
osFamily,
                            Key
"VCpuCount" Key -> VCpuCountRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VCpuCountRangeProperty
vCpuCount]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> AcceleratorCountRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AcceleratorCount" (AcceleratorCountRangeProperty -> (Key, Value))
-> Maybe AcceleratorCountRangeProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AcceleratorCountRangeProperty
acceleratorCount,
                               Key -> AcceleratorTotalMemoryMiBRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AcceleratorTotalMemoryMiB"
                                 (AcceleratorTotalMemoryMiBRangeProperty -> (Key, Value))
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTotalMemoryMiB,
                               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
"AcceleratorTypes" (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)
acceleratorTypes,
                               Key -> [FleetAmountCapabilityProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomAmounts" ([FleetAmountCapabilityProperty] -> (Key, Value))
-> Maybe [FleetAmountCapabilityProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FleetAmountCapabilityProperty]
customAmounts,
                               Key -> [FleetAttributeCapabilityProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomAttributes" ([FleetAttributeCapabilityProperty] -> (Key, Value))
-> Maybe [FleetAttributeCapabilityProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FleetAttributeCapabilityProperty]
customAttributes]))}
instance JSON.ToJSON CustomerManagedWorkerCapabilitiesProperty where
  toJSON :: CustomerManagedWorkerCapabilitiesProperty -> Value
toJSON CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = [(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
"CpuArchitectureType" 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
cpuArchitectureType,
               Key
"MemoryMiB" Key -> MemoryMiBRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MemoryMiBRangeProperty
memoryMiB, Key
"OsFamily" 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
osFamily,
               Key
"VCpuCount" Key -> VCpuCountRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= VCpuCountRangeProperty
vCpuCount]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> AcceleratorCountRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AcceleratorCount" (AcceleratorCountRangeProperty -> (Key, Value))
-> Maybe AcceleratorCountRangeProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AcceleratorCountRangeProperty
acceleratorCount,
                  Key -> AcceleratorTotalMemoryMiBRangeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AcceleratorTotalMemoryMiB"
                    (AcceleratorTotalMemoryMiBRangeProperty -> (Key, Value))
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTotalMemoryMiB,
                  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
"AcceleratorTypes" (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)
acceleratorTypes,
                  Key -> [FleetAmountCapabilityProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomAmounts" ([FleetAmountCapabilityProperty] -> (Key, Value))
-> Maybe [FleetAmountCapabilityProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FleetAmountCapabilityProperty]
customAmounts,
                  Key -> [FleetAttributeCapabilityProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomAttributes" ([FleetAttributeCapabilityProperty] -> (Key, Value))
-> Maybe [FleetAttributeCapabilityProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FleetAttributeCapabilityProperty]
customAttributes])))
instance Property "AcceleratorCount" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "AcceleratorCount" CustomerManagedWorkerCapabilitiesProperty = AcceleratorCountRangeProperty
  set :: PropertyType
  "AcceleratorCount" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType
  "AcceleratorCount" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorCount = AcceleratorCountRangeProperty
-> Maybe AcceleratorCountRangeProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "AcceleratorCount" CustomerManagedWorkerCapabilitiesProperty
AcceleratorCountRangeProperty
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "AcceleratorTotalMemoryMiB" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "AcceleratorTotalMemoryMiB" CustomerManagedWorkerCapabilitiesProperty = AcceleratorTotalMemoryMiBRangeProperty
  set :: PropertyType
  "AcceleratorTotalMemoryMiB"
  CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType
  "AcceleratorTotalMemoryMiB"
  CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTotalMemoryMiB = AcceleratorTotalMemoryMiBRangeProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "AcceleratorTotalMemoryMiB"
  CustomerManagedWorkerCapabilitiesProperty
AcceleratorTotalMemoryMiBRangeProperty
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "AcceleratorTypes" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "AcceleratorTypes" CustomerManagedWorkerCapabilitiesProperty = ValueList Prelude.Text
  set :: PropertyType
  "AcceleratorTypes" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType
  "AcceleratorTypes" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {acceleratorTypes :: Maybe (ValueList Text)
acceleratorTypes = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "AcceleratorTypes" CustomerManagedWorkerCapabilitiesProperty
ValueList Text
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "CpuArchitectureType" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "CpuArchitectureType" CustomerManagedWorkerCapabilitiesProperty = Value Prelude.Text
  set :: PropertyType
  "CpuArchitectureType" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType
  "CpuArchitectureType" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {cpuArchitectureType :: Value Text
cpuArchitectureType = PropertyType
  "CpuArchitectureType" CustomerManagedWorkerCapabilitiesProperty
Value Text
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "CustomAmounts" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "CustomAmounts" CustomerManagedWorkerCapabilitiesProperty = [FleetAmountCapabilityProperty]
  set :: PropertyType
  "CustomAmounts" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType
  "CustomAmounts" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAmounts = [FleetAmountCapabilityProperty]
-> Maybe [FleetAmountCapabilityProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [FleetAmountCapabilityProperty]
PropertyType
  "CustomAmounts" CustomerManagedWorkerCapabilitiesProperty
newValue, Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "CustomAttributes" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "CustomAttributes" CustomerManagedWorkerCapabilitiesProperty = [FleetAttributeCapabilityProperty]
  set :: PropertyType
  "CustomAttributes" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType
  "CustomAttributes" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {customAttributes :: Maybe [FleetAttributeCapabilityProperty]
customAttributes = [FleetAttributeCapabilityProperty]
-> Maybe [FleetAttributeCapabilityProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [FleetAttributeCapabilityProperty]
PropertyType
  "CustomAttributes" CustomerManagedWorkerCapabilitiesProperty
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "MemoryMiB" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "MemoryMiB" CustomerManagedWorkerCapabilitiesProperty = MemoryMiBRangeProperty
  set :: PropertyType "MemoryMiB" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType "MemoryMiB" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {memoryMiB :: MemoryMiBRangeProperty
memoryMiB = PropertyType "MemoryMiB" CustomerManagedWorkerCapabilitiesProperty
MemoryMiBRangeProperty
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "OsFamily" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "OsFamily" CustomerManagedWorkerCapabilitiesProperty = Value Prelude.Text
  set :: PropertyType "OsFamily" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType "OsFamily" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {osFamily :: Value Text
osFamily = PropertyType "OsFamily" CustomerManagedWorkerCapabilitiesProperty
Value Text
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
vCpuCount :: VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
vCpuCount :: VCpuCountRangeProperty
..}
instance Property "VCpuCount" CustomerManagedWorkerCapabilitiesProperty where
  type PropertyType "VCpuCount" CustomerManagedWorkerCapabilitiesProperty = VCpuCountRangeProperty
  set :: PropertyType "VCpuCount" CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
-> CustomerManagedWorkerCapabilitiesProperty
set PropertyType "VCpuCount" CustomerManagedWorkerCapabilitiesProperty
newValue CustomerManagedWorkerCapabilitiesProperty {Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
VCpuCountRangeProperty
haddock_workaround_ :: CustomerManagedWorkerCapabilitiesProperty -> ()
acceleratorCount :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: CustomerManagedWorkerCapabilitiesProperty -> Maybe (ValueList Text)
cpuArchitectureType :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
customAmounts :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAmountCapabilityProperty]
customAttributes :: CustomerManagedWorkerCapabilitiesProperty
-> Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: CustomerManagedWorkerCapabilitiesProperty -> MemoryMiBRangeProperty
osFamily :: CustomerManagedWorkerCapabilitiesProperty -> Value Text
vCpuCount :: CustomerManagedWorkerCapabilitiesProperty -> VCpuCountRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
vCpuCount :: VCpuCountRangeProperty
..}
    = CustomerManagedWorkerCapabilitiesProperty
        {vCpuCount :: VCpuCountRangeProperty
vCpuCount = PropertyType "VCpuCount" CustomerManagedWorkerCapabilitiesProperty
VCpuCountRangeProperty
newValue, Maybe [FleetAmountCapabilityProperty]
Maybe [FleetAttributeCapabilityProperty]
Maybe (ValueList Text)
Maybe AcceleratorCountRangeProperty
Maybe AcceleratorTotalMemoryMiBRangeProperty
()
Value Text
MemoryMiBRangeProperty
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
haddock_workaround_ :: ()
acceleratorCount :: Maybe AcceleratorCountRangeProperty
acceleratorTotalMemoryMiB :: Maybe AcceleratorTotalMemoryMiBRangeProperty
acceleratorTypes :: Maybe (ValueList Text)
cpuArchitectureType :: Value Text
customAmounts :: Maybe [FleetAmountCapabilityProperty]
customAttributes :: Maybe [FleetAttributeCapabilityProperty]
memoryMiB :: MemoryMiBRangeProperty
osFamily :: Value Text
..}